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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 11 17:10:17 UTC 2018


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

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

Name: Tools-eem.790
Author: eem
Time: 11 January 2018, 9:07:29.791856 am
UUID: 24ea3a83-3589-4e8f-8a7f-cdf01eb2b06e
Ancestors: Tools-eem.789

Add source range support for full blocks by adding DebuggerMethodMapForFullBlockCompiledMethods.  Shift to using startKeys instead of merely startPcs.

Interface with the debuggerMap via rangeForPC:in:contextIsActiveContext: rather than rangeForPC:contextIsActiveContext: so that if a full block is in use the debuggerMap has the method in hand to choose the right source range map.

=============== Diff against Tools-eem.789 ===============

Item was added:
+ ----- Method: CompiledBlock>>blockExtentsToTempsMap (in category '*Tools-Debugger-support') -----
+ blockExtentsToTempsMap
+ 	^self homeMethod blockExtentsToTempsMap!

Item was added:
+ ----- Method: CompiledBlock>>debuggerMap (in category '*Tools-Debugger-support') -----
+ debuggerMap
+ 	^self homeMethod debuggerMap!

Item was added:
+ ----- Method: CompiledBlock>>startKey (in category '*Tools-Debugger-support') -----
+ startKey
+ 	"The startKey is used as a key to identify the active sequence of temporaries for a block or
+ 	 method in a DebuggerMethodMapForClosureCompiledMethod's startKeysToTempRefs map."
+ 	^self!

Item was added:
+ ----- Method: CompiledCode>>abstractPCForConcretePC: (in category '*Tools-Debugger-support') -----
+ abstractPCForConcretePC: concretePC
+ 	"Answer the abstractPC matching concretePC."
+ 
+ 	| abstractPC scanner client endPC |
+ 	self flag: 'belongs in DebuggerMethodMap?'.
+ 	abstractPC := 1.
+ 	scanner := InstructionStream on: self.
+ 	client := InstructionClient new.
+ 	"cache endPC for methods with embedded source; finding out the endPC is very slow in this case..."
+ 	endPC := self endPC.
+ 	[(scanner pc > endPC
+ 	  or: [scanner pc >= concretePC]) ifTrue:
+ 		[^abstractPC].
+ 	 abstractPC := abstractPC + 1.
+ 	 scanner interpretNextInstructionFor: client] repeat!

Item was removed:
- ----- Method: CompiledMethod>>abstractPCForConcretePC: (in category '*Tools-Debugger-support') -----
- abstractPCForConcretePC: concretePC
- 	"Answer the abstractPC matching concretePC."
- 
- 	| abstractPC scanner client endPC |
- 	self flag: 'belongs in DebuggerMethodMap?'.
- 	abstractPC := 1.
- 	scanner := InstructionStream on: self.
- 	client := InstructionClient new.
- 	"cache endPC for methods with embedded source; finding out the endPC is very slow in this case..."
- 	endPC := self endPC.
- 	[(scanner pc > endPC
- 	  or: [scanner pc >= concretePC]) ifTrue:
- 		[^abstractPC].
- 	 abstractPC := abstractPC + 1.
- 	 scanner interpretNextInstructionFor: client] repeat!

Item was changed:
  ----- Method: CompiledMethod>>blockExtentsToTempsMap (in category '*Tools-Debugger-support') -----
  blockExtentsToTempsMap
  	"If the receiver has been copied with temp names answer a
  	 map from blockExtent to temps map in the same format as
  	 BytecodeEncoder>>blockExtentsToTempNamesMap.  if the
  	 receiver has not been copied with temps answer nil."
  	^self holdsTempNames ifTrue:
+ 		[self mapFromBlockKeys: (self startKeysToBlockExtents values sort: [:assocA :assocB| assocA first <= assocB first])
- 		[self mapFromBlockKeys: ((self startpcsToBlockExtents associations sort:
- 										[:a1 :a2| a1 key < a2 key]) replace:
- 									[:assoc| assoc value])
  			toSchematicTemps: self tempNamesString]!

Item was removed:
- ----- Method: CompiledMethod>>mapFromBlockKeys:toSchematicTemps: (in category '*Tools-Debugger-support') -----
- mapFromBlockKeys: keys toSchematicTemps: schematicTempNamesString
- 	"Decode a schematicTempNamesString that encodes the layout of temp names
- 	 in a method and any closures/blocks within it, matching keys in keys to
- 	 vectors of temp names."
- 	| map tempNames |
- 	map := Dictionary new.
- 	tempNames := schematicTempNamesString readStream.
- 	keys do:
- 		[:key| | tempSequence tempIndex |
- 		tempSequence := OrderedCollection new.
- 		tempIndex := 0.
- 		[(tempNames skipSeparators; peek) ifNil: [true] ifNotNil: [:ch| '[]' includes: ch]] whileFalse:
- 			[tempNames peek = $(
- 				ifTrue: [tempSequence addAllLast: ((self tempsSubSequenceFrom: (tempNames next; yourself)) withIndexCollect:
- 														[:temp :index|
- 														{ temp. { tempIndex + 1. index } }]).
- 						tempNames peek ~= $) ifTrue: [self error: 'parse error'].
- 						tempIndex := tempIndex + 1.
- 						tempNames next]
- 				ifFalse: [tempSequence addAllLast: ((self tempsSubSequenceFrom: tempNames) withIndexCollect:
- 														[:temp :index|
- 														{ temp. tempIndex := tempIndex + 1 }])]].
- 		map at: key put: tempSequence asArray.
- 		[tempNames peek = $]] whileTrue: [tempNames next].
- 		tempNames peek = $[ ifTrue:
- 			[tempNames next]].
- 	^map!

Item was added:
+ ----- Method: CompiledMethod>>startKey (in category '*Tools-Debugger-support') -----
+ startKey
+ 	"The startKey is used as a key to identify the active sequence of temporaries for a block or
+ 	 method in a DebuggerMethodMapForClosureCompiledMethod's startKeysToTempRefs map."
+ 	^self initialPC!

Item was added:
+ ----- Method: Context>>startKey (in category '*Tools-debugger access') -----
+ startKey
+ 	"The startKey is used as a key to identify the active sequence of temporaries for a block or
+ 	 method in a DebuggerMethodMapForClosureCompiledMethod's startKeysToTempRefs map."
+ 	^closureOrNil
+ 		ifNil:	[method initialPC]
+ 		ifNotNil: [closureOrNil isFullBlock
+ 					ifTrue: [method]
+ 					ifFalse: [closureOrNil startpc]]!

Item was changed:
  ----- Method: Debugger>>pcRange (in category 'code pane') -----
  pcRange
  	"Answer the indices in the source code for the method corresponding to 
  	the selected context's program counter value."
  
+ 	| ctxt |
  	(selectingPC and: [contextStackIndex ~= 0]) ifFalse:
  		[^1 to: 0].
+ 	(ctxt := self selectedContext) isDead ifTrue:
- 	self selectedContext isDead ifTrue:
  		[^1 to: 0].
+ 	^ctxt debuggerMap
+ 		rangeForPC: ctxt pc
+ 		in: ctxt method
- 	^self selectedContext debuggerMap
- 		rangeForPC: self selectedContext pc
  		contextIsActiveContext: contextStackIndex = 1!

Item was changed:
  ----- Method: DebuggerMethodMap class>>forMethod:methodNode: (in category 'instance creation') -----
+ forMethod: aMethod "<CompiledCode>" methodNode: methodNode "<MethodNode>"
- forMethod: aMethod "<CompiledMethod>" methodNode: methodNode "<MethodNode>"
  	"Uncached instance creation method for private use or for tests.
  	 Please consider using forMethod: instead."
  	^(aMethod isBlueBookCompiled
  			ifTrue: [DebuggerMethodMapForBlueBookMethods]
+ 			ifFalse:
+ 				[aMethod encoderClass supportsFullBlocks
+ 					ifTrue: [DebuggerMethodMapForFullBlockCompiledMethods]
+ 					ifFalse: [DebuggerMethodMapForClosureCompiledMethods]]) new
+ 		forMethod: aMethod homeMethod
- 			ifFalse: [DebuggerMethodMapForClosureCompiledMethods]) new
- 		forMethod: aMethod
  		methodNode: methodNode!

Item was changed:
+ ----- Method: DebuggerMethodMap>>abstractSourceMap (in category 'private') -----
- ----- Method: DebuggerMethodMap>>abstractSourceMap (in category 'source mapping') -----
  abstractSourceMap
  	"Answer with a Dictionary of abstractPC <Integer> to sourceRange <Interval>."
  	| theMethodToScan rawSourceRanges concreteSourceRanges abstractPC scanner client |
  	abstractSourceRanges ifNotNil:
  		[^abstractSourceRanges].
  	"If the methodNode hasn't had a method generated it doesn't have pcs set in its
  	 nodes so we must generate a new method and might as well use it for scanning."
  	methodNode rawSourceRangesAndMethodDo:
  		[:ranges :method|
  		 rawSourceRanges := ranges.
  		 theMethodToScan := method].
  	concreteSourceRanges := Dictionary new.
  	rawSourceRanges keysAndValuesDo:
  		[:node :range|
  		node pc ~= 0 ifTrue:
  			[concreteSourceRanges at: node pc put: range]].
  	abstractPC := 1.
  	abstractSourceRanges := Dictionary new.
  	scanner := InstructionStream on: theMethodToScan.
  	client := InstructionClient new.
  	[(concreteSourceRanges includesKey: scanner pc) ifTrue:
  		[abstractSourceRanges at: abstractPC put: (concreteSourceRanges at: scanner pc)].
  	 abstractPC := abstractPC + 1.
  	 scanner interpretNextInstructionFor: client.
  	 scanner atEnd] whileFalse.
  	^abstractSourceRanges!

Item was added:
+ ----- Method: DebuggerMethodMap>>abstractSourceMapForMethod: (in category 'source mapping') -----
+ abstractSourceMapForMethod: aCompiledMethod
+ 	"The default source mapping is for block bytecodes embedded within a
+ 	 single compiled method, as in the BlueBook and EncoderForV3PlusClosures."
+ 	^self abstractSourceMap!

Item was changed:
+ ----- Method: DebuggerMethodMap>>rangeForPC:contextIsActiveContext: (in category 'private but obsolete') -----
- ----- Method: DebuggerMethodMap>>rangeForPC:contextIsActiveContext: (in category 'source mapping') -----
  rangeForPC: contextsConcretePC contextIsActiveContext: contextIsActiveContext
  	"Answer the indices in the source code for the supplied pc.
  	 If the context is the actve context (is at the hot end of the stack)
  	 then its pc is the current pc.  But if the context isn't, because it is
  	 suspended sending a message, then its current pc is the previous pc."
  
  	| pc i end |
  	pc := self method abstractPCForConcretePC: (contextIsActiveContext
  													ifTrue: [contextsConcretePC]
  													ifFalse: [(self method pcPreviousTo: contextsConcretePC)
  																ifNotNil: [:prevpc| prevpc]
  																ifNil: [contextsConcretePC]]).
  	(self abstractSourceMap includesKey: pc) ifTrue:
  		[^self abstractSourceMap at: pc].
  	sortedSourceMap ifNil:
  		[sortedSourceMap := self abstractSourceMap associations
  			replace: [ :each | each copy ];
  			sort].
  	sortedSourceMap isEmpty ifTrue: [^1 to: 0].
  	i := sortedSourceMap findNearbyBinaryIndex: [:assoc| pc - assoc key].
  	i < 1 ifTrue: [^1 to: 0].
  	i > sortedSourceMap size ifTrue:
  		[end := sortedSourceMap inject: 0 into:
  			[:prev :this | prev max: this value last].
  		^end+1 to: end].
  	^(sortedSourceMap at: i) value
  
  	"| method source scanner map |
  	 method := DebuggerMethodMap compiledMethodAt: #rangeForPC:contextIsActiveContext:.
  	 source := method getSourceFromFile asString.
  	 scanner := InstructionStream on: method.
  	 map := method debuggerMap.
  	 Array streamContents:
  		[:ranges|
  		[scanner atEnd] whileFalse:
  			[| range |
  			 range := map rangeForPC: scanner pc contextIsActiveContext: true.
  			 ((map abstractSourceMap includesKey: scanner abstractPC)
  			  and: [range first ~= 0]) ifTrue:
  				[ranges nextPut: (source copyFrom: range first to: range last)].
  			scanner interpretNextInstructionFor: InstructionClient new]]"!

Item was added:
+ ----- Method: DebuggerMethodMap>>rangeForPC:in:contextIsActiveContext: (in category 'source mapping') -----
+ rangeForPC: contextsConcretePC in: method contextIsActiveContext: contextIsActiveContext
+ 	"Answer the indices in the source code for the supplied pc.
+ 	 If the context is the actve context (is at the hot end of the stack)
+ 	 then its pc is the current pc.  But if the context isn't, because it is
+ 	 suspended sending a message, then its current pc is the previous pc."
+ 
+ 	| pc i end |
+ 	pc := self method abstractPCForConcretePC: (contextIsActiveContext
+ 													ifTrue: [contextsConcretePC]
+ 													ifFalse: [(self method pcPreviousTo: contextsConcretePC)
+ 																ifNotNil: [:prevpc| prevpc]
+ 																ifNil: [contextsConcretePC]]).
+ 	(self abstractSourceMap includesKey: pc) ifTrue:
+ 		[^self abstractSourceMap at: pc].
+ 	sortedSourceMap ifNil:
+ 		[sortedSourceMap := self abstractSourceMap associations
+ 			replace: [ :each | each copy ];
+ 			sort].
+ 	sortedSourceMap isEmpty ifTrue: [^1 to: 0].
+ 	i := sortedSourceMap findNearbyBinaryIndex: [:assoc| pc - assoc key].
+ 	i < 1 ifTrue: [^1 to: 0].
+ 	i > sortedSourceMap size ifTrue:
+ 		[end := sortedSourceMap inject: 0 into:
+ 			[:prev :this | prev max: this value last].
+ 		^end+1 to: end].
+ 	^(sortedSourceMap at: i) value
+ 
+ 	"| method source scanner map |
+ 	 method := DebuggerMethodMap compiledMethodAt: #rangeForPC:in:contextIsActiveContext:.
+ 	 source := method getSourceFromFile asString.
+ 	 scanner := InstructionStream on: method.
+ 	 map := method debuggerMap.
+ 	 Array streamContents:
+ 		[:ranges|
+ 		[scanner atEnd] whileFalse:
+ 			[| range |
+ 			 range := map rangeForPC: scanner pc in: method contextIsActiveContext: true.
+ 			 ((map abstractSourceMap includesKey: scanner abstractPC)
+ 			  and: [range first ~= 0]) ifTrue:
+ 				[ranges nextPut: (source copyFrom: range first to: range last)].
+ 			scanner interpretNextInstructionFor: InstructionClient new]]"!

Item was changed:
  DebuggerMethodMap subclass: #DebuggerMethodMapForBlueBookMethods
  	instanceVariableNames: 'tempNames'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tools-Debugger'!
  
+ !DebuggerMethodMapForBlueBookMethods commentStamp: 'eem 1/6/2018 16:57' prior: 0!
+ I am a place-holder for information needed by the Debugger to inspect method activations.  See my superclass's comment. I map methods compiled using BlueBook blocks.!
- !DebuggerMethodMapForBlueBookMethods commentStamp: '<historical>' prior: 0!
- I am a place-holder for information needed by the Debugger to inspect method activations.  See my superclass's comment. I map methods compiled using Closures.!

Item was changed:
  DebuggerMethodMap subclass: #DebuggerMethodMapForClosureCompiledMethods
+ 	instanceVariableNames: 'blockExtentsToTempRefs startpcsToTempRefs startKeysToTempRefs'
- 	instanceVariableNames: 'blockExtentsToTempRefs startpcsToTempRefs'
  	classVariableNames: 'FirstTime'
  	poolDictionaries: ''
  	category: 'Tools-Debugger'!
  
+ !DebuggerMethodMapForClosureCompiledMethods commentStamp: 'eem 1/8/2018 12:42' prior: 0!
+ I am a place-holder for information needed by the Debugger to inspect method activations.  See my superclass's comment. I map methods compiled using closures.
- !DebuggerMethodMapForClosureCompiledMethods commentStamp: '<historical>' prior: 0!
- I am a place-holder for information needed by the Debugger to inspect method activations.  See my superclass's comment. I map methods compiled using BlueBook blocks.
  
  Instance variables
  	blockExtentsToTempsRefs <Dictionary of: Interval -> Array of: (Array with: String with: (Integer | (Array with: Integer with: Integer)))>
  		maps a block extent to an Array of temp references for that block/method.
  		Each reference is a pair of temp name and index, where the index can itself be a pair for a remote temp.
+ 	startKeysToTempRefs <Dictionary of: Integer startpc -> Array of: (Array with: String with: temp reference)> where
- 	startpcsToTempRefs <Dictionary of: Integer -> Array of: (Array with: String with: temp reference)> where
  		temp reference ::= Integer
+ 							| (Array with: Integer with: Integer)
+ 							| (Array with: #outer with: temp reference)!
- 						| (Array with: Integer with: Integer)
- 						| (Array with: #outer with: temp reference)!

Item was removed:
- ----- Method: DebuggerMethodMapForClosureCompiledMethods>>ensureExtentsMapsInitialized (in category 'private') -----
- ensureExtentsMapsInitialized
- 	| encoderTempRefs "<Dictionary of: Interval -> <Array of: <String | <Array of: String>>>>" |
- 	blockExtentsToTempRefs ifNotNil: [^self].
- 	blockExtentsToTempRefs := Dictionary new.
- 	startpcsToTempRefs := Dictionary new.
- 	encoderTempRefs := methodNode blockExtentsToTempRefs.
- 	encoderTempRefs keysAndValuesDo:
- 		[:blockExtent :tempVector|
- 		blockExtentsToTempRefs
- 			at: blockExtent
- 			put: (Array streamContents:
- 					[:stream|
- 					tempVector withIndexDo:
- 						[:nameOrSequence :index|
- 						nameOrSequence isString
- 							ifTrue:
- 								[stream nextPut: {nameOrSequence. index}]
- 							ifFalse:
- 								[nameOrSequence withIndexDo:
- 									[:name :indirectIndex|
- 									stream nextPut: { name. { index. indirectIndex }}]]]])]!

Item was changed:
  ----- Method: DebuggerMethodMapForClosureCompiledMethods>>namedTempAt:in: (in category 'accessing') -----
  namedTempAt: index in: aContext
  	"Answer the value of the temp at index in aContext where index is relative
  	 to the array of temp names answered by tempNamesForContext:"
  	^self
  		privateTempAt: index
  		in: aContext
+ 		startKeysToBlockExtents: aContext method startKeysToBlockExtents!
- 		startpcsToBlockExtents: aContext method startpcsToBlockExtents!

Item was changed:
  ----- Method: DebuggerMethodMapForClosureCompiledMethods>>namedTempAt:put:in: (in category 'accessing') -----
  namedTempAt: index put: aValue in: aContext
  	"Assign the value of the temp at index in aContext where index is relative
  	 to the array of temp names answered by tempNamesForContext:.
  	 If the value is a copied value we also need to set it along the lexical chain."
  	^self
  		privateTempAt: index
  		in: aContext
  		put: aValue
+ 		startKeysToBlockExtents: aContext method startKeysToBlockExtents!
- 		startpcsToBlockExtents: aContext method startpcsToBlockExtents!

Item was added:
+ ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempAt:in:put:startKeysToBlockExtents: (in category 'private') -----
+ privateTempAt: index in: aContext put: aValue startKeysToBlockExtents: theContextsStartKeysToBlockExtents
+ 	| nameRefPair |
+ 	nameRefPair := (self privateTempRefsForContext: aContext
+ 						 startKeysToBlockExtents: theContextsStartKeysToBlockExtents)
+ 						at: index
+ 						ifAbsent: [aContext errorSubscriptBounds: index].
+ 	^self privateDereference: nameRefPair last in: aContext put: aValue!

Item was changed:
+ ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempAt:in:put:startpcsToBlockExtents: (in category 'private but obsolete') -----
- ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempAt:in:put:startpcsToBlockExtents: (in category 'private') -----
  privateTempAt: index in: aContext put: aValue startpcsToBlockExtents: theContextsStartpcsToBlockExtents
  	| nameRefPair |
  	nameRefPair := (self privateTempRefsForContext: aContext
  						 startpcsToBlockExtents: theContextsStartpcsToBlockExtents)
  						at: index
  						ifAbsent: [aContext errorSubscriptBounds: index].
  	^self privateDereference: nameRefPair last in: aContext put: aValue!

Item was added:
+ ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempAt:in:startKeysToBlockExtents: (in category 'private') -----
+ privateTempAt: index in: aContext startKeysToBlockExtents: theContextsStartKeysToBlockExtents
+ 	| nameRefPair |
+ 	nameRefPair := (self privateTempRefsForContext: aContext
+ 						 startKeysToBlockExtents: theContextsStartKeysToBlockExtents)
+ 						at: index
+ 						ifAbsent: [aContext errorSubscriptBounds: index].
+ 	^self privateDereference: nameRefPair last in: aContext!

Item was changed:
+ ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempAt:in:startpcsToBlockExtents: (in category 'private but obsolete') -----
- ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempAt:in:startpcsToBlockExtents: (in category 'private') -----
  privateTempAt: index in: aContext startpcsToBlockExtents: theContextsStartpcsToBlockExtents
  	| nameRefPair |
  	nameRefPair := (self privateTempRefsForContext: aContext
  						 startpcsToBlockExtents: theContextsStartpcsToBlockExtents)
  						at: index
  						ifAbsent: [aContext errorSubscriptBounds: index].
  	^self privateDereference: nameRefPair last in: aContext!

Item was added:
+ ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempRefsForContext:startKeysToBlockExtents: (in category 'private') -----
+ privateTempRefsForContext: aContext startKeysToBlockExtents: theContextsStartKeysToBlockExtents
+ 	"Answer the sequence of temps in scope in aContext in the natural order,
+ 	 outermost arguments and temporaries first, innermost last.  Each temp is
+ 	 a pair of the temp's name followed by a reference.  The reference can be
+ 		integer - index of temp in aContext
+ 		#( indirectionVectorIndex tempIndex ) - remote temp in indirectionVector at index in aContext
+ 		#( outer. temp reference ) - a temp reference in an outer context."
+ 	blockExtentsToTempRefs ifNil:
+ 		[blockExtentsToTempRefs := (aContext method holdsTempNames
+ 										ifTrue: [aContext method]
+ 										ifFalse: [methodNode]) blockExtentsToTempsMap.
+ 		 blockExtentsToTempRefs ifNil:
+ 			["an empty method.  shouldn't be able to step into here but it
+ 			  can happen in weird circumstances (i.e. with MethodWrapper)."
+ 			blockExtentsToTempRefs := Dictionary new.
+ 			blockExtentsToTempRefs
+ 				at: (theContextsStartKeysToBlockExtents at: aContext startKey)
+ 				put: {}].
+ 		 startKeysToTempRefs := Dictionary new].
+ 	^startKeysToTempRefs
+ 		at: aContext startKey
+ 		ifAbsentPut:
+ 			[| localRefs |
+ 			 localRefs := blockExtentsToTempRefs at: (theContextsStartKeysToBlockExtents at: aContext startKey) ifAbsent: [#()].
+ 			 aContext outerContext
+ 				ifNil: [localRefs]
+ 				ifNotNil:
+ 					[:outer| | outerTemps |
+ 					"Present temps in the order outermost to innermost left-to-right, but replace
+ 					 copied outermost temps with their innermost copies"
+ 					 outerTemps := (self
+ 										privateTempRefsForContext: outer
+ 										startKeysToBlockExtents: theContextsStartKeysToBlockExtents) collect:
+ 						[:outerPair|
+ 						localRefs
+ 							detect: [:localPair| outerPair first = localPair first]
+ 							ifNone: [{ outerPair first. { #outer. outerPair last } }]].
+ 					outerTemps,
+ 					 (localRefs reject: [:localPair| outerTemps anySatisfy: [:outerPair| localPair first = outerPair first]])]]!

Item was changed:
+ ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempRefsForContext:startpcsToBlockExtents: (in category 'private but obsolete') -----
- ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempRefsForContext:startpcsToBlockExtents: (in category 'private') -----
  privateTempRefsForContext: aContext startpcsToBlockExtents: theContextsStartpcsToBlockExtents
  	"Answer the sequence of temps in scope in aContext in the natural order,
  	 outermost arguments and temporaries first, innermost last.  Each temp is
  	 a pair of the temp's name followed by a reference.  The reference can be
  		integer - index of temp in aContext
  		#( indirectionVectorIndex tempIndex ) - remote temp in indirectionVector at index in aContext
  		#( outer. temp reference ) - a temp reference in an outer context."
  	blockExtentsToTempRefs ifNil:
  		[blockExtentsToTempRefs := (aContext method holdsTempNames
  										ifTrue: [aContext method]
  										ifFalse: [methodNode]) blockExtentsToTempsMap.
  		 blockExtentsToTempRefs ifNil:
  			["an empty method.  shouldn't be able to step into here but it
  			  can happen in weird circumstances (i.e. with MethodWrapper)."
  			blockExtentsToTempRefs := Dictionary new.
  			blockExtentsToTempRefs
  				at: (theContextsStartpcsToBlockExtents at: aContext startpc)
  				put: {}].
  		 startpcsToTempRefs := Dictionary new].
  	^startpcsToTempRefs
  		at: aContext startpc
  		ifAbsentPut:
  			[| localRefs |
  			 localRefs := blockExtentsToTempRefs at: (theContextsStartpcsToBlockExtents at: aContext startpc).
  			 aContext outerContext
  				ifNil: [localRefs]
  				ifNotNil:
  					[:outer| | outerTemps |
  					"Present temps in the order outermost to innermost left-to-right, but replace
  					 copied outermost temps with their innermost copies"
  					 outerTemps := (self
  										privateTempRefsForContext: outer
  										startpcsToBlockExtents: theContextsStartpcsToBlockExtents) collect:
  						[:outerPair|
  						localRefs
  							detect: [:localPair| outerPair first = localPair first]
  							ifNone: [{ outerPair first. { #outer. outerPair last } }]].
  					outerTemps,
  					 (localRefs reject: [:localPair| outerTemps anySatisfy: [:outerPair| localPair first = outerPair first]])]]!

Item was added:
+ ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempRefsForMethod:startKeysToBlockExtents: (in category 'private') -----
+ privateTempRefsForMethod: method startKeysToBlockExtents: startKeysToBlockExtents
+ 	"Answer the sequence of temps in scope in method in the natural order,
+ 	 outermost arguments and temporaries first, innermost last.  Each temp is
+ 	 a pair of the temp's name followed by a reference.  The reference can be
+ 		integer - index of temp in aContext
+ 		#( indirectionVectorIndex tempIndex ) - remote temp in indirectionVector at index in aContext
+ 		#( outer. temp reference ) - a temp reference in an outer context."
+ 	blockExtentsToTempRefs ifNil:
+ 		[blockExtentsToTempRefs := (method holdsTempNames
+ 										ifTrue: [method]
+ 										ifFalse: [methodNode]) blockExtentsToTempsMap.
+ 		 blockExtentsToTempRefs ifNil:
+ 			["an empty method.  shouldn't be able to step into here but it
+ 			  can happen in weird circumstances (i.e. with MethodWrapper)."
+ 			blockExtentsToTempRefs := Dictionary new.
+ 			blockExtentsToTempRefs
+ 				at: (startKeysToBlockExtents at: method startKey)
+ 				put: {}].
+ 		 startKeysToTempRefs := Dictionary new].
+ 	^startKeysToTempRefs
+ 		at: method startKey
+ 		ifAbsentPut:
+ 			[blockExtentsToTempRefs at: (startKeysToBlockExtents at: method startKey)]!

Item was changed:
+ ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempRefsForMethod:startpcsToBlockExtents: (in category 'private but obsolete') -----
- ----- Method: DebuggerMethodMapForClosureCompiledMethods>>privateTempRefsForMethod:startpcsToBlockExtents: (in category 'private') -----
  privateTempRefsForMethod: method startpcsToBlockExtents: startpcsToBlockExtents
  	"Answer the sequence of temps in scope in method in the natural order,
  	 outermost arguments and temporaries first, innermost last.  Each temp is
  	 a pair of the temp's name followed by a reference.  The reference can be
  		integer - index of temp in aContext
  		#( indirectionVectorIndex tempIndex ) - remote temp in indirectionVector at index in aContext
  		#( outer. temp reference ) - a temp reference in an outer context."
  	blockExtentsToTempRefs ifNil:
  		[blockExtentsToTempRefs := (method holdsTempNames
  										ifTrue: [method]
  										ifFalse: [methodNode]) blockExtentsToTempsMap.
  		 blockExtentsToTempRefs ifNil:
  			["an empty method.  shouldn't be able to step into here but it
  			  can happen in weird circumstances (i.e. with MethodWrapper)."
  			blockExtentsToTempRefs := Dictionary new.
  			blockExtentsToTempRefs
  				at: (startpcsToBlockExtents at: method initialPC)
  				put: {}].
  		 startpcsToTempRefs := Dictionary new].
  	^startpcsToTempRefs
  		at: method initialPC
  		ifAbsentPut:
  			[blockExtentsToTempRefs at: (startpcsToBlockExtents at: method initialPC)]!

Item was changed:
  ----- Method: DebuggerMethodMapForClosureCompiledMethods>>tempNamesForContext: (in category 'accessing') -----
  tempNamesForContext: aContext
  	"Answer an Array of all the temp names in scope in aContext starting with
  	 the home's first local (the first argument or first temporary if no arguments)."
  	^(self
  		privateTempRefsForContext: aContext
+ 		startKeysToBlockExtents: aContext method startKeysToBlockExtents) collect:
- 		startpcsToBlockExtents: aContext method startpcsToBlockExtents) collect:
  			[:pair| pair first]!

Item was changed:
  ----- Method: DebuggerMethodMapForClosureCompiledMethods>>tempNamesForMethod: (in category 'accessing') -----
  tempNamesForMethod: aMethod
  	"Answer an Array of all the temp names in scope in aMethod starting with
  	 the home's first local (the first argument or first temporary if no arguments)."
  	^(self
  		privateTempRefsForMethod: aMethod
+ 		startKeysToBlockExtents: aMethod startKeysToBlockExtents) collect:
- 		startpcsToBlockExtents: aMethod startpcsToBlockExtents) collect:
  			[:pair| pair first]!

Item was added:
+ DebuggerMethodMapForClosureCompiledMethods subclass: #DebuggerMethodMapForFullBlockCompiledMethods
+ 	instanceVariableNames: 'sortedSourceMaps'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Tools-Debugger'!
+ 
+ !DebuggerMethodMapForFullBlockCompiledMethods commentStamp: 'eem 1/10/2018 16:28' prior: 0!
+ I am a place-holder for information needed by the Debugger to inspect method activations.  See DebuggerMethodMap's comment. I map methods compiled using full block closures.
+ 
+ Instance variables
+ 	(inherited)
+ 	abstractSourceRanges <Dictionary of: CompiledCode -> (Dictionary of: Integer-> Interval)
+ 	startKeysToTempRefs <Dictionary of: CompiledCode -> Array of: (Array with: String with: temp reference)> where
+ 		temp reference ::= Integer
+ 							| (Array with: Integer with: Integer)
+ 							| (Array with: #outer with: temp reference)
+ 	(locally defined)
+ 	sortedSourceMaps <Dictionary of: CompiledCode -> (Dictionary of: Integer-> Interval)!

Item was added:
+ ----- Method: DebuggerMethodMapForFullBlockCompiledMethods>>abstractSourceMap (in category 'source mapping') -----
+ abstractSourceMap
+ 	self shouldNotImplement!

Item was added:
+ ----- Method: DebuggerMethodMapForFullBlockCompiledMethods>>abstractSourceMapForMethod: (in category 'source mapping') -----
+ abstractSourceMapForMethod: compiledCode
+ 	"Answer with a Dictionary of abstractPC <Integer> to sourceRange <Interval>
+ 	 for compiledCode which may be either a CompiledMethod or a CompiledBlock."
+ 	| rawSourceRanges theMethodToScan |
+ 	abstractSourceRanges ifNotNil:
+ 		[^abstractSourceRanges at: compiledCode].
+ 	abstractSourceRanges := IdentityDictionary new.
+ 	"If the methodNode hasn't had a method generated it doesn't have pcs set in its
+ 	 nodes so we must generate a new method.  We use this method for scanning
+ 	 since its rawSourceRanges refer to the block methods within the method, and
+ 	 that means we can use identity comparisons to match nodes with blocks."
+ 	methodNode rawSourceRangesAndMethodDo:
+ 		[:ranges :method|
+ 		 rawSourceRanges := ranges.
+ 		 theMethodToScan := method].
+ 	self scanMethod: theMethodToScan mappingRanges: rawSourceRanges.
+ 	self mapBlockMethodKeysIn: theMethodToScan toActualBlockMethodsIn: compiledCode homeMethod.
+ 	^abstractSourceRanges at: compiledCode!

Item was added:
+ ----- Method: DebuggerMethodMapForFullBlockCompiledMethods>>mapBlockMethodKeysIn:toActualBlockMethodsIn: (in category 'source mapping') -----
+ mapBlockMethodKeysIn: theMethodToScan toActualBlockMethodsIn: actualMethod
+ 	abstractSourceRanges at: actualMethod put: (abstractSourceRanges removeKey: theMethodToScan).
+ 	1 to: theMethodToScan numLiterals - 1 do: "i.e. don't scan the last literal which, in CompiledBlocks is a back pointer"
+ 		[:i| | lit |
+ 		 (lit := theMethodToScan literalAt: i) isCompiledCode ifTrue:
+ 			[self mapBlockMethodKeysIn: lit toActualBlockMethodsIn: (actualMethod literalAt: i)]]!

Item was added:
+ ----- Method: DebuggerMethodMapForFullBlockCompiledMethods>>rangeForPC:in:contextIsActiveContext: (in category 'source mapping') -----
+ rangeForPC: contextsConcretePC in: method contextIsActiveContext: contextIsActiveContext
+ 	"Answer the indices in the source code for the supplied pc.
+ 	 If the context is the actve context (is at the hot end of the stack)
+ 	 then its pc is the current pc.  But if the context isn't, because it is
+ 	 suspended sending a message, then its current pc is the previous pc."
+ 
+ 	| pc i end mapForMethod sortedMap |
+ 	pc := self method abstractPCForConcretePC: (contextIsActiveContext
+ 													ifTrue: [contextsConcretePC]
+ 													ifFalse: [(self method pcPreviousTo: contextsConcretePC)
+ 																ifNotNil: [:prevpc| prevpc]
+ 																ifNil: [contextsConcretePC]]).
+ 	((mapForMethod := self abstractSourceMapForMethod: method) includesKey: pc) ifTrue:
+ 		[^mapForMethod at: pc].
+ 	sortedSourceMap ifNil:
+ 		[sortedSourceMap := IdentityDictionary new].
+ 	sortedMap := sortedSourceMap
+ 						at: method
+ 						ifAbsentPut: [mapForMethod associations
+ 										replace: [ :each | each copy ];
+ 										sort].
+ 	sortedMap isEmpty ifTrue: [^1 to: 0].
+ 	i := sortedMap findNearbyBinaryIndex: [:assoc| pc - assoc key].
+ 	i < 1 ifTrue: [^1 to: 0].
+ 	i > sortedMap size ifTrue:
+ 		[end := sortedMap inject: 0 into:
+ 			[:prev :this | prev max: this value last].
+ 		^end+1 to: end].
+ 	^(sortedMap at: i) value
+ 
+ 	"| method source scanner map |
+ 	 method := DebuggerMethodMapForFullBlockCompiledMethods compiledMethodAt: #rangeForPC:in:contextIsActiveContext:.
+ 	 source := method getSourceFromFile asString.
+ 	 scanner := InstructionStream on: method.
+ 	 map := method debuggerMap.
+ 	 Array streamContents:
+ 		[:ranges|
+ 		[scanner atEnd] whileFalse:
+ 			[| range |
+ 			 range := map rangeForPC: scanner pc in: method contextIsActiveContext: true.
+ 			 ((map abstractSourceMap includesKey: scanner abstractPC)
+ 			  and: [range first ~= 0]) ifTrue:
+ 				[ranges nextPut: (source copyFrom: range first to: range last)].
+ 			scanner interpretNextInstructionFor: InstructionClient new]]"!

Item was added:
+ ----- Method: DebuggerMethodMapForFullBlockCompiledMethods>>scanMethod:mappingRanges: (in category 'source mapping') -----
+ scanMethod: theMethodToScan mappingRanges: rawSourceRanges
+ 	| abstractPC scanner client maybeBlock concreteSourceRanges rangesForMethod |
+ 	rangesForMethod := (abstractSourceRanges at: theMethodToScan put: Dictionary new).
+ 	concreteSourceRanges := Dictionary new.
+ 	"The rawSourceRanges map node pcs to ranges.
+ 	 When node is one in the home method the node's pc is an integer.
+ 	When the node is within a block method the node's pc is an association from CompiledBlock to pc.
+ 	 Extract pc -> range for this particular CompiledMethod or CompiledBlock."
+ 	rawSourceRanges keysAndValuesDo:
+ 		(theMethodToScan isCompiledMethod
+ 			ifTrue:
+ 				[[:node :range|
+ 				   (node pc isVariableBinding
+ 				    or: [node pc = 0]) ifFalse:
+ 						[concreteSourceRanges at: node pc put: range]]]
+ 			ifFalse:
+ 				[[:node :range|
+ 				   (node pc isVariableBinding
+ 				    and: [node pc key == theMethodToScan
+ 				    and: [node pc value ~= 0]]) ifTrue:
+ 					[concreteSourceRanges at: node pc value put: range]]]).
+ 	abstractPC := 1.
+ 	scanner := InstructionStream on: theMethodToScan.
+ 	client := BlockStartLocator new.
+ 	[(concreteSourceRanges includesKey: scanner pc) ifTrue:
+ 		[rangesForMethod at: abstractPC put: (concreteSourceRanges at: scanner pc)].
+ 	 abstractPC := abstractPC + 1.
+ 	 maybeBlock := scanner interpretNextInstructionFor: client.
+ 	 (maybeBlock ~~ client
+ 	  and: [maybeBlock isCompiledCode]) ifTrue:
+ 		[self assert: maybeBlock isCompiledBlock.
+ 		 self scanMethod: maybeBlock mappingRanges: rawSourceRanges].
+ 	 scanner atEnd] whileFalse!

Item was changed:
  ----- Method: ProcessBrowser>>pcRange (in category 'stack list') -----
  pcRange
  	"Answer the indices in the source code for the method corresponding to  
  	the selected context's program counter value."
+ 	(selectedContext isNil or: [methodText isEmptyOrNil]) ifTrue:
+ 		[^ 1 to: 0].
- 	(selectedContext isNil or: [methodText isEmptyOrNil])
- 		ifTrue: [^ 1 to: 0].
  	^selectedContext debuggerMap
  		rangeForPC: (selectedContext pc ifNotNil: [:pc| pc] ifNil: [selectedContext method endPC])
+ 		in: selectedContext method
  		contextIsActiveContext: stackListIndex = 1!



More information about the Squeak-dev mailing list