[Pkg] The Trunk: Tools-fbs.329.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 20 23:18:11 UTC 2011


Levente Uzonyi uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-fbs.329.mcz

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

Name: Tools-fbs.329
Author: fbs
Time: 29 March 2011, 4:47:17.821 pm
UUID: acf29c50-9eed-c34b-8160-7c865c66a47d
Ancestors: Tools-fbs.328

* In Browser: the big swapover from messageListIndex -> selectedMessageName.
* In MessageSet: pulling down functionality from Browser to shield it from the changes happening in its superclass.

Ideally, MessageSet would subclass from a new CodeHolder subclass BaseMessageSet, which would take all the methods currently in CodeHolder's 'message list' category, plus any other methods from Browser needed to support same. That's a step too far for this branch.

=============== Diff against Tools-fbs.328 ===============

Item was changed:
  ----- Method: Browser>>compileMessage:notifying: (in category 'code pane') -----
  compileMessage: aText notifying: aController
  	"Compile the code that was accepted by the user, placing the compiled method into an appropriate message category.  Return true if the compilation succeeded, else false."
  
+ 	| fallBackCategoryIndex fallBackMethodIndex originalSelectorName result fallBackMethodName |
- 	| fallBackCategoryIndex fallBackMethodIndex originalSelectorName result |
  
  	self selectedMessageCategoryName ifNil:
  			[ self selectOriginalCategoryForCurrentMethod 	
  										ifFalse:["Select the '--all--' category"
  											self messageCategoryListIndex: 1]]. 
  
  
  	self selectedMessageCategoryName asSymbol = ClassOrganizer allCategory
  		ifTrue:
  			[ "User tried to save a method while the ALL category was selected"
  			fallBackCategoryIndex := messageCategoryListIndex.
  			fallBackMethodIndex := messageListIndex.
+ 			fallBackMethodName := selectedMessageName.
  			editSelection == #newMessage
  				ifTrue:
  					[ "Select the 'as yet unclassified' category"
  					messageCategoryListIndex := 0.
  					(result := self defineMessageFrom: aText notifying: aController)
  						ifNil:
  							["Compilation failure:  reselect the original category & method"
  							messageCategoryListIndex := fallBackCategoryIndex.
+ 							messageListIndex := fallBackMethodIndex.
+ 							selectedMessageName := fallBackMethodName]
- 							messageListIndex := fallBackMethodIndex]
  						ifNotNil:
  							[self setSelector: result]]
  				ifFalse:
  					[originalSelectorName := self selectedMessageName.
  					self setOriginalCategoryIndexForCurrentMethod.
  					messageListIndex := fallBackMethodIndex := self messageList indexOf: originalSelectorName.			
  					(result := self defineMessageFrom: aText notifying: aController)
  						ifNotNil:
  							[self setSelector: result]
  						ifNil:
  							[ "Compilation failure:  reselect the original category & method"
  							messageCategoryListIndex := fallBackCategoryIndex.
  							messageListIndex := fallBackMethodIndex.
+ 							selectedMessageName := fallBackMethodName.
  							^ result notNil]].
  			self changed: #messageCategoryList.
  			^ result notNil]
  		ifFalse:
  			[ "User tried to save a method while the ALL category was NOT selected"
  			^ (self defineMessageFrom: aText notifying: aController) notNil]!

Item was changed:
  ----- Method: Browser>>messageListIndex: (in category 'message list') -----
  messageListIndex: anInteger
  	"Set the selected message selector to be the one indexed by anInteger."
  
+ 	self selectMessageNamed: (self messageList at: anInteger ifAbsent: [nil])!
- 	messageListIndex := anInteger.
- 	self editSelection: (anInteger > 0
- 		ifTrue: [#editMessage]
- 		ifFalse: [self messageCategoryListIndex > 0
- 			ifTrue: [#newMessage]
- 			ifFalse: [self hasClassSelected
- 				ifTrue: [#editClass]
- 				ifFalse: [#newClass]]]).
- 	contents := nil.
- 	self changed: #messageListIndex. "update my selection"
- 	self contentsChanged.
- 	self decorateButtons.!

Item was changed:
  ----- Method: Browser>>selectMessageNamed: (in category 'message list') -----
  selectMessageNamed: aSymbolOrString
  	| name |
+ 	name := aSymbolOrString ifNotNil: [ aSymbolOrString asSymbol ].
+ 	selectedMessageName := name.
+ 
+ 	messageListIndex := self messageListIndexOf: name.
+ 	self editSelection: (name notNil
+ 		ifTrue: [#editMessage]
+ 		ifFalse: [self messageCategoryListIndex > 0
+ 			ifTrue: [#newMessage]
+ 			ifFalse: [self hasClassSelected
+ 				ifTrue: [#editClass]
+ 				ifFalse: [#newClass]]]).
+ 	contents := nil.
+ 	self changed: #messageListIndex. "update my selection"
+ 	self contentsChanged.
+ 	self decorateButtons.!
- 	name := aSymbolOrString ifNil: [ 0] ifNotNil: [ aSymbolOrString asSymbol ].
- 	self messageListIndex: (self messageListIndexOf: name).!

Item was changed:
  ----- Method: MessageNames>>selectedClassOrMetaClass (in category 'class list') -----
  selectedClassOrMetaClass
  	"Answer the currently selected class (or metaclass)."
+ 	self hasMessageSelected ifTrue:
+ 		[ ^ self setClassAndSelectorIn: [:c :s | ^c] ].
+ 	
- 	messageListIndex > 0 ifTrue: [
- 		^ self setClassAndSelectorIn: [:c :s | ^c]].
  	(selectorListIndex isNil not and: [selectorListIndex > 0]) ifTrue: [^Smalltalk classNamed: (self selectorList at: selectorListIndex)].
  	
  	^ nil.
  	!

Item was changed:
  ----- Method: MessageNames>>selectedMessageName (in category 'selection') -----
  selectedMessageName
+ 	selectorList ifNil: [^ nil].
+ 	^selectorListIndex = 0 ifFalse: [selectorList at: selectorListIndex ifAbsent: [nil]]!
- 	^selectorListIndex = 0 ifFalse: [selectorList at: selectorListIndex]!

Item was removed:
- ----- Method: MessageNames>>selection (in category 'selection') -----
- selection
- 	"Answer the item in the list that is currently selected, or nil if no selection is present"
- 
- 	^ messageListIndex = 0
- 		ifTrue: [self selectorList at: selectorListIndex ifAbsent: [nil]]
- 		ifFalse: [self messageList at: messageListIndex ifAbsent: [nil]].!

Item was changed:
  ----- Method: MessageSet>>contents (in category 'contents') -----
  contents
  	"Answer the contents of the receiver"
  
  	^ contents == nil
  		ifTrue: [currentCompiledMethod := nil. '']
  		ifFalse: [self hasMessageSelected
  			ifTrue: [self editContents]
  			ifFalse: [currentCompiledMethod := nil. contents]]!

Item was added:
+ ----- Method: MessageSet>>hasMessageSelected (in category 'message list') -----
+ hasMessageSelected
+ 	^ messageListIndex ~= 0.!

Item was added:
+ ----- Method: MessageSet>>messageListIndex (in category 'message list') -----
+ messageListIndex
+ 	^messageListIndex!

Item was changed:
  ----- Method: MessageSet>>messageListIndex: (in category 'message list') -----
+ messageListIndex: anInteger
+ 	"Set the selected message selector to be the one indexed by anInteger."
- messageListIndex: anInteger 
- 	"Set the index of the selected item to be anInteger."
- 
  	messageListIndex := anInteger.
+ 	
+ 	self editSelection: (anInteger > 0
+ 		ifTrue: [#editMessage]
+ 		ifFalse: [self messageCategoryListIndex > 0
+ 			ifTrue: [#newMessage]
+ 			ifFalse: [self hasClassSelected
+ 				ifTrue: [#editClass]
+ 				ifFalse: [#newClass]]]).
+ 	contents := ''.
+ 	self changed: #messageListIndex. "update my selection"
- 	contents := 
- 		messageListIndex ~= 0
- 			ifTrue: [self selectedMessage]
- 			ifFalse: [''].
- 	self changed: #messageListIndex.	 "update my selection"
- 	self editSelection: #editMessage.
  	self contentsChanged.
+ 	self decorateButtons.!
- 	(messageListIndex ~= 0 and: [ autoSelectString notNil and: [ self contents notEmpty ] ]) ifTrue: [ self changed: #autoSelect ].
- 	self decorateButtons
- !

Item was added:
+ ----- Method: MessageSet>>selectMessageNamed: (in category 'message list') -----
+ selectMessageNamed: aSymbolOrString
+ 	super selectMessageNamed: aSymbolOrString.
+ 	
+ 	contents := 
+ 		selectedMessageName notNil
+ 			ifTrue: [self selectedMessage]
+ 			ifFalse: [''].
+ 	self changed: #messageListIndex.	 "update my selection"
+ 	self editSelection: #editMessage.
+ 	self contentsChanged.
+ 	(selectedMessageName notNil and: [ autoSelectString notNil and: [ self contents notEmpty ] ]) ifTrue: [ self changed: #autoSelect ].
+ 	self decorateButtons!

Item was changed:
+ ----- Method: MessageSet>>selectedMessage (in category 'message list') -----
- ----- Method: MessageSet>>selectedMessage (in category 'contents') -----
  selectedMessage
  	"Answer the source method for the currently selected message."
  
  	
  	self setClassAndSelectorIn: [:class :selector | | source | 
  		class ifNil: [^ 'Class vanished'].
  		selector first isUppercase ifTrue:
  			[selector == #Comment ifTrue:
  				[currentCompiledMethod := class organization commentRemoteStr.
  				^ class comment].
  			selector == #Definition ifTrue:
  				[^ class definition].
  			selector == #Hierarchy ifTrue: [^ class printHierarchy]].
  		source := class sourceMethodAt: selector ifAbsent:
  			[currentCompiledMethod := nil.
  			^ 'Missing'].
  
  		self showingDecompile ifTrue: [^ self decompiledSourceIntoContents].
  
  		currentCompiledMethod := class compiledMethodAt: selector ifAbsent: [nil].
  		self showingDocumentation ifTrue: [^ self commentContents].
  
  	source := self sourceStringPrettifiedAndDiffed.
  	^ source asText makeSelectorBoldIn: class]!

Item was changed:
  ----- Method: MessageSet>>selectedMessageName (in category 'message list') -----
  selectedMessageName
  	"Answer the name of the currently selected message."
  	"wod 6/16/1998: answer nil if none are selected."
  
  	messageListIndex = 0 ifTrue: [^ nil].
  	^ self setClassAndSelectorIn: [:class :selector | ^ selector]!

Item was changed:
  ----- Method: MessageSet>>selection (in category 'private') -----
  selection
  	"Answer the item in the list that is currently selected, or nil if no selection is present"
  
+ 	^ self messageList at: (self messageListIndex) ifAbsent: [nil]!
- 	^ messageList at: (self messageListIndex) ifAbsent: [nil]!

Item was changed:
  ----- Method: MessageTrace>>removeMessageFromBrowser (in category 'building') -----
  removeMessageFromBrowser
  	| indexToSelect |
+ 	self hasMessageSelected ifFalse: [^ self].
  	"Try to keep the same selection index."
  	indexToSelect := (messageSelections indexOf: true) max: 1.
  	self selectedMessages do: [ :eachMethodReference | self deleteFromMessageList: eachMethodReference ].
  	self deselectAll.
  	messageSelections ifNotEmpty:
  		[ messageSelections 
  			at: (indexToSelect min: messageSelections size)  "safety"
  			put: true ].
  	anchorIndex := indexToSelect min: messageSelections size.
  	self 
  		messageListIndex: anchorIndex ; 
  		reformulateList!



More information about the Packages mailing list