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

commits at source.squeak.org commits at source.squeak.org
Sun Sep 6 05:17:02 UTC 2009


Andreas Raab uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-eem.122.mcz

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

Name: Tools-eem.122
Author: eem
Time: 5 September 2009, 5:20:28 am
UUID: 915ae117-3206-46e9-8554-3cf57c998eca
Ancestors: Tools-ar.121

Eighth package of eight in closure compiler fixes 9/5/2009.

Debugger fixes for method maps.
DebuggerMethodMap moves to new factorisation of symbolic temps computation.

=============== Diff against Tools-ar.121 ===============

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."
  
  	(selectingPC and: [contextStackIndex ~= 0]) ifFalse:
  		[^1 to: 0].
  	self selectedContext isDead ifTrue:
  		[^1 to: 0].
+ 	^self selectedContext debuggerMap
- 	debuggerMap ifNil:
- 		[debuggerMap := self selectedContext debuggerMap].
- 	^debuggerMap
  		rangeForPC: self selectedContext pc
  		contextIsActiveContext: contextStackIndex = 1!

Item was changed:
  ----- 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]
- 																ifNotNilDo: [:prevpc| prevpc]
  																ifNil: [contextsConcretePC]]).
  	(self abstractSourceMap includesKey: pc) ifTrue:
  		[^self abstractSourceMap at: pc].
  	sortedSourceMap ifNil:
  		[sortedSourceMap := self abstractSourceMap.
  		 sortedSourceMap := (sortedSourceMap keys collect: 
  								[:key| key -> (sortedSourceMap at: key)]) asSortedCollection].
  	(sortedSourceMap isNil or: [sortedSourceMap isEmpty]) ifTrue: [^1 to: 0].
  	i := sortedSourceMap indexForInserting: (pc -> nil).
  	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 changed:
  ----- 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.
+ 		 startpcsToTempRefs := Dictionary new].
- 	self ensureExtentsMapsInitialized.
  	^startpcsToTempRefs
  		at: aContext startpc
  		ifAbsentPut:
  			[| localRefs |
  			 localRefs := blockExtentsToTempRefs at: (theContextsStartpcsToBlockExtents at: aContext startpc).
  			 aContext outerContext
  				ifNil: [localRefs]
+ 				ifNotNil:
- 				ifNotNilDo:
  					[: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 changed:
  ----- Method: Debugger>>selectedMessage (in category 'context stack (message list)') -----
  selectedMessage
  	"Answer the source code of the currently selected context."
+ 	^contents := self selectedContext debuggerMap sourceText asText makeSelectorBold!
- 	debuggerMap isNil ifTrue:
- 		[debuggerMap := self selectedContext debuggerMap].
- 	^contents := debuggerMap sourceText asText makeSelectorBold!

Item was changed:
  ----- Method: DebuggerMethodMap>>sourceText (in category 'source mapping') -----
  sourceText
+ 	self method ifNotNil:
+ 		[:method|
+ 		method holdsTempNames ifTrue:
+ 			[^method
+ 				getSourceFor: (method selector ifNil: [method defaultSelector])
+ 				in: method methodClass]].
  	^methodNode sourceText!

Item was changed:
  ----- Method: Debugger>>contents:notifying: (in category 'accessing') -----
  contents: aText notifying: aController
  	"The retrieved information has changed and its source must now be updated.
  	 In this case, the retrieved information is the method of the selected context."
  	| result selector classOfMethod category h ctxt newMethod |
  	contextStackIndex = 0 ifTrue:
  		[^false].
  	self selectedContext isExecutingBlock ifTrue:
  		[h := self selectedContext activeHome.
  		 h ifNil:
  			[self inform: 'Method for block not found on stack, can''t edit and continue'.
  			 ^false].
  		 (self confirm: 'I will have to revert to the method from\which this block originated.  Is that OK?' withCRs) ifFalse:
  			[^false].
  		self resetContext: h.
  		result := self contents: aText notifying: aController.
  		self contentsChanged.
  		^result].
  
  	classOfMethod := self selectedClass.
  	category := self selectedMessageCategoryName.
  	selector := self selectedClass parserClass new parseSelector: aText.
  	(selector == self selectedMessageName
  	 or: [(self selectedMessageName beginsWith: 'DoIt')
  		and: [selector numArgs = self selectedMessageName numArgs]]) ifFalse:
  		[self inform: 'can''t change selector'.
  		 ^false].
  	selector := classOfMethod
  				compile: aText
  				classified: category
  				notifying: aController.
  	selector ifNil: [^false]. "compile cancelled"
  	contents := aText.
  	newMethod := classOfMethod compiledMethodAt: selector.
  	newMethod isQuick ifTrue:
  		[self down.
  		 self selectedContext jump: (self selectedContext previousPc - self selectedContext pc)].
  	ctxt := interruptedProcess popTo: self selectedContext.
  	ctxt == self selectedContext
  		ifFalse:
  			[self inform: 'Method saved, but current context unchanged\because of unwind error. Click OK to see error' withCRs]
  		ifTrue:
  			[newMethod isQuick ifFalse:
  				[interruptedProcess
  					restartTopWith: newMethod;
  				 	stepToSendOrReturn].
+ 			contextVariablesInspector object: nil].
- 			contextVariablesInspector object: nil.
- 			debuggerMap := nil].
  	self resetContext: ctxt.
  	Smalltalk isMorphic ifTrue:
  		[World
  			addAlarm: #changed:
  			withArguments: #(contentsSelection)
  			for: self
  			at: (Time millisecondClockValue + 200)].
  	^true!

Item was changed:
  ----- Method: Debugger>>contextStackIndex:oldContextWas: (in category 'private') -----
  contextStackIndex: anInteger oldContextWas: oldContext 
  	"Change the context stack index to anInteger, perhaps in response to user selection."
  
  	| isNewMethod selectedContextSlotName index |
  	contextStackIndex := anInteger.
  	anInteger = 0 ifTrue:
+ 		[currentCompiledMethod := contents := nil.
- 		[currentCompiledMethod := debuggerMap := contents := nil.
  		 self changed: #contextStackIndex.
  		 self decorateButtons.
  		 self contentsChanged.
  		 contextVariablesInspector object: nil.
  		 receiverInspector object: self receiver.
  		 ^self].
  	selectedContextSlotName := contextVariablesInspector selectedSlotName.
  	isNewMethod := oldContext == nil
  					or: [oldContext method ~~ (currentCompiledMethod := self selectedContext method)].
  	isNewMethod ifTrue:
+ 		[contents := self selectedMessage.
- 		[debuggerMap := nil.
- 		 contents := self selectedMessage.
  		 self contentsChanged.
  		 self pcRange].
  	self changed: #contextStackIndex.
  	self decorateButtons.
  	contextVariablesInspector object: self selectedContext.
  	((index := contextVariablesInspector fieldList indexOf: selectedContextSlotName) ~= 0
  	 and: [index ~= contextVariablesInspector selectionIndex]) ifTrue:
  		[contextVariablesInspector toggleIndex: index].
  	receiverInspector object: self receiver.
  	isNewMethod ifFalse:
  		[self changed: #contentsSelection]!




More information about the Squeak-dev mailing list