[squeak-dev] The Trunk: Tools-tpr.1182.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jan 16 05:21:00 UTC 2023


tim Rowledge uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-tpr.1182.mcz

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

Name: Tools-tpr.1182
Author: tpr
Time: 15 January 2023, 9:20:55.947778 pm
UUID: 71b83582-ebfd-4e7a-bc40-317f448aa587
Ancestors: Tools-mt.1181

Remove some variable shadowing

=============== Diff against Tools-mt.1181 ===============

Item was changed:
  ----- Method: BasicInspector>>fieldObjectClass (in category 'fields') -----
  fieldObjectClass
  
  	^ (self newFieldForType: #proto key: #class)
  		name: 'class'; emphasizeName;
+ 		valueGetter: [:obj | thisContext objectClass: obj];
- 		valueGetter: [:object | thisContext objectClass: object];
  		valueGetterExpression: 'thisContext objectClass: self';
  		yourself!

Item was changed:
  ----- Method: BasicInspector>>fieldObjectSize (in category 'fields') -----
  fieldObjectSize
  
  	^ (self newFieldForType: #proto key: #size)
  		name: 'size'; emphasizeName;
+ 		valueGetter: [:obj | thisContext objectSize: obj];
- 		valueGetter: [:object | thisContext objectSize: object];
  		valueGetterExpression: 'thisContext objectSize: self';
  		yourself!

Item was changed:
  ----- Method: BasicInspector>>streamIndexedVariablesOn: (in category 'fields - streaming') -----
  streamIndexedVariablesOn: aStream
  	"Truncate indexed variables if there are too many of them."
  	
  	self
  		streamOn: aStream
  		truncate: (1 to: (thisContext objectSize: self object))
  		collectFields: [:index |
  			(self newFieldForType: #indexed key: index)
  				name: index asString;
+ 				valueGetter: [:obj | thisContext object: obj basicAt: index];
- 				valueGetter: [:object | thisContext object: object basicAt: index];
  				valueGetterExpression: ('thisContext object: {1} basicAt: {2}' format: { 'self'. index }); 
+ 				valueSetter: [:obj :value | thisContext object: obj basicAt: index put: value];
- 				valueSetter: [:object :value | thisContext object: object basicAt: index put: value];
  				yourself]!

Item was changed:
  ----- Method: ClassInspector>>streamClassVariablesOn: (in category 'fields - streaming') -----
  streamClassVariablesOn: aStream
  	
  	self object classVarNames do: [:name |
  		aStream nextPut: ((self newFieldForType: #classVar key: name)
  			shouldStyleName: true;
+ 			valueGetter: [:obj | obj classPool at: name];
+ 			valueSetter: [:obj :value | obj classPool at: name put: value];
- 			valueGetter: [:object | object classPool at: name];
- 			valueSetter: [:object :value | object classPool at: name put: value];
  			yourself)]!

Item was changed:
  ----- Method: ClassInspector>>streamSharedPoolsOn: (in category 'fields - streaming') -----
  streamSharedPoolsOn: aStream
  
  	self object sharedPools withIndexDo: [:pool :index |
  		aStream nextPut: ((self newFieldForType: #poolDictionary key: (self environment keyAtIdentityValue: pool))
  			shouldStyleName: true;
+ 			valueGetter: [:obj | obj sharedPools at: index];
+ 			valueSetter: [:obj :value | obj sharedPools at: index put: value];
- 			valueGetter: [:object | object sharedPools at: index];
- 			valueSetter: [:object :value | object sharedPools at: index put: value];
  			yourself)].!

Item was changed:
  ----- Method: CompiledCodeInspector>>fieldByteCodes (in category 'fields') -----
  fieldByteCodes
  
  	^ (self newFieldForType: #all key: #byteCodes)
  		name: 'all bytecodes' translated; emphasizeName;
+ 		valueGetter: [:obj | obj symbolic]; printValueAsIs;
- 		valueGetter: [:object | object symbolic]; printValueAsIs;
  		yourself!

Item was changed:
  ----- Method: CompiledCodeInspector>>fieldHeader (in category 'fields') -----
  fieldHeader
  
  	^ (self newFieldForType: #misc key: #header)
  		name: 'header' translated; emphasizeName;
+ 		valueGetter: [:obj | obj headerDescription]; printValueAsIs;
- 		valueGetter: [:object | object headerDescription]; printValueAsIs;
  		yourself!

Item was changed:
  ----- Method: ContextInspector>>streamStackVariablesOn: (in category 'fields - streaming') -----
  streamStackVariablesOn: aStream
  	"If this context's stack pointer is not valid, silently skip streaming fields for stack variables. Do not stream an error field because freshly created or terminated contexts can be like this."
  
  	self object stackPtr ifNil: [^ self].
  
  	self flag: #decompile. "mt: Use #to: and #do: instead of #to:do: to avoid inlining to preserve bindings in enumeration block for later decompilation. See InspectorField."
  	(self object numTemps + 1 to: self object stackPtr) do: [:index |
  		aStream nextPut: ((self newFieldForType: #stackItem key: index)
  			name: 'stack', index; deEmphasizeName;
+ 			valueGetter: [:obj | obj at: index];
+ 			valueSetter: [:obj :value | obj at: index put: value];
- 			valueGetter: [:object | object at: index];
- 			valueSetter: [:object :value | object at: index put: value];
  			yourself)]!

Item was changed:
  ----- Method: ContextInspector>>streamTemporaryVariablesOn: (in category 'fields - streaming') -----
  streamTemporaryVariablesOn: aStream
  
  	| tempNames |
  	tempNames := [self object tempNames] ifError: [
  		^ self streamError: 'Invalid temporaries' translated on: aStream].
  	
  	tempNames withIndexDo: [:name :index |
  		aStream nextPut: ((self newFieldForType: #tempVar key: name)
  			name: ('[{1}]' format: {name});
+ 			valueGetter: [:obj | obj namedTempAt: index];
+ 			valueSetter: [:obj :value | obj namedTempAt: index put: value];
- 			valueGetter: [:context | context namedTempAt: index];
- 			valueSetter: [:context :value | context namedTempAt: index put: value];
  			yourself)]!

Item was changed:
  ----- Method: ContextVariablesInspector>>fieldAllTempVars (in category 'fields') -----
  fieldAllTempVars
  
  	^ (self newFieldForType: #all key: #allTempVars)
  		name: self allTempVarsTranslated; emphasizeName;
+ 		valueGetter: [:obj | obj tempsAndValuesContractedTo: 64]; printValueAsIs;
- 		valueGetter: [:object | object tempsAndValuesContractedTo: 64]; printValueAsIs;
  		yourself!

Item was changed:
  ----- Method: ContextVariablesInspector>>streamTemporaryVariablesOn: (in category 'fields - streaming') -----
  streamTemporaryVariablesOn: aStream
  	"Overwritten to change the visuals of temps in debuggers."
  	
  	| tempNames |
  	tempNames := [self object tempNames] ifError: [
  		^ self streamError: 'Invalid temporaries' translated on: aStream].
  	
  	tempNames withIndexDo: [:name :index |
  		aStream nextPut: ((self newFieldForType: #tempVar key: name)
  			shouldStyleName: true;
+ 			valueGetter: [:obj | obj namedTempAt: index];
+ 			valueSetter: [:obj :value | obj namedTempAt: index put: value];
- 			valueGetter: [:context | context namedTempAt: index];
- 			valueSetter: [:context :value | context namedTempAt: index put: value];
  			yourself)].!

Item was changed:
  ----- Method: FileList2 class>>endingSpecs (in category 'blue ui') -----
  endingSpecs
  	"Answer a collection of specs to build the selective 'find anything' tool called by the Navigator. This version uses the services registry to do so."
  	"FileList2 morphicViewGeneralLoaderInWorld: Project current world"
  	| specs rejects |
  	rejects := #(addFileToNewZip: compressFile: openInZipViewer: extractAllFrom: openOn:).
  	specs := OrderedCollection new.
+ 	self fileExtensionsByCategory keysAndValuesDo: [:cat :extensions |
- 	self fileExtensionsByCategory keysAndValuesDo: [:category :extensions |
  		| services okExtensions |
  		services := Dictionary new.
  		okExtensions := Set new.
  		
  		extensions do: [:ext |
  			(FileServices itemsForFile: (FileDirectory default fullPathFor: 'fred.' , ext))
  				reject: [:service | rejects includes: service selector]
  				thenDo: [:service |
  					services at: service label put: service.
  					okExtensions add: ext]].
  		services isEmpty ifFalse: [ 
  			specs add: {
+ 				cat.
- 				category.
  				okExtensions.
  				services values }]].
  	^ specs!

Item was changed:
  ----- Method: Inspector>>elementGetterAt: (in category 'private - collections') -----
  elementGetterAt: indexOrKey
  	"Backstop to simplify #inspectOne for all kinds of inspectors."
  
+ 	^ [:obj | obj basicAt: indexOrKey]!
- 	^ [:object | object basicAt: indexOrKey]!

Item was changed:
  ----- Method: Inspector>>getContents (in category 'user interface') -----
  getContents
  	
  	| newContents |
  	selectionUpdateTime := 0.
  
  	self hasSelection ifFalse: [^ ''].
  	
  	selectionUpdateTime := [
+ 		newContents := self selection in:
+ 			[:obj |
- 		newContents := self selection in: [:object |
  			self selectedField shouldPrintValueAsIs
+ 				ifTrue:
+ 					[obj asStringOrText] "Show strings and texts without quoting and without ellipsis."
+ 				ifFalse: 
+ 					[obj isInteger
+ 						ifTrue: [obj storeStringBase: self defaultIntegerBase]
+ 						ifFalse: [obj printString]]].
- 				ifTrue: [object asStringOrText] "Show strings and texts without quoting and without ellipsis."
- 				ifFalse: [
- 					object isInteger
- 						ifTrue: [object storeStringBase: self defaultIntegerBase]
- 						ifFalse: [object printString]]].
  	] timeToRun.
  
  	^ newContents!

Item was changed:
  ----- Method: Inspector>>streamError:on: (in category 'fields - error handling') -----
  streamError: aMessageString on: aStream
  
  	aStream nextPut: ((self newFieldForType: #error)
  		name: (Text
  			string: '<error>' translated
  			attribute: self textColorForError);
+ 		valueGetter: [:obj | self emphasizeError: aMessageString];
- 		valueGetter: [:object | self emphasizeError: aMessageString];
  		printValueAsIs;
  		yourself)!

Item was changed:
  ----- Method: Inspector>>streamIndexedVariablesOn: (in category 'fields - streaming') -----
  streamIndexedVariablesOn: aStream
  	"Truncate indexed variables if there are too many of them."
  	
  	self
  		streamOn: aStream
  		truncate: (1 to: self object basicSize)
  		collectFields: [:index |
  			(self newFieldForType: #indexed key: index)
+ 				valueGetter: [:obj | obj basicAt: index];
+ 				valueSetter: [:obj :value | obj basicAt: index put: value];
- 				valueGetter: [:object | object basicAt: index];
- 				valueSetter: [:object :value | object basicAt: index put: value];
  				yourself]!

Item was changed:
  ----- Method: Inspector>>streamOn:truncate:collectFields: (in category 'fields - truncation') -----
  streamOn: aStream truncate: aList collectFields: aBlock
  
  	^ self
  		streamOn: aStream
  		truncate: aList
  		collectFields: aBlock
  		ellipsisFrom: [:truncatedObjects | (self newFieldForType: #ellipsis)
  			name: '...';
+ 			valueGetter: [:obj | self contentsForTruncationOf: truncatedObjects];
- 			valueGetter: [:object | self contentsForTruncationOf: truncatedObjects];
  			printValueAsIs;
  			yourself]!

Item was changed:
  ----- Method: Inspector>>valuePane (in category 'user interface') -----
  valuePane
  	"Private. This is a workaround to interact with the value pane directly and not interfere with the code pane."
  
  	^ self dependents
+ 		detect: [:obj | obj knownName = #valuePane]
- 		detect: [:object | object knownName = #valuePane]
  		ifNone: []!

Item was changed:
  ----- Method: InspectorField class>>generateExpressionFrom:argumentNames: (in category 'support') -----
  generateExpressionFrom: aBlock argumentNames: argumentNames
  
  	| blockNode arguments variables context receiver |
  	self flag: #experimental.
  	blockNode := aBlock decompile veryDeepCopy. "some literals are singletons, see #becomeForward: below"
  	arguments := blockNode arguments collect: #name.
  	variables := Dictionary new.
  	variables
  		at: #true put: true;
  		at: #false put: false;
  		at: #nil put: nil.
  	receiver := aBlock receiver.
  	receiver class allInstVarNames
+ 		withIndexDo: [:clsName :index |
+ 			variables at: clsName put: (receiver instVarAt: index)].
- 		withIndexDo: [:name :index |
- 			variables at: name put: (receiver instVarAt: index)].
  	context := aBlock outerContext.
  	context tempNames
+ 		withIndexDo: [:tmpName :index |
+ 			variables at: tmpName put: (context namedTempAt: index)].
- 		withIndexDo: [:name :index |
- 			variables at: name put: (context namedTempAt: index)].
  	blockNode nodesDo: [:node |
  		self flag: #ct. "Should we introduce #nodesCollect: instead of using dangerous #becomeForward:?"
  		{
  			[node isVariableNode not].
  			[| argumentIndex |
  			argumentIndex := arguments indexOf: node name.
  			argumentIndex isZero
  				ifFalse: [node name: (argumentNames at: argumentIndex)];
  				not].
  			[variables at: node name
  				ifPresent: [:value |
  					value isLiteral
  						ifTrue: [node becomeForward: (LiteralNode new key: value)];
  						yourself]
  				ifAbsent: [^ nil]].
  		} detect: #value ifNone: [^ nil]].
  	^ String streamContents: [:stream |
  		blockNode
  			printStatementsOn: stream
  			indent: 0].!

Item was changed:
  ----- Method: VersionsBrowser>>fileOutSelection (in category 'menu') -----
  fileOutSelection
+ 	| them it |
- 	| them it file |
  	them := OrderedCollection new.
  	listSelections with: changeList do: 
  		[:selected :item | selected ifTrue: [them add: item]].
  	them size ~= 1
  		ifTrue: [self inform: 'single version not selected, so nothing done' translated]
  		ifFalse:
  			[it := them first.
+ 			 FileStream newFileNamed: it methodClassName, (it isMetaClassChange ifTrue: [' class'] ifFalse: ['']), '-' , (it methodSelector copyReplaceAll: ':' with: '') do:
+ 			[:strm|
+ 			strm header; timeStamp.
+ 			it fileOutOn: strm]]!
- 			 file := FileStream newFileNamed: it methodClassName, (it isMetaClassChange ifTrue: [' class'] ifFalse: ['']), '-' , (it methodSelector copyReplaceAll: ':' with: '').
- 			 [file header; timeStamp.
- 			  it fileOutOn: file] ensure: [file close]]!



More information about the Squeak-dev mailing list