[squeak-dev] The Inbox: Compiler-fm.288.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Aug 14 02:35:56 UTC 2014


A new version of Compiler was added to project The Inbox:
http://source.squeak.org/inbox/Compiler-fm.288.mcz

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

Name: Compiler-fm.288
Author: fm
Time: 13 August 2014, 10:35:42.664 pm
UUID: 4138a85c-25c8-3147-b9b9-092e2ef26e45
Ancestors: Compiler-fm.287, Compiler-eem.287

merged with eem.287

Fix literals in decompiled method nodes, they were screwed up - they were not unique, they had wrong indices.

Fix temp names generation in decompiled methods when no temp names are provided - no check was made that the names were not clashing with instvars (and they were clashing sometimes)

Decompiler>>pushConstant: did not recognize some of the special constants

make the decompiler raise a warning if an unknown instvar is encountered - the original would just silently generate a node named 'unkown', but this obviously leads to uncompileable code

=============== Diff against Compiler-fm.287 ===============

Item was changed:
  ----- Method: Decompiler>>pushConstant: (in category 'instruction decoding') -----
  pushConstant: value
  
  	| node |
  	node := value == true ifTrue: [constTable at: 2]
  		ifFalse: [value == false ifTrue: [constTable at: 3]
  		ifFalse: [value == nil ifTrue: [constTable at: 4]
+ 		ifFalse: [value == -1 ifTrue: [constTable at: 5]
+ 		ifFalse: [value == 0 ifTrue: [constTable at: 6]
+ 		ifFalse: [value == 1 ifTrue: [constTable at: 7]
+ 		ifFalse: [value == 2 ifTrue: [constTable at: 8]
+ 		ifFalse: [constructor codeAnyLiteral: value]]]]]]].
- 		ifFalse: [constructor codeAnyLiteral: value]]].
  	stack addLast: node!

Item was changed:
  ----- Method: DecompilerConstructor>>codeAnyLitInd: (in category 'constructor') -----
  codeAnyLitInd: association
  
  	^VariableNode new
  		name: association key
  		key: association
+ 		index: ((1 to: literalValues size) detect: [:i | association literalEqual: (literalValues at: i)]) - 1
- 		index: 0
  		type: LdLitIndType!

Item was changed:
  ----- Method: DecompilerConstructor>>codeAnyLiteral: (in category 'constructor') -----
  codeAnyLiteral: value
  
  	^LiteralNode new
  		key: value
+ 		index: ((1 to: literalValues size) detect: [:i | value literalEqual: (literalValues at: i)]) - 1
- 		index: 0
  		type: LdLitType!

Item was changed:
  ----- Method: DecompilerConstructor>>codeAnySelector: (in category 'constructor') -----
  codeAnySelector: selector
  
  	^SelectorNode new
  		key: selector
+ 		index: ((1 to: literalValues size) 
+ 					detect: [:i | selector literalEqual: (literalValues at: i)]
+ 					ifNone: [^StdSelectors at: selector]) - 1
- 		index: 0
  		type: SendType!

Item was changed:
  ----- Method: Encoder>>temps:literals:class: (in category 'initialize-release') -----
  temps: tempVars literals: lits class: cl 
  	"Initialize this encoder for decompilation."
  
  	self setCue: (CompilationCue class: cl).
  	supered := false.
  	nTemps := tempVars size.
  	tempVars do: [:node | scopeTable at: node name put: node].
  	literalStream := WriteStream on: (Array new: lits size).
  	literalStream nextPutAll: lits.
  	sourceRanges := Dictionary new: 32.
+ 	globalSourceRanges := OrderedCollection new: 32.
+ 	addedSelectorAndMethodClassLiterals := true.
+ !
- 	globalSourceRanges := OrderedCollection new: 32.!

Item was changed:
  ----- Method: MethodNode>>generate:using: (in category 'code generation') -----
  generate: trailer using: aCompiledMethodClass
  	"The receiver is the root of a parse tree. Answer an instance of aCompiledMethodClass.
  	 The argument, trailer, is arbitrary but is typically either the reference to the source code
  	 that is stored with every CompiledMethod, or an encoding of the method's temporary names."
  
  	| primErrNode blkSize nLits literals stack method |
  	self generate: trailer
  		using: aCompiledMethodClass
  		ifQuick:
  			[:m |
+ 			 encoder noteBlockExtent: (0 to: 2) hasLocals: arguments.
+ 			 m	literalAt: 2 put: encoder associationForClass;
- 			  m	literalAt: 2 put: encoder associationForClass;
  				properties: properties.
+ 			 ^m].
- 			^m].
  	primErrNode := self primitiveErrorVariableName ifNotNil:
  						[encoder fixTemp: self primitiveErrorVariableName].
  	encoder supportsClosureOpcodes ifTrue:
  		[self ensureClosureAnalysisDone.
  		 encoder rootNode: self. "this is for BlockNode>>sizeCodeForClosureValue:"].
  	blkSize := (block sizeCodeForEvaluatedValue: encoder)
  				+ (primErrNode
  					ifNil: [0]
  					ifNotNil:
  						[primErrNode
  							index: arguments size + temporaries size;
  							sizeCodeForStore: encoder "The VM relies on storeIntoTemp: (129)"]).
  	method := aCompiledMethodClass
  				newBytes: blkSize
  				trailerBytes: trailer 
  				nArgs: arguments size
  				nTemps: (encoder supportsClosureOpcodes
  							ifTrue: [| locals |
  									locals := arguments,
  											  temporaries,
  											  (primErrNode
  												ifNil: [#()]
  												ifNotNil: [{primErrNode}]).
  									encoder
  										noteBlockExtent: block blockExtent
  										hasLocals: locals.
  									locals size]
  							ifFalse: [encoder maxTemp])
  				nStack: 0
  				nLits: (nLits := (literals := encoder allLiterals) size)
  				primitive: primitive.
  	nLits > 255 ifTrue:
  		[^self error: 'Too many literals referenced'].
  	1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
  	encoder streamToMethod: method.
  	stack := ParseStack new init.
  	primErrNode ifNotNil: [primErrNode emitCodeForStore: stack encoder: encoder].
  	stack position: method numTemps.
  	[block emitCodeForEvaluatedValue: stack encoder: encoder]
  		on: Error "If an attempt is made to write too much code the method will be asked"
  		do: [:ex|  "to grow, and the grow attempt will fail in CompiledMethod class>>#new:"
  			ex signalerContext sender method = (CompiledMethod class>>#new:)
  				ifTrue: [^self error: 'Compiler code size discrepancy']
  				ifFalse: [ex pass]].
  	stack position ~= (method numTemps + 1) ifTrue:
  		[^self error: 'Compiler stack discrepancy'].
  	encoder methodStreamPosition ~= (method size - trailer size) ifTrue:
  		[^self error: 'Compiler code size discrepancy'].
  	method needsFrameSize: stack size - method numTemps.
  	method properties: properties.
  	^method!



More information about the Squeak-dev mailing list