[squeak-dev] The Trunk: System-cmm.433.mcz

commits at source.squeak.org commits at source.squeak.org
Mon May 2 23:39:33 UTC 2011


Chris Muller uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-cmm.433.mcz

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

Name: System-cmm.433
Author: cmm
Time: 2 May 2011, 6:38:44.996 pm
UUID: 89627de9-ab75-419e-a876-2399387987dd
Ancestors: System-mtf.432

- Updates to SystemNavigation to support streamlined variable-reference / assignment browsing.

=============== Diff against System-mtf.432 ===============

Item was changed:
  ----- Method: SystemNavigation>>browseAllStoresInto:from: (in category 'browse') -----
+ browseAllStoresInto: varName from: aClass 
- browseAllStoresInto: instVarName from: aClass
  	"Create and schedule a Message Set browser for all the receiver's methods 
  	or any methods of a subclass/superclass that refer to the instance variable name."
- 	
  	"self new browseAllStoresInto: 'contents' from: Collection."
- 
  	| coll |
  	coll := OrderedCollection new.
+ 	Cursor wait showWhile:
+ 		[ aClass withAllSubAndSuperclassesDo:
+ 			[ : class | (class whichMethodsStoreInto: varName) do:
+ 				[ : eachMethod | eachMethod selector isDoIt ifFalse: [ coll add: eachMethod methodReference ] ] ] ].
- 	Cursor wait showWhile: [
- 		aClass withAllSubAndSuperclassesDo: [:class | 
- 			(class whichSelectorsStoreInto: instVarName) do: [:sel |
- 				sel isDoIt ifFalse: [
- 					coll add: (
- 						MethodReference new
- 							setStandardClass: class 
- 							methodSymbol: sel
- 					)
- 				]
- 			]
- 		].
- 	].
  	^ self
+ 		browseMessageList: coll
+ 		name: 'Stores into ' , varName
+ 		autoSelect: varName!
- 		browseMessageList: coll 
- 		name: 'Stores into ' , instVarName 
- 		autoSelect: instVarName!

Item was removed:
- ----- Method: SystemNavigation>>browseClassVarRefs: (in category 'browse') -----
- browseClassVarRefs: aClass
- 	"Put up a menu offering all class variable names; if the user chooses one, open up a message-list browser on all methods 
- 	that refer to the selected class variable"
- 
- 	| lines labelStream allVars index owningClasses |
- 	lines := OrderedCollection new.
- 	allVars := OrderedCollection new.
- 	owningClasses := OrderedCollection new.
- 	labelStream := WriteStream on: (String new: 200).
- 	aClass withAllSuperclasses reverseDo:
- 		[:class | | vars |
- 		vars := class classVarNames.
- 		vars do:
- 			[:var |
- 			labelStream nextPutAll: var; cr.
- 			allVars add: var.
- 			owningClasses add: class].
- 		vars isEmpty ifFalse: [lines add: allVars size]].
- 	labelStream contents isEmpty ifTrue: [^Beeper beep]. "handle nil superclass better"
- 	labelStream skip: -1 "cut last CR".
- 	index := (UIManager default chooseFrom: (labelStream contents substrings) lines: lines).
- 	index = 0 ifTrue: [^ self].
- 	self browseAllCallsOn:
- 		((owningClasses at: index) classPool associationAt: (allVars at: index))!

Item was removed:
- ----- Method: SystemNavigation>>browseClassVariables: (in category 'browse') -----
- browseClassVariables: aClass
- 	aClass classPool inspectWithLabel: 'Class Variables in ' , aClass name!

Item was removed:
- ----- Method: SystemNavigation>>browseInstVarDefs: (in category 'browse') -----
- browseInstVarDefs: aClass
- 	"Copied from browseInstVarRefs.  Should be consolidated some day. 7/29/96 di
- 	7/30/96 sw: did the consolidation"
- 	"Change to use SystemNavigation  27 March 2003 sd"
- 
- 	aClass chooseInstVarThenDo:	
- 		[:aVar | self browseAllStoresInto: aVar from: aClass]!

Item was removed:
- ----- Method: SystemNavigation>>browseInstVarRefs: (in category 'browse') -----
- browseInstVarRefs: aClass
- 	"1/16/96 sw: moved here from Browser so that it could be used from a variety of places.
- 	 7/30/96 sw: call chooseInstVarThenDo: to get the inst var choice"
- 
- 	aClass chooseInstVarThenDo: 
- 		[:aVar | self browseAllAccessesTo: aVar from: aClass]!

Item was added:
+ ----- Method: SystemNavigation>>browseVariableAssignments: (in category 'browse') -----
+ browseVariableAssignments: aClass 
+ 	aClass chooseVarThenDo:
+ 		[ : aVar | self
+ 			browseAllStoresInto: aVar
+ 			from: aClass ]!

Item was added:
+ ----- Method: SystemNavigation>>browseVariableReferences: (in category 'browse') -----
+ browseVariableReferences: aClass
+ 	aClass chooseVarThenDo:
+ 		[ : aVar | (aClass allInstVarNames includes: aVar)
+ 			ifTrue:
+ 				[ self
+ 					browseAllAccessesTo: aVar
+ 					from: aClass ]
+ 			ifFalse: [ self browseAllCallsOn: aVar ] ]!

Item was changed:
  ----- Method: SystemNavigation>>headingAndAutoselectForLiteral:do: (in category 'private') -----
+ headingAndAutoselectForLiteral: aLiteral do: binaryBlock 
+ 	"Evaluate binaryBlock with either Users of ... or Senders of ... plus the auto-select string for the given literal.  aLiteral can be a Symbol, a VariableBinding or an arbitrary object."
- headingAndAutoselectForLiteral: aLiteral do: binaryBlock
- 	"Evaluate aBlock with either Users of ... or Senders of ... plus the auto-select string
- 	 for the given literal.  aLiteral can be a Symbol, a VariableBinding or an arbitrary object."
- 
  	| autoSelect |
+ 	^ aLiteral isSymbol
+ 		ifTrue:
+ 			[ binaryBlock
+ 				value: 'Senders of ' , aLiteral
+ 				value: aLiteral keywords first ]
- 	^aLiteral isSymbol
- 		ifTrue: [binaryBlock value: 'Senders of ', aLiteral value: aLiteral keywords first]
  		ifFalse:
+ 			[ autoSelect := aLiteral isVariableBinding
+ 				ifTrue: [ aLiteral key ]
+ 				ifFalse: [ aLiteral printString ].
+ 			binaryBlock
+ 				value: 'Users of ' , autoSelect
+ 				value: autoSelect ]!
- 			[autoSelect := aLiteral isVariableBinding
- 							ifTrue: [aLiteral key]
- 							ifFalse: [aLiteral printString].
- 			binaryBlock value: 'Users of ', autoSelect value: autoSelect]!




More information about the Squeak-dev mailing list