[squeak-dev] The Trunk: Tools-eem.249.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jun 30 17:14:20 UTC 2010


Eliot Miranda uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-eem.249.mcz

==================== Summary ====================

Name: Tools-eem.249
Author: eem
Time: 29 June 2010, 6:08:05.192 pm
UUID: de379f2a-657e-4776-afa8-cdb1a6a21823
Ancestors: Tools-eem.248

ChangeList improvements
- recognize class definitions and reorganization doits and
  class comments so they can be diffed
- include class defs and comments in "remove unchanged
  definitions" so they are removed as well as unchanged
  methods, and in select methods for this class
- provide a "select changes containing pattern" operation
- provide a "select itemps for existig classes" operation
- use class's parser class (if it exists) when parsing selectors,
  defaulting the selector to unparsableSelector if it can't be parsed.

=============== Diff against Tools-eem.248 ===============

Item was changed:
  ----- Method: ChangeList>>changeListMenu: (in category 'menu actions') -----
  changeListMenu: aMenu
  	"Fill aMenu up so that it comprises the primary changelist-browser menu"
  
  	aMenu addTitle: 'change list'.
  	aMenu addStayUpItemSpecial.
  
  	aMenu addList: #(
  
  	('fileIn selections'							fileInSelections						'import the selected items into the image')
  	('fileOut selections...	'						fileOutSelections						'create a new file containing the selected items')
  	-
  	('compare to current'						compareToCurrentVersion			'open a separate window which shows the text differences between the on-file version and the in-image version.' )
  	('toggle diffing (D)'							toggleDiffing						'start or stop showing diffs in the code pane.')
  	-
  	('select conflicts with any changeset'		selectAllConflicts					'select methods in the file which also occur in any change-set in the system')
  	('select conflicts with current changeset'	selectConflicts						'select methods in the file which also occur in the current change-set')
  	('select conflicts with...'						selectConflictsWith					'allows you to designate a file or change-set against which to check for code conflicts.')
  	-
+ 	('select unchanged definitions'				selectUnchangedDefinitions			'select class definitions, class comments and methods in the file whose in-image versions are the same as their in-file counterparts' )
  	('select unchanged methods'					selectUnchangedMethods				'select methods in the file whose in-image versions are the same as their in-file counterparts' )
  	('select new methods'						selectNewMethods					'select methods in the file that do not current occur in the image')
  	('select methods for this class'				selectMethodsForThisClass			'select all methods in the file that belong to the currently-selected class')
+ 	('select methods for extant classes'			selectMethodsForExtantClasses		'select all methods in the file that belong to a class that exists in the image')
+ 	('select changes with contents matching'		selectContentsMatching				'select all changes in the file whose text includes a pattern')
  
  	-
  	('select all (a)'								selectAll								'select all the items in the list')
  	('deselect all'								deselectAll							'deselect all the items in the list')
  	('invert selections'							invertSelections						'select every item that is not currently selected, and deselect every item that *is* currently selected')
  	-
  	('browse all versions of single selection'			browseVersions		'open a version browser showing the versions of the currently selected method')
  	('browse all versions of selections'			browseAllVersionsOfSelections		'open a version browser showing all the versions of all the selected methods')
  	('browse current versions of selections'		browseCurrentVersionsOfSelections	'open a message-list browser showing the current (in-image) counterparts of the selected methods')
  	('destroy current methods of selections'		destroyCurrentCodeOfSelections		'remove (*destroy*) the in-image counterparts of all selected methods')
  	-
  	('remove doIts'								removeDoIts							'remove all items that are doIts rather than methods')
  	('remove older versions'						removeOlderMethodVersions			'remove all but the most recent versions of methods in the list')
  	('remove up-to-date versions'				removeExistingMethodVersions		'remove all items whose code is the same as the counterpart in-image code')
  	('remove selected items'						removeSelections					'remove the selected items from the change-list')
  	('remove unselected items'					removeNonSelections					'remove all the items not currently selected from the change-list')).
  
  	^ aMenu
  
  !

Item was added:
+ ----- Method: ChangeList>>selectContentsMatching (in category 'menu actions') -----
+ selectContentsMatching
+ 	| pattern |
+ 	pattern := UIManager default request: 'pattern to match'.
+ 	pattern isEmpty ifTrue: [^self].
+ 	^Cursor execute showWhile:
+ 		[self selectSuchThat: ((pattern includesAnyOf: '?*')
+ 								ifTrue: [[ :change | pattern match: change string]]
+ 								ifFalse: [[ :change | change string includesSubString: pattern]])]!

Item was changed:
  ----- Method: ChangeList>>scanCategory (in category 'scanning') -----
  scanCategory  
  	"Scan anything that involves more than one chunk; method name is historical only"
  
+ 	| itemPosition item tokens stamp anIndex |
- 	| itemPosition item tokens stamp isComment anIndex |
  	itemPosition := file position.
  	item := file nextChunk.
  
+ 	((item includesSubString: 'commentStamp:')
+ 	or: [(item includesSubString: 'methodsFor:')
+ 	or: [item endsWith: 'reorganize']]) ifFalse:
- 	isComment := (item includesSubString: 'commentStamp:').
- 	(isComment or: [item includesSubString: 'methodsFor:']) ifFalse:
  		["Maybe a preamble, but not one we recognize; bail out with the preamble trick"
  		^ self addItem: (ChangeRecord new file: file position: itemPosition type: #preamble)
  				 text: ('preamble: ' , item contractTo: 50)].
  
  	tokens := Scanner new scanTokens: item.
  	tokens size >= 3 ifTrue:
  		[stamp := ''.
  		anIndex := tokens indexOf: #stamp: ifAbsent: [nil].
  		anIndex ifNotNil: [stamp := tokens at: (anIndex + 1)].
  
  		tokens second == #methodsFor:
  			ifTrue: [^ self scanCategory: tokens third class: tokens first
  							meta: false stamp: stamp].
  		tokens third == #methodsFor:
  			ifTrue: [^ self scanCategory: tokens fourth class: tokens first
  							meta: true stamp: stamp]].
  
+ 	tokens second == #commentStamp:
+ 		ifTrue:
+ 			[stamp := tokens third.
+ 			self addItem:
+ 					(ChangeRecord new file: file position: file position type: #classComment
+ 									class: tokens first category: nil meta: false stamp: stamp)
+ 					text: 'class comment for ' , tokens first, 
+ 						  (stamp isEmpty ifTrue: [''] ifFalse: ['; ' , stamp]).
+ 			file nextChunk.
+ 			^ file skipStyleChunk].
+ 
+ 	self assert: tokens last == #reorganize.
+ 	self addItem:
+ 		(ChangeRecord new
+ 			file: file position: file position type: #reorganize
+ 			class: tokens first category: nil meta: false stamp: stamp)
+ 		text: 'organization for ' , tokens first, (tokens second == #class ifTrue: [' class'] ifFalse: ['']).
+ 	file nextChunk!
- 		tokens second == #commentStamp:
- 			ifTrue:
- 				[stamp := tokens third.
- 				self addItem:
- 						(ChangeRecord new file: file position: file position type: #classComment
- 										class: tokens first category: nil meta: false stamp: stamp)
- 						text: 'class comment for ' , tokens first, 
- 							  (stamp isEmpty ifTrue: [''] ifFalse: ['; ' , stamp]).
- 				file nextChunk.
- 				^ file skipStyleChunk]!

Item was added:
+ ----- Method: ChangeList>>selectUnchangedDefinitions (in category 'menu actions') -----
+ selectUnchangedDefinitions
+ 	"Selects all recognizable definitions for which there is already a definition in the current image, whose source is exactly the same."
+ 	| change class tokens |
+ 	Cursor read showWhile: 
+ 	[1 to: changeList size do:
+ 		[:i | change := changeList at: i.
+ 		listSelections at: i put: false.
+ 
+ 		(change type = #method
+ 		 and: [(class := change methodClass) notNil
+ 		 and: [class includesSelector: change methodSelector]]) ifTrue:
+ 			[listSelections
+ 				at: i
+ 				put: change string withBlanksCondensed
+ 					= (class sourceCodeAt: change methodSelector) asString withBlanksCondensed].
+ 
+ 		(change type == #classComment
+ 		and: [(class := change commentClass) notNil]) ifTrue:
+ 			[listSelections at: i put: change string = class comment asString].
+ 
+ 		change type == #doIt ifTrue:
+ 			[tokens := Scanner new scanTokens: change string.
+ 
+ 			 ((tokens select:
+ 				[:substr| #(subclass: variableByteSubclass: variableWordSubclass:
+ 							instanceVariableNames: classVariableNames: ) includes: substr])
+ 					asSet size >= 3
+ 			 and: [(class := Smalltalk at: tokens third ifAbsent: []) notNil
+ 			 and: [class isBehavior]]) ifTrue:
+ 				[listSelections
+ 					at: i
+ 					put: change string withBlanksCondensed
+ 						= class definition withBlanksCondensed].
+ 
+ 			(tokens size = 4
+ 			 and: [tokens second == #class
+ 			 and: [tokens third == #instanceVariableNames:
+ 			 and: [(class := Smalltalk at: tokens first ifAbsent: []) notNil
+ 			 and: [class isBehavior]]]]) ifTrue:
+ 				[listSelections
+ 					at: i
+ 					put: change string withBlanksCondensed
+ 						= class class definition withBlanksCondensed].
+ 
+ 			(tokens size = 3
+ 			 and: [tokens second == #removeSelector:
+ 			 and: [(class := Smalltalk at: tokens first ifAbsent: []) isNil
+ 			 	or: [class isBehavior and: [(class includesSelector: tokens third) not]]]]) ifTrue:
+ 				[listSelections at: i put: true].
+ 
+ 			(tokens size = 4
+ 			 and: [tokens second == #class
+ 			 and: [tokens third == #removeSelector:
+ 			 and: [(class := Smalltalk at: tokens first ifAbsent: []) isNil
+ 			 	or: [class isBehavior and: [(class class includesSelector: tokens fourth) not]]]]]) ifTrue:
+ 				[listSelections at: i put: true]]]].
+ 
+ 	self changed: #allSelections!

Item was changed:
  ----- Method: ChangeList>>scanCategory:class:meta:stamp: (in category 'scanning') -----
  scanCategory: category class: class meta: meta stamp: stamp
+ 	| itemPosition method selector |
- 	| itemPosition method |
  	[itemPosition := file position.
  	method := file nextChunk.
  	file skipStyleChunk.
  	method size > 0]						"done when double terminators"
  		whileTrue:
  		[self addItem: (ChangeRecord new file: file position: itemPosition type: #method
  							class: class category: category meta: meta stamp: stamp)
  			text: 'method: ' , class , (meta ifTrue: [' class '] ifFalse: [' '])
+ 				, ((selector := (Smalltalk at: class ifAbsent: [Object]) parserClass new parseSelector: method) isNil
+ 					ifTrue: ['unparsableSelector']
+ 					ifFalse: [selector])
- 				, (self class parserClass new parseSelector: method)
  				, (stamp isEmpty ifTrue: [''] ifFalse: ['; ' , stamp])]!

Item was changed:
  ----- Method: ChangeList>>contentsDiffedFromCurrent (in category 'viewing access') -----
  contentsDiffedFromCurrent
  	"Answer the contents diffed forward from current (in-memory) method version"
  
  	| aChange aClass |
  	listIndex = 0
  		ifTrue: [^ ''].
  	aChange := changeList at: listIndex.
+ 	 (aChange type == #method
+ 	 and: [(aClass := aChange methodClass) notNil
+ 	 and: [aClass includesSelector: aChange methodSelector]]) ifTrue:
+ 		[^Utilities
+ 			methodDiffFor: aChange text
+ 			class: aClass
+ 			selector: aChange methodSelector
+ 			prettyDiffs: self showingPrettyDiffs].
+ 
+ 	aChange type == #doIt ifTrue:
+ 		[| tokens |
+ 		 tokens := Scanner new scanTokens: aChange string.
+ 		 ((tokens select:
+ 				[:substr| #(subclass: variableByteSubclass: variableWordSubclass:
+ 							instanceVariableNames: classVariableNames: ) includes: substr])
+ 					asSet size >= 3
+ 		  and: [(aClass := Smalltalk at: tokens third ifAbsent: []) notNil
+ 		  and: [aClass isBehavior]]) ifTrue:
+ 			[^TextDiffBuilder buildDisplayPatchFrom: aClass definition to: aChange string].
+ 
+ 		(tokens size = 4
+ 		 and: [tokens second == #class
+ 		 and: [tokens third == #instanceVariableNames:
+ 		 and: [(aClass := Smalltalk at: tokens first ifAbsent: []) notNil
+ 		 and: [aClass isBehavior]]]]) ifTrue:
+ 			[^TextDiffBuilder buildDisplayPatchFrom: aClass class definition to: aChange string]].
+ 
+ 	(aChange type == #classComment
+ 	and: [(aClass := aChange commentClass) notNil]) ifTrue:
+ 		[^TextDiffBuilder buildDisplayPatchFrom: aClass comment asString to: aChange string].
+ 
+ 	^(changeList at: listIndex) text!
- 	^ ((aChange type == #method and: [(aClass := aChange methodClass) notNil]) and: [aClass includesSelector: aChange methodSelector])
- 		ifTrue:
- 			 [Utilities methodDiffFor: aChange text class: aClass selector: aChange methodSelector prettyDiffs: self showingPrettyDiffs]
- 		ifFalse:
- 			[(changeList at: listIndex) text]!

Item was added:
+ ----- Method: ChangeList>>selectMethodsForExtantClasses (in category 'menu actions') -----
+ selectMethodsForExtantClasses
+ 	^self selectSuchThat:
+ 		[ :change |
+ 		Smalltalk hasClassNamed: change methodClassName]!




More information about the Squeak-dev mailing list