[squeak-dev] The Trunk: Compiler-eem.484.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jan 10 20:42:06 UTC 2023


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

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

Name: Compiler-eem.484
Author: eem
Time: 10 January 2023, 12:42:03.339564 pm
UUID: f98aa13d-19cf-4f6a-8bd6-31a0429c0d15
Ancestors: Compiler-eem.483

Fix an aliasing bug in the Decompiler that could cause it to enter an infinite loop decompiling conditionals. The copy used to decompile a full block must partially reinitialize to avoid aliasing lastJumpPc.

=============== Diff against Compiler-eem.483 ===============

Item was added:
+ ----- Method: Decompiler>>initializeCopy (in category 'control') -----
+ initializeCopy
+ 	lastJumpPc := lastReturnPc := exit := limit := nil.
+ 	stack := OrderedCollection new.
+ 	caseExits := OrderedCollection new.
+ 	lastJumpIfPcStack := OrderedCollection new.
+ 	!

Item was changed:
  ----- Method: Decompiler>>interpretNextInstructionFor: (in category 'private') -----
  interpretNextInstructionFor: client
+ 	| varNames |
  
+ "Change false here (& edit statementsTo:) to trace all state in Transcript, printing pcs as relative to method initialPC."
- 	| code varNames |
- 
- "Change false here will trace all state in Transcript."
  true ifTrue: [^super interpretNextInstructionFor: client].
  
  	varNames := self class allInstVarNames.
+ 	Transcript crtab. self printPCRelative: pc on: Transcript.
+ 	Transcript space; nextPut: $<.
+ 	(self method at: pc) printOn: Transcript base: 16.
+ 	Transcript nextPut: $>; cr.
- 	code := (self method at: pc) radix: 16.
- 	Transcript cr; cr; print: pc; space; nextPutAll: '<' , code, '>'.
  	(varNames indexOf: 'stack') to: varNames size do:
+ 		[:i | | name |
+ 		name := varNames at: i.
+ 		self printInstVarNamed: name
+ 			at: i
+ 			on: Transcript
+ 			asPc: (#('pc' 'lastPc' 'exit' 'caseExits'  'lastJumpPc' 'lastReturnPc' 'limit' 'lastJumpIfPcStack') includes: name)].
- 		[:i |
- 		i <= 10 ifTrue: [Transcript cr] ifFalse: [Transcript space; space].
- 		Transcript nextPutAll: (varNames at: i); nextPutAll: ': '; print: (self instVarAt: i)].
  	Transcript flush.
  	^super interpretNextInstructionFor: client!

Item was added:
+ ----- Method: Decompiler>>printInstVarNamed:at:on:asPc: (in category 'private') -----
+ printInstVarNamed: ivName at: index on: aStream asPc: isPC
+ 
+ 	| value |
+ 	aStream tab; nextPutAll: ivName; nextPutAll: ': '.
+ 	value := self instVarAt: index.
+ 	isPC
+ 		ifTrue:
+ 			[value isCollection
+ 				ifTrue: [value do: [:v| self printPCRelative: v on: aStream. aStream space]]
+ 				ifFalse: [self printPCRelative: value on: aStream. aStream space]]
+ 		ifFalse:
+ 			[value printOn: aStream].
+ 	aStream cr!

Item was added:
+ ----- Method: Decompiler>>printPCRelative:on: (in category 'private') -----
+ printPCRelative: value on: aStream
+ 	value
+ 		ifNil: [value printOn: aStream]
+ 		ifNotNil:
+ 			[value < method initialPC
+ 				ifTrue: [value printOn: aStream]
+ 				ifFalse: [aStream nextPut: $+; print: value - method initialPC]]!

Item was changed:
  ----- Method: Decompiler>>pushFullClosure:numCopied: (in category 'instruction decoding') -----
  pushFullClosure: aCompiledBlock numCopied: numCopied
  	| copiedValues |
  	copiedValues := ((1 to: numCopied) collect: [:ign| stack removeLast]) reversed.
+ 	stack addLast: (self shallowCopy initializeCopy doClosureCopy: aCompiledBlock copiedValues: copiedValues)!
- 	stack addLast: (self shallowCopy doClosureCopy: aCompiledBlock copiedValues: copiedValues)!

Item was changed:
  ----- Method: Decompiler>>statementsTo: (in category 'control') -----
  statementsTo: end
  	"Decompile the method from pc up to end and return an array of
  	expressions. If at run time this block will leave a value on the stack,
  	set hasValue to true. If the block ends with a jump or return, set exit
  	to the destination of the jump, or the end of the method; otherwise, set
  	exit = end. Leave pc = end."
  
+ 	| encoderClass blockPos stackPos localLastPC initialPC |
+ 	initialPC := pc.
- 	| encoderClass blockPos stackPos localLastPC |
  	encoderClass := method encoderClass.
  	blockPos := statements size.
  	stackPos := stack size.
  	[pc < end]
  		whileTrue:
+ 			[lastPc := localLastPC := pc.  limit := end. "for performs"
+ 			 "for logging use the first form"
+ 			 false
+ 				ifTrue: [self interpretNextInstructionFor: self]
+ 			 	ifFalse: [encoderClass interpretNextInstructionFor: self in: self]].
+ 	"If there is an additional item on the stack, it will be the value of this block."
- 			[lastPc := localLastPC := pc.  limit := end.  "for performs"
- 			 "If you want instrumentation replace the following statement with this one,
- 			  and edit the implementation:
- 				self interpretNextInstructionFor: self"
- 			encoderClass interpretNextInstructionFor: self in: self].
- 	"If there is an additional item on the stack, it will be the value
- 	of this block."
  	(hasValue := stack size > stackPos)
  		ifTrue:
  			[statements addLast: stack removeLast].
  	lastJumpPc = lastPc ifFalse: [exit := pc].
  	^self popTo: blockPos!



More information about the Squeak-dev mailing list