[ENH] Change Sorter mods to provided filtered lists and checks

Steve Wessels stephan.wessels at sdrc.com
Thu Mar 30 14:03:16 UTC 2000


change-sorter-lists

This change sets adds two capabilities to the change set sorter
(single list and dual list).

1.  change set filter menu
 A new hierarchical menu is added to the change set menu.
 The following options are provided in the menu:
  - sort the change set list
   This toggles a local preference used by the change sorter
   to view the change sets sorted alphabetically.  For the dual
   change list sorter you could decide to filter one side sorted
   and the other side not.  Note that an additional Preference
   is also provided in the fileout category to sort change set
   lists by default.
  - show all
   Default behavior of existing Sqeuak change sets.
  - show only base
   Uses the existing Squeak change sorter logic to display only
   those change sets that exist before the updates.  For example
   the Play With Me series.
  - show only named
   Shows change sets which are not updates and not base.
   Typically this is a list of the change sets that you have
   installed.
  - show only updates
   Shows only those change sets that are updates.  Note that
   there was some minor refactoring done to the methods
   to support these features with a minimum of duplicate code.

2.  check for unimplemented messages in a change set
 A new menu item is added to the more... menu for a
 selected change set which allows you to perform a
 search for unimplemented messages that your change
 set depends upon.  Message  browsers are open for each
 unimplemented message found.  This is a handy sanity check
 to catch dependencies between change sets before you file out
 code.
-------------- next part --------------
'From Squeak2.8alpha of 13 January 2000 [latest update: #1974] on 29 March 2000 at 9:01:09 am'!
CodeHolder subclass: #ChangeSorter
	instanceVariableNames: 'parent myChangeSet currentClassName currentSelector priorChangeSetList filter currentChangeSetName sortChangeList '
	classVariableNames: 'AllChangeSets '
	poolDictionaries: ''
	category: 'Tools-Changes'!

!ChangeSet methodsFor: 'fileIn/Out' stamp: 'sbw 3/29/2000 08:45'!
checkForUnimplementedMessages
	| msgs changes method missing nameLine |
	msgs _ Set new.
	self changedClasses do: 
		[:cls | 
		changes _ methodChanges at: cls name ifAbsent: [].
		changes isNil ifFalse: [changes
				associationsDo: 
					[:mAssoc | 
					method _ cls compiledMethodAt: mAssoc key ifAbsent: [].
					method isNil ifFalse: [msgs addAll: method messages]]]].
	missing _ msgs select: [:selector | (Smalltalk allImplementorsOf: selector) isEmpty].
	nameLine _ '"' , self name , '"'.
	missing size = 0
		ifTrue: [self inform: 'There are no unimplemented messages in change set ' , nameLine]
		ifFalse: [
			"For now, loop with multiple message browser.  A neat thing to do would be to make a
			 special version of the protocol browser to see all unimplemented messages in one browser."
			missing do: [:sel | Smalltalk browseAllCallsOn: sel]]! !


!ChangeSorter reorganize!
('creation' morphicWindow open openAsMorph openAsMorphIn:rect: openView:offsetBy: veryDeepFixupWith: veryDeepInner:)
('access' changeSet changeSetCurrentlyDisplayed label labelString modelWakeUp myChangeSet: parent parent: showChangeSet: showChangeSetNamed:)
('changeSet menu' addFilterMenuItemTo:label:action:help: addFilterSubMenuTo: addPreamble browseChangeSet browseMethodConflicts changeSetList changeSetListKey:from: changeSetMenu:shifted: checkForUnimplementedMessages checkForUnsentMessages checkThatSidesDiffer: chooseCngSet clearChangeSet copyAllToOther currentCngSet editPostscript editPreamble fileIntoNewChangeSet fileOut filteredChangedSetList findCngSet goToChangeSetsProject inspectChangeSet lookForSlips mainButtonName methodConflictsWithOtherSide newCurrent newSet promoteToTopChangeSet remove removePostscript removePreamble removePrompting: rename shiftedChangeSetMenu: submergeIntoOtherSide subtractOtherSide uninstallChangeSet update updateIfNecessary updateViaFilterChange)
('class list' classList classListKey:from: classMenu: copyClassToOther currentClassName currentClassName: forgetClass moveClassToOther selectedClass selectedClassOrMetaClass)
('message list' browseVersions copyMethodToOther currentSelector currentSelector: forget messageList messageMenu:shifted: moveMethodToOther removeFromCurrentChanges removeMessage selectedMessage selectedMessageName shiftedMessageMenu:)
('code pane' contents:notifying: setContents spawn:)
('optional panes' buildAnnotationPaneMorph optionalButtonPairs optionalButtonRow)
('initialize variables' initializeFilter initializeSortChangeList setFilterBase setFilterNamed setFilterNone setFilterUpdates setNoSortChangesList setSortChangesList)
('accessing' filter filter: isFilterBase isFilterNamed isFilterNone isFilterUpdates sortChangeList sortChangeList:)
!


!ChangeSorter methodsFor: 'creation' stamp: 'sbw 3/11/2000 08:02'!
openAsMorphIn: window rect: rect 
	"Add a set of change sorter views to the given top view offset by the 
	given amount. To create a single change sorter, call this once with an 
	offset of 0 at 0. To create a dual change sorter, call it twice with offsets 
	of 0 at 0 and 0.5 at 0."
	| chgSetList aListMorph baseline aTextMorph |
	contents _ ''.
	self addDependent: window.
	"so it will get changed: #relabel"
	window addMorph: (chgSetList _ PluggableListMorphByItem
					on: self
					list: #filteredChangedSetList
					selected: #currentCngSet
					changeSelected: #showChangeSetNamed:
					menu: #changeSetMenu:shifted:
					keystroke: #changeSetListKey:from:) frame: (((0 @ 0 extent: 0.5 @ 0.25)
			scaleBy: rect extent)
			translateBy: rect origin).
	chgSetList autoDeselect: false.
	window addMorph: (PluggableListMorphByItem
			on: self
			list: #classList
			selected: #currentClassName
			changeSelected: #currentClassName:
			menu: #classMenu:
			keystroke: #classListKey:from:)
		frame: (((0.5 @ 0 extent: 0.5 @ 0.25)
				scaleBy: rect extent)
				translateBy: rect origin).
	aListMorph _ PluggableListMorphByItem
				on: self
				list: #messageList
				selected: #currentSelector
				changeSelected: #currentSelector:
				menu: #messageMenu:shifted:
				keystroke: #messageListKey:from:.
	aListMorph menuTitleSelector: #messageListSelectorTitle.
	baseline _ 0.43.
	window addMorph: aListMorph frame: (((0 @ 0.25 extent: 1 @ (baseline - 0.25))
			scaleBy: rect extent)
			translateBy: rect origin).
	baseline _ 0.43.
	Preferences useAnnotationPanes
		ifTrue: 
			[aTextMorph _ self buildAnnotationPaneMorph.
			aTextMorph askBeforeDiscardingEdits: false.
			window addMorph: aTextMorph frame: (((0 @ baseline corner: 1 @ 0.5)
					scaleBy: rect extent)
					translateBy: rect origin).
			baseline _ 0.5].
	Preferences optionalButtons
		ifTrue: 
			[window addMorph: self optionalButtonRow frame: (((0 @ baseline corner: 1 @ 0.56)
					scaleBy: rect extent)
					translateBy: rect origin).
			baseline _ 0.56].
	window addMorph: (PluggableTextMorph
			on: self
			text: #contents
			accept: #contents:notifying:
			readSelection: #contentsSelection
			menu: #codePaneMenu:shifted:)
		frame: (((0 @ baseline corner: 1 @ 1)
				scaleBy: rect extent)
				translateBy: rect origin)! !

!ChangeSorter methodsFor: 'creation' stamp: 'sbw 3/11/2000 08:02'!
openView: topView offsetBy: offset 
	"Add a set of change sorter views to the given top view offset by the 
	given amount. To create a single change sorter, call this once with an 
	offset of 0 at 0. To create a dual change sorter, call it twice with offsets 
	of 0 at 0 and 360 at 0."
	| classView messageView codeView cngSetListView |
	contents _ ''.
	self addDependent: topView.
	"so it will get changed: #relabel"
	cngSetListView _ PluggableListViewByItem
				on: self
				list: #filteredChangedSetList
				selected: #currentCngSet
				changeSelected: #showChangeSetNamed:
				menu: #changeSetMenu:shifted:.
	cngSetListView window: ((0 @ 0 extent: 180 @ 100)
			translateBy: offset).
	topView addSubView: cngSetListView.
	classView _ PluggableListViewByItem
				on: self
				list: #classList
				selected: #currentClassName
				changeSelected: #currentClassName:
				menu: #classMenu:
				keystroke: #classListKey:from:.
	classView window: (180 @ 0 extent: 180 @ 100).
	topView addSubView: classView toRightOf: cngSetListView.
	messageView _ PluggableListViewByItem
				on: self
				list: #messageList
				selected: #currentSelector
				changeSelected: #currentSelector:
				menu: #messageMenu:shifted:
				keystroke: #messageListKey:from:.
	messageView menuTitleSelector: #messageListSelectorTitle.
	messageView window: (0 @ 100 extent: 360 @ 100).
	topView addSubView: messageView below: cngSetListView.
	codeView _ PluggableTextView
				on: self
				text: #contents
				accept: #contents:notifying:
				readSelection: #contentsSelection
				menu: #codePaneMenu:shifted:.
	codeView window: (0 @ 0 extent: 360 @ 180).
	topView addSubView: codeView below: messageView! !

!ChangeSorter methodsFor: 'creation' stamp: 'sbw 3/19/2000 15:16'!
veryDeepInner: deepCopier
	"Copy all of my instance variables.  Some need to be not copied at all, but shared."

super veryDeepInner: deepCopier.
"parent _ parent.		Weakly copied"
"myChangeSet _ myChangeSet.		Weakly copied"
currentClassName _ currentClassName veryDeepCopyWith: deepCopier.
"currentSelector _ currentSelector.		Symbol"
priorChangeSetList _ priorChangeSetList veryDeepCopyWith: deepCopier.
filter _ filter veryDeepCopyWith: deepCopier.
sortChangeList _ sortChangeList veryDeepCopyWith: deepCopier.! !

!ChangeSorter methodsFor: 'access' stamp: 'sbw 3/11/2000 10:58'!
myChangeSet: anObject 
	myChangeSet _ anObject.
	currentChangeSetName _ myChangeSet name! !

!ChangeSorter methodsFor: 'access' stamp: 'sbw 3/11/2000 10:53'!
showChangeSetNamed: aName 
	aName ifNil: [^ self showChangeSet: nil].
	currentChangeSetName _ aName.
	self showChangeSet: (AllChangeSets detect: [:each | each name = aName])! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/12/2000 15:12'!
addFilterMenuItemTo: menu label: aString action: aSelector help: hString
	World isNil
		ifTrue: [menu add: aString action: aSelector]
		ifFalse: [
			menu add: aString target: self action: aSelector.
			hString isNil ifFalse: [menu balloonTextForLastItem: hString]]! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/12/2000 15:20'!
addFilterSubMenuTo: menu 
	| title subMenu |
	World isNil
		ifTrue: [subMenu _ menu]
		ifFalse: 
			[title _ 'change set filter...'.
			subMenu _ MenuMorph entitled: title.
			subMenu defaultTarget: menu defaultTarget].
	self sortChangeList
		ifTrue: [self
				addFilterMenuItemTo: subMenu
				label: 'no sorting of change set list'
				action: #setNoSortChangesList
				help: nil]
		ifFalse: [self
				addFilterMenuItemTo: subMenu
				label: 'sort the change set list'
				action: #setSortChangesList
				help: nil].
	subMenu addLine.
	self isFilterBase not
		ifTrue: [self
				addFilterMenuItemTo: subMenu
				label: 'show only base'
				action: #setFilterBase
				help: 'Resets the list of change sets to be only those in the "base" before updates.'].
	self isFilterNamed not
		ifTrue: [self
				addFilterMenuItemTo: subMenu
				label: 'show only named'
				action: #setFilterNamed
				help: 'Resets the list of change sets to be only those which are non updates and not base.'].
	self isFilterNone not
		ifTrue: 
			[self
				addFilterMenuItemTo: subMenu
				label: 'show all'
				action: #setFilterNone
				help: 'Resets the list of change sets to be all change sets.'].
	self isFilterUpdates not
		ifTrue: 
			[self
				addFilterMenuItemTo: subMenu
				label: 'show only updates'
				action: #setFilterUpdates
				help: 'Resets the list of change sets to be only those which are numbered updates.'].
	World isNil ifFalse: [menu add: title subMenu: subMenu]! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/11/2000 11:37'!
changeSetMenu: aMenu shifted: isShifted 
	"Could be for a single or double changeSorter"
	aMenu title: 'Change Set:
' , myChangeSet name.
	isShifted ifTrue: [^ self shiftedChangeSetMenu: aMenu].
	aMenu add: 'make changes go to me' action: #newCurrent.
	aMenu addLine.
	aMenu add: 'new change set...' action: #newSet.
	aMenu add: 'find...' action: #findCngSet.
	aMenu add: 'show...' action: #chooseCngSet.
	aMenu add: 'rename change set' action: #rename.
	aMenu addLine.
	aMenu add: 'file out' action: #fileOut.
	aMenu add: 'browse methods' action: #browseChangeSet.
	aMenu addLine.
	parent
		ifNotNil: 
			[aMenu add: 'copy all to other side' action: #copyAllToOther.
			aMenu add: 'submerge into other side' action: #submergeIntoOtherSide.
			aMenu add: 'subtract other side' action: #subtractOtherSide.
			aMenu addLine].
	myChangeSet hasPreamble
		ifTrue: 
			[aMenu add: 'edit preamble' action: #addPreamble.
			aMenu add: 'remove preamble' action: #removePreamble]
		ifFalse: [aMenu add: 'add preamble' action: #addPreamble].
	"aMenu add: 'edit preamble...' action: #editPreamble."
	myChangeSet hasPostscript
		ifTrue: 
			[aMenu add: 'edit postscript...' action: #editPostscript.
			aMenu add: 'remove postscript' action: #removePostscript]
		ifFalse: [aMenu add: 'add postscript...' action: #editPostscript].
	aMenu addLine.
	aMenu add: 'destroy change set' action: #remove.
	aMenu addLine.
	self addFilterSubMenuTo: aMenu.
	aMenu add: 'more...' action: #shiftedYellowButtonActivity.
	^ aMenu! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/28/2000 16:14'!
checkForUnimplementedMessages
	"Open a message list browser on all unimplemented messages sent in the current change set"

	myChangeSet checkForUnimplementedMessages

! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/12/2000 13:37'!
filteredChangedSetList
	"Filtering only supported in Morphic window right now."
	| dict list |
	"World isNil ifTrue: [^ self changeSetList]."
	dict _ self class divideChangeSets.
	list _ self changeSetList.
	self isFilterBase ifTrue: [list _ (dict at: 'release')
					collect: [:cs | cs name]].
	self isFilterNamed ifTrue: [list _ (dict at: 'remaining')
					collect: [:cs | cs name]].
	self isFilterUpdates ifTrue: [list _ (dict at: 'numbered')
					collect: [:cs | cs name]].
	^ self sortChangeList
		ifTrue: [list asSortedCollection]
		ifFalse: [list]! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/11/2000 11:40'!
promoteToTopChangeSet
	self class promoteToTop: myChangeSet.
	self filter: #none.
	self setNoSortChangesList! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/28/2000 15:58'!
shiftedChangeSetMenu: aMenu
	aMenu add: 'conflicts with other change sets' action: #browseMethodConflicts.
	aMenu balloonTextForLastItem: 
'Browse all methods that occur both in this change set and in at least one other change set.'.

	parent ifNotNil:
		[aMenu add: 'conflicts with opposite side' action: #methodConflictsWithOtherSide.
			aMenu balloonTextForLastItem: 
'Browse all methods that occur both in this change set and in the one on the opposite side of the change sorter.'.
].
	aMenu addLine.
	aMenu add: 'check for slips' action: #lookForSlips.
	aMenu balloonTextForLastItem: 
'Check this change set for halts and references to Transcript.'.

	aMenu add: 'check for unsent messages' action: #checkForUnsentMessages.
	aMenu balloonTextForLastItem:
'Check this change set for messages that are not sent anywhere in the system'.

	aMenu add: 'check for unimplemented messages' action: #checkForUnimplementedMessages.
	aMenu balloonTextForLastItem:
'Check this change set for sent messages that are not implemented anywhere in the system'.
	aMenu addLine.

	aMenu add: 'inspect change set' action: #inspectChangeSet.
	aMenu balloonTextForLastItem: 
'Open an inspector on this change set. (There are some details in a change set which you don''t see in a change sorter.)'.

	aMenu add: 'update' action: #update.
	aMenu balloonTextForLastItem: 
'Update the display for this change set.  (This is done automatically when you activate this window, so is seldom needed.)'.

	aMenu add: 'go to change set''s project' action: #goToChangeSetsProject.
	aMenu balloonTextForLastItem: 
'If this change set is currently associated with a Project, go to that project right now.'.

	aMenu add: 'promote to top of list' action: #promoteToTopChangeSet.
	aMenu balloonTextForLastItem:
'Make this change set appear first in change-set lists in all change sorters.'.

	aMenu add: 'clear this change set' action: #clearChangeSet.
	aMenu balloonTextForLastItem: 
'Reset this change set to a pristine state where it holds no information. CAUTION: this is destructive and irreversible!!'.

	aMenu add: 'uninstall this change set' action: #uninstallChangeSet.
	aMenu balloonTextForLastItem: 
'Attempt to uninstall this change set. CAUTION: this may not work completely and is irreversible!!'.

	aMenu addLine.
	aMenu add: 'file into new...' action: #fileIntoNewChangeSet.
	aMenu balloonTextForLastItem: 
'Load a fileout from disk and place its changes into a new change set (seldom needed -- much better to do this from a file-list browser these days.)'.

	aMenu addLine.
	aMenu add: 'more...' action: #unshiftedYellowButtonActivity.
	aMenu balloonTextForLastItem: 
'Takes you back to the primary change-set menu.'.

	^ aMenu! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/11/2000 08:01'!
updateIfNecessary
	"recompute all of my panes"
	| newList |
	myChangeSet isMoribund ifTrue: [^ self showChangeSet: Smalltalk changes].
	self okToChange ifFalse: [^ self].
	priorChangeSetList == nil
		ifTrue: 
			[priorChangeSetList _ self filteredChangedSetList.
			self changed: #filteredChangedSetList]
		ifFalse: 
			[newList _ self filteredChangedSetList.
			priorChangeSetList = newList
				ifFalse: 
					[priorChangeSetList _ newList.
					self changed: #filteredChangedSetList]].
	self showChangeSet: myChangeSet! !

!ChangeSorter methodsFor: 'changeSet menu' stamp: 'sbw 3/11/2000 10:57'!
updateViaFilterChange
	(self filteredChangedSetList includes: self currentCngSet)
		ifTrue: [currentChangeSetName _ self currentCngSet]
		ifFalse: 
			[currentChangeSetName _ nil.
			currentClassName _ nil.
			currentSelector _ nil].
	self changed: #filteredChangedSetList.
	self showChangeSet: myChangeSet! !

!ChangeSorter methodsFor: 'class list' stamp: 'sbw 3/11/2000 10:53'!
classList
	"Computed.  View should try to preserve selections, even though index 
	changes "
	currentChangeSetName isNil ifTrue: [^#()].
	^ myChangeSet changedClassNames! !

!ChangeSorter methodsFor: 'optional panes' stamp: 'sbw 2/3/2000 12:01'!
buildAnnotationPaneMorph

	^PluggableTextMorph
		on: self
		text: #annotation
		accept: nil
		readSelection: nil
		menu: nil! !

!ChangeSorter methodsFor: 'optional panes' stamp: 'sbw 2/3/2000 15:05'!
optionalButtonPairs

	^#(('senders' 		browseSendersOfMessages)
	('impl.'				browseMessages)
	('vers.'				browseVersions)
	('inherit'			methodHierarchy)
	('browse'			browseMethodFull))! !

!ChangeSorter methodsFor: 'optional panes' stamp: 'sbw 2/3/2000 12:23'!
optionalButtonRow
	| aRow aButton clr |
	aRow _ AlignmentMorph newRow.
	aButton _ SimpleButtonMorph new target: self.
	clr _ self defaultBackgroundColor darker.
	aButton color: clr; borderWidth: 1; borderColor: Color black.
	self optionalButtonPairs  do:
			[:pair |
				aButton _ aButton fullCopy.
				aButton actionSelector: pair second.
				aButton label: pair first pad: 6 at 1.
				aRow addMorphBack: aButton.
				aRow addTransparentSpacerOfSize: (2 @ 0)].

	^ aRow! !

!ChangeSorter methodsFor: 'initialize variables' stamp: 'sbw 3/11/2000 10:30'!
initializeFilter
	"Generated - Private.  Initialize the value of filter."
	self filter: #none!
]style[(16 2 55 2 4 14)f1b,f1,f1cred;,f1,f1cblue;b,f1! !

!ChangeSorter methodsFor: 'initialize variables' stamp: 'sbw 3/11/2000 18:44'!
initializeSortChangeList
	"Generated - Private.  Initialize the value of sortChangeList."
	self sortChangeList: Preferences sortChangeSets! !

!ChangeSorter methodsFor: 'initialize variables' stamp: 'sbw 3/11/2000 10:15'!
setFilterBase
	self filter: #base.
	self updateViaFilterChange! !

!ChangeSorter methodsFor: 'initialize variables' stamp: 'sbw 3/11/2000 10:15'!
setFilterNamed
	self filter: #named.
	self updateViaFilterChange! !

!ChangeSorter methodsFor: 'initialize variables' stamp: 'sbw 3/11/2000 10:15'!
setFilterNone
	self filter: #none.
	self updateViaFilterChange! !

!ChangeSorter methodsFor: 'initialize variables' stamp: 'sbw 3/11/2000 10:15'!
setFilterUpdates
	self filter: #updates.
	self updateViaFilterChange! !

!ChangeSorter methodsFor: 'initialize variables' stamp: 'sbw 3/11/2000 11:14'!
setNoSortChangesList
	self sortChangeList: false.
	self updateViaFilterChange! !

!ChangeSorter methodsFor: 'initialize variables' stamp: 'sbw 3/11/2000 18:45'!
setSortChangesList
	self sortChangeList: true.
	self updateViaFilterChange! !

!ChangeSorter methodsFor: 'accessing' stamp: 'sbw 3/11/2000 07:54'!
filter
	"Generated - Return the value of filter."

	filter == nil ifTrue: [self initializeFilter].
	^filter! !

!ChangeSorter methodsFor: 'accessing' stamp: 'sbw 3/11/2000 07:54'!
filter: anObject
	"Generated - Set the value of filter to <anObject>."

	filter _ anObject! !

!ChangeSorter methodsFor: 'accessing' stamp: 'sbw 3/11/2000 07:57'!
isFilterBase

	^self filter = #base! !

!ChangeSorter methodsFor: 'accessing' stamp: 'sbw 3/11/2000 07:57'!
isFilterNamed

	^self filter = #named! !

!ChangeSorter methodsFor: 'accessing' stamp: 'sbw 3/11/2000 07:57'!
isFilterNone

	^self filter = #none! !

!ChangeSorter methodsFor: 'accessing' stamp: 'sbw 3/11/2000 07:58'!
isFilterUpdates

	^self filter = #updates! !

!ChangeSorter methodsFor: 'accessing' stamp: 'sbw 3/11/2000 11:05'!
sortChangeList
	"Generated - Return the value of sortChangeList."

	sortChangeList == nil ifTrue: [self initializeSortChangeList].
	^sortChangeList! !

!ChangeSorter methodsFor: 'accessing' stamp: 'sbw 3/11/2000 11:05'!
sortChangeList: anObject
	"Generated - Set the value of sortChangeList to <anObject>."

	sortChangeList _ anObject! !


!ChangeSorter class reorganize!
('as yet unclassified' allChangeSetNames allChangeSetsWithClass:selector: allChangeSetsWithClassChangesForClassNamed: browseChangeSetsWithClass:selector: changeSetNamed: changeSetsNamedSuchThat: divideChangeSets gatherChangeSets highestNumberedChangeSet initialize mostRecentChangeSetWithChangeForClass:selector: newChangeSet newChangesFromStream:named: promoteToTop: removeChangeSet: removeChangeSetsBefore: removeChangeSetsNamedSuchThat: removeEmptyUnnamedChangeSets reorderChangeSets secondaryChangeSet)
('install prefs' installConflictsCheckPreferences installConflictsCheckPreferencesHelp installSortChangesPreferences installSortChangesPreferencesHelp)
!


!ChangeSorter class methodsFor: 'as yet unclassified' stamp: 'sbw 3/11/2000 07:44'!
divideChangeSets
	"ChangeSorter divideChangeSets"
	"Answers a dictionary containing all the change sets, partitioned along the following keys:
		'release'	- the unnumbered changesets that come with the release.
		'numbered'	- the numbered updates.
		'remaining'	- all remaining changesets."
	| newHead newMid newTail itsName dict |
	self gatherChangeSets.
	newHead _ OrderedCollection new.
	newMid _ OrderedCollection new.
	newTail _ OrderedCollection new.
	AllChangeSets do: 
		[:aSet | 
		itsName _ aSet name.
		((itsName beginsWith: 'Play With Me')
			or: [#('New Changes' 'MakeInternal' ) includes: itsName])
			ifTrue: [newHead add: aSet]
			ifFalse: [itsName startsWithDigit
					ifTrue: [newMid add: aSet]
					ifFalse: [newTail add: aSet]]].
	dict _ Dictionary new.
	dict at: 'release' put: newHead.
	dict at: 'numbered' put: newMid.
	dict at: 'remaining' put: newTail.
	^dict! !

!ChangeSorter class methodsFor: 'as yet unclassified' stamp: 'sbw 3/11/2000 07:46'!
reorderChangeSets
	"ChangeSorter reorderChangeSets"
	"Change the order of the change sets to something more convenient: 
	First come the unnumbered changesets that come with the release. 
	Next come the numbered updates. 
	Next come all remaining changesets 
	In a ChangeSorter, they will appear in the reversed order."
	| newHead newMid newTail dict |
	dict _ self divideChangeSets.
	newHead _ dict at: 'release'.
	newMid _ dict at: 'numbered'.
	newTail _ dict at: 'remaining'.
	AllChangeSets _ newHead , newMid , newTail.
	Smalltalk isMorphic ifTrue: [SystemWindow wakeUpTopWindowUponStartup]! !

!ChangeSorter class methodsFor: 'install prefs' stamp: 'sbw 3/11/2000 18:47'!
installSortChangesPreferences
	"ChangeSorter installSortChangesPreferences"
	Preferences setPreference: #sortChangeSets toValue: false.
	self installSortChangesPreferencesHelp.
	Preferences resetCategoryInfo! !

!ChangeSorter class methodsFor: 'install prefs' stamp: 'sbw 3/11/2000 18:47'!
installSortChangesPreferencesHelp
	"ChangeSorter installSortChangesPreferencesHelp"
	Preferences setHelpFor: #sortChangeSets toString: 'If true, will cause changes sets to show as sorted by default.'! !


!MenuMorph methodsFor: 'menu' stamp: 'sbw 3/11/2000 09:40'!
setInvokingView: invokingView 
	"Re-work every menu item of the form   
	<target> perform: <selector>   
	to the form   
	<target> perform: <selector> orSendTo: <invokingView>.   
	This supports MVC's vectoring of non-model messages to the editPane."
	self items do: [:item | item subMenu isNil
			ifTrue: ["sbw - This added check is to work around a bug in the base 
				system.  If the item holds a sub-menu we should ignore it here. "
				item arguments isEmpty
					ifTrue: 
						["only the simple messages"
						item arguments: (Array with: item selector with: invokingView).
						item selector: #perform:orSendTo:]]]! !


!Preferences class methodsFor: 'standard preferences' stamp: 'sbw 3/11/2000 18:43'!
sortChangeSets
	^ self valueOfFlag: #sortChangeSets! !

!Preferences class methodsFor: 'initial values' stamp: 'sbw 3/11/2000 18:43'!
initialValuesSortChangesPrefs
	"Preferences resetCategoryInfo."
	"Preferences openFactoredPanel"
	^ #((sortChangeSets false (fileout ) ) )! !


"Postscript:"
ChangeSorter installSortChangesPreferences!



More information about the Squeak-dev mailing list