[squeak-dev] The Trunk: Kernel-fbs.783.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jul 6 13:39:02 UTC 2013


Frank Shearar uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-fbs.783.mcz

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

Name: Kernel-fbs.783
Author: fbs
Time: 6 July 2013, 2:36:43.813 pm
UUID: b1d6f27c-91e2-8c4a-ae42-b0b2f25b280b
Ancestors: Kernel-fbs.782

Debugger support methods belong in Tools-Debugger.

=============== Diff against Kernel-fbs.782 ===============

Item was removed:
- ----- Method: CompiledMethod>>abstractPCForConcretePC: (in category 'debugger support') -----
- abstractPCForConcretePC: concretePC
- 	"Answer the abstractPC matching concretePC."
- 
- 	| abstractPC scanner client |
- 	self flag: 'belongs in DebuggerMethodMap?'.
- 	abstractPC := 1.
- 	scanner := InstructionStream on: self.
- 	client := InstructionClient new.
- 	[(scanner atEnd
- 	  or: [scanner pc >= concretePC]) ifTrue:
- 		[^abstractPC].
- 	 abstractPC := abstractPC + 1.
- 	 scanner interpretNextInstructionFor: client] repeat!

Item was removed:
- ----- Method: CompiledMethod>>blockExtentsInto:from:to:scanner:numberer: (in category 'debugger support') -----
- blockExtentsInto: aDictionary from: initialPC to: endPC scanner: scanner numberer: numbererBlock
- 	"Support routine for startpcsToBlockExtents"
- 	| extentStart blockSizeOrLocator |
- 	self flag: 'belongs in DebuggerMethodMap'.
- 	extentStart := numbererBlock value.
- 	[scanner pc <= endPC] whileTrue:
- 		[blockSizeOrLocator := scanner interpretNextInstructionFor: BlockStartLocator new.
- 		 blockSizeOrLocator isInteger ifTrue:
- 			[self
- 				blockExtentsInto: aDictionary
- 				from: scanner pc
- 				to: scanner pc + blockSizeOrLocator - 1
- 				scanner: scanner
- 				numberer: numbererBlock]].
- 	aDictionary at: initialPC put: (extentStart to: numbererBlock value).
- 	^aDictionary!

Item was removed:
- ----- Method: CompiledMethod>>blockExtentsToTempsMap (in category '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 startpcsToBlockExtents associations asSortedCollection:
- 										[:a1 :a2| a1 key < a2 key]) collect:
- 									[:assoc| assoc value])
- 			toSchematicTemps: self tempNamesString]!

Item was removed:
- ----- Method: CompiledMethod>>debuggerMap (in category 'debugger support') -----
- debuggerMap
- 	^DebuggerMethodMap forMethod: self!

Item was removed:
- ----- Method: CompiledMethod>>mapFromBlockKeys:toSchematicTemps: (in category '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 removed:
- ----- Method: CompiledMethod>>pcPreviousTo: (in category 'debugger support') -----
- pcPreviousTo: pc
- 	| scanner client prevPc |
- 	self flag: 'belongs in DebuggerMethodMap?'.
- 	pc > self endPC ifTrue: [^self endPC].
- 	scanner := InstructionStream on: self.
- 	client := InstructionClient new.
- 	[scanner pc < pc] whileTrue:
- 		[prevPc := scanner pc.
- 		 scanner interpretNextInstructionFor: client].
- 	^prevPc!

Item was removed:
- ----- Method: CompiledMethod>>startpcsToBlockExtents (in category 'debugger support') -----
- startpcsToBlockExtents
- 	"Answer a Dictionary of startpc to Interval of blockExtent, using the
- 	 identical numbering scheme described in and orchestrated by
- 	 BlockNode>>analyseArguments:temporaries:rootNode:.  This is
- 	 used in part to find the temp names for any block in a method, as
- 	 needed by the debugger.  The other half is to recompile the method,
- 	 obtaining the temp names for each block extent.  By indirecting through
- 	 the blockExtent instead of using the startpc directly we decouple the
- 	 debugger's access to temp names from the exact bytecode; insulating
- 	 debugging from minor changes in the compiler (e.g. changes in literal
- 	 pooling, adding prefix bytecodes, adding inst vars to CompiledMethod
- 	 in literals towards the end of the literal frame, etc).  If the recompilation
- 	 doesn't produce exactly the same bytecode at exactly the same offset
- 	 no matter; the blockExtents will be the same."
- 	| index |
- 	self flag: 'belongs in DebuggerMethodMap'.
- 	index := 0.
- 	^self
- 		blockExtentsInto: Dictionary new
- 		from: self initialPC
- 		to: self endPC
- 		scanner: (InstructionStream on: self)
- 		numberer: [| value | value := index. index := index + 2. value]!

Item was removed:
- ----- Method: CompiledMethod>>tempsSubSequenceFrom: (in category 'debugger support') -----
- tempsSubSequenceFrom: tempNamesStream
- 	^Array streamContents:
- 		[:tsss|
- 		[tempNamesStream skipSeparators.
- 		 tempNamesStream atEnd
- 		 or: ['[]()' includes: tempNamesStream peek]] whileFalse:
- 			[tsss nextPut: (String streamContents:
- 							[:s|
- 							[s nextPut: tempNamesStream next.
- 							 tempNamesStream peek
- 								ifNil: [true]
- 								ifNotNil: [:peek| ' []()' includes: peek]] whileFalse])]]
- 
- 	"thisContext method tempsSubSequenceFrom: 'les temps perdu(sont n''est pas la)' readStream"
- 	"thisContext method tempsSubSequenceFrom: ('les temps perdu(sont n''est pas la)' readStream skipTo: $(; yourself)"!



More information about the Squeak-dev mailing list