The Trunk: Compiler-eem.345.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Compiler-eem.345.mcz

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

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

Name: Compiler-eem.345
Author: eem
Time: 6 April 2017, 10:40:46.118475 am
UUID: efc37a11-9654-451e-ab54-722190fbd9fa
Ancestors: Compiler-eem.344

Update EncoderForSistaV1.  revise the comment with the latest inline primitive spec and with better description and ordering of the Smalltalk and Sista parts of the bytecode set.

Fix encoding bugs for genPushConsArray:, genPushSpecialLiteral:, genReturnTopToCaller, genSend:numArgs: & genStoreTemp:.

Cirrect some limit warnings amd several comments.

=============== Diff against Compiler-eem.344 ===============

Item was removed:
- ----- Method: BytecodeEncoder>>supportsClosureOpcodes (in category 'testing') -----
- supportsClosureOpcodes
- "Answer if the receiver supports the
- genPushNewArray:/genPushConsArray:
- genPushRemoteTemp:inVectorAt:
- genStoreRemoteTemp:inVectorAt:
- genStorePopRemoteTemp:inVectorAt:
- genPushClosureCopyCopiedValues:numArgs:jumpSize:
- opcodes"
- ^false!

Item was added:
+ ----- Method: BytecodeEncoder>>supportsFullBlocks (in category 'testing') -----
+ supportsFullBlocks
+ "Answer if the instruction set supports full closures (closure creation from
+ specfic methods instead of bytecodes embedded in an outer home method)."
+
+ ^self subclassResponsibility!

Item was changed:
  BytecodeEncoder subclass: #EncoderForSistaV1
(excessive size, no diff calculated)

Item was added:
+ ----- Method: EncoderForSistaV1 class>>createClosureCode (in category 'bytecode decoding') -----
+ createClosureCode
+ "Answer the create closure bytecode, if it exists in the encoder's bytecode set, or nil if not.
+ Actually this code is that for a closure whose bytecodes are nested within its home method's."
+
+ ^250!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>nopCode (in category 'bytecode decoding') -----
+ nopCode
+ "Answer the call primitive bytecode, if it exists in the encoder's bytecode set, or nil if not.
+ 95 01011111 Nop"
+ ^95!

Item was added:
+ ----- Method: EncoderForSistaV1 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.
+
+ The compilcation is that for convenience we assume the pc could be
+ pointing to the raw send bytecode after its extensions, or at the extension
+ preceeding the raw send bytecode.
+ 96-111 0110 iiii Send Arithmetic Message #iiii #(#+ #- #< #> #'<=' #'>=' #= #'~=' #* #/ #'\\' #@ #bitShift: #'//' #bitAnd: #bitOr:)
+ 112-119 01110 iii Send Special Message #iii #(#at: #at:put: #size #next #nextPut: #atEnd #'==' class)
+ 120 01111000 UNASSIGNED (was: blockCopy:)
+ 121 01111001 Send Special Message #value
+ 122-123 0111101 i Send Special Message #i #(#value: #do:)
+ 124-127 011111 ii Send Special Message #ii #(#new #new: #x #y))
+ 128-143 1000 iiii Send Literal Selector #iiii With 0 Argument
+ 144-159 1001 iiii Send Literal Selector #iiii With 1 Arguments
+ 160-175 1010 iiii Send Literal Selector #iiii With 2 Arguments
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 225 11100001 bbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)
+ ** 234 11101010 iiiiijjj Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
+ ** 235 11101011 iiiiijjj Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+
+ | byte |
+ byte := method at: pc.
+ byte < 96 ifTrue:
+ [^anInstructionStream].
+ byte <= 175 ifTrue:
+ ["special byte or short send"
+ ^byte >= 128
+ ifTrue: [method literalAt: (byte bitAnd: 15) + 1]
+ ifFalse: [Smalltalk specialSelectorAt: byte - 95]].
+ byte < 234 ifTrue: "need to check for either extension cuz order of extensions is not restricted. so extB could preceed extA"
+ [(byte >= 224 and: [byte <= 225]) ifTrue:
+ [^self extensionsAt: pc in: method into:
+ [:extA :extB :nExtBytes| | byteAfter index |
+ byteAfter := method at: pc + nExtBytes.
+ (byteAfter >= 234 and: [byteAfter <= 235])
+ ifTrue:
+ [index := ((method at: pc + nExtBytes + 1) bitShift: -3) + (extA bitShift: 5).
+ method literalAt: index + 1]
+ ifFalse: [anInstructionStream]]].
+ ^anInstructionStream].
+ byte > 235 ifTrue:
+ [^anInstructionStream].
+ "they could be extended..."
+ ^self extensionsAt: pc in: method into:
+ [:extA :extB :nExtBytes| | index |
+ index := ((method at: pc + 1) bitShift: -3) + (extA bitShift: 5).
+ method literalAt: index + 1]!

Item was changed:
+ ----- Method: EncoderForSistaV1>>genCallInlinePrimitive: (in category 'extended bytecode generation') -----
- ----- Method: EncoderForSistaV1>>genCallInlinePrimitive: (in category 'bytecode generation') -----
  genCallInlinePrimitive: primitiveIndex
+ " 248 (2) 11111000 iiiiiiii mssjjjjj Call Primitive #iiiiiiii + (jjjjj * 256)
+ m=1 means inlined primitive, no hard return after execution.
+ ss defines the unsafe operation set used to encode the operations.
+ (ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)"
- "248 11111000 i i i i i i i i 1jjjjjjj Call Primitive #iiiiiiii + (jjjjjjj * 256)"
  "N.B. We could have made CallPrimitive a 2-byte code taking an extension, but that would
  complicate the VM's determination of the primitive number and the primitive error code
  store since the extension, being optional, would make the sequence variable length."
  (primitiveIndex < 1 or: [primitiveIndex > 32767]) ifTrue:
  [self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 32767].
  stream
  nextPut: 248;
  nextPut: (primitiveIndex bitAnd: 255);
  nextPut: (primitiveIndex bitShift: -8) + 128!

Item was changed:
  ----- Method: EncoderForSistaV1>>genCallPrimitive: (in category 'bytecode generation') -----
  genCallPrimitive: primitiveIndex
+ "248 (2) 11111000 iiiiiiii mssjjjjj Call Primitive #iiiiiiii + (jjjjj * 256)
+ m=1 means inlined primitive, no hard return after execution.
+ ss defines the unsafe operation set used to encode the operations.
+ (ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)"
- "248 11111000 i i i i i i i i 0jjjjjjj Call Primitive #iiiiiiii + (jjjjjjj * 256)"
  "N.B. We could have made CallPrimitive a 2-byte code taking an extension, but that would
  complicate the VM's determination of the primitive number and the primitive error code
  store since the extension, being optional, would make the sequence variable length."
+ (primitiveIndex < 1 or: [primitiveIndex > 32767]) ifTrue:
+ [self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 32767].
- (primitiveIndex < 1 or: [primitiveIndex > 65535]) ifTrue:
- [self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 65535].
  stream
  nextPut: 248;
  nextPut: (primitiveIndex bitAnd: 255);
  nextPut: (primitiveIndex bitShift: -8)!

Item was changed:
  ----- Method: EncoderForSistaV1>>genPushConsArray: (in category 'bytecode generation') -----
  genPushConsArray: size
  (size < 0 or: [size > 127]) ifTrue:
  [^self outOfRangeError: 'size' index: size range: 0 to: 127].
+ "231 11100111 jkkkkkkk Push (Array new: kkkkkkk) (j = 0)
- "233 11101001 jkkkkkkk Push (Array new: kkkkkkk) (j = 0)
  & Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)"
  stream
+ nextPut: 231;
- nextPut: 233;
  nextPut: size + 128!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied: (in category 'extended bytecode generation') -----
+ genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied
+ "By default the closure will have an outer context and the receiver will be fetched from the current context"
+ self genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: false ignoreOuterContext: false!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied:receiverOnStack:ignoreOuterContext: (in category 'extended bytecode generation') -----
+ genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: receiverOnStack ignoreOuterContext: ignoreOuterContext
+ "* 249 11111001 xxxxxxxx siyyyyyy push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1"
+ | extendedIndex |
+ (numCopied < 0 or: [numCopied > 64]) ifTrue:
+ [self outOfRangeError: 'num copied' index: numCopied range: 1 to: 64].
+ (compiledBlockLiteralIndex < 0 or: [compiledBlockLiteralIndex > 32767]) ifTrue:
+ [^self outOfRangeError: 'index' index: compiledBlockLiteralIndex range: 0 to: 32767].
+ (extendedIndex := compiledBlockLiteralIndex) > 255 ifTrue:
+ [self genUnsignedSingleExtendA: extendedIndex // 256.
+ extendedIndex := extendedIndex \\ 256].
+ stream
+ nextPut: 249;
+ nextPut: extendedIndex;
+ nextPut: receiverOnStack asBit << 7 + (ignoreOuterContext asBit << 6) + numCopied!

Item was changed:
  ----- Method: EncoderForSistaV1>>genPushLiteral: (in category 'bytecode generation') -----
  genPushLiteral: literalIndex
  | extendedIndex |
  (literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65535].
- [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65536].
  literalIndex < 32 ifTrue:
  ["32-63 001iiiii Push Literal #iiiii"
  stream nextPut: 32 + literalIndex.
  ^self].
  "228 11100100 i i i i i i i i Push Literal #iiiiiiii (+ Extend A * 256)"
  (extendedIndex := literalIndex) > 255 ifTrue:
  [self genUnsignedSingleExtendA: extendedIndex // 256.
  extendedIndex := extendedIndex \\ 256].
  stream
  nextPut: 228;
  nextPut: extendedIndex!

Item was changed:
  ----- Method: EncoderForSistaV1>>genPushRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
  genPushRemoteTemp: tempIndex inVectorAt: tempVectorIndex
+ "251 11111011 kkkkkkkk sjjjjjjj Push Temp At kkkkkkkk In Temp Vector At: jjjjjjj, s = 1 implies remote inst var access instead of remote temp vector access"
- "251 11111011 kkkkkkkk jjjjjjjj Push Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
  (tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
  [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
+ (tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
+ [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
- (tempVectorIndex < 0 or: [tempVectorIndex >= 256]) ifTrue:
- [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255].
  stream
  nextPut: 251;
  nextPut: tempIndex;
  nextPut: tempVectorIndex!

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)"
  | index |
  aLiteral isInteger ifTrue:
  [aLiteral == 0 ifTrue:
  [stream nextPut: 80.
  ^self].
  aLiteral == 1 ifTrue:
  [stream nextPut: 81.
  ^self].
  ^self genPushInteger: aLiteral].
+ index := #(true false nil)
- index := #(false true 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>>genReturnTopToCaller (in category 'bytecode generation') -----
  genReturnTopToCaller
+ "94 01011110 Return Stack Top From Block [* return from enclosing block N, ExtA]"
- "93 1011101 Return Stack Top From Block [* return from enclosing block N, ExtA]"
  "If extended, the least significant bit of the extension determines if we return to the caller or not
  and the most significant bits determine how many levels of the static chain to return from.
  ExtA = iiiiiiij
  iiiiiii=0,j=0 => return to caller
  iiiiiii=0,j=1 => illegal
  iiiiiii=1,j=0 => return to outerContext
  iiiiiii=1,j=1 => return to outerContext sender/return from outerContext
  iiiiiii=2,j=0 => return to outerContext outerContext
  iiiiiii=2,j=1 => return to outerContext outerContext sender/return from outerContext outerContext
  etc"
 
+ stream nextPut: 94!
- stream nextPut: 93!

Item was changed:
  ----- Method: EncoderForSistaV1>>genSend:numArgs: (in category 'bytecode generation') -----
  genSend: selectorLiteralIndex numArgs: nArgs
  | extendedIndex extendedNArgs |
  (selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
  [^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
  (nArgs < 0 or: [nArgs > 31]) ifTrue:
  [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
  (selectorLiteralIndex < 16 and: [nArgs < 3]) ifTrue:
  ["128-143 1000 iiii Send Literal Selector #iiii With 0 Argument
   144-159 1001 iiii Send Literal Selector #iiii With 1 Arguments
   160-175 1010 iiii Send Literal Selector #iiii With 2 Arguments"
  stream nextPut: 128 + (nArgs * 16) + selectorLiteralIndex.
  ^self].
  (extendedIndex := selectorLiteralIndex) > 31 ifTrue:
  [self genUnsignedSingleExtendA: extendedIndex // 32.
  extendedIndex := extendedIndex \\ 32].
  (extendedNArgs := nArgs) > 7 ifTrue:
  [self genUnsignedSingleExtendB: extendedNArgs // 8.
  extendedNArgs := extendedNArgs \\ 8].
  "234 11101010 i i i i i j j j Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  stream
+ nextPut: 234;
- nextPut: 238;
  nextPut: extendedNArgs + (extendedIndex * 8)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genSendDirectedSuper:numArgs: (in category 'extended bytecode generation') -----
+ genSendDirectedSuper: selectorLiteralIndex numArgs: nArgs
+ | extendedIndex |
+ (selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
+ (nArgs < 0 or: [nArgs > 31]) ifTrue:
+ [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
+ (extendedIndex := selectorLiteralIndex) > 31 ifTrue:
+ [self genUnsignedSingleExtendA: extendedIndex // 32.
+ extendedIndex := extendedIndex \\ 32].
+ "Bit 6 of the ExtB byte is the directed send flag.  Bit 6 allows for future expansion to up to 255 args."
+ self genUnsignedSingleExtendB: nArgs // 8 + 64.
+ "235 11101011 iiiiijjj Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+ stream
+ nextPut: 235;
+ nextPut: nArgs \\ 8 + (extendedIndex * 8)!

Item was changed:
  ----- Method: EncoderForSistaV1>>genStorePopRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
  genStorePopRemoteTemp: tempIndex inVectorAt: tempVectorIndex
+ "* 253 (3) 11111101 kkkkkkkk sjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access"
- "253 11111101 kkkkkkkk jjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
  (tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
  [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
+ (tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
+ [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
- (tempVectorIndex < 0 or: [tempVectorIndex >= 256]) ifTrue:
- [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255].
  stream
  nextPut: 253;
  nextPut: tempIndex;
  nextPut: tempVectorIndex!

Item was changed:
  ----- Method: EncoderForSistaV1>>genStoreRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
  genStoreRemoteTemp: tempIndex inVectorAt: tempVectorIndex
+ "*252 (3) 11111100 kkkkkkkk sjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access"
- "252 11111100 kkkkkkkk jjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
  (tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
  [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
+ (tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
+ [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
- (tempVectorIndex < 0 or: [tempVectorIndex >= 256]) ifTrue:
- [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255].
  stream
  nextPut: 252;
  nextPut: tempIndex;
  nextPut: tempVectorIndex!

Item was changed:
  ----- Method: EncoderForSistaV1>>genStoreTemp: (in category 'bytecode generation') -----
  genStoreTemp: tempIndex
+ "245 11110110 iiiiiiii Store Temporary Variable #iiiiiiii"
- "242 11110010 iiiiiiii Pop and Store Temporary Variable #iiiiiiii"
  (tempIndex < 0 or: [tempIndex > 63]) ifTrue:
  [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63].
  stream
+ nextPut: 245;
- nextPut: 242;
  nextPut: tempIndex!

Item was changed:
  ----- Method: EncoderForSistaV1>>genUnsignedSingleExtendA: (in category 'bytecode generation') -----
  genUnsignedSingleExtendA: extendedIndex
  (extendedIndex between: 0 and: 255) ifFalse:
  [^self outOfRangeError: 'index' index: extendedIndex range: 0 to: 255].
+ "224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ ExtA is normally unsigned."
- "224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)"
  stream
  nextPut: 224;
  nextPut: extendedIndex!

Item was changed:
  ----- Method: EncoderForSistaV1>>genUnsignedSingleExtendB: (in category 'bytecode generation') -----
  genUnsignedSingleExtendB: extendedIndex
  (extendedIndex between: 0 and: 255) ifFalse:
  [^self outOfRangeError: 'index' index: extendedIndex range: 0 to: 255].
+ "225 11100001 sbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B).
+ ExtB is normally signed"
- "225 11100001 sbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)"
  stream
  nextPut: 225;
  nextPut: extendedIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>isSpecialLiteralForPush: (in category 'special literal encodings') -----
+ isSpecialLiteralForPush: literal
+ ^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>>maxIndexableLiterals (in category 'accessing') -----
+ maxIndexableLiterals
+ "Answer the maximum number of literals supported by the receiver's
+ bytecode set."
+ ^65536!

Item was added:
+ ----- Method: EncoderForSistaV1>>supportsFullBlocks (in category 'testing') -----
+ supportsFullBlocks
+ "Answer if the instruction set supports full closures (closure creation from
+ specfic methods instead of bytecodes embedded in an outer home method)."
+
+ ^true!

Item was added:
+ ----- Method: EncoderForV3>>supportsFullBlocks (in category 'testing') -----
+ supportsFullBlocks
+ "Answer if the instruction set supports full closures (closure creation from
+ specfic methods instead of bytecodes embedded in an outer home method)."
+
+ ^false!

Item was changed:
  ----- Method: EncoderForV3PlusClosures class>>createClosureCode (in category 'bytecode decoding') -----
  createClosureCode
+ "Answer the create closure bytecode, if it exists in the encoder's bytecode set, or nil if not.
+ Actually this code is that for a closure whose bytecodes are nested within its home method's."
- "Answer the create closure bytecode, if it exists in the encoder's byetcode set, or nil if not."
  ^143!