Re: The Trunk: Kernel-eem.852.mcz

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

Re: The Trunk: Kernel-eem.852.mcz

Nicolas Cellier



2014-05-19 20:50 GMT+02:00 <[hidden email]>:
Eliot Miranda uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-eem.852.mcz

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

Name: Kernel-eem.852
Author: eem
Time: 19 May 2014, 11:49:49.951 am
UUID: 6d0add2f-b4ae-4e90-9b0d-7c938c4f4c1c
Ancestors: Kernel-eem.851

Change scanning methods in InstructionStream and
CompiledMethod to double-dispatch through
CompiledMethod>>#encoderClass to provide pluggable
multiple bytecode set support.  The sign of a method's
header chooses which of two bytecode sets are in effect,
choosing between PrimaryBytecodeSetEncoderClass
(header >= 0), and SecondaryBytecodeSetEncoderClass
(header <= 0).

=============== Diff against Kernel-eem.851 ===============

Item was changed:
  ----- Method: CompiledMethod class>>newBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive: (in category 'instance creation') -----
  newBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex
        "Answer an instance of me. The header is specified by the message
+        arguments. The remaining parts are not as yet determined."
-       arguments. The remaining parts are not as yet determined."
        | largeBit primBits |
        nTemps > 63 ifTrue:
                [^ self error: 'Cannot compile -- too many temporary variables'].
        nLits > 255 ifTrue:
+               [^ self error: 'Cannot compile -- too many literals'].
-               [^ self error: 'Cannot compile -- too many literals variables'].
        largeBit := (nTemps + stackSize) > SmallFrame ifTrue: [1] ifFalse: [0].
        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)].

        ^trailer
                createMethod: numberOfBytes
                class: self
                header: (nArgs bitShift: 24) +
                                (nTemps bitShift: 18) +
                                (largeBit bitShift: 17) +
                                (nLits bitShift: 9) +
                                primBits!

Item was changed:
  ----- Method: CompiledMethod class>>newBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive:flag: (in category 'instance creation') -----
  newBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex flag: flag
        "Answer an instance of me. The header is specified by the message
+        arguments. The remaining parts are not as yet determined."
-       arguments. The remaining parts are not as yet determined."
        | largeBit primBits flagBit |
        nTemps > 63 ifTrue:
                [^ self error: 'Cannot compile -- too many temporary variables'].
        nLits > 255 ifTrue:
+               [^ self error: 'Cannot compile -- too many literals'].
-               [^ self error: 'Cannot compile -- too many literals variables'].
        largeBit := (nTemps + stackSize) > SmallFrame ifTrue: [1] ifFalse: [0].

        "For now the high bit of the primitive no. is in a high bit of the header"
        primBits := (primitiveIndex bitAnd: 16r1FF) + ((primitiveIndex bitAnd: 16r200) bitShift: 19).

        flagBit := flag ifTrue: [ 1 ] ifFalse: [ 0 ].

-       "Copy the source code trailer to the end"
        ^trailer
                createMethod: numberOfBytes
                class: self
                header: (nArgs bitShift: 24) +
                                (nTemps bitShift: 18) +
                                (largeBit bitShift: 17) +
                                (nLits bitShift: 9) +
                                primBits +
                                (flagBit bitShift: 29)!

Item was changed:
  ----- Method: CompiledMethod>>containsBlockClosures (in category 'closures') -----
  containsBlockClosures
+       ^self scanner scanFor: self encoderClass createClosureScanBlock!
-       ^ self scanner scanFor: [ :bc | bc = 143 "push closure bytecode" ]!

Item was changed:
  ----- Method: CompiledMethod>>header (in category 'literals') -----
  header
        "Answer the word containing the information about the form of the
+        receiver and the form of the context needed to run the receiver.
+        There are two different formats, selected by the sign bit.  These are
-       receiver and the form of the context needed to run the receiver."

+        Original Squeak V3:
+               30:sign:0 29:flag 28:prim (high bit) 27-24:numArgs 23-18:numTemps 17:largeFrameFlag 16-9:numLits 8-0:prim (low 9 bits)
+
+        Alternate Bytecode Set
+               30:sign:1 29-28:accessModifier 27-24:numArgs 23-18:numTemps 17:largeFrameFlag 16:hasPrimitive 15-0:numLits
+
+        i.e. the Alternate Bytecode Set expands the number of literals to 65535 by assuming a CallPrimitive bytecode."
+
        ^self objectAt: 1!

Item was changed:
  ----- Method: CompiledMethod>>isBlueBookCompiled (in category 'testing') -----
  isBlueBookCompiled
+       "Answer whether the receiver was compiled using the old Smalltalk-80 blocks
+        compiler.  This is used to help DebuggerMethodMap choose which mechanisms
+        to use to inspect (debug) activations of the receiver."
-       "Answer whether the receiver was compiled using the closure compiler.
-        This is used to help DebuggerMethodMap choose which mechanisms to
-        use to inspect activations of the receiver.
-        This method answers false negatives in that it only identifies methods
-        that create old BlockClosures or use the new BlockClosure bytecodes.
-        It cannot tell if a method which uses neither the old nor the new block
-        bytecodes is compiled with the blue-book compiler or the new compiler.
-        But since methods that don't create blocks have essentially the same
-        code when compiled with either compiler this makes little difference."

+       ^self encoderClass supportsClosures not!
-       ^((InstructionStream on: self) scanFor:
-               [:instr |
-               (instr >= 138 and: [instr <= 143]) ifTrue: [^false].
-               instr = 200])
-          or: [(self hasLiteral: #blockCopy:)
-                  and: [self messages includes: #blockCopy:]]!

Item was changed:
  ----- Method: CompiledMethod>>isClosureCompiled (in category 'testing') -----
  isClosureCompiled
        "Answer whether the receiver was compiled using the closure compiler.
         This is used to help DebuggerMethodMap choose which mechanisms to
+        use to inspect (debug) activations of the receiver."
-        use to inspect activations of the receiver.
-        This method answers false negatives in that it only identifies methods
-        that create new BlockClosures or use the new BlockClosure bytecodes.
-        But since methods that don't create blocks have essentially the same
-        code when compiled with either compiler this makes little difference."

+       ^self encoderClass supportsClosures!
-       ^((InstructionStream on: self) scanFor: [:instr | instr >= 138 and: [instr <= 143]])
-          or: [(self hasLiteral: #closureCopy:copiedValues:)
-                  and: [self messages includes: #closureCopy:copiedValues:]]!


Note that this change makes ClosureCompilerTest>>#testSourceRangeAccessForBlueBookInjectInto fail
But the test itself is for pre-closure byteCodes (using EncoderForV3, or so called Blue Book blocks with blockCopy byteCode)

In my image, I have no blue book CompiledMethod, if I believe this snippet:

CompiledMethod allInstances count: [:e |
    ((InstructionStream on: e) scanFor: [:instr | instr = 200])
           or: [(e hasLiteral: #blockCopy:)
                   and: [e messages includes: #blockCopy:]]].

Do we really want to support this old thing?
Or shall we remove this test and support of previous bytecode set (EncoderForV3)?
Or is there a danger that some old ImageSegment bring some zombies back?
Or are these things still usefull for some boostrap voodoo?

Currently, debugging such compiled method fails with sticky debuggers...
Some bytes are rotting, we lack tests, a single person is active/fluent on this part, so dropping support is a reasonnable option.