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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 6 04:45:26 UTC 2014


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

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

Name: Compiler-eem.286
Author: eem
Time: 5 August 2014, 9:44:57.105 pm
UUID: 34f9ea24-6e5a-4bb3-9e9f-0f59fb8c93cf
Ancestors: Compiler-eem.285

Provide the selector scanning support InstructionStream
needs to make selectorToSendOrSelf multiple bytecode set
capable.

Provide the method generators so that methods can be
generated with the two different header formats.

Provide a class comment for SpecialSelectorNode.

=============== Diff against Compiler-eem.285 ===============

Item was added:
+ ----- Method: BytecodeEncoder class>>selectorToSendOrItselfFor:in:at: (in category 'instruction stream support') -----
+ selectorToSendOrItselfFor: anInstructionStream in: method at: pc
+ 	"If anInstructionStream is at a send bytecode then answer the send's selector,
+ 	 otherwise answer anInstructionStream itself.  The rationale for answering
+ 	 anInstructionStream instead of, say, nil, is that potentially any existing object
+ 	 can be used as a selector, but since anInstructionStream postdates the method,
+ 	 it can't be one of them."
+ 
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: BytecodeEncoder>>computeMethodHeaderForNumArgs:numTemps:numLits:primitive: (in category 'method generation') -----
+ computeMethodHeaderForNumArgs: numArgs numTemps: numTemps numLits: numLits primitive: primitiveIndex
+ 	"Compute the compiled method header that encodes the arguments
+ 	 in the receiver's header format (see CompiledMehtod's class comment)."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: BytecodeEncoder>>generateMethodOfClass:trailer:from: (in category 'method generation') -----
+ generateMethodOfClass: aCompiledMethodClass trailer: trailer from: methodNode
+ 	"methodNode is the root of a parse tree. Answer an instance of aCompiledMethodClass
+ 	 in the receiver's bytecode set and using the receiver's method header format.
+ 	 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."
+ 
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: EncoderForV3 class>>selectorToSendOrItselfFor:in:at: (in category 'instruction stream support') -----
+ selectorToSendOrItselfFor: anInstructionStream in: method at: pc
+ 	"If anInstructionStream is at a send bytecode then answer the send's selector,
+ 	 otherwise answer anInstructionStream itself.  The rationale for answering
+ 	 anInstructionStream instead of, say, nil, is that potentially any existing object
+ 	 can be used as a selector, but since anInstructionStream postdates the method,
+ 	 it can't be one of them."
+ 
+ 	| byte byte2 |
+ 	byte := method at: pc.
+ 	byte < 131 ifTrue: [^anInstructionStream].
+ 	byte >= 176
+ 		ifTrue: 
+ 			["special byte or short send"
+ 			byte >= 208
+ 				ifTrue: [^method literalAt: (byte bitAnd: 15) + 1]
+ 				ifFalse: [^Smalltalk specialSelectorAt: byte - 176 + 1]]
+ 		ifFalse: 
+ 			[byte <= 134 ifTrue: 
+ 				[byte2 := method at: pc + 1.
+ 				 byte = 131 ifTrue: [^method literalAt: byte2 \\ 32 + 1].
+ 				 byte = 132 ifTrue: [byte2 < 64 ifTrue: [^method literalAt: (method at: pc + 2) + 1]].
+ 				 byte = 133 ifTrue: [^method literalAt: byte2 \\ 32 + 1].
+ 				 byte = 134 ifTrue: [^method literalAt: byte2 \\ 64 + 1]]].
+ 	^anInstructionStream!

Item was added:
+ ----- Method: EncoderForV3>>computeMethodHeaderForNumArgs:numTemps:numLits:primitive: (in category 'method generation') -----
+ computeMethodHeaderForNumArgs: numArgs numTemps: numTemps numLits: numLits primitive: primitiveIndex
+ 	| primBits |
+ 	numTemps > 63 ifTrue:
+ 		[^self error: 'Cannot compile -- too many temporary variables'].	
+ 	numLits > 255 ifTrue:
+ 		[^self error: 'Cannot compile -- too many literals'].
+ 	primBits := primitiveIndex <= 16r1FF
+ 					ifTrue: [primitiveIndex]
+ 					ifFalse: "For now the high bit of primitive no. is in the 29th bit of header"
+ 						[primitiveIndex > 16r3FF ifTrue: [self error: 'prim num too large'].
+ 						 (primitiveIndex bitAnd: 16r1FF) + ((primitiveIndex bitAnd: 16r200) bitShift: 19)].
+ 	^(numArgs bitShift: 24)
+ 	+ (numTemps bitShift: 18)
+ 	"+ (largeBit bitShift: 17)" "largeBit gets filled in later"
+ 	+ (numLits bitShift: 9)
+ 	+ primBits!

Item was added:
+ ----- Method: EncoderForV3>>generateMethodOfClass:trailer:from: (in category 'method generation') -----
+ 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 literals header method stack |
+ 	primErrNode := methodNode primitiveErrorVariableName ifNotNil:
+ 						[self fixTemp: methodNode primitiveErrorVariableName].
+ 	blkSize := (methodNode block sizeCodeForEvaluatedValue: self)
+ 				+ (primErrNode
+ 					ifNil: [0]
+ 					ifNotNil: [primErrNode sizeCodeForStore: self "The VM relies on storeIntoTemp: (129)"]).
+ 	header := self computeMethodHeaderForNumArgs: methodNode arguments size
+ 					numTemps: self maxTemp
+ 					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)].
+ 	self streamToMethod: method.
+ 	stack := ParseStack new init.
+ 	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 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 added:
+ ----- Method: EncoderForV3PlusClosures>>generateMethodOfClass:trailer:from: (in category 'method generation') -----
+ 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)
+ 				+ (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)].
+ 	self streamToMethod: method.
+ 	stack := ParseStack new init.
+ 	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 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:
  SelectorNode subclass: #SpecialSelectorNode
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-ParseNodes'!
+ 
+ !SpecialSelectorNode commentStamp: 'eem 8/5/2014 20:18' prior: 0!
+ A SpecialSelectorNode is a subclass of SelectorNode that handles the special selectors, a high static and/or dynamic frequency set of selectors that are assigned their own bytecodes.  Special selectors both save space in the literal frame and allow an interpreter to implement these sends directly for certain classes of receiver and argument, for example the SmallIntegers, a technique known as static receiver prediction.!



More information about the Squeak-dev mailing list