Colored lists (was: Diff between two change sets)

squeak-dev at lists.squeakfoundation.org squeak-dev at lists.squeakfoundation.org
Thu Oct 31 17:24:12 UTC 2002


I think colored pluggable lists should get into the image. I think we
could use those in lots of projects, I've seen at least 3 independent
implementations of it, and anyway, I really want it ;-)

And if it's too big a change to get into the image, it should be a SM
package, so I can depend on it as soon as we implement depedencies...



Daniel Vainsencher

Masashi Umezawa <umejava at mars.dti.ne.jp> wrote:
> This is a multi-part message in MIME format.
> 
> --Boundary_(ID_ypGspb+Ulcz08ltRBqgWfA)
> Content-type: text/plain; charset=iso-2022-jp
> Content-transfer-encoding: 7BIT
> 
> Hi,
> 
> ----- Original Message -----
> From: "Nevin Pratt" <nevin at smalltalkpro.com>
> To: <squeak-dev at lists.squeakfoundation.org>
> Sent: Tuesday, October 29, 2002 6:02 AM
> Subject: Diff between two change sets
> 
> 
> > Is there any way to get Squeak to show the diffs between two change sets?
> >
> 
> Try the attached MergeBrowser. It can read two changeSets and display one
> merged view.
> First file-in 'ColoredPluggableListMorph.cs' and then 'MergeBrowser.cs'.
> 
> From the FileList, select the 'browse diff code' menu.
> 
> This tool is used daily for our project - NetMorph. Maybe useful.
> 
> Cheers,
> ---
> [:masashi | ^umezawa]
> 
> --Boundary_(ID_ypGspb+Ulcz08ltRBqgWfA)
> Content-type: application/octet-stream; name=ColoredPluggableListMorph.cs
> Content-transfer-encoding: quoted-printable
> Content-disposition: attachment; filename=ColoredPluggableListMorph.cs
> 
> 'From Squeak 3.2 of 11 July 2002 [latest update: #4917] on 7 August 2002 =
> at 7:24:34 pm'!=0D"Change Set:		Colored PluggableListMorph=0DDate:			7 =
> August 2002=0DAuthor:			Masashi Umezawa=0D=0DHighlight/unhighlight color =
> support for PluggableListMorph.=0D=0DBy setting =
> #getHighlightColorSelector and #getUnhighlightColorSelector, you can =
> customize highlight/unhighlight colors of =
> PluggableListMorph.=0D=0D"!=0D=0DScrollPane subclass: =
> #PluggableListMorph=0D	instanceVariableNames: 'list selectedMorph =
> selection getListSelector getIndexSelector setIndexSelector =
> keystrokeActionSelector autoDeselect font lastKeystrokeTime =
> lastKeystrokes lastClickTime doubleClickSelector potentialDropMorph =
> getUnhighlightColorSelector getHighlightColorSelector '=0D	=
> classVariableNames: ''=0D	poolDictionaries: ''=0D	category: =
> 'Morphic-Windows'!=0D=0D!PluggableListMorph methodsFor: 'accessing' =
> stamp: 'MU 6/13/2002 13:59'!=0DgetHighlightColorSelector: aSymbol=0D	=
> getHighlightColorSelector :=3D aSymbol! !=0D=0D!PluggableListMorph =
> methodsFor: 'accessing' stamp: 'MU 6/13/2002 =
> 13:59'!=0DgetUnhighlightColorSelector: aSymbol=0D	=
> getUnhighlightColorSelector :=3D aSymbol! !=0D=0D!PluggableListMorph =
> methodsFor: 'drawing' stamp: 'MU 6/13/2002 =
> 13:43'!=0DhighlightSelection=0D	selectedMorph ifNotNil: [selectedMorph =
> color: self highlightSelectionColor; changed]! =
> !=0D=0D!PluggableListMorph methodsFor: 'drawing' stamp: 'MU 6/13/2002 =
> 13:43'!=0DunhighlightSelection=0D	selectedMorph ifNotNil: [selectedMorph =
> color: self unhighlightSelectionColor; changed]! =
> !=0D=0D!PluggableListMorph methodsFor: 'selection' stamp: 'MU 6/13/2002 =
> 15:02'!=0DhighlightSelectionColor=0D	^ getHighlightColorSelector =
> isNil=0D		ifTrue: [Color red]=0D		ifFalse: [self model perform: =
> getHighlightColorSelector with: selection]! !=0D=0D!PluggableListMorph =
> methodsFor: 'selection' stamp: 'MU 6/13/2002 =
> 15:02'!=0DunhighlightSelectionColor=0D	^ getUnhighlightColorSelector =
> isNil=0D		ifTrue: [Color black]=0D		ifFalse: [self model perform: =
> getUnhighlightColorSelector with: selection]! !=0D=0DScrollPane =
> subclass: #PluggableListMorph=0D	instanceVariableNames: 'list =
> selectedMorph selection getListSelector getIndexSelector =
> setIndexSelector keystrokeActionSelector autoDeselect font =
> lastKeystrokeTime lastKeystrokes lastClickTime doubleClickSelector =
> potentialDropMorph getHighlightColorSelector getUnhighlightColorSelector =
> '=0D	classVariableNames: ''=0D	poolDictionaries: ''=0D	category: =
> 'Morphic-Windows'!=0D=
> 
> --Boundary_(ID_ypGspb+Ulcz08ltRBqgWfA)
> Content-type: application/octet-stream; name=MergeBrowser.cs
> Content-transfer-encoding: quoted-printable
> Content-disposition: attachment; filename=MergeBrowser.cs
> 
> 'From Squeak3.2gamma of 15 January 2002 [latest update: #4857] on 10 =
> July 2002 at 6:26:15 pm'!=0D"Change Set:		MergeBrowser=0DDate:			27 June =
> 2002=0DAuthor:			Masashi Umezawa=0D=0DMerging support for =
> FileContentsBrowser.=0D=0DBy using FileMergeContentsBrowser, you can =
> easily integrate two changeSets without filing-in =
> them.=0D=0DFileContentsBrowser is colored, so you can quickly detect =
> conflicts. It can also extract conlicted parts from two changeSets and =
> write them to other file.  =0D =0DPrerequisites: #('Colored =
> PluggableListMorph')=0D"!=0D=0DFileContentsBrowser subclass: =
> #FileMergeContentsBrowser=0D	instanceVariableNames: 'otherPackage '=0D	=
> classVariableNames: ''=0D	poolDictionaries: ''=0D	category: 'Tools-File =
> Contents Browser'!=0DFileMergeContentsBrowser class=0D	=
> instanceVariableNames: ''!=0DObject subclass: #PseudoClass=0D	=
> instanceVariableNames: 'name definition organization source metaClass =
> classDefinitionMergeStatus methodFileInStatusDict methodMergeStatusDict =
> isClassDefinitionFileIn isClassCommentFileIn classCommentMergeStatus =
> '=0D	classVariableNames: ''=0D	poolDictionaries: ''=0D	category: =
> 'Tools-File Contents Browser'!=0D=0D!FileList methodsFor: 'file list =
> menu' stamp: 'MU 6/26/2002 17:25'!=0DitemsForFileEnding: suffix=0D	| =
> labels lines selectors |=0D	labels _ OrderedCollection new.=0D	lines _ =
> OrderedCollection new.=0D	selectors _ OrderedCollection new.=0D	(suffix =
> =3D 'bmp') | (suffix =3D 'gif') | (suffix =3D 'jpg') | (suffix =3D =
> 'form') | (suffix =3D '*') | (suffix =3D 'png') ifTrue:=0D		[labels =
> addAll: #('open image in a window' 'read image into ImageImports' 'open =
> image as background').=0D		selectors addAll: #(openImageInWindow =
> importImage openAsBackground)].=0D	(suffix =3D 'morph') | (suffix =3D =
> 'morphs') | (suffix =3D 'sp') | (suffix =3D '*') ifTrue:=0D		[labels =
> add: 'load as morph'.=0D		selectors add: #openMorphFromFile.=0D		labels =
> add: 'load as project'.=0D		selectors add: #openProjectFromFile].=0D	=
> (suffix =3D 'mdl') ifTrue:=0D		[labels add: 'load into Wonderland'.=0D		 =
> selectors add: #openModelintoAlice].=0D	(suffix =3D 'extseg') | (suffix =
> =3D 'project') | (suffix =3D 'pr') ifTrue:=0D		[labels add: 'load as =
> project'.=0D		selectors add: #openProjectFromFile].=0D	(suffix =3D 'bo') =
> | (suffix =3D '*') ifTrue:[=0D		labels add: 'load as book'.=0D		=
> selectors add: #openBookFromFile].=0D	(suffix =3D 'mid') | (suffix =3D =
> '*') ifTrue:=0D		[labels add: 'play midi file'.=0D		selectors add: =
> #playMidiFile].=0D	(suffix =3D 'movie') | (suffix =3D '*') ifTrue:=0D		=
> [labels add: 'open as movie'.=0D		selectors add: #openAsMovie].=0D	=
> (suffix =3D 'st') | (suffix =3D 'cs') | (suffix =3D '*') ifTrue:=0D		=
> [suffix =3D '*' ifTrue: [lines add: labels size].=0D		labels addAll: =
> #('fileIn' 'file into new change set' 'browse changes' 'browse code' =
> 'browse diff code' 'remove line feeds' 'broadcast as update').=0D		lines =
> add: labels size - 1.=0D		selectors addAll: #(fileInSelection =
> fileIntoNewChangeSet browseChanges browseFile browseDiffFile =
> removeLinefeeds putUpdate)].=0D	(suffix =3D 'swf') | (suffix =3D '*') =
> ifTrue:[=0D		labels add:'open as Flash'.=0D		selectors add: =
> #openAsFlash].=0D	(suffix =3D 'ttf') | (suffix =3D '*') ifTrue:[=0D		=
> labels add: 'open true type font'.=0D		selectors add: #openAsTTF].=0D	=
> (suffix =3D 'gz') | (suffix =3D '*') ifTrue:[=0D		labels addAll: #('view =
> decompressed' 'decompress to file').=0D		selectors addAll: =
> #(viewGZipContents saveGZipContents)].=0D	(suffix =3D '3ds') | (suffix =
> =3D '*') ifTrue:[=0D		labels add: 'Open 3DS file'.=0D		selectors add: =
> #open3DSFile].=0D	(suffix =3D 'tape') | (suffix =3D '*') ifTrue:=0D		=
> [labels add: 'open for playback'.=0D		selectors add: =
> #openTapeFromFile].=0D	(suffix =3D 'wrl') | (suffix =3D '*') ifTrue:=0D		=
> [labels add: 'open in Wonderland'.=0D		selectors add: #openVRMLFile].=0D	=
> (suffix =3D 'htm') | (suffix =3D 'html') ifTrue:=0D		[labels add: 'open =
> in browser'.=0D		selectors add: #openInBrowser].=0D	(suffix =3D 'zip') | =
> (suffix =3D '*') ifTrue:=0D		[labels add: 'open archive viewer'.=0D		=
> selectors add: #openArchiveViewer].=0D	(suffix =3D '*') ifTrue:=0D		=
> [labels addAll: #('generate HTML').=0D		lines add: labels size - 1.=0D		=
> selectors addAll: #(renderFile)].=0D	(suffix =3D CRDictionary =
> fileNameSuffix) ifTrue:=0D		[labels add: 'load Genie Gesture =
> Dictionary'.=0D		selectors add: #loadCRDictionary].=0D	(suffix =3D =
> CRDisplayProperties fileNameSuffix) ifTrue:=0D		[labels add: 'load Genie =
> Display Properties'.=0D		selectors add: #loadCRDisplayProperties].=0D	^ =
> Array with: labels with: lines with: selectors! !=0D=0D!FileList =
> methodsFor: 'menu messages' stamp: 'MU 6/26/2002 =
> 17:39'!=0DbrowseDiffFile=0D=0D	| aResult otherName |=0D	(aResult :=3D =
> StandardFileMenu oldFileFrom: directory) printString.=0D	otherName :=3D  =
> (aResult directory fullNameFor: aResult name).=0D	=0D	=
> FileMergeContentsBrowser browseFile:  self fullName with: otherName! =
> !=0D=0D=0D!FileMergeContentsBrowser methodsFor: 'accessing' stamp: =
> 'kuri-t 6/4/2002 15:13'!=0DotherPackage=0D	otherPackage isNil ifTrue: =
> [otherPackage :=3D self buildOtherPackage].=0D	^ otherPackage! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'accessing' stamp: 'kuri-t =
> 6/4/2002 14:33'!=0DotherPackage: aValue=0D=0D	otherPackage :=3D aValue! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'accessing' stamp: 'kuri-t =
> 6/12/2002 14:38'!=0DselectedPackage=0D	| selectedPkg |=0D	selectedPkg =
>:=3D super selectedPackage.=0D	^ selectedPkg isNil=0D		ifTrue: [self =
> systemCategoryListIndex: 1.=0D			super selectedPackage]=0D		ifFalse: =
> [selectedPkg]! !=0D=0D!FileMergeContentsBrowser methodsFor: 'interface =
> opening' stamp: 'kuri-t 6/5/2002 18:41'!=0DopenBrowserOnOtherPackage=0D	=
> self class browseFile: self otherPackage fullPackageName with: self =
> selectedPackage fullPackageName! !=0D=0D!FileMergeContentsBrowser =
> methodsFor: 'actions' stamp: 'kuri-t 6/5/2002 =
> 18:35'!=0DotherPackageName=0D	^self otherPackage packageName! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'actions' stamp: 'kuri-t =
> 6/5/2002 18:43'!=0DpackageName=0D	^self selectedPackage packageName! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'actions' stamp: 'MU =
> 6/25/2002 19:00'!=0Dreset=0D	self packageFilename: self selectedPackage =
> fullPackageName otherPackageFilename: self otherPackage =
> fullPackageName.=0D	self systemCategoryListIndex: 1.=0D	self changed: =
> #classList.=0D	! !=0D=0D!FileMergeContentsBrowser methodsFor: 'actions' =
> stamp: 'kuri-t 7/2/2002 19:11'!=0DswapMessageWithOther=0D	| messageName =
> otherClassOrMetaClass originalMessage otherMessage |=0D	messageName :=3D =
> self selectedMessageName=0D				ifNil: [^ self].=0D	otherClassOrMetaClass =
>:=3D self otherPseudoClassOf: self selectedClassOrMetaClass.=0D	=
> otherClassOrMetaClass isNil=0D		ifFalse: [originalMessage :=3D self =
> selectedClassOrMetaClass sourceCode=0D						at: messageName=0D						=
> ifAbsent: [].=0D			otherMessage :=3D otherClassOrMetaClass sourceCode=0D	=
> 					at: messageName=0D						ifAbsent: [^self inform: 'Cannot =
> swap!!'].=0D			self selectedClassOrMetaClass sourceCode at: messageName =
> put: otherMessage.=0D			otherClassOrMetaClass sourceCode at: messageName =
> put: originalMessage].=0D	self changed: #contents.! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'private' stamp: 'MU =
> 6/21/2002 11:58'!=0DbuildOtherPackage=0D	| aResult |=0D	(aResult :=3D =
> StandardFileMenu oldFile) printString.=0D	^FilePackage fromFileNamed: =
> (aResult directory fullNameFor: aResult name).=0D	! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'private' stamp: 'kuri-t =
> 6/4/2002 19:03'!=0DotherPseudoClassOf: pseudoClass =0D	^pseudoClass =
> isMetaClass=0D		ifTrue: [(self otherPackage classes values collect: =
> [:each | each metaClass]) =0D				detect: [:pMetaClass | pMetaClass name =
> =3D pseudoClass name]=0D				ifNone: []]=0D		ifFalse: [self otherPackage =
> classes=0D				at: pseudoClass name=0D				ifAbsent: []]! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'private' stamp: 'MU =
> 6/26/2002 19:07'!=0DsharedFileDirectory=0D	^FileDirectory on: =
> (FileDirectory dirPathFor: self selectedPackage fullPackageName)! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'merging' stamp: 'kuri-t =
> 6/12/2002 16:57'!=0DmergeAll=0D	self mergeClassesWithOtherPackage! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'merging' stamp: 'kuri-t =
> 6/18/2002 16:24'!=0DmergeClassesWithOtherPackage=0D	| selectedPkg =
> movingKeys |=0D	self okToChange=0D		ifFalse: [^ self].=0D	selectedPkg =
>:=3D self selectedPackage.=0D	selectedPkg isNil=0D		ifTrue: [^ self].=0D	=
> Cursor wait=0D		showWhile: [selectedPkg classes=0D				do: [:theClass | =
> =0D					| otherPseudoClass | =0D					otherPseudoClass :=3D self =
> otherPseudoClassOf: theClass.=0D					theClass mergeWith: =
> otherPseudoClass.=0D					(otherPseudoClass notNil=0D							and: =
> [otherPseudoClass hasChanges not])=0D						ifTrue: [self otherPackage =
> removeClass: theClass]].=0D			movingKeys :=3D self otherPackage classes =
> keys=0D						reject: [:eachKey | selectedPkg classes includesKey: =
> eachKey].=0D			movingKeys=0D				do: [:eachKey | =0D					| migrated | =0D	=
> 				migrated :=3D self otherPackage classes at: eachKey.=0D					=
> selectedPkg addClass: migrated.=0D					migrated =
> setClassMergeStatusMigrated.=0D					migrated =
> setAllMessagesMergeStatusMigrated.=0D					self otherPackage classes =
> removeKey: eachKey]].=0D	self classListIndex: 0.=0D	self changed: =
> #classList! !=0D=0D!FileMergeContentsBrowser methodsFor: 'merging' =
> stamp: 'MU 6/21/2002 11:58'!=0DmergeMessageCategoriesWithOtherPackage=0D	=
> | theClass otherPseudoClass |=0D	self okToChange ifFalse: [^self].=0D	=
> theClass :=3D self selectedClass.=0D	theClass isNil ifTrue: [^self].=0D	=
> otherPseudoClass :=3D self otherPseudoClassOf: theClass.=0D	=
> otherPseudoClass isNil ifTrue: [^self].=0D	Cursor wait showWhile:=0D		=
> [theClass mergeMessages: theClass selectors with: otherPseudoClass.=0D		=
> theClass metaClass mergeMessages: theClass metaClass selectors with: =
> otherPseudoClass].=0D	self messageCategoryListIndex: 0.=0D	self changed: =
> #messageCategoryList.! !=0D=0D!FileMergeContentsBrowser methodsFor: =
> 'merging' stamp: 'kuri-t 6/5/2002 =
> 17:10'!=0DmergeMessagesWithOtherPackage=0D	| theClass cat =
> otherPseudoClass |=0D	self okToChange ifFalse:[^self].=0D	theClass :=3D =
> self selectedClassOrMetaClass.=0D	theClass isNil ifTrue:[^self].=0D	=
> otherPseudoClass :=3D self otherPseudoClassOf: theClass.=0D	=
> otherPseudoClass isNil ifTrue: [^self].=0D	cat :=3D self =
> selectedMessageCategoryName.=0D	cat isNil ifTrue:[^self].=0D	Cursor wait =
> showWhile:[=0D		theClass mergeMessages: (theClass organization =
> listAtCategoryNamed: cat) with: otherPseudoClass.=0D	].=0D	self =
> messageListIndex: 0.=0D	self changed: #messageList.! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'menus' stamp: 'MU =
> 6/26/2002 16:06'!=0DclassListMenu: aMenu=0D=0D	^ aMenu =0D		=
> labels:=0D'definition=0Dcomment=0Dbrowse full (b)=0Dclass refs =
> (N)=0DfileIn=0DfileInOther=0DfileInDefinition=0DfileInOtherDefinition=0Df=
> ileInComment=0DfileInOtherComment=0DfileOut=0Drename...=0Dremove=0Dmerge =
> with other...'=0D		lines: #(2 4 10 11 13)=0D		selections: #(editClass =
> editComment browseMethodFull browseClassRefs fileInClass =
> fileInOtherClass fileInClassDefinition fileInOtherClassDefinition =
> fileInClassComment fileInOtherClassComment fileOutClass renameClass =
> removeClass mergeMessageCategoriesWithOtherPackage)! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'menus' stamp: 'kuri-t =
> 6/5/2002 17:10'!=0DmessageCategoryMenu: aMenu=0D=0D	^ aMenu =0D		=
> labels:=0D'fileIn=0DfileOut=0Dreorganize=0Dadd =
> item...=0Drename...=0Dremove=0Dmerge with other...'=0D		lines: #(2 3 =
> 6)=0D		selections: #(fileInMessageCategories fileOutMessageCategories =
> editMessageCategories addCategory renameCategory removeMessageCategory =
> mergeMessagesWithOtherPackage)! !=0D=0D!FileMergeContentsBrowser =
> methodsFor: 'menus' stamp: 'MU 6/21/2002 16:27'!=0DmessageListMenu: =
> aMenu=0D=0D	^ aMenu =0D		=
> labels:=0D'fileIn=0DfileInOther=0DfileOut=0DfileOutOther=0Dswap=0Dsenders=
>  (n)=0Dimplementors (m)=0Dmethod inheritance (h)=0Dremove'=0D		lines: =
> #(4 5)=0D		selections: #(fileInMessage fileInOtherMessage fileOutMessage =
> fileOutOtherMessage swapMessageWithOther=0DbrowseSenders =
> browseImplementors methodHierarchy =0DremoveMessage).! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'menus' stamp: 'MU =
> 6/26/2002 17:00'!=0DpackageListMenu: aMenu=0D	^ aMenu =0D		=
> labels:=0D'find class... (f)=0Dmerge with other...=0Dreset=0Dopen =
> other...=0DfileIn=0DfileIn not conflicted=0Dfile into new =
> changeset=0Dfile into new changeset not conflicted=0DfileOut=0DfileOut =
> conflicted only=0DfileOut not conflicted=0D'=0D		lines: #(1 4 8)=0D		=
> selections: #(findClass mergeClassesWithOtherPackage reset =
> openBrowserOnOtherPackage fileInPackage fileInNotConflicted =
> fileIntoNewChangeSet fileIntoNewChangeSetNotConflicted fileOutPackage =
> fileOutConflicted fileOutNotConflicted )! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'infoView' stamp: 'MU =
> 6/26/2002 17:42'!=0DextraInfo=0D	^ (self=0D		methodDiffFor: (self =
> selectedClassOrMetaClass sourceCodeAt: self selectedMessageName)=0D		=
> class: self selectedClass=0D		selector: self selectedMessageName=0D		=
> meta: self metaClassIndicated) asText unembellished=0D			ifTrue: [' - =
> identical']=0D			ifFalse: [' - #CONFLICTED#']! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'infoView' stamp: 'mu =
> 7/4/2002 12:33'!=0DinfoViewContents=0D	| theClass |=0D	editSelection =
> =3D=3D #newClass=0D		ifTrue: [^ self packageInfo: self =
> selectedPackage].=0D	self selectedClass isNil=0D		ifTrue: [^ ''].=0D	=
> theClass :=3D self otherPseudoClassOf: self selectedClass.=0D	=
> editSelection =3D=3D #editClass=0D		ifTrue: [self =
> selectedClassOrMetaClass mergeStatus =3D=3D #original ifTrue: [^'Class =
> exists original package'].=0D				self selectedClassOrMetaClass =
> mergeStatus =3D=3D #migrated ifTrue: [^'Class was migrated from the =
> other package'].=0D				self selectedClassOrMetaClass mergeStatus =3D=3D =
> #conflicted ifTrue: [^'#CONFLICTS# in the class or methods'].].=0D	=
> editSelection =3D=3D #editMessage=0D		ifFalse: [^ ''].=0D	(theClass =
> notNil=0D			and: [self classMessagesIndicated])=0D		ifTrue: [theClass =
>:=3D theClass metaClass].=0D	^ (theClass notNil=0D			and: [theClass =
> includesSelector: self selectedMessageName])=0D		ifTrue: ['Method also =
> exists in the other package' , self extraInfo]=0D		ifFalse: [(self =
> selectedClassOrMetaClass methodMergeStatusAt: self =
> selectedMessageName)=0D					=3D=3D #migrated=0D				ifTrue: ['Method was =
> migrated from the other package']=0D				ifFalse: ['Method exists in =
> original package']]! !=0D=0D!FileMergeContentsBrowser methodsFor: =
> 'infoView' stamp: 'kuri-t 6/4/2002 16:16'!=0DpackageInfo: p=0D	| =
> nClasses newClasses oldClasses |=0D	p isNil ifTrue:[^''].=0D	nClasses =
>:=3D newClasses :=3D oldClasses :=3D 0.=0D	p classes do:[:cls|=0D		=
> nClasses :=3D nClasses + 1.=0D		((self otherPseudoClassOf: cls) =
> notNil)=0D			ifTrue:[oldClasses :=3D oldClasses + 1]=0D			=
> ifFalse:[newClasses :=3D newClasses + 1]].=0D	^nClasses printString,' =
> classes (', newClasses printString, ' new / ', oldClasses printString, ' =
> modified)'! !=0D=0D!FileMergeContentsBrowser methodsFor: 'diffs' stamp: =
> 'MU 6/26/2002 17:44'!=0DmethodDiffFor: aString class: aPseudoClass =
> selector: selector meta: meta =0D	"Answer the diff between the current =
> copy of the given class/selector/meta for the string provided"=0D=0D	| =
> theClass source |=0D	theClass :=3D self otherPseudoClassOf: =
> aPseudoClass.=0D	theClass isNil ifTrue: [^aString copy].=0D	meta=0D		=
> ifTrue: [theClass :=3D theClass metaClass].=0D	(theClass =
> includesSelector: selector)=0D		ifFalse: [^ aString copy].=0D	source =
>:=3D theClass sourceCodeAt: selector.=0D	^ Cursor wait=0D		showWhile: =
> [TextDiffBuilder buildDisplayPatchFrom: source to: aString inClass: =
> theClass prettyDiffs: self showingPrettyDiffs]! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'diffs' stamp: 'kuri-t =
> 7/2/2002 18:51'!=0DmodifiedClassDefinition=0D	| pClass old new diff =
> oClass |=0D	pClass :=3D self selectedClassOrMetaClass.=0D	pClass isNil =
> ifTrue: [^ nil].=0D	pClass hasDefinition ifFalse:[^pClass =
> definition].=0D	oClass :=3D self otherPseudoClassOf: self =
> selectedClass.=0D	oClass isNil ifTrue:[^pClass definition].=0D	self =
> metaClassIndicated ifTrue:[ oClass :=3D oClass metaClass].=0D	old :=3D =
> oClass hasDefinition ifTrue: [oClass definition] ifFalse:[^pClass =
> definition].=0D	new :=3D pClass definition.=0D	Cursor wait =
> showWhile:[=0D		diff :=3D ClassDiffBuilder buildDisplayPatchFrom: old =
> to: new=0D	].=0D	^diff! !=0D=0D!FileMergeContentsBrowser methodsFor: =
> 'other' stamp: 'kuri-t 6/4/2002 16:31'!=0DlabelString=0D	"Answer the =
> string for the window title"=0D=0D	^ self class name, ': ', (self =
> selectedSystemCategoryName ifNil: ['']), '/', self otherPackage =
> packageName! !=0D=0D!FileMergeContentsBrowser methodsFor: =
> 'initialize-release' stamp: 'mu 7/4/2002 16:11'!=0DhighlightClassList: =
> list with: morphList=0D	list=0D		with: morphList=0D		do: [:item :morph | =
> | cls | cls :=3D (self selectedPackage classAt: item).=0D				self =
> classMessagesIndicated ifTrue: [cls :=3D cls metaClass].=0D				cls =
> mergeStatus =3D=3D #conflicted ifTrue: [morph color: self class =
> conflictedColor].=0D				cls mergeStatus =3D=3D #migrated ifTrue: [morph =
> color: self class migratedColor].=0D				cls mergeStatus =3D=3D #original =
> ifTrue: [morph color: self class originalColor]]! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'initialize-release' stamp: =
> 'kuri-t 6/13/2002 15:24'!=0DhighlightMessageList: list with: =
> morphList=0D	| selClass |=0D	selClass :=3D self selectedClass.=0D	self =
> classMessagesIndicated ifTrue: [selClass :=3D selClass metaClass].=0D	=
> list=0D		with: morphList=0D		do: [:item :morph | | methodStatus | =
> methodStatus :=3D selClass methodMergeStatusAt: item. =0D				=
> methodStatus =3D=3D #conflicted ifTrue: [morph color: self class =
> conflictedColor].=0D				methodStatus =3D=3D #migrated ifTrue: [morph =
> color: self class migratedColor].=0D				methodStatus =3D=3D #original =
> ifTrue: [morph color: self class originalColor]]! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'initialize-release' stamp: =
> 'kuri-t 6/7/2002 14:05'!=0DpackageFilename: aFilename =
> otherPackageFilename: otherFilename =0D	| packageDict organizer package =
> |=0D	packageDict :=3D Dictionary new.=0D	organizer :=3D SystemOrganizer =
> defaultList: Array new.=0D	package :=3D FilePackage fromFileNamed: =
> aFilename.=0D	otherPackage :=3D FilePackage fromFileNamed: =
> otherFilename.=0D	packageDict at: package packageName put: package.=0D	=
> organizer classifyAll: package classes keys under: package =
> packageName.=0D	self systemOrganizer: organizer.=0D	self packages: =
> packageDict.=0D	self otherPackage: otherPackage! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'view creation' stamp: =
> 'kuri-t 6/13/2002 15:02'!=0DbuildMorphicClassList=0D	| morph |=0D	morph =
>:=3D super buildMorphicClassList.=0D	morph getUnhighlightColorSelector: =
> #classMergeStatusColor:.=0D	^morph! !=0D=0D!FileMergeContentsBrowser =
> methodsFor: 'view creation' stamp: 'kuri-t 6/13/2002 =
> 15:02'!=0DbuildMorphicMessageList=0D	| messageListMorph |=0D	=
> messageListMorph :=3D PluggableListMorph=0D				on: self=0D				list: =
> #messageList=0D				selected: #messageListIndex=0D				changeSelected: =
> #messageListIndex:=0D				menu: #messageListMenu:=0D				keystroke: =
> #messageListKey:from:.=0D	messageListMorph setProperty: =
> #highlightSelector toValue: #highlightMessageList:with:.=0D	=
> messageListMorph getUnhighlightColorSelector: =
> #messageMergeStatusColor:.=0D	^ messageListMorph! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'view creation' stamp: =
> 'kuri-t 6/13/2002 16:32'!=0DclassMergeStatusColor: selection=0D	| status =
> selClass |=0D	selClass :=3D self selectedPackage classAt: selection =
> ifAbsent: [].=0D	selClass isNil ifTrue: [^self class originalColor].=0D	=
> self classMessagesIndicated ifTrue: [selClass :=3D selClass =
> metaClass].=0D	status :=3D selClass mergeStatus.=0D	status =3D=3D =
> #conflicted ifTrue:[^self class conflictedColor].=0D	status =3D=3D =
> #migrated ifTrue:[^self class migratedColor].=0D	^self class =
> originalColor! !=0D=0D!FileMergeContentsBrowser methodsFor: 'view =
> creation' stamp: 'kuri-t 6/13/2002 15:27'!=0DmessageMergeStatusColor: =
> selection=0D	| status selClass |=0D	self selectedClassName isNil ifTrue: =
> [^self class originalColor].=0D	selClass :=3D self selectedPackage =
> classAt: self selectedClassName.=0D	self classMessagesIndicated ifTrue: =
> [selClass :=3D selClass metaClass].=0D	status :=3D selClass =
> methodMergeStatusAt: selection.=0D	status =3D=3D #conflicted =
> ifTrue:[^self class conflictedColor].=0D	status =3D=3D #migrated =
> ifTrue:[^self class migratedColor].=0D	^self class originalColor! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'view creation' stamp: 'MU =
> 6/21/2002 12:00'!=0DopenAsMorph=0D	"Create a pluggable version of all =
> the views for a Browser, including views and controllers."=0D	| window =
> aListExtent next mySingletonList |=0D	window :=3D (SystemWindow =
> labelled: 'later') model: self.=0D	self packages size =3D 1=0D		ifTrue: =
> [=0D			aListExtent :=3D 0.333333 @ 0.34.=0D			self =
> systemCategoryListIndex: 1.=0D			mySingletonList :=3D PluggableListMorph =
> on: self list: #systemCategorySingleton=0D					selected: #indexIsOne =
> changeSelected: #indexIsOne:=0D					menu: #packageListMenu:=0D					=
> keystroke: #packageListKey:from:.=0D			mySingletonList =
> hideScrollBarIndefinitely.=0D			window addMorph: mySingletonList frame: =
> (0 at 0 extent: 1.0 at 0.06).=0D			next :=3D 0 at 0.06]=0D		ifFalse: [=0D			=
> aListExtent :=3D 0.25 @ 0.4.=0D			window addMorph: (PluggableListMorph =
> on: self list: #systemCategoryList=0D					selected: =
> #systemCategoryListIndex changeSelected: #systemCategoryListIndex:=0D				=
> 	menu: #packageListMenu:=0D					keystroke: #packageListKey:from:)=0D				=
> frame: (0 at 0 extent: aListExtent).=0D			next :=3D aListExtent x @ =
> 0].=0D=0D	self addClassAndSwitchesTo: window at: (next extent: =
> aListExtent) plus: 0.=0D=0D	next :=3D next + (aListExtent x @ 0).=0D	=
> window addMorph: (PluggableListMorph on: self list: =
> #messageCategoryList=0D			selected: #messageCategoryListIndex =
> changeSelected: #messageCategoryListIndex:=0D			menu: =
> #messageCategoryMenu:)=0D		frame: (next extent: aListExtent).=0D	next =
>:=3D next + (aListExtent x @ 0).=0D	=0D	window addMorph: self =
> buildMorphicMessageList=0D		frame: (next extent: aListExtent).=0D=0D	=
> self addLowerPanesTo: window at: (0 at 0.4 corner: 1 at 1) with: nil.=0D	^ =
> window=0D! !=0D=0D!FileMergeContentsBrowser methodsFor: 'fileIn/fileOut' =
> stamp: 'MU 6/26/2002 17:08'!=0DfileInClass=0D	super fileInClass.=0D	self =
> changed: #classList! !=0D=0D!FileMergeContentsBrowser methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 17:06'!=0DfileInClassComment=0D	=
> Cursor read showWhile:[=0D		self selectedClass fileInComment.=0D	].=0D	=
> self changed: #classList! !=0D=0D!FileMergeContentsBrowser methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 17:06'!=0DfileInClassDefinition=0D	=
> Cursor read showWhile:[=0D		self selectedClass fileInDefinition.=0D	=
> ].=0D	self changed: #classList! !=0D=0D!FileMergeContentsBrowser =
> methodsFor: 'fileIn/fileOut' stamp: 'kuri-t 7/2/2002 =
> 18:26'!=0DfileInNotConflicted=0D	Cursor read showWhile:[=0D		self =
> selectedPackage fileInNotConflicted.=0D	].=0D	self changed: #classList! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'fileIn/fileOut' stamp: 'MU =
> 6/26/2002 17:06'!=0DfileInOtherClass=0D	Cursor read showWhile:[ | =
> otherClass |=0D		otherClass :=3D self otherPseudoClassOf: self =
> selectedClass.=0D		otherClass isNil ifFalse: [otherClass fileIn].=0D	=
> ].=0D	self changed: #classList! !=0D=0D!FileMergeContentsBrowser =
> methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 17:06'!=0DfileInOtherClassComment=0D	Cursor read showWhile:[ | =
> otherClass |=0D		otherClass :=3D self otherPseudoClassOf: self =
> selectedClass.=0D		otherClass isNil ifFalse: [otherClass =
> fileInComment].=0D	].=0D	self changed: #classList! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'fileIn/fileOut' stamp: 'MU =
> 6/26/2002 17:06'!=0DfileInOtherClassDefinition=0D	Cursor read =
> showWhile:[ | otherClass |=0D		otherClass :=3D self otherPseudoClassOf: =
> self selectedClass.=0D		otherClass isNil ifFalse: [otherClass =
> fileInDefinitionOnly].=0D	].=0D	self changed: #classList! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'fileIn/fileOut' stamp: 'MU =
> 6/21/2002 16:24'!=0DfileInOtherMessage=0D	| otherClassOrMetaClass |=0D	=
> self selectedMessageName=0D		ifNil: [^ self].=0D	Cursor read=0D		=
> showWhile: [otherClassOrMetaClass :=3D self otherPseudoClassOf: self =
> selectedClassOrMetaClass.=0D			otherClassOrMetaClass isNil=0D				=
> ifFalse: [otherClassOrMetaClass fileInMethod: self =
> selectedMessageName]]! !=0D=0D!FileMergeContentsBrowser methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/25/2002 19:02'!=0DfileInPackage=0D	super =
> fileInPackage.=0D	self changed: #classList! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'fileIn/fileOut' stamp: 'MU =
> 6/26/2002 17:10'!=0DfileIntoNewChangeSetNotConflicted=0D=0D	| package =
> changeSet |=0D	(package :=3D self selectedPackage) ifNil: [^ self =
> beep].=0D	changeSet :=3D ChangeSorter newChangeSet: package =
> packageName.=0D	Smalltalk newChanges: changeSet.=0D	self =
> fileInPackageNotConflicted=0D	! !=0D=0D!FileMergeContentsBrowser =
> methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 18:27'!=0DfileOutConflicted=0D	Cursor write=0D		showWhile: [| fileStream =
> | =0D			fileStream :=3D self sharedFileDirectory forceNewFileNamed: self =
> selectedPackage shortPackageName , ' x ' , self otherPackage =
> shortPackageName , ' Conflicts.cs'.=0D			self selectedPackage =
> fileOutConflictedOn: fileStream.=0D			fileStream cr; cr.=0D			self =
> otherPackage fileOutConflictedOn: fileStream]! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'fileIn/fileOut' stamp: 'MU =
> 6/26/2002 19:24'!=0DfileOutMessage=0D	self selectedMessageName=0D		=
> ifNil: [^ self].=0D	Cursor write=0D		showWhile: [| fileStream | =0D					=
> fileStream :=3D self sharedFileDirectory forceNewFileNamed: self =
> selectedMessageName , '.st'.=0D					self selectedClassOrMetaClass=0D					=
> 	fileOutMethods: (Array with: self selectedMessageName)=0D						on: =
> fileStream]! !=0D=0D!FileMergeContentsBrowser methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 18:27'!=0DfileOutNotConflicted=0D	=
> Cursor write=0D		showWhile: [| fileStream | =0D			fileStream :=3D self =
> sharedFileDirectory forceNewFileNamed: self selectedPackage =
> shortPackageName , ' x ' , self otherPackage shortPackageName , ' =
> NotConflicts.cs'.=0D			self selectedPackage fileOutNotConflictedOn: =
> fileStream.=0D			fileStream cr; cr.=0D			self otherPackage =
> fileOutNotConflictedOn: fileStream]! !=0D=0D!FileMergeContentsBrowser =
> methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 19:20'!=0DfileOutOtherMessage=0D	| otherClassOrMetaClass |=0D	self =
> selectedMessageName=0D		ifNil: [^ self].=0D	Cursor write=0D		showWhile: =
> [otherClassOrMetaClass :=3D self otherPseudoClassOf: self =
> selectedClassOrMetaClass.=0D			otherClassOrMetaClass isNil=0D				=
> ifFalse: [| fileStream | =0D					fileStream :=3D self =
> sharedFileDirectory forceNewFileNamed: self selectedMessageName , ' =
> Other.st'.=0D					otherClassOrMetaClass=0D						fileOutMethods: (Array =
> with: self selectedMessageName)=0D						on: fileStream]]! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'class list' stamp: 'MU =
> 6/25/2002 18:59'!=0DclassList=0D	| originalList selectedPkg clsList |=0D	=
> originalList :=3D super classList.=0D	selectedPkg :=3D self =
> selectedPackage.=0D	clsList :=3D originalList=0D				collect: [:each | =
> (selectedPkg classAt: each) isClassDefinitionFileIn=0D						ifTrue: =
> [each asText addAttribute: TextEmphasis struckOut]=0D						ifFalse: =
> [each]].=0D	clsList :=3D clsList=0D				collect: [:each | (selectedPkg =
> classAt: each) isClassCommentFileIn=0D						ifTrue: [each asText =
> addAttribute: TextEmphasis italic]=0D						ifFalse: [each]].=0D	^ =
> clsList! !=0D=0D!FileMergeContentsBrowser methodsFor: 'code pane' stamp: =
> 'MU 6/25/2002 19:32'!=0Dcontents=0D	| cont |=0D	cont :=3D super =
> contents.=0D	editSelection =3D=3D #editComment=0D		ifTrue: [| theClass =
> comment otherClass otherClassComment | =0D			(theClass :=3D self =
> selectedClass)=0D				ifNil: [^ ''].=0D			comment :=3D theClass =
> comment.=0D			otherClass :=3D self otherPseudoClassOf: theClass.=0D			=
> otherClassComment :=3D otherClass isNil=0D						ifTrue: [^ comment]=0D			=
> 			ifFalse: [otherClass comment].=0D			cont :=3D (TextDiffBuilder from: =
> otherClassComment to: comment) buildDisplayPatch].=0D	^ cont! =
> !=0D=0D!FileMergeContentsBrowser methodsFor: 'message list' stamp: 'MU =
> 6/25/2002 19:12'!=0DmessageList=0D	| msgList selectedClassOrMetaClass =
> originalList |=0D	originalList :=3D super messageList.=0D	self =
> selectedClass isNil ifTrue: [^originalList].=0D	selectedClassOrMetaClass =
>:=3D self selectedClassOrMetaClass.=0D	msgList :=3D originalList=0D				=
> collect: [:sele | (selectedClassOrMetaClass methodFileInStatusAt: =
> sele)=0D						ifTrue: [sele asText addAttribute: TextEmphasis =
> struckOut;=0D								 addAttribute: TextEmphasis italic;=0D								 =
> yourself]=0D						ifFalse: [sele]].=0D	^ msgList! =
> !=0D=0D=0D!FileMergeContentsBrowser class methodsFor: 'instance =
> creation' stamp: 'MU 7/3/2002 16:28'!=0DbrowseFile: aFilename with: =
> otherFilename =0D	| browser |=0D	Cursor wait=0D		showWhile: [browser =
>:=3D self new packageFilename: aFilename otherPackageFilename: =
> otherFilename.=0D			self openBrowserView: browser createViews label: =
> self name , ': ' , browser packageName , '/' , browser =
> otherPackageName.=0D			browser mergeAll]! =
> !=0D=0D!FileMergeContentsBrowser class methodsFor: 'instance creation' =
> stamp: 'kuri-t 6/12/2002 14:39'!=0DfileNamed: aFilename with: =
> otherFilename =0D	^self new packageFilename: aFilename =
> otherPackageFilename: otherFilename.! !=0D=0D!FileMergeContentsBrowser =
> class methodsFor: 'window color' stamp: 'kuri-t 6/7/2002 =
> 13:57'!=0DwindowColorSpecification=0D	"Answer a WindowColorSpec object =
> that declares my preference"=0D	^ WindowColorSpec=0D		classSymbol: self =
> name=0D		wording: 'File Merge Contents Browser'=0D		brightColor: =
> (Color=0D				r: 0.977=0D				g: 0.963=0D				b: 0.923)=0D		pastelColor: =
> #paleTan=0D		helpMessage: 'Lets you view the contents of a file as code, =
> in a browser-like tool.'! !=0D=0D!FileMergeContentsBrowser class =
> methodsFor: 'constants' stamp: 'kuri-t 6/13/2002 =
> 15:10'!=0DconflictedColor=0D	^Color magenta! =
> !=0D=0D!FileMergeContentsBrowser class methodsFor: 'constants' stamp: =
> 'kuri-t 6/13/2002 14:36'!=0DmigratedColor=0D	^Color blue! =
> !=0D=0D!FileMergeContentsBrowser class methodsFor: 'constants' stamp: =
> 'kuri-t 6/13/2002 14:36'!=0DoriginalColor=0D	^Color black! =
> !=0D=0D=0D!FilePackage methodsFor: 'accessing' stamp: 'kuri-t 6/13/2002 =
> 16:31'!=0DclassAt: className ifAbsent: aBlock=0D	^self classes at: =
> className ifAbsent: aBlock! !=0D=0D!FilePackage methodsFor: 'accessing' =
> stamp: 'MU 6/26/2002 15:52'!=0DshortPackageName=0D	 ^FileDirectory =
> baseNameFor: self packageName=0D=0D=0D! !=0D=0D!FilePackage methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 16:59'!=0DfileInNotConflicted=0D	| =
> doitsMark |=0D	doitsMark :=3D 1.=0D	doIts isEmpty ifFalse: [doitsMark =
>:=3D self askForDoits].=0D	doitsMark =3D 4 ifTrue: [^ nil].=0D	doitsMark =
> =3D 2 ifTrue: [self fileInDoits].=0D	self superclassOrder=0D		do: [:cls =
> | cls hasDefinition=0D				ifTrue: [cls =
> fileInDefinitionOnlyNotConflicted]].=0D	classes=0D		do: [:cls | =0D			=
> cls hasComment=0D				ifTrue: [cls fileInCommentNotConflicted].=0D			cls =
> fileInMethodsNotConflicted.=0D			cls hasMetaclass=0D				ifTrue: [cls =
> metaClass fileInNotConflicted]].=0D	doitsMark =3D 3 ifTrue: [self =
> fileInDoits]! !=0D=0D!FilePackage methodsFor: 'fileIn/fileOut' stamp: =
> 'MU 6/26/2002 17:01'!=0DfileOutConflicted=0D	| fileName stream |=0D	=
> fileName :=3D FillInTheBlank request: 'Enter the file name' =
> initialAnswer:''.=0D	stream :=3D FileStream newFileNamed: fileName.=0D	=
> self fileOutConflictedOn: stream! !=0D=0D!FilePackage methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 17:01'!=0DfileOutConflictedOn: =
> aStream=0D	self superclassOrder do:[:each | each fileOutConflictedOn: =
> aStream].=0D	 ! !=0D=0D!FilePackage methodsFor: 'fileIn/fileOut' stamp: =
> 'MU 6/26/2002 17:03'!=0DfileOutNotConflicted=0D	| fileName stream |=0D	=
> fileName :=3D FillInTheBlank request: 'Enter the file name' =
> initialAnswer:''.=0D	stream :=3D FileStream newFileNamed: fileName.=0D	=
> self fileOutNotConflictedOn: stream! !=0D=0D!FilePackage methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 17:01'!=0DfileOutNotConflictedOn: =
> aStream=0D	self superclassOrder do:[:each | each fileOutNotConflictedOn: =
> aStream].=0D	 ! !=0D=0D!FilePackage methodsFor: 'actions' stamp: 'kuri-t =
> 6/18/2002 16:24'!=0DaddClass: aClass=0D	self classes at: aClass name =
> put: aClass.=0D	classOrder add: aClass.! !=0D=0D!FilePackage methodsFor: =
> 'superclass ordering' stamp: 'MU 6/21/2002 =
> 12:31'!=0DallSuperPseudoClassNamesOf: aPseudoClass =0D	| pseudoCls =
> isMeta allSuperClassNames completed allClasses |=0D	pseudoCls :=3D =
> aPseudoClass.=0D	isMeta :=3D aPseudoClass isMetaClass.=0D	=
> allSuperClassNames :=3D OrderedCollection new.=0D	completed :=3D =
> false.=0D	allClasses :=3D classes values.=0D	[completed]=0D		whileFalse: =
> [| superCls | =0D			superCls :=3D allClasses=0D						detect: [:each | =
> each name =3D pseudoCls parsedSuperPseudoClassName]=0D						ifNone: =
> [].=0D			superCls isNil=0D				ifTrue: [completed :=3D true]=0D				=
> ifFalse: [allSuperClassNames addFirst: superCls name.=0D					pseudoCls =
>:=3D superCls]].=0D	isMeta=0D		ifTrue: [allSuperClassNames addFirst: =
> #'Object class']=0D		ifFalse: [allSuperClassNames addFirst: #Object].=0D	=
> ^ allSuperClassNames! !=0D=0D!FilePackage methodsFor: 'superclass =
> ordering' stamp: 'MU 6/21/2002 12:31'!=0DallSuperPseudoClassesOf: =
> aPseudoClass =0D	| names allClasses allSuperClasses |=0D	names :=3D self =
> allSuperPseudoClassNamesOf: aPseudoClass.=0D	allClasses :=3D classes =
> values.=0D	allSuperClasses :=3D OrderedCollection new.=0D	names =0D		do: =
> [:eachName | =0D			| superClass | =0D			(eachName =3D 'Object' or: =
> [eachName =3D 'Object class'])=0D				ifTrue: [allSuperClasses=0D						=
> add: (PseudoClass new name: eachName)].=0D			superClass :=3D =
> allClasses=0D						detect: [:cls | cls name =3D eachName]=0D						=
> ifNone: [].=0D			superClass isNil=0D				ifFalse: [allSuperClasses add: =
> superClass]].=0D	^ allSuperClasses! !=0D=0D!FilePackage methodsFor: =
> 'superclass ordering' stamp: 'MU 6/21/2002 12:30'!=0DdoWeFileOut: aClass =
> given: aSet cache: cache =0D	"Weird but copied from ChangeSet"=0D	| =
> aClassAllSuperclasses aClassSoleInstanceAllSuperclasses |=0D	=
> aClassAllSuperclasses :=3D cache=0D				at: aClass=0D				ifAbsent: [cache =
> at: aClass put: (self allSuperPseudoClassesOf: aClass) asArray].=0D	=
> (aSet includesAnyOf: aClassAllSuperclasses)=0D		ifTrue: [^ false].=0D	=
> aClass isMetaClass=0D		ifFalse: [^ true].=0D	(aSet=0D			includes: (self =
> soleInstanceOf: aClass))=0D		ifTrue: [^ false].=0D	=
> aClassSoleInstanceAllSuperclasses :=3D cache=0D				at: (self =
> soleInstanceOf: aClass)=0D				ifAbsent: [cache at: aClass soleInstance =
> put: (self=0D							allSuperPseudoClassesOf: (self soleInstanceOf: =
> aClass)) asArray].=0D	(aSet includesAnyOf: =
> aClassSoleInstanceAllSuperclasses)=0D		ifTrue: [^ false].=0D	^ true! =
> !=0D=0D!FilePackage methodsFor: 'superclass ordering' stamp: 'MU =
> 6/21/2002 12:31'!=0DsoleInstanceOf: aPseudoClass =0D	^ classes values=0D	=
> 	detect: [:each | each name =3D aPseudoClass soleInstanceName]=0D		=
> ifNone: []! !=0D=0D!FilePackage methodsFor: 'superclass ordering' stamp: =
> 'MU 6/25/2002 17:15'!=0DsuperclassOrder=0D	^self superclassOrder: =
> classes values! !=0D=0D!FilePackage methodsFor: 'superclass ordering' =
> stamp: 'MU 6/21/2002 12:30'!=0DsuperclassOrder: klasses =0D	| all list =
> aClass inclusionSet aClassIndex cache |=0D	list :=3D klasses copy.=0D	=
> "list is indexable"=0D	inclusionSet :=3D list asSet.=0D	cache :=3D =
> Dictionary new.=0D	all :=3D OrderedCollection new: list size.=0D	list =
> size=0D		timesRepeat: [aClassIndex :=3D list=0D						findFirst: [:one | =
> one isNil not=0D								and: [self=0D										doWeFileOut: one=0D							=
> 			given: inclusionSet=0D										cache: cache]].=0D			aClass :=3D list =
> at: aClassIndex.=0D			all addLast: aClass.=0D			inclusionSet remove: =
> aClass.=0D			list at: aClassIndex put: nil].=0D	^ all! =
> !=0D=0D=0D!PseudoClass methodsFor: 'accessing' stamp: 'kuri-t 6/17/2002 =
> 15:32'!=0DclassCommentMergeStatus=0D	^ classCommentMergeStatus! =
> !=0D=0D!PseudoClass methodsFor: 'accessing' stamp: 'kuri-t 6/17/2002 =
> 15:32'!=0DclassCommentMergeStatus: statusSymbol=0D	=
> classCommentMergeStatus :=3D statusSymbol! !=0D=0D!PseudoClass =
> methodsFor: 'accessing' stamp: 'kuri-t 6/17/2002 =
> 15:31'!=0DclassDefinitionMergeStatus=0D	^ classDefinitionMergeStatus! =
> !=0D=0D!PseudoClass methodsFor: 'accessing' stamp: 'kuri-t 6/17/2002 =
> 15:31'!=0DclassDefinitionMergeStatus: statusSymbol=0D	=
> classDefinitionMergeStatus :=3D statusSymbol! !=0D=0D!PseudoClass =
> methodsFor: 'accessing' stamp: 'MU 6/25/2002 =
> 14:45'!=0DisClassCommentFileIn=0D	isClassCommentFileIn isNil ifTrue: =
> [isClassCommentFileIn :=3D false].=0D	^isClassCommentFileIn! =
> !=0D=0D!PseudoClass methodsFor: 'accessing' stamp: 'MU 6/25/2002 =
> 14:39'!=0DisClassCommentFileIn: anObject=0D	isClassCommentFileIn :=3D =
> anObject! !=0D=0D!PseudoClass methodsFor: 'accessing' stamp: 'MU =
> 6/25/2002 14:45'!=0DisClassDefinitionFileIn=0D	isClassDefinitionFileIn =
> isNil ifTrue: [isClassDefinitionFileIn :=3D false].=0D	=
> ^isClassDefinitionFileIn! !=0D=0D!PseudoClass methodsFor: 'accessing' =
> stamp: 'MU 6/25/2002 14:39'!=0DisClassDefinitionFileIn: anObject=0D	=
> isClassDefinitionFileIn :=3D anObject! !=0D=0D!PseudoClass methodsFor: =
> 'accessing' stamp: 'MU 6/25/2002 14:40'!=0DmethodFileInStatusDict=0D	=
> methodFileInStatusDict isNil=0D		ifTrue: [methodFileInStatusDict :=3D =
> Dictionary new].=0D	^ methodFileInStatusDict! !=0D=0D!PseudoClass =
> methodsFor: 'accessing' stamp: 'kuri-t 6/11/2002 =
> 17:09'!=0DmethodMergeStatusDict=0D	methodMergeStatusDict isNil=0D		=
> ifTrue: [methodMergeStatusDict :=3D Dictionary new].=0D	^ =
> methodMergeStatusDict! !=0D=0D!PseudoClass methodsFor: 'accessing' =
> stamp: 'MU 6/20/2002 17:17'!=0DparsedSuperPseudoClassName=0D	| clsName =
> |=0D	self hasDefinition ifFalse: [^nil].=0D	clsName :=3D  (self =
> definition readStream upTo: Character space) asSymbol.=0D	^clsName! =
> !=0D=0D!PseudoClass methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 16:19'!=0DfileInComment=0D	self exists ifFalse:[^self =
> classNotDefined].=0D	self hasComment ifTrue: [self realClass =
> classComment: self comment.=0D	self isClassCommentFileIn: true=0D	]! =
> !=0D=0D!PseudoClass methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 16:56'!=0DfileInCommentNotConflicted=0D	(self classCommentMergeStatus =
> =3D=3D #conflicted) ifTrue: [^ self].=0D	self fileInComment! =
> !=0D=0D!PseudoClass methodsFor: 'fileIn/fileOut' stamp: 'MU 6/25/2002 =
> 15:39'!=0DfileInDefinition=0D	(self=0D			makeSureSuperClassExists: =
> (definition copyUpTo: Character space))=0D		ifFalse: [^ self].=0D	self =
> hasDefinition=0D		ifTrue: [Transcript cr; show: 'Defining ' , self =
> name.=0D			self evaluate: self definition.=0D			self =
> isClassDefinitionFileIn: true].=0D	self exists=0D		ifFalse: [^ self].=0D	=
> self hasComment=0D		ifTrue: [self realClass classComment: self =
> comment.=0D			self isClassCommentFileIn: true]! !=0D=0D!PseudoClass =
> methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 16:24'!=0DfileInDefinitionOnly=0D	"file-in ##definition only##"=0D	self =
> hasDefinition=0D		ifFalse: [^ self].=0D	(self=0D			=
> makeSureSuperClassExists: (definition copyUpTo: Character space))=0D		=
> ifFalse: [^ self].=0D	Transcript cr; show: 'Defining ' , self name.=0D	=
> self evaluate: self definition.=0D	self isClassDefinitionFileIn: true! =
> !=0D=0D!PseudoClass methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 16:57'!=0DfileInDefinitionOnlyNotConflicted=0D	"file-in ##definition =
> only##"=0D	(self classDefinitionMergeStatus =3D=3D #conflicted) ifTrue: =
> [^ self].=0D	self fileInDefinitionOnly! !=0D=0D!PseudoClass methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/25/2002 14:46'!=0DfileInMethods: =
> aCollection=0D	"FileIn all methods with selectors taken from =
> aCollection"=0D	| theClass cat |=0D	self exists ifFalse:[^self =
> classNotDefined].=0D	theClass :=3D self realClass.=0D	aCollection =
> do:[:sel|=0D		cat :=3D self organization categoryOfElement: sel.=0D		cat =
> =3D self removedCategoryName ifFalse:[=0D			theClass =0D				compile: =
> (self sourceCodeAt: sel) =0D				classified: cat=0D				withStamp: (self =
> stampAt: sel)=0D				notifying: nil.=0D		self methodFileInStatusDict at: =
> sel put: true.=0D		].=0D	].! !=0D=0D!PseudoClass methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 16:57'!=0DfileInMethodsNotConflicted=0D	^self =
> fileInMethodsNotConflicted: self selectors! !=0D=0D!PseudoClass =
> methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 16:57'!=0DfileInMethodsNotConflicted: aCollection =0D	| selectors |=0D	=
> selectors :=3D aCollection=0D				reject: [:sel | (self =
> methodMergeStatusAt: sel)=0D						=3D=3D #conflicted].=0D	self =
> fileInMethods: selectors! !=0D=0D!PseudoClass methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 16:58'!=0DfileInNotConflicted=0D	=
> self hasDefinition ifTrue: [self fileInDefinitionOnlyNotConflicted].=0D	=
> self hasComment ifTrue: [self fileInCommentNotConflicted].=0D	self =
> fileInMethodsNotConflicted.=0D	metaClass ifNotNil:[metaClass =
> fileInNotConflicted].=0D	self needsInitialize ifTrue:[=0D		self =
> evaluate: self name,' initialize'.=0D	].! !=0D=0D!PseudoClass =
> methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 17:02'!=0DfileOutConflicted=0D	| f |=0D	f :=3D (FileStream newFileNamed: =
> self name,'---conflicts.st').=0D	self fileOutConflictedOn: f.! =
> !=0D=0D!PseudoClass methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 17:02'!=0DfileOutConflictedOn: aStream =0D	| methods |=0D	(self =
> hasDefinition=0D			and: [self classDefinitionMergeStatus =3D=3D =
> #conflicted])=0D		ifTrue: [aStream nextChunkPut: self definition;=0D				 =
> cr].=0D	(self hasComment=0D			and: [self classCommentMergeStatus =3D=3D =
> #conflicted])=0D		ifTrue: [aStream cr.=0D			self organization =
> commentRemoteStr fileOutOn: aStream].=0D	methods :=3D OrderedCollection =
> new.=0D	self methodMergeStatusDict=0D		keysAndValuesDo: [:key :value | =
> value =3D=3D #conflicted=0D				ifTrue: [methods add: key]].=0D	self =
> fileOutMethods: methods on: aStream.=0D	self hasMetaclass=0D		ifTrue: =
> [self metaClass fileOutConflictedOn: aStream]! !=0D=0D!PseudoClass =
> methodsFor: 'fileIn/fileOut' stamp: 'MU 6/26/2002 =
> 17:03'!=0DfileOutNotConflicted=0D	| f |=0D	f :=3D (FileStream =
> newFileNamed: self name,'---notConflicts.st').=0D	self =
> fileOutNotConflictedOn: f.! !=0D=0D!PseudoClass methodsFor: =
> 'fileIn/fileOut' stamp: 'MU 6/26/2002 17:03'!=0DfileOutNotConflictedOn: =
> aStream =0D	| methods |=0D	(self hasDefinition=0D			and: [self =
> classDefinitionMergeStatus ~=3D #conflicted])=0D		ifTrue: [aStream =
> nextChunkPut: self definition;=0D				 cr].=0D	(self hasComment=0D			and: =
> [self classCommentMergeStatus ~=3D #conflicted])=0D		ifTrue: [aStream =
> cr.=0D			self organization commentRemoteStr fileOutOn: aStream].=0D	=
> methods :=3D OrderedCollection new.=0D	self methodMergeStatusDict=0D		=
> keysAndValuesDo: [:key :value | value ~=3D #conflicted=0D				ifTrue: =
> [methods add: key]].=0D	self fileOutMethods: methods on: aStream.=0D	=
> self hasMetaclass=0D		ifTrue: [self metaClass fileOutNotConflictedOn: =
> aStream]! !=0D=0D!PseudoClass methodsFor: 'methods' stamp: 'MU 6/25/2002 =
> 15:41'!=0DmethodFileInStatusAt: selector=0D	^ self =
> methodFileInStatusDict at: selector ifAbsent:[false]! =
> !=0D=0D!PseudoClass methodsFor: 'methods' stamp: 'kuri-t 6/12/2002 =
> 19:00'!=0DmethodMergeStatusAt: selector=0D	^ self methodMergeStatusDict =
> at: selector ifAbsent:[]! !=0D=0D!PseudoClass methodsFor: 'methods' =
> stamp: 'kuri-t 6/7/2002 16:28'!=0DmethodMergeStatusAt: selector put: =
> statusSymbol=0D	^ self methodMergeStatusDict at: selector put: =
> statusSymbol! !=0D=0D!PseudoClass methodsFor: 'methods' stamp: 'kuri-t =
> 6/4/2002 15:31'!=0DsourceCodeAt: sel ifAbsent: aBlock=0D	| src |=0D	src =
>:=3D self sourceCode at: sel ifAbsent:[].=0D	src isNil ifFalse: [^src =
> string].=0D	^aBlock value! !=0D=0D!PseudoClass methodsFor: 'printing' =
> stamp: 'MU 6/21/2002 12:05'!=0DprintOn: aStream=0D	super printOn: =
> aStream.=0D	aStream space; nextPutAll: self name.=0D	! =
> !=0D=0D!PseudoClass methodsFor: 'testing method dictionary' stamp: =
> 'kuri-t 6/4/2002 15:47'!=0DincludesSelector: aSymbol=0D	^self selectors =
> includes: aSymbol! !=0D=0D!PseudoClass methodsFor: 'merging' stamp: 'MU =
> 6/26/2002 19:13'!=0DmergeMessages: selectors with: otherPseudoClass =0D	=
> | addedKeys |=0D	otherPseudoClass isNil=0D		ifTrue: [^ self].=0D	=
> addedKeys :=3D otherPseudoClass selectors removeAllFoundIn: =
> selectors;=0D				 yourself.=0D	addedKeys=0D		do: [:addedKey | =0D			| =
> methodChange | =0D			methodChange :=3D otherPseudoClass sourceCode at: =
> addedKey.=0D			methodChange isText=0D				ifFalse: [self addMethodChange: =
> methodChange.=0D					self methodMergeStatusAt: addedKey put: =
> #migrated.=0D					otherPseudoClass removeMethod: methodChange =
> methodSelector]].=0D	selectors=0D		do: [:sel | =0D			| otherMethod | =0D	=
> 		otherMethod :=3D otherPseudoClass=0D						sourceCodeAt: sel=0D						=
> ifAbsent: [].=0D			otherMethod isNil=0D				ifFalse: [(self sourceCodeAt: =
> sel)=0D							=3D otherMethod asString=0D						ifTrue: [otherPseudoClass =
> removeMethod: sel]=0D						ifFalse: [self methodMergeStatusAt: sel put: =
> #conflicted.=0D							otherPseudoClass methodMergeStatusAt: sel put: =
> #conflicted]]].=0D	otherPseudoClass organization removeEmptyCategories! =
> !=0D=0D!PseudoClass methodsFor: 'merging' stamp: 'kuri-t 6/5/2002 =
> 16:08'!=0DmergeMessagesWith: otherPseudoClass =0D	^self mergeMessages: =
> self selectors with: otherPseudoClass ! !=0D=0D!PseudoClass methodsFor: =
> 'merging' stamp: 'MU 6/26/2002 15:28'!=0DmergeStatus=0D	| status |=0D	=
> status :=3D Set new.=0D	self methodMergeStatusDict=0D		valuesDo: [:each =
> | status add: each].=0D	self classDefinitionMergeStatus isNil=0D		=
> ifFalse: [status add: self classDefinitionMergeStatus].=0D	self =
> classCommentMergeStatus isNil=0D		ifFalse: [status add: self =
> classCommentMergeStatus].=0D	(status includes: #conflicted) ifTrue: [^ =
> #conflicted].=0D	(status includes: #migrated) ifTrue: [^ #migrated].=0D	=
> ^ #original! !=0D=0D!PseudoClass methodsFor: 'merging' stamp: 'kuri-t =
> 6/14/2002 16:39'!=0DmergeWith: theOtherPseudoClass =0D	=
> theOtherPseudoClass isNil=0D		ifTrue: [^ self].=0D	self =
> mergeMessagesWith: theOtherPseudoClass.=0D	(self hasDefinition=0D			and: =
> [self definition =3D theOtherPseudoClass definition])=0D		ifTrue: =
> [theOtherPseudoClass definition: nil].=0D	(self hasComment=0D			and: =
> [self comment asString =3D theOtherPseudoClass comment asString])=0D		=
> ifTrue: [theOtherPseudoClass classComment: nil].=0D	(theOtherPseudoClass =
> hasComment=0D			and: [self hasComment not])=0D		ifTrue: [self =
> commentString: theOtherPseudoClass comment asString. =0D			=
> theOtherPseudoClass classComment: nil].=0D	self =
> setClassMergeStatusUsing: theOtherPseudoClass.=0D	metaClass isNil=0D		=
> ifFalse: [metaClass mergeWith: theOtherPseudoClass metaClass]! =
> !=0D=0D!PseudoClass methodsFor: 'merging' stamp: 'kuri-t 6/11/2002 =
> 19:01'!=0DsetAllMessagesMergeStatusMigrated=0D	self sourceCode=0D		=
> keysAndValuesDo: [:key :value | self methodMergeStatusDict at: key put: =
> #migrated].=0D	metaClass isNil=0D		ifFalse: [self metaClass =
> setAllMessagesMergeStatusMigrated]! !=0D=0D!PseudoClass methodsFor: =
> 'merging' stamp: 'kuri-t 6/17/2002 =
> 16:43'!=0DsetClassMergeStatusMigrated=0D	self hasDefinition=0D		ifTrue: =
> [self classDefinitionMergeStatus: #migrated].=0D	self hasComment=0D		=
> ifTrue: [self classCommentMergeStatus: #migrated].=0D	self =
> hasMetaclass=0D		ifTrue: [self metaClass hasDefinition=0D				ifTrue: =
> [self metaClass classDefinitionMergeStatus: #migrated]]! =
> !=0D=0D!PseudoClass methodsFor: 'merging' stamp: 'MU 6/26/2002 =
> 15:34'!=0DsetClassMergeStatusUsing: theOtherPseudoClass =0D	| =
> otherDefinition otherComment |=0D	self hasDefinition=0D		ifTrue: =
> [theOtherPseudoClass hasDefinition=0D				ifTrue: [otherDefinition :=3D =
> theOtherPseudoClass definition.=0D					self definition =3D =
> otherDefinition=0D						ifFalse: [self classDefinitionMergeStatus: =
> #conflicted.=0D							theOtherPseudoClass classDefinitionMergeStatus: =
> #conflicted]]]=0D		ifFalse: [theOtherPseudoClass hasDefinition=0D				=
> ifTrue: [self classDefinitionMergeStatus: #migrated]].=0D	=
> theOtherPseudoClass hasComment=0D		ifTrue: [self hasComment=0D				=
> ifTrue: [otherComment :=3D theOtherPseudoClass comment.=0D					self =
> comment =3D otherComment=0D						ifFalse: [self classCommentMergeStatus: =
> #conflicted.=0D							theOtherPseudoClass classDefinitionMergeStatus: =
> #conflicted]]=0D				ifFalse: [self classCommentMergeStatus: #migrated]]! =
> !=0D=0D!PseudoClass methodsFor: 'comparing' stamp: 'kuri-t 6/18/2002 =
> 17:54'!=0D<=3D aPsudoClass=0D	=0D	^self name <=3D aPsudoClass name! =
> !=0D=0D!PseudoClass methodsFor: 'comparing' stamp: 'kuri-t 6/18/2002 =
> 17:54'!=0D=3D aPsudoClass=0D	=0D	^self name =3D aPsudoClass name! =
> !=0D=0D=0D!PseudoMetaclass methodsFor: 'accessing' stamp: 'MU 6/20/2002 =
> 17:18'!=0DparsedSuperPseudoClassName=0D	| clsName |=0D	self =
> hasDefinition ifFalse: [^nil].=0D	clsName :=3D  (self definition =
> readStream upTo: Character space) asSymbol.=0D	^clsName, ' class'! =
> !=0D=0D!PseudoMetaclass methodsFor: 'accessing' stamp: 'kuri-t 6/18/2002 =
> 17:25'!=0DsoleInstance=0D	^ super realClass class soleInstance! =
> !=0D=0D!PseudoMetaclass methodsFor: 'accessing' stamp: 'MU 6/20/2002 =
> 17:57'!=0DsoleInstanceName=0D	| clsName |=0D	clsName :=3D  (self name =
> readStream upTo: Character space) asSymbol.=0D	^clsName! !=0D=0DObject =
> subclass: #PseudoClass=0D	instanceVariableNames: 'name definition =
> organization source metaClass classDefinitionMergeStatus =
> classCommentMergeStatus methodMergeStatusDict isClassDefinitionFileIn =
> isClassCommentFileIn methodFileInStatusDict '=0D	classVariableNames: =
> ''=0D	poolDictionaries: ''=0D	category: 'Tools-File Contents Browser'!=0D=
> 
> --Boundary_(ID_ypGspb+Ulcz08ltRBqgWfA)--



More information about the Squeak-dev mailing list