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

commits at source.squeak.org commits at source.squeak.org
Wed Jan 3 01:51:31 UTC 2018


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

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

Name: Compiler-eem.361
Author: eem
Time: 2 January 2018, 5:47:32.911397 pm
UUID: 5fe8c44c-f098-43cc-b689-1bf367f5ed8e
Ancestors: Compiler-eem.360

First cut of FullBlockClosure support in the compiler.  If the encoder answers true to supportsFullBlocks then non-optimized blocks are compiled to their own CompiledBlock instance.

Reduce the use of code in a few ParseNode subclasses.  Use the more generic isSpecialLiteralForPush:  [todo: use SistaV1's BlockReturn nil].

[And for the curious here's a way to exercise the compiler
(self systemNavigation allMethodsSelect: [:m| m scanFor: 143]) do:
	[:mr|
	(Parser new
	encoderClass: EncoderForSistaV1;
		parse: mr sourceString
		class: mr actualClass) generate]

=============== Diff against Compiler-eem.360 ===============

Item was changed:
  ----- Method: BlockNode>>constructClosureCreationNode: (in category 'code generation') -----
  constructClosureCreationNode: encoder
  	copiedValues := self computeCopiedValues: encoder rootNode.
+ 	^self ensureClosureCreationNode: encoder!
- 	^self ensureClosureCreationNode!

Item was added:
+ ----- Method: BlockNode>>createBlockLiteral: (in category 'code generation (closures)') -----
+ createBlockLiteral: encoder
+ 	^self
+ 		reindexingLocalsDo:
+ 			[encoder reindexingLiteralsDo:
+ 				[encoder copyWithNewLiterals
+ 					generateBlockMethodOfClass: CompiledBlock
+ 					trailer: CompiledMethodTrailer empty
+ 					from: self]]
+ 		encoder: encoder!

Item was added:
+ ----- Method: BlockNode>>emitCodeForEvaluatedFullClosureValue:encoder: (in category 'code generation') -----
+ emitCodeForEvaluatedFullClosureValue: stack encoder: encoder
+ 	| position |
+ 	position := stack position.
+ 	self emitCodeExceptLast: stack encoder: encoder.
+ 	statements last emitCodeForBlockValue: stack encoder: encoder.
+ 	self returns ifFalse:
+ 		[encoder genReturnTopToCaller.
+ 		 pc := encoder methodStreamPosition].
+ 	self assert: stack position - 1 = position!

Item was added:
+ ----- Method: BlockNode>>emitCodeForFullBlockValue:encoder: (in category 'code generation (closures)') -----
+ emitCodeForFullBlockValue: stack encoder: encoder
+ 	copiedValues do:
+ 		[:copiedValue| copiedValue emitCodeForValue: stack encoder: encoder].
+ 	encoder
+ 		genPushFullClosure: closureCreationNode index
+ 		numCopied: copiedValues size.
+ 	stack
+ 		pop: copiedValues size;
+ 		push: 1!

Item was changed:
  ----- Method: BlockNode>>emitCodeForValue:encoder: (in category 'code generation') -----
  emitCodeForValue: stack encoder: encoder
+ 	encoder supportsFullBlocks ifTrue:
+ 		[^self emitCodeForFullBlockValue: stack encoder: encoder].
  	copiedValues do:
  		[:copiedValue| copiedValue emitCodeForValue: stack encoder: encoder].
  	closureCreationNode pc: encoder methodStreamPosition + 1.
  	encoder
  		genPushClosureCopyNumCopiedValues: copiedValues size
  		numArgs: arguments size
  		jumpSize: size.
  	stack
  		pop: copiedValues size;
  		push: 1.
  	"Emit the body of the block"
  	self emitCodeForEvaluatedClosureValue: stack encoder: encoder!

Item was removed:
- ----- Method: BlockNode>>ensureClosureCreationNode (in category 'accessing') -----
- ensureClosureCreationNode
- 	closureCreationNode ifNil:
- 		[closureCreationNode := LeafNode new
- 									key: #closureCreationNode
- 									code: nil].
- 	^closureCreationNode!

Item was added:
+ ----- Method: BlockNode>>ensureClosureCreationNode: (in category 'accessing') -----
+ ensureClosureCreationNode: encoder
+ 	closureCreationNode ifNil:
+ 		[closureCreationNode := LiteralNode new
+ 									key: #closureCreationNode
+ 									code: (encoder supportsFullBlocks ifTrue: [LdLitType negated])].
+ 	^closureCreationNode!

Item was added:
+ ----- Method: BlockNode>>localsNodes (in category 'accessing') -----
+ localsNodes
+ 	"Answer the correctly ordered sequence of local nodes (arguments and temporaries) in the receiver."
+ 	^arguments asArray, copiedValues, temporaries!

Item was changed:
  ----- Method: BlockNode>>noteSourceRangeStart:end:encoder: (in category 'initialize-release') -----
  noteSourceRangeStart: start end: end encoder: encoder
  	"Note two source ranges for this node.  One is for the debugger
  	 and is of the last expression, the result of the block.  One is for
  	 source analysis and is for the entire block."
  	encoder
  		noteSourceRange: (start to: end)
+ 		forNode: (self ensureClosureCreationNode: encoder).
- 		forNode: self ensureClosureCreationNode.
  	startOfLastStatement
  		ifNil:
  			[encoder
  				noteSourceRange: (start to: end)
  				forNode: self]
  		ifNotNil:
  			[encoder
  				noteSourceRange: (startOfLastStatement to: end - 1)
  				forNode: self]!

Item was added:
+ ----- Method: BlockNode>>sizeCodeForEvaluatedFullClosureValue: (in category 'code generation') -----
+ sizeCodeForEvaluatedFullClosureValue: encoder
+ 	"The closure value primitives push the arguments and the copied values.
+ 	 The compiler guarantees that any copied values come before all local temps.
+ 	 So on full closure activation we need do nothing."
+ 	^(self sizeCodeForEvaluatedValue: encoder)
+ 	+ (self returns ifTrue: [0] ifFalse: [encoder sizeReturnTopToCaller])!

Item was changed:
  ----- Method: BlockNode>>sizeCodeForValue: (in category 'code generation') -----
  sizeCodeForValue: encoder
  	"Compute the size for the creation of the block and its code."
  	copiedValues := self computeCopiedValues: encoder rootNode.
+ 	self ensureClosureCreationNode: encoder.
+ 	encoder supportsFullBlocks ifTrue:
+ 		[^(copiedValues inject: 0 into: [:sum :node| sum + (node sizeCodeForValue: encoder)])
+ 		 + (encoder
+ 				sizePushFullClosure:
+ 					(closureCreationNode
+ 						key: (self createBlockLiteral: encoder);
+ 						reserve: encoder;
+ 						index)
+ 				numCopied: copiedValues size)].
- 	self ensureClosureCreationNode.
  	"Remember size of body for emit time so we know the size of the jump around it."
  	size := self sizeCodeForEvaluatedClosureValue: encoder.
  	^(copiedValues inject: 0 into: [:sum :node| sum + (node sizeCodeForValue: encoder)])
  	  + (encoder sizePushClosureCopyNumCopiedValues: copiedValues size numArgs: arguments size jumpSize: size)
  	  + size!

Item was added:
+ ----- Method: BytecodeEncoder>>copyWithNewLiterals (in category 'full blocks') -----
+ copyWithNewLiterals
+ 	^self shallowCopy resetLiteralStreamForFullBlock!

Item was added:
+ ----- Method: BytecodeEncoder>>generateBlockMethodOfClass:trailer:from: (in category 'method encoding') -----
+ generateBlockMethodOfClass: aCompiledBlockClass trailer: trailer from: blockNode
+ 	"Generate a CompiledBlock for the block whose parse tree is blockNode."
+ 
+ 	"The closure analysis should already have been done."
+ 	| blkSize header literals locals method nLits stack |
+ 	self assert: blockNode blockExtent notNil.
+ 	self assert: rootNode notNil.
+ 	blkSize := blockNode sizeCodeForEvaluatedFullClosureValue: self.
+ 	locals := blockNode localsNodes.
+ 	self noteBlockExtent: blockNode blockExtent hasLocals: locals.
+ 	header := self computeMethodHeaderForNumArgs: blockNode arguments size
+ 					numTemps: locals size
+ 					numLits: (nLits := (literals := self allLiterals) size)
+ 					primitive: 0.
+ 	method := trailer
+ 					createMethod: blkSize
+ 					class: aCompiledBlockClass
+ 					header: header.
+ 	1 to: nLits do:
+ 		[:lit |
+ 		(method literalAt: lit put: (literals at: lit)) isCompiledCode ifTrue:
+ 			[(literals at: lit) outerCode: method]].
+ 	self streamToMethod: method.
+ 	stack := ParseStack new init.
+ 	stack position: method numTemps.
+ 	[blockNode emitCodeForEvaluatedFullClosureValue: stack encoder: self]
+ 		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 CompiledCode class>>#newMethodViaNewError"
+ 			ex signalerContext sender method = (CompiledCode class>>#newMethodViaNewError)
+ 				ifTrue: [^self error: 'Compiler code size discrepancy']
+ 				ifFalse: [ex pass]].
+ 	stack position ~= (method numTemps + 1) ifTrue:
+ 		[^self error: 'Compiler stack discrepancy'].
+ 	self methodStreamPosition ~= (method size - trailer size) ifTrue:
+ 		[^self error: 'Compiler code size discrepancy'].
+ 	method needsFrameSize: stack size - method numTemps.
+ 	^method!

Item was changed:
  ----- Method: BytecodeEncoder>>generateMethodOfClass:trailer:from: (in category 'method encoding') -----
  generateMethodOfClass: aCompiledMethodClass trailer: trailer from: methodNode
  	"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 locals literals header method stack |
  	primErrNode := methodNode primitiveErrorVariableName ifNotNil:
  						[self fixTemp: methodNode primitiveErrorVariableName].
  	methodNode ensureClosureAnalysisDone.
  	self rootNode: methodNode. "this is for BlockNode>>sizeCodeForClosureValue:"
  	blkSize := (methodNode block sizeCodeForEvaluatedValue: self)
  				+ (methodNode primitive > 0
  					ifTrue: [self sizeCallPrimitive: methodNode primitive]
  					ifFalse: [0])
  				+ (primErrNode
  					ifNil: [0]
  					ifNotNil:
  						[primErrNode
  							index: methodNode arguments size + methodNode temporaries size;
  							sizeCodeForStore: self "The VM relies on storeIntoTemp: (129)"]).
  	locals := methodNode arguments, methodNode temporaries, (primErrNode ifNil: [#()] ifNotNil: [{primErrNode}]).
  	self noteBlockExtent: methodNode block blockExtent hasLocals: locals.
  	header := self computeMethodHeaderForNumArgs: methodNode arguments size
  					numTemps: locals size
  					numLits: (nLits := (literals := self allLiterals) size)
  					primitive: methodNode primitive.
  	method := trailer
  					createMethod: blkSize
  					class: aCompiledMethodClass
  					header: header.
+ 	1 to: nLits do:
+ 		[:lit |
+ 		(method literalAt: lit put: (literals at: lit)) isCompiledCode ifTrue:
+ 			[(literals at: lit) outerCode: method]].
- 	1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
  	self streamToMethod: method.
  	stack := ParseStack new init.
  	methodNode primitive > 0 ifTrue:
  		[self genCallPrimitive: methodNode primitive].
  	primErrNode ifNotNil:
  		[primErrNode emitCodeForStore: stack encoder: self].
  	stack position: method numTemps.
  	[methodNode block emitCodeForEvaluatedValue: stack encoder: self]
  		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 CompiledCode class>>#newMethodViaNewError"
+ 			ex signalerContext sender method = (CompiledCode class>>#newMethodViaNewError)
- 		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'].
  	self methodStreamPosition ~= (method size - trailer size) ifTrue:
  		[^self error: 'Compiler code size discrepancy'].
  	method needsFrameSize: stack size - method numTemps.
  	^method!

Item was changed:
  ----- Method: BytecodeEncoder>>if:isSpecialLiteralForPush: (in category 'special literal encodings') -----
  if: code isSpecialLiteralForPush: aBlock
  	"If code is that of a special literal for push then evaluate aBlock with the special literal
+ 	 The special literals for push are at least nil true false which have special encodings
- 	 The special literals for push are nil true false -1 0 1 & 2 which have special encodings
  	 in the blue book bytecode set.  Answer whether it was a special literal."
+ 	^(code between: LdTrue and: LdNil)
+ 	    and: [aBlock value: (#(true false nil) at: code - LdSelf).
- 	^(code between: LdTrue and: LdNil + 4)
- 	    and: [aBlock value: (#(true false nil -1 0 1 2) at: code - LdSelf).
  			true]!

Item was added:
+ ----- Method: BytecodeEncoder>>reindexingLiteralsDo: (in category 'code generation') -----
+ reindexingLiteralsDo: aBlock
+ 	| savedLiterals |
+ 	savedLiterals := PluggableDictionary new equalBlock: litSet equalBlock.
+ 	litSet associationsDo:
+ 		[:assoc|
+ 		savedLiterals at: assoc key put: assoc value shallowCopy].
+ 	litIndSet associationsDo:
+ 		[:assoc|
+ 		savedLiterals at: assoc key put: assoc value shallowCopy].
+ 	^[aBlock value]
+ 		ensure:
+ 			[litSet associationsDo:
+ 				[:assoc|
+ 				assoc value resetFromCopy: (savedLiterals at: assoc key)].
+ 			 litIndSet associationsDo:
+ 				[:assoc|
+ 				assoc value resetFromCopy: (savedLiterals at: assoc key)]]!

Item was added:
+ ----- Method: BytecodeEncoder>>resetLiteralStreamForFullBlock (in category 'code generation') -----
+ resetLiteralStreamForFullBlock
+ 	literalStream := WriteStream on: (Array new: 32).
+ 	addedSelectorAndMethodClassLiterals := false.
+ 	optimizedSelectors := Set new!

Item was added:
+ ----- Method: BytecodeEncoder>>sizePushFullClosure:numCopied: (in category 'opcode sizing') -----
+ sizePushFullClosure: compiledBlockLiteralIndex numCopied: numCopied
+ 	^self sizeOpcodeSelector: #genPushFullClosure:numCopied:
+ 		withArguments: {compiledBlockLiteralIndex. numCopied}!

Item was added:
+ ----- Method: BytecodeEncoder>>sizePushFullClosure:numCopied:receiverOnStack:ignoreOuterContext: (in category 'opcode sizing') -----
+ sizePushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: receiverOnStack ignoreOuterContext: ignoreOuterContext
+ 	^self sizeOpcodeSelector: #genPushFullClosure:numCopied:receiverOnStack:ignoreOuterContext
+ 		withArguments: {compiledBlockLiteralIndex. numCopied. receiverOnStack. ignoreOuterContext}!

Item was added:
+ ----- Method: Decompiler>>doClosureCopy:copiedValues: (in category 'control') -----
+ doClosureCopy: aCompiledBlock copiedValues: blockCopiedValues
+ 	| savedTemps savedTempVarCount savedNumLocalTemps savedMethod savedPC
+ 	  blockArgs blockTemps blockTempsOffset block |
+ 	savedTemps := tempVars.
+ 	savedTempVarCount := tempVarCount.
+ 	savedNumLocalTemps := numLocalTemps.
+ 	numLocalTemps := aCompiledBlock numTemps - aCompiledBlock numArgs - blockCopiedValues size.
+ 	blockTempsOffset := aCompiledBlock numArgs + blockCopiedValues size.
+ 	(blockStartsToTempVars notNil "implies we were intialized with temp names."
+ 	 and: [blockStartsToTempVars includesKey: pc])
+ 		ifTrue:
+ 			[tempVars := blockStartsToTempVars at: pc]
+ 		ifFalse:
+ 			[blockArgs := (1 to: aCompiledBlock numArgs) collect:
+ 							[:i| (constructor
+ 									codeTemp: i - 1
+ 									named: 't', (tempVarCount + i) printString)
+ 								  beBlockArg].
+ 			blockTemps := (1 to: numLocalTemps) collect:
+ 							[:i| constructor
+ 									codeTemp: i + blockTempsOffset - 1
+ 									named: 't', (tempVarCount + i + aCompiledBlock numArgs) printString].
+ 			tempVars := blockArgs, blockCopiedValues, blockTemps].
+ 	tempVarCount := tempVarCount + aCompiledBlock numArgs + numLocalTemps.
+ 	savedMethod := self method. savedPC := pc.
+ 	super method: aCompiledBlock pc: aCompiledBlock initialPC.
+ 	block := [self blockTo: aCompiledBlock endPC]
+ 				ensure: [super method: savedMethod pc: savedPC].
+ 	stack addLast: ((constructor
+ 						codeArguments: (tempVars copyFrom: 1 to: aCompiledBlock numArgs)
+ 						temps: (tempVars copyFrom: blockTempsOffset + 1 to: blockTempsOffset + numLocalTemps)
+ 						block: block)
+ 							pc: pc;
+ 							yourself).
+ 	tempVars := savedTemps.
+ 	tempVarCount := savedTempVarCount.
+ 	numLocalTemps := savedNumLocalTemps!

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

Item was removed:
- ----- Method: Encoder>>bindAndJuggle: (in category 'temps') -----
- bindAndJuggle: name
- 
- 	| node nodes first thisCode |
- 	node := self reallyBind: name.
- 
- 	"Declared temps must precede block temps for decompiler and debugger to work right"
- 	nodes := self tempNodes.
- 	(first := nodes findFirst: [:n | n scope > 0]) > 0 ifTrue:
- 		[node == nodes last ifFalse: [self error: 'logic error'].
- 		thisCode := (nodes at: first) code.
- 		first to: nodes size - 1 do:
- 			[:i | (nodes at: i) key: (nodes at: i) key
- 							code: (nodes at: i+1) code].
- 		nodes last key: nodes last key code: thisCode].
- 	
- 	^ node!

Item was changed:
  ----- Method: Encoder>>fixTemp: (in category 'temps') -----
  fixTemp: name
  	| node |
  	node := scopeTable at: name ifAbsent: [].
+ 	(node isTemp and: [node isIndirectTempVector not]) ifFalse:
- 	node class ~~ TempVariableNode ifTrue:
  		[self error: 'can only fix a floating temp var'].
  	node index: nTemps.
  	nTemps := nTemps + 1.
  	^node!

Item was changed:
  ----- Method: Encoder>>floatTemp: (in category 'temps') -----
  floatTemp: node
+ 	(node == (scopeTable at: node name ifAbsent: [])
+ 	 and: [node isTemp
+ 	 and: [node index = (nTemps - 1)]]) ifFalse:
- 	(node ~~ (scopeTable at: node name ifAbsent: [])
- 	or: [node class ~~ TempVariableNode
- 	or: [node code ~= (node code: nTemps - 1 type: LdTempType)]]) ifTrue:
  		[self error: 'can only float the last allocated temp var'].
  	nTemps := nTemps - 1!

Item was changed:
  ----- Method: Encoder>>tempNodes (in category 'results') -----
  tempNodes
  
  	| tempNodes |
  	tempNodes := OrderedCollection new.
  	scopeTable associationsDo:
  		[:assn |
  		assn value isArray
  			ifTrue: [assn value do: [:temp| tempNodes add: temp]]
  			ifFalse: [assn value isTemp ifTrue: [tempNodes add: assn value]]].
+ 	^tempNodes sort: [:n1 :n2 | n1 index <= n2 index]!
- 	^tempNodes sort: [:n1 :n2 | n1 code <= n2 code]!

Item was changed:
  ----- Method: EncoderForSistaV1>>genPushSpecialLiteral: (in category 'bytecode generation') -----
  genPushSpecialLiteral: aLiteral
  	"77			01001101			Push true
  	 78			01001110			Push false
  	 79			01001111			Push nil
  	 80			01010000			Push 0
  	 81			01010001			Push 1
+ 	 232		11101000	iiiiiiii		Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)
+ 	 233		11101001	i i i i i i i i	Push Character #iiiiiiii (+ Extend B * 256)"
- 	 232		11101000	iiiiiiii		Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
  	| index |
  	aLiteral isInteger ifTrue:
  		[aLiteral == 0 ifTrue:
  			[stream nextPut: 80.
  			 ^self].
  		 aLiteral == 1 ifTrue:
  			[stream nextPut: 81.
  			 ^self].
  		 ^self genPushInteger: aLiteral].
+ 	aLiteral isCharacter ifTrue:
+ 		[^self genPushCharacter: aLiteral].
  	index := #(true false nil)
  					indexOf: aLiteral
  					ifAbsent: [^self error: 'push special literal: ', aLiteral printString,  ' is not one of true false nil'].
  	stream nextPut: 76 + index!

Item was changed:
  ----- Method: EncoderForSistaV1>>isSpecialLiteralForPush: (in category 'special literal encodings') -----
  isSpecialLiteralForPush: literal
+ 	^literal isInteger
+ 		ifFalse:
+ 			[literal isCharacter
+ 				ifFalse:
+ 					[false == literal
+ 					 or: [true == literal
+ 					 or: [nil == literal]]]
+ 				ifTrue:
+ 					[literal asInteger between: 0 and: 65535]]
+ 	 	ifTrue:
+ 			[literal between: -32768 and: 32767]!
- 	^literal == false
- 	  or: [literal == true
- 	  or: [literal == nil
- 	  or: [(literal isInteger and: [literal between: -32768 and: 32767])
- 	  or: [(literal isCharacter and: [literal asInteger between: 0 and: 65535])]]]]!

Item was added:
+ ----- Method: EncoderForSistaV1>>isSpecialLiteralForReturn: (in category 'special literal encodings') -----
+ isSpecialLiteralForReturn: literal
+ 	^literal == false
+ 	  or: [literal == true
+ 	  or: [literal == nil]]!

Item was added:
+ ----- Method: EncoderForV3>>if:isSpecialLiteralForPush: (in category 'special literal encodings') -----
+ if: code isSpecialLiteralForPush: aBlock
+ 	"If code is that of a special literal for push then evaluate aBlock with the special literal
+ 	 The special literals for push are nil true false -1 0 1 & 2 which have special encodings
+ 	 in the blue book bytecode set.  Answer whether it was a special literal."
+ 	^(code between: LdTrue and: LdNil + 4)
+ 	    and: [aBlock value: (#(true false nil -1 0 1 2) at: code - LdSelf).
+ 			true]!

Item was added:
+ ----- Method: EncoderForV3>>if:isSpecialLiteralForReturn: (in category 'special literal encodings') -----
+ if: code isSpecialLiteralForReturn: aBlock
+ 	"If code is that of a special literal for return then evaluate aBlock with the special literal.
+ 	 The special literals for return are nil true false which have special encodings
+ 	 in the blue book bytecode set.  Answer whether it was a special literal."
+ 	^(code between: LdTrue and: LdNil)
+ 	   and: [aBlock value: (#(true false nil) at: code - LdSelf).
+ 			true]!

Item was added:
+ ----- Method: EncoderForV3>>isSpecialLiteralForPush: (in category 'special literal encodings') -----
+ isSpecialLiteralForPush: literal
+ 	^literal isInteger
+ 		ifFalse:
+ 			[false == literal
+ 			 or: [true == literal
+ 			 or: [nil == literal]]]
+ 		ifTrue: [literal between: -1 and: 2]!

Item was added:
+ ----- Method: EncoderForV3>>isSpecialLiteralForReturn: (in category 'special literal encodings') -----
+ isSpecialLiteralForReturn: literal
+ 	^literal == false
+ 	  or: [literal == true
+ 	  or: [literal == nil]]!

Item was added:
+ ----- Method: FieldNode>>resetFromCopy: (in category 'code generation') -----
+ resetFromCopy: aFieldNode
+ 	"Reset the state of the recever to match that of the argument.
+ 	 This is used to reset nodes that may have been repurposed
+ 	 while generatig the compiled method for a full block."
+ 
+ 	self assert: (fieldDef == aFieldNode fieldDef
+ 				and: [rcvrNode == (aFieldNode instVarNamed: 'rcvrNode')
+ 				and: [readNode == (aFieldNode instVarNamed: 'readNode')
+ 				and: [writeNode == (aFieldNode instVarNamed: 'writeNode')]]]).
+ 	super resetFromCopy: aFieldNode!

Item was added:
+ ----- Method: LeafNode>>index (in category 'accessing') -----
+ index
+ 	"Answer the index of the receiver, which has various uses depending on the class of the receiver."
+ 
+ 	^index!

Item was added:
+ ----- Method: LeafNode>>resetFromCopy: (in category 'code generation') -----
+ resetFromCopy: aLeafNode
+ 	"Reset the state of the recever to match that of the argument.
+ 	 This is used to reset nodes that may have been repurposed
+ 	 while generatig the compiled method for a full block."
+ 
+ 	self assert: key == aLeafNode key.
+ 	code := aLeafNode code.
+ 	index := aLeafNode index!

Item was changed:
  ----- Method: LiteralNode>>emitCodeForValue:encoder: (in category 'code generation') -----
  emitCodeForValue: stack encoder: encoder
  	stack push: 1.
+ 	(encoder isSpecialLiteralForPush: key)
+ 		ifTrue: [encoder genPushSpecialLiteral: key]
+ 		ifFalse: [encoder genPushLiteral: index]!
- 	(encoder
- 		if: code
- 		isSpecialLiteralForPush:
- 			[:specialLiteral|
- 			 encoder genPushSpecialLiteral: specialLiteral])
- 		ifFalse:
- 			[encoder genPushLiteral: index]!

Item was changed:
  ----- Method: LiteralNode>>sizeCodeForValue: (in category 'code generation') -----
  sizeCodeForValue: encoder
  	self reserve: encoder.
+ 	^(encoder isSpecialLiteralForPush: key)
+ 		ifTrue: [encoder sizePushSpecialLiteral: key]
+ 		ifFalse: [encoder sizePushLiteral: index]!
- 	(encoder
- 		if: code
- 		isSpecialLiteralForPush:
- 			[:specialLiteral|
- 			 ^encoder sizePushSpecialLiteral: specialLiteral])
- 		ifFalse:
- 			[^encoder sizePushLiteral: index]!

Item was added:
+ ----- Method: LiteralVariableNode>>resetFromCopy: (in category 'code generation') -----
+ resetFromCopy: aLiteralVariableNode
+ 	"Reset the state of the recever to match that of the argument.
+ 	 This is used to reset nodes that may have been repurposed
+ 	 while generatig the compiled method for a full block."
+ 
+ 	self assert: (readNode == (aLiteralVariableNode instVarNamed: 'readNode')
+ 				and: [writeNode == (aLiteralVariableNode instVarNamed: 'writeNode')]).
+ 	super resetFromCopy: aLiteralVariableNode!

Item was added:
+ ----- Method: TempVariableNode>>resetFromCopy: (in category 'code generation') -----
+ resetFromCopy: aFieldNode
+ 	"Reset the state of the recever to match that of the argument.
+ 	 This is used to reset nodes that may have been repurposed
+ 	 while generatig the compiled method for a full block.
+ 	 Temps are managed via the reindexingLocalsDo:encoder: route,
+ 	 not via reindexingLiteralsDo:."
+ 	self shouldNotImplement!

Item was changed:
  ----- Method: VariableNode>>emitCodeForValue:encoder: (in category 'code generation') -----
  emitCodeForValue: stack encoder: encoder
  	stack push: 1.
  	encoder
  		if: code
  		isSpecialLiteralForPush:
  			[:specialLiteral|
  			 ^encoder genPushSpecialLiteral: specialLiteral].
  	(code = LdSelf or: [code = LdSuper]) ifTrue:
  		[^encoder genPushReceiver].
  	code = LdThisContext ifTrue:
  		[^encoder genPushThisContext].
+ 	self error: 'internal compiler error; should not happen'!
- 	self flag: 'probably superfluous'.
- 	self halt.
- 	^encoder genPushInstVar: index!

Item was added:
+ ----- Method: VariableNode>>resetFromCopy: (in category 'code generation') -----
+ resetFromCopy: aVariableNode
+ 	"Reset the state of the recever to match that of the argument.
+ 	 This is used to reset nodes that may have been repurposed
+ 	 while generatig the compiled method for a full block."
+ 
+ 	self assert: name == aVariableNode name.
+ 	super resetFromCopy: aVariableNode!

Item was changed:
  ----- Method: VariableNode>>sizeCodeForValue: (in category 'code generation') -----
  sizeCodeForValue: encoder
  	self reserve: encoder.
  	encoder
  		if: code
  		isSpecialLiteralForPush:
  			[:specialLiteral| "i.e. the pseudo-variables nil true & false"
  			 ^encoder sizePushSpecialLiteral: specialLiteral].
  	(code = LdSelf or: [code = LdSuper]) ifTrue:
  		[^encoder sizePushReceiver].
  	code = LdThisContext ifTrue:
  		[^encoder sizePushThisContext].
+ 	self error: 'internal compiler error; should not happen'!
- 	self flag: 'probably superfluous'.
- 	self halt.
- 	^encoder sizePushInstVar: index!



More information about the Squeak-dev mailing list