ByteCodeCompiler.st
author claus
Wed, 13 Oct 1993 03:41:56 +0100
changeset 4 f6fd83437415
parent 3 b63b8a6b71fb
child 5 020d67cc590e
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Parser subclass:#ByteCodeCompiler
       instanceVariableNames:'code codeIndex
                              litArray
                              stackDelta extra lineno
                              maxStackDepth
                              relocList'
       classVariableNames:'JumpToAbsJump'
       poolDictionaries:''
       category:'System-Compiler'
!

ByteCodeCompiler comment:'

COPYRIGHT (c) 1989 by Claus Gittinger
             All Rights Reserved

$Header: /cvs/stx/stx/libcomp/ByteCodeCompiler.st,v 1.4 1993-10-13 02:41:03 claus Exp $
'!

!ByteCodeCompiler class methodsFor:'documentation'!

documentation
"
This class performs compilation into ByteCodes.
First, parsing is done using superclass methods,
then the parse-tree is converted into an array of symbolic codes
and a relocation table; 
these two are finally combined into a byteArray of the codes.

There are many dependancies to the run-time-system (especially the
interpreter) in here - be careful when playing around ...

Instance variables:

code            <ByteArry>              bytecodes
codeIndex       <SmallInteger>          next index to put into code array
litArray        <OrderedCollection>     literals
stackDelta      <SmallInteger>          return value of byteCodeFor:
extra           <Symbol>                return value of byteCodeFor:
maxStackDepth   <SmallInteger>          stack need of method
relocList       <Array>                 used temporary for relocation
"
! !

!ByteCodeCompiler class methodsFor:'compiling methods'!

compile:methodText forClass:classToCompileFor
    "compile a source-string for a method in classToCompileFor"

    ^ self compile:methodText
          forClass:classToCompileFor
        inCategory:'others'
         notifying:nil
           install:true
        skipIfSame:false
!

compile:aString forClass:aClass inCategory:cat
    "compile a source-string for a method in classToCompileFor.
     The method will get cat as category"

    ^ self compile:aString
          forClass:aClass
        inCategory:cat
         notifying:nil
           install:true
        skipIfSame:false
!

compile:methodText forClass:classToCompileFor notifying:someOne
    "compile a source-string for a method in classToCompileFor.
     errors are forwarded to someOne."

    ^ self compile:methodText
          forClass:classToCompileFor
        inCategory:'others'
         notifying:someOne
           install:true
        skipIfSame:false
!

compile:aString forClass:aClass inCategory:cat notifying:someOne
    "compile a source-string for a method in classToCompileFor.
     errors are forwarded to someOne.
     The method will get cat as category"

    ^ self compile:aString
          forClass:aClass
        inCategory:cat
         notifying:someOne
           install:true
        skipIfSame:false
!

compile:aString forClass:aClass inCategory:cat notifying:someOne
                                                 install:install
    ^ self compile:aString
          forClass:aClass
        inCategory:cat
         notifying:someOne
           install:true
        skipIfSame:false
!

compile:aString forClass:aClass inCategory:cat notifying:someOne
                 install:install skipIfSame:skipIfSame

    "the basic workhorse method for compiling.
     compile a source-string for a method in classToCompileFor.
     errors are forwarded to someOne (report on Transcript and return
     #Error, if someOne is nil).

     The new method will get cat as category. If install is true, the method
     will go into the classes method-table, otherwise the method is simply
     returned (for anonymous methods).
     If skipIsSame is true, and the source is the same as an existing
     methods source, this is a noop (for fast fileIn)."

    |compiler newMethod tree lits machineCode 
     symbolicCodeArray sharedCode sharedCodeSymbol oldMethod|

    aString isNil ifTrue:[^ nil].

    "create a compiler, let it parse and create the parsetree"

    compiler := self for:(ReadStream on:aString).
    compiler setClassToCompileFor:aClass.
    compiler notifying:someOne.

    compiler nextToken.
    (compiler parseMethodSpec == #Error) ifTrue:[
        tree := #Error
    ] ifFalse:[
        "check if same source"
        (skipIfSame and:[compiler selector notNil]) ifTrue:[
            oldMethod := aClass compiledMethodAt:(compiler selector).
            oldMethod notNil ifTrue:[
                oldMethod source = aString ifTrue:[
                    SilentLoading ifFalse:[
                        Transcript showCr:('unchanged: ',aClass name,' ',compiler selector)
                    ].
                    ^ oldMethod
                ]
            ]
        ].
        tree := compiler parseMethodBody.
        compiler tree:tree.
    ].

    (compiler errorFlag or:[tree == #Error]) ifTrue:[
        compiler selector notNil ifTrue:[
            Transcript show:(compiler selector,' ')
        ].
        Transcript showCr:'syntax error'.
        ^ #Error
    ].

    compiler selector isNil ifTrue:[
        "it was just a comment or other empty stuff"
        ^ nil
    ].

    "produce symbolic code first"

    symbolicCodeArray := compiler genSymbolicCode.
    (symbolicCodeArray == #Error) ifTrue:[
        compiler selector notNil ifTrue:[
            Transcript show:(compiler selector,' ')
        ].
        Transcript showCr:'translation error'.
        ^ #Error
    ].

    ((compiler genByteCodeFrom:symbolicCodeArray) == #Error) ifTrue:[
        compiler selector notNil ifTrue:[
            Transcript show:(compiler selector,' ')
        ].
        Transcript showCr:'relocation error - must be simplified'.
        ^ #Error
    ].

    "check for primitive code"
    compiler primitiveNumber notNil ifTrue:[
        machineCode := compiler checkForPrimitiveCode:compiler primitiveNumber.
        machineCode isNil ifTrue:[
            Transcript showCr:'primitive ', compiler primitiveNumber printString , ' is not supported'.
            ^ #Error
        ]
    ].

    machineCode isNil ifTrue:[
        "check for shared-code (only trivial methods)"

        sharedCodeSymbol := compiler checkForSharedCode:symbolicCodeArray.
        sharedCodeSymbol notNil ifTrue:[
            sharedCode := self sharedCodeFunctionFor:sharedCodeSymbol
        ].

        "try to make it machine code"

        machineCode := compiler checkForMachineCode:symbolicCodeArray
    ].

    "finally create the new method-object"

    newMethod := Method new.
    lits := compiler literalArray.
    lits notNil ifTrue:[
        "literals MUST be an array - not just any Collection"
        lits := Array withAll:lits.
        newMethod literals:lits
    ].
    newMethod byteCode:(compiler code).
    sharedCode notNil ifTrue:[
        newMethod code:sharedCode
    ] ifFalse:[
        machineCode notNil ifTrue:[
            newMethod code:machineCode
        ]
    ].
    newMethod source:aString.
    newMethod category:cat.
    newMethod numberOfMethodVars:(compiler numberOfMethodVars).
    newMethod stackSize:(compiler maxStackDepth).

    install ifTrue:[
        aClass addSelector:(compiler selector) withMethod:newMethod
    ].

    SilentLoading ifFalse:[
        Transcript showCr:('compiled: ',aClass name,' ',compiler selector)
    ].

    ^ newMethod
! !

!ByteCodeCompiler methodsFor:'accessing'!

literalArray
    "return the literal array - only valid after parsing"

    ^ litArray
!

code
    "return the bytecode array - only valid after code-generation"

    ^ code
!

maxStackDepth
    "return the stack-need of the method - only valid after code-generation"

    ^ maxStackDepth
! !

!ByteCodeCompiler methodsFor:'code generation'!

genSymbolicCode
    "traverse the parse-tree producing symbolicCode - return the codeArray"

    |codeStream thisStatement lastStatement|

    codeStream := WriteStream on:(Array new:100).
    thisStatement := tree.
    [thisStatement notNil] whileTrue:[
        lastStatement := thisStatement.
        thisStatement codeForSideEffectOn:codeStream inBlock:nil.
        thisStatement := thisStatement nextStatement
    ].
    (lastStatement isNil or:[(lastStatement isMemberOf:ReturnNode) not])
    ifTrue:[
        "not a return - add retSelf"
        codeStream nextPut:#retSelf
    ].
    ^ codeStream contents
!

checkForPrimitiveCode:primNr
    "this was added to allow emulation of (some) ST-80
     primitives (to fileIn Remote-Package)"

    |cls sel|

    (primNr == 75)  ifTrue:[ cls := Object. sel := #identityHash ].
    (primNr == 110) ifTrue:[ cls := Object. sel := #==           ].
    (primNr == 111) ifTrue:[ cls := Object. sel := #class        ].
    cls notNil ifTrue:[
        ^ (cls compiledMethodAt:sel) code
    ].
    ^ nil
!

genByteCodeFrom:symbolicCodeArray
    "convert symbolicCode into bytecodes"

    |symIndex    "<SmallInteger>"
     codeSize    "<SmallInteger>"
     symCodeSize "<SmallInteger>"
     index addr
     codeSymbol nargs done
     stackDepth relocInfo level nvars|

    symbolicCodeArray isNil ifTrue:[^ self].

    done := false.
    symCodeSize := symbolicCodeArray size.
    codeSize := symCodeSize.

    [done] whileFalse:[
        litArray := nil.
        stackDepth := 0.
        maxStackDepth := 0.

        code := ByteArray uninitializedNew:codeSize.
        relocInfo := Array new:(codeSize + 1).
        symIndex := 1.
        codeIndex := 1.

        [symIndex <= symCodeSize] whileTrue:[
            relocInfo at:symIndex put:codeIndex.

            codeSymbol := symbolicCodeArray at:symIndex.
            symIndex := symIndex + 1.
            stackDelta := 0.
            extra := nil.
            lineno := false.
            self appendByteCodeFor:codeSymbol.
            lineno ifTrue:[
                self appendByte:((symbolicCodeArray at:symIndex) min:255).
                symIndex := symIndex + 1
            ].
            extra notNil ifTrue:[
              (extra == #number) ifTrue:[
                index := symbolicCodeArray at:symIndex.
                symIndex := symIndex + 1.
                self appendSignedByte:index
              ] ifFalse:[
                (extra == #index) ifTrue:[
                  index := symbolicCodeArray at:symIndex.
                  symIndex := symIndex + 1.
                  self appendByte:index
                ] ifFalse:[
                  (extra == #lit) ifTrue:[
                    index := self addLiteral:(symbolicCodeArray at:symIndex).
                    symIndex := symIndex + 1.
                    self appendByte:index
                  ] ifFalse:[
                    (extra == #speciallit) ifTrue:[
                      index := self addLiteral:(symbolicCodeArray at:symIndex).
                      symIndex := symIndex + 1.
                      self appendByte:index.
                      self appendByte:0.  "space for inline-generation"
                      self appendByte:0.  "space for inline-address"
                      self appendByte:0.
                      self appendByte:0.
                      self appendByte:0.
                      symIndex := symIndex + 5
                    ] ifFalse:[
                      (extra == #offset) ifTrue:[
                        relocInfo at:symIndex put:codeIndex.
                        self addReloc:symIndex.
                        symIndex := symIndex + 1.
                        self appendByte:0
                      ] ifFalse:[
                        (extra == #indexLevel) ifTrue:[
                          index := symbolicCodeArray at:symIndex.
                          symIndex := symIndex + 1.
                          self appendByte:index.
                          level := symbolicCodeArray at:symIndex.
                          symIndex := symIndex + 1.
                          self appendByte:level
                        ] ifFalse:[
                          (extra == #offsetNvarNarg) ifTrue:[
                            relocInfo at:symIndex put:codeIndex.
                            self addReloc:symIndex.
                            symIndex := symIndex + 1.
                            self appendByte:0.
                            nvars := symbolicCodeArray at:symIndex.
                            symIndex := symIndex + 1.
                            self appendByte:nvars.
                            level := symbolicCodeArray at:symIndex.
                            symIndex := symIndex + 1.
                            self appendByte:level
                          ] ifFalse:[
                            (extra == #absoffset) ifTrue:[
                              relocInfo at:symIndex put:codeIndex.
                              self addReloc:symIndex.
                              addr := symbolicCodeArray at:symIndex.
                              symIndex := symIndex + 1.
                              self appendByte:(addr bitAnd:16rFF).
                              self appendByte:((addr bitShift:-8) bitAnd:16rFF).
                            ] ifFalse:[
                              (extra == #absoffsetNvarNarg) ifTrue:[
                                relocInfo at:symIndex put:codeIndex.
                                self addReloc:symIndex.
                                addr := symbolicCodeArray at:symIndex.
                                symIndex := symIndex + 1.
                                self appendByte:(addr bitAnd:16rFF).
                                self appendByte:((addr bitShift:-8) bitAnd:16rFF).
                                nvars := symbolicCodeArray at:symIndex.
                                symIndex := symIndex + 1.
                                self appendByte:nvars.
                                level := symbolicCodeArray at:symIndex.
                                symIndex := symIndex + 1.
                                self appendByte:level
                              ] ifFalse:[
                                self error:'compiler botch'
                              ]
                            ]
                          ]
                        ]
                      ]
                    ]
                  ]
                ]
              ]
            ].
            ((codeSymbol == #send) or:[codeSymbol == #superSend]) ifTrue:[
              index := self addLiteral:(symbolicCodeArray at:symIndex).
              symIndex := symIndex + 1.
              nargs := symbolicCodeArray at:symIndex.
              symIndex := symIndex + 1.
              self appendByte:nargs.
              self appendByte:index.
              (codeSymbol == #superSend) ifTrue:[
                  symIndex := symIndex + 1.
                  index := self addLiteral:(classToCompileFor superclass).
                  self appendByte:index
              ].
              stackDelta := nargs negated
            ] ifFalse:[
              (codeSymbol == #sendDrop) ifTrue:[
                  index := self addLiteral:(symbolicCodeArray at:symIndex).
                  symIndex := symIndex + 1.
                  nargs := symbolicCodeArray at:symIndex.
                  symIndex := symIndex + 1.
                  self appendByte:nargs.
                  self appendByte:index.
                  stackDelta := (nargs + 1) negated
                ]
            ].
            stackDepth := stackDepth + stackDelta.
            (stackDepth > maxStackDepth) ifTrue:[
                maxStackDepth := stackDepth
            ]
        ].
        relocInfo at:symIndex put:codeIndex.

        "relocate - returns true if ok, false if we have to rerun"
        done := true.
        relocList notNil ifTrue:[
            done := self relocateWith:symbolicCodeArray relocInfo:relocInfo.
            "if returned with false, a relative jump was made into
             an absolute jump - need to start over with one more byte space"
            done ifFalse:[
                relocList := nil.
                codeSize := codeSize + 1.
            ]
        ].
    ].
    "code printNewline."
    ^ errorFlag
!

absJumpFromJump:code
    "given a jump-symbolic code, return corresponding absolute jump"

    JumpToAbsJump isNil ifTrue:[
        JumpToAbsJump := IdentityDictionary new.
        JumpToAbsJump at:#jump put:#jumpabs.
        JumpToAbsJump at:#trueJump put:#trueJumpabs.
        JumpToAbsJump at:#falseJump put:#falseJumpabs.
        JumpToAbsJump at:#nilJump put:#nilJumpabs.
        JumpToAbsJump at:#notNilJump put:#notNilJumpabs.
        JumpToAbsJump at:#eqJump put:#eqJumpabs.
        JumpToAbsJump at:#notEqJump put:#notEqJumpabs.
        JumpToAbsJump at:#zeroJump put:#zeroJumpabs.
        JumpToAbsJump at:#notZeroJump put:#notZeroJumpabs.
        JumpToAbsJump at:#makeBlock put:#makeBlockabs.
    ].
    ^ JumpToAbsJump at:code
!

relocateWith:symbolicCodeArray relocInfo:relocInfo
    "helper for genByteCodeFrom - relocate code using relocInfo.
     if relocation fails badly (due to long relative jumps) patch
     symbolicCode to use absolute jumps instead and return false
     (genByteCodeFrom will then try again). Otherwise return true.
     Also, on the fly, jumps to jumps and jumps to return are handled."

    |delta       "<SmallInteger>"
     codePos     "<SmallInteger>"
     opCodePos   "<SmallInteger>"
     codeOffset  "<SmallInteger>"
     symOffset opcode dstOpcode jumpTarget
     jumpCode deleteSet|

    deleteSet := OrderedCollection new.
    relocList do:[:sIndex |
        "have to relocate symCode at sIndex ..." 
        symOffset := symbolicCodeArray at:sIndex.   "the target in the symbolic code"
        codePos := relocInfo at:sIndex.             "position of the offet in byte code"
        codeOffset := relocInfo at:symOffset.       "position of the target in byte code"
        delta := codeOffset - codePos - 1.
        opCodePos := codePos - 1.
        opcode := code at:opCodePos.

        (opcode between:190 and:199) ifTrue:[
            "an absolute jump/makeBlock"

            code at:codePos put:(codeOffset bitAnd:16rFF).
            code at:(codePos + 1) put:(codeOffset bitShift:-8)
        ] ifFalse:[
            "get jump-code from long and vlong codes"
            (opcode between:50 and:59) ifFalse:[
                (opcode between:60 and:69) ifTrue:[
                    opcode := opcode - 10
                ] ifFalse:[
                    (opcode between:70 and:79) ifTrue:[
                        opcode := opcode - 20
                    ] ifFalse:[
                        self error:'invalid code to relocate'
                    ]
                ].
            ].

            "optimize jump to return and jump to jump"

            (opcode == 54) ifTrue:[
                "a jump"
                dstOpcode := symbolicCodeArray at:symOffset.

                (#(retSelf retTop retNil retTrue retFalse ret0 blockRetTop) includes:dstOpcode) ifTrue:[
                    "a jump to a return - put in the return instead jump"

                    symbolicCodeArray at:(sIndex - 1) put:dstOpcode.
                    symbolicCodeArray at:sIndex put:dstOpcode.
                    code at:opCodePos put:(self byteCodeFor:dstOpcode).
                    delta := 0.
                    deleteSet add:sIndex.

" 
'jump to return at: ' print. (sIndex - 1) printNewline.
" 
                ] ifFalse:[
                    (dstOpcode == #jump) ifTrue:[
                        "jump to jump to be done soon"
                        jumpTarget := symbolicCodeArray at:(symOffset + 1).
" 
'jump to jump at: ' print. (sIndex - 1) print.
'  newTarget:' print. jumpTarget printNewline.
" 

                        symbolicCodeArray at:sIndex put:jumpTarget.
                        symOffset := jumpTarget.
                        codeOffset := relocInfo at:symOffset.
                        delta := codeOffset - codePos - 1.

                        "continue with new delta"
                    ]
                ]
            ].
            (#(50 51 52 53 56 57 58 59) includes:opcode) ifTrue:[
                "a conditional jump"

                dstOpcode := symbolicCodeArray at:symOffset.
                (dstOpcode == #jump) ifTrue:[
                    "conditional jump to unconditional jump"
                    jumpTarget := symbolicCodeArray at:(symOffset + 1).
" 
'cond jump to jump at: ' print. (sIndex - 1) print.
'  newTarget:' print. jumpTarget printNewline.
" 

                    symbolicCodeArray at:sIndex put:jumpTarget.
                    symOffset := jumpTarget.
                    codeOffset := relocInfo at:symOffset.
                    delta := codeOffset - codePos - 1.

                    "continue with new delta"
                ].
            ].

            (delta >= 0) ifTrue:[
                (delta > 127) ifTrue:[
                    (opcode between:50 and:59) ifFalse:[
                        self error:'invalid code to relocate'
                    ].
                    (delta > 255) ifTrue:[
                        "change jmp into vljmp ..."
                        code at:opCodePos put:(opcode + 20).
                        delta := delta - 256 
                    ] ifFalse:[
                        "change jmp into ljmp ..."
                        code at:opCodePos put:(opcode + 10).
                        delta := delta - 128
                    ].
                    (delta > 127) ifTrue:[
                        "change symbolic into a jump absolute and fail"
                        jumpCode := symbolicCodeArray at:(sIndex - 1).
                        symbolicCodeArray at:(sIndex - 1) put:(self absJumpFromJump:jumpCode).
                        symbolicCodeArray at:sIndex put:symOffset.
"
'change short into abs jump' printNewline.
"
                        deleteSet do:[:d | relocList remove:d].
                        ^ false
                    ].
                ].
                code at:codePos put:delta
            ] ifFalse:[
                (delta < -128) ifTrue:[
                    (opcode between:50 and:59) ifFalse:[
                        self error:'invalid code to relocate'
                    ].
                    (delta < -256) ifTrue:[
                        "change jmp into vljmp ..."
                        code at:opCodePos put:(opcode + 20).
                        delta := delta + 256
                    ] ifFalse:[
                        "change jmp into ljmp ..."
                        code at:opCodePos put:(opcode + 10).
                        delta := delta + 128
                    ].
                    (delta < -128) ifTrue:[
                        "change symbolic into a jump absolute and fail"
                        jumpCode := symbolicCodeArray at:(sIndex - 1).
                        symbolicCodeArray at:(sIndex - 1) put:(self absJumpFromJump:jumpCode).
                        symbolicCodeArray at:sIndex put:symOffset.
"
'change short into abs jump' printNewline.
"
                        deleteSet do:[:d | relocList remove:d].
                        ^ false
                    ]
                ].
                code at:codePos put:(256 + delta)
            ]
        ]
    ].
    (errorFlag == #Error) ifTrue:[
        self error:'relocation range error'
    ].
    ^ true
!

addLiteral:anObject
    "add a literal to the literalArray - watch for and eliminate
     duplicates. return the index of the literal in the Array"

    |index class|

    litArray isNil ifTrue:[
        litArray := Array with:anObject.
        ^ 1
    ].
    index := litArray identityIndexOf:anObject.
    (index == 0) ifTrue:[
        class := anObject class.
        ((class == Float) or:[class == Fraction]) ifTrue:[
            index := litArray indexOf:anObject.
        ].
        (index == 0) ifTrue:[
            litArray := litArray copyWith:anObject.
            ^ litArray size
        ].
    ].
    ^ index
!

appendByteCodeFor:codeSymbol
    "append the byteCode for an instructionSymbol to the code-Array"

    code at:codeIndex put:(self byteCodeFor:codeSymbol).
    codeIndex := codeIndex + 1
!

appendByte:aByte
    "append a byte to the code-Array, checking for byte-range (debug-only)"

    (aByte between:0 and:255) ifTrue:[
        code at:codeIndex put:aByte.
        codeIndex := codeIndex + 1
    ] ifFalse:[
        self error:'byte range error'.
        errorFlag := #Error
    ]
!

appendSignedByte:aByte
    "append a signedbyte (as in jump-offsets) to the code-Array,
     check range and report an error if invalid"

    |b "<SmallInteger>" |

    b := aByte.
    (b >= 0) ifTrue:[
        (b > 127) ifTrue:[
            self error:'jump-range error'.
            errorFlag := #Error
        ].
        code at:codeIndex put:b
    ] ifFalse:[
        (b < -128) ifTrue:[
            self error:'jump-range error'.
            errorFlag := #Error
        ].
        code at:codeIndex put:(256 + b)
    ].
    codeIndex := codeIndex + 1
!

addReloc:symIndex
    "remember to relocate offset at symIndex later ..."

    relocList isNil ifTrue:[
        relocList := OrderedCollection new.
    ].
    relocList add:symIndex
!

byteCodeFor:aSymbol
    "given a symbolic instruction, return the corresponding bytecode.
     as a side-effect, leave number of bytes pushed/popped by this instr.
     in stackDelta, and, if the instruction needs extra arguments, leave
     this info in extra"

    "standard bytecodes"

    (aSymbol == #pushNil) ifTrue:[stackDelta := 1. ^ 10].
    (aSymbol == #pushTrue) ifTrue:[stackDelta := 1. ^ 11].
    (aSymbol == #pushFalse) ifTrue:[stackDelta := 1. ^ 12].
    (aSymbol == #pushLit) ifTrue:[stackDelta := 1. extra := #lit. ^ 14].
    (aSymbol == #pushSelf) ifTrue:[stackDelta := 1. ^ 15].
    (aSymbol == #pushNum) ifTrue:[stackDelta := 1. extra := #number. ^ 16].

    (aSymbol == #pushMethodArg) ifTrue:[stackDelta := 1. extra := #index. ^ 30].
    (aSymbol == #pushMethodVar) ifTrue:[stackDelta := 1. extra := #index. ^ 31].
    (aSymbol == #pushBlockArg) ifTrue:[stackDelta := 1. extra := #index. ^ 32].
    (aSymbol == #pushBlockVar) ifTrue:[stackDelta := 1. extra := #index. ^ 33].
    (aSymbol == #pushInstVar) ifTrue:[stackDelta := 1. extra := #index. ^ 34].
    (aSymbol == #pushOuterBlockArg) ifTrue:[stackDelta := 1. extra := #indexLevel. ^ 42].
    (aSymbol == #pushOuterBlockVar) ifTrue:[stackDelta := 1. extra := #indexLevel. ^ 128].

    (aSymbol == #storeMethodVar) ifTrue:[extra := #index. stackDelta := -1. ^ 37].
    (aSymbol == #storeBlockVar) ifTrue:[extra := #index. stackDelta := -1. ^ 38].
    (aSymbol == #storeInstVar) ifTrue:[extra := #index. stackDelta := -1. ^ 39].

    (aSymbol == #retTop) ifTrue:[stackDelta := -1. ^ 0].
    (aSymbol == #blockRetTop) ifTrue:[stackDelta := -1. ^ 6].

    (aSymbol == #retSelf) ifTrue:[^5].

    (aSymbol == #==) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^ 45].
    (aSymbol == #~~) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^ 46].

    (aSymbol == #falseJump) ifTrue:[stackDelta := -1. extra := #offset. ^ 50].
    (aSymbol == #trueJump) ifTrue:[stackDelta := -1. extra := #offset. ^ 51].
    (aSymbol == #nilJump) ifTrue:[stackDelta := -1. extra := #offset. ^ 52].
    (aSymbol == #notNilJump) ifTrue:[stackDelta := -1. extra := #offset. ^ 53].
    (aSymbol == #jump) ifTrue:[extra := #offset. ^ 54].
    (aSymbol == #makeBlock) ifTrue:[stackDelta := 1. extra := #offsetNvarNarg. ^ 55].
    (aSymbol == #zeroJump) ifTrue:[stackDelta := -1. extra := #offset. ^ 56].
    (aSymbol == #notZeroJump) ifTrue:[stackDelta := -1. extra := #offset. ^ 57].
    (aSymbol == #eqJump) ifTrue:[stackDelta := -2. extra := #offset. ^ 58].
    (aSymbol == #notEqJump) ifTrue:[stackDelta := -2. extra := #offset. ^ 59].

    (aSymbol == #send) ifTrue:[lineno := true. ^ 19].
    (aSymbol == #superSend) ifTrue:[lineno := true. ^ 20].

    (aSymbol == #drop) ifTrue:[stackDelta := -1. ^ 18].
    (aSymbol == #dup) ifTrue:[stackDelta := 1. ^ 47].

    (aSymbol == #pushClassVar) ifTrue:[stackDelta := 1. extra := #speciallit. ^ 35].
    (aSymbol == #pushClassInstVar) ifTrue:[stackDelta := 1. extra := #index. ^ 176].
    (aSymbol == #pushGlobal) ifTrue:[stackDelta := 1. extra := #speciallit. ^ 36].

    (aSymbol == #storeClassVar) ifTrue:[extra := #speciallit.stackDelta := -1. ^ 40].
    (aSymbol == #storeClassInstVar) ifTrue:[extra := #index.stackDelta := -1. ^ 177].
    (aSymbol == #storeGlobal) ifTrue:[extra := #speciallit. stackDelta := -1. ^ 41].
    (aSymbol == #storeOuterBlockVar) ifTrue:[stackDelta := -1. extra := #indexLevel. ^ 129].

    "optimized bytecodes"

    (aSymbol == #retNil) ifTrue:[^ 1].
    (aSymbol == #retTrue) ifTrue:[^ 2].
    (aSymbol == #retFalse) ifTrue:[^ 3].
    (aSymbol == #ret0) ifTrue:[^ 4].
    (aSymbol == #retNum) ifTrue:[extra := #number. ^ 127].

    (aSymbol == #pushChar) ifTrue:[stackDelta := 1. ^17].
    (aSymbol == #push0) ifTrue:[stackDelta := 1. ^120].
    (aSymbol == #push1) ifTrue:[stackDelta := 1. ^121].
    (aSymbol == #push2) ifTrue:[stackDelta := 1. ^139].
    (aSymbol == #pushMinus1) ifTrue:[stackDelta := 1. ^122].

    (aSymbol == #send0) ifTrue:[lineno := true. extra := #lit. ^21].
    (aSymbol == #send1) ifTrue:[lineno := true. extra := #lit. stackDelta := -1. ^22].
    (aSymbol == #send2) ifTrue:[lineno := true. extra := #lit. stackDelta := -2. ^23].
    (aSymbol == #send3) ifTrue:[lineno := true. extra := #lit. stackDelta := -3. ^24].

    (aSymbol == #sendSelf0) ifTrue:[lineno := true. extra := #lit. stackDelta := 1. ^180].
    (aSymbol == #sendSelf1) ifTrue:[lineno := true. extra := #lit. ^181].
    (aSymbol == #sendSelf2) ifTrue:[lineno := true. extra := #lit. stackDelta := -1. ^182].
    (aSymbol == #sendSelf3) ifTrue:[lineno := true. extra := #lit. stackDelta := -2. ^183].
    (aSymbol == #sendSelfDrop0) ifTrue:[lineno := true. extra := #lit. ^184].
    (aSymbol == #sendSelfDrop1) ifTrue:[lineno := true. extra := #lit. stackDelta := -1. ^185].
    (aSymbol == #sendSelfDrop2) ifTrue:[lineno := true. extra := #lit. stackDelta := -2. ^186].
    (aSymbol == #sendSelfDrop3) ifTrue:[lineno := true. extra := #lit. stackDelta := -3. ^187].

    (aSymbol == #sendDrop) ifTrue:[lineno := true. ^25].
    (aSymbol == #sendDrop0) ifTrue:[lineno := true. extra := #lit. stackDelta := -1. ^26].
    (aSymbol == #sendDrop1) ifTrue:[lineno := true. extra := #lit. stackDelta := -2. ^27].
    (aSymbol == #sendDrop2) ifTrue:[lineno := true. extra := #lit. stackDelta := -3. ^28].
    (aSymbol == #sendDrop3) ifTrue:[lineno := true. extra := #lit. stackDelta := -4. ^29].

    (aSymbol == #pushMethodVar1) ifTrue:[stackDelta := 1. ^80].
    (aSymbol == #pushMethodVar2) ifTrue:[stackDelta := 1. ^81].
    (aSymbol == #pushMethodVar3) ifTrue:[stackDelta := 1. ^82].
    (aSymbol == #pushMethodVar4) ifTrue:[stackDelta := 1. ^83].
    (aSymbol == #pushMethodVar5) ifTrue:[stackDelta := 1. ^84].
    (aSymbol == #pushMethodVar6) ifTrue:[stackDelta := 1. ^85].

    (aSymbol == #pushMethodArg1) ifTrue:[stackDelta := 1. ^86].
    (aSymbol == #pushMethodArg2) ifTrue:[stackDelta := 1. ^87].
    (aSymbol == #pushMethodArg3) ifTrue:[stackDelta := 1. ^88].
    (aSymbol == #pushMethodArg4) ifTrue:[stackDelta := 1. ^89].

    (aSymbol == #pushInstVar1) ifTrue:[stackDelta := 1. ^90].
    (aSymbol == #pushInstVar2) ifTrue:[stackDelta := 1. ^91].
    (aSymbol == #pushInstVar3) ifTrue:[stackDelta := 1. ^92].
    (aSymbol == #pushInstVar4) ifTrue:[stackDelta := 1. ^93].
    (aSymbol == #pushInstVar5) ifTrue:[stackDelta := 1. ^94].
    (aSymbol == #pushInstVar6) ifTrue:[stackDelta := 1. ^95].
    (aSymbol == #pushInstVar7) ifTrue:[stackDelta := 1. ^96].
    (aSymbol == #pushInstVar8) ifTrue:[stackDelta := 1. ^97].
    (aSymbol == #pushInstVar9) ifTrue:[stackDelta := 1. ^98].
    (aSymbol == #pushInstVar10) ifTrue:[stackDelta := 1. ^99].

    (aSymbol == #storeMethodVar1) ifTrue:[stackDelta := -1. ^100].
    (aSymbol == #storeMethodVar2) ifTrue:[stackDelta := -1. ^101].
    (aSymbol == #storeMethodVar3) ifTrue:[stackDelta := -1. ^102].
    (aSymbol == #storeMethodVar4) ifTrue:[stackDelta := -1. ^103].
    (aSymbol == #storeMethodVar5) ifTrue:[stackDelta := -1. ^104].
    (aSymbol == #storeMethodVar6) ifTrue:[stackDelta := -1. ^105].

    (aSymbol == #storeInstVar1) ifTrue:[stackDelta := -1. ^110].
    (aSymbol == #storeInstVar2) ifTrue:[stackDelta := -1. ^111].
    (aSymbol == #storeInstVar3) ifTrue:[stackDelta := -1. ^112].
    (aSymbol == #storeInstVar4) ifTrue:[stackDelta := -1. ^113].
    (aSymbol == #storeInstVar5) ifTrue:[stackDelta := -1. ^114].
    (aSymbol == #storeInstVar6) ifTrue:[stackDelta := -1. ^115].
    (aSymbol == #storeInstVar7) ifTrue:[stackDelta := -1. ^116].
    (aSymbol == #storeInstVar8) ifTrue:[stackDelta := -1. ^117].
    (aSymbol == #storeInstVar9) ifTrue:[stackDelta := -1. ^118].
    (aSymbol == #storeInstVar10) ifTrue:[stackDelta := -1. ^119].

    (aSymbol == #retMethodVar1) ifTrue:[^160].
    (aSymbol == #retMethodVar2) ifTrue:[^161].
    (aSymbol == #retMethodVar3) ifTrue:[^162].
    (aSymbol == #retMethodVar4) ifTrue:[^163].
    (aSymbol == #retMethodVar5) ifTrue:[^164].
    (aSymbol == #retMethodVar6) ifTrue:[^165].

    (aSymbol == #retInstVar1) ifTrue:[^166].
    (aSymbol == #retInstVar2) ifTrue:[^167].
    (aSymbol == #retInstVar3) ifTrue:[^168].
    (aSymbol == #retInstVar4) ifTrue:[^169].
    (aSymbol == #retInstVar5) ifTrue:[^170].
    (aSymbol == #retInstVar6) ifTrue:[^171].
    (aSymbol == #retInstVar7) ifTrue:[^172].
    (aSymbol == #retInstVar8) ifTrue:[^173].

    (aSymbol == #retMethodArg1) ifTrue:[^174].
    (aSymbol == #retMethodArg2) ifTrue:[^175].

    (aSymbol == #pushBlockArg1) ifTrue:[stackDelta := 1. ^140].
    (aSymbol == #pushBlockArg2) ifTrue:[stackDelta := 1. ^141].
    (aSymbol == #pushBlockArg3) ifTrue:[stackDelta := 1. ^142].
    (aSymbol == #pushBlockArg4) ifTrue:[stackDelta := 1. ^143].

    (aSymbol == #pushOuter1BlockArg) ifTrue:[stackDelta := 1. extra := #index. ^ 43].
    (aSymbol == #pushOuter2BlockArg) ifTrue:[stackDelta := 1. extra := #index. ^ 44].

    (aSymbol == #=) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^130].
    (aSymbol == #+) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^131].
    (aSymbol == #~=) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^132].
    (aSymbol == #-) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^133].
    (aSymbol == #class) ifTrue:[self addLiteral:aSymbol. ^134].
    (aSymbol == #x) ifTrue:[self addLiteral:aSymbol. ^106].
    (aSymbol == #y) ifTrue:[self addLiteral:aSymbol. ^107].
    (aSymbol == #width) ifTrue:[self addLiteral:aSymbol. ^108].
    (aSymbol == #height) ifTrue:[self addLiteral:aSymbol. ^109].
    (aSymbol == #origin) ifTrue:[self addLiteral:aSymbol. ^154].
    (aSymbol == #extent) ifTrue:[self addLiteral:aSymbol. ^155].
    (aSymbol == #at:) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^135].
    (aSymbol == #at:put:)ifTrue:[stackDelta := -2. self addLiteral:aSymbol. ^136].
    (aSymbol == #bitAnd:) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^137].
    (aSymbol == #bitOr:) ifTrue:[stackDelta := -1. self addLiteral:aSymbol. ^138].
    (aSymbol == #plus1) ifTrue:[self addLiteral:#+. ^123].
    (aSymbol == #minus1) ifTrue:[self addLiteral:#-. ^124].

    (aSymbol == #incMethodVar) ifTrue:[self addLiteral:#+. extra := #index. ^125].
    (aSymbol == #decMethodVar) ifTrue:[self addLiteral:#-. extra := #index. ^126].

    (aSymbol == #eq0) ifTrue:[self addLiteral:#==. ^48].
    (aSymbol == #ne0) ifTrue:[self addLiteral:#~~. ^49].

    (aSymbol == #>) ifTrue:[self addLiteral:aSymbol. stackDelta := -1. ^ 145].
    (aSymbol == #>=) ifTrue:[self addLiteral:aSymbol. stackDelta := -1. ^ 146].
    (aSymbol == #<) ifTrue:[self addLiteral:aSymbol. stackDelta := -1. ^ 147].
    (aSymbol == #<=) ifTrue:[self addLiteral:aSymbol. stackDelta := -1. ^ 148].
    (aSymbol == #next) ifTrue:[self addLiteral:aSymbol. ^ 149].
    (aSymbol == #peek) ifTrue:[self addLiteral:aSymbol. ^ 150].
    (aSymbol == #value) ifTrue:[self addLiteral:aSymbol. ^ 151].
    (aSymbol == #value:) ifTrue:[self addLiteral:aSymbol.  stackDelta := -1. ^ 152].
    (aSymbol == #size) ifTrue:[self addLiteral:aSymbol. ^ 153].
    (aSymbol == #mk0Block) ifTrue:[^ 156].
    (aSymbol == #mkNilBlock) ifTrue:[^ 157].

    (aSymbol == #falseJumpabs) ifTrue:[stackDelta := -1. extra := #absoffset. ^ 190].
    (aSymbol == #trueJumpabs) ifTrue:[stackDelta := -1. extra := #absoffset. ^ 191].
    (aSymbol == #nilJumpabs) ifTrue:[stackDelta := -1. extra := #absoffset. ^ 192].
    (aSymbol == #notNilJumpabs) ifTrue:[stackDelta := -1. extra := #absoffset. ^ 193].
    (aSymbol == #jumpabs) ifTrue:[extra := #absoffset. ^ 194].
    (aSymbol == #makeBlockabs) ifTrue:[stackDelta := 1. extra := #absoffsetNvarNarg. ^ 195].
    (aSymbol == #zeroJumpabs) ifTrue:[stackDelta := -1. extra := #absoffset. ^ 196].
    (aSymbol == #notZeroJumpabs) ifTrue:[stackDelta := -1. extra := #absoffset. ^ 197].
    (aSymbol == #eqJumpabs) ifTrue:[stackDelta := -2. extra := #absoffset. ^ 198].
    (aSymbol == #notEqJumpabs) ifTrue:[stackDelta := -2. extra := #absoffset. ^ 199].

    (aSymbol == #pushThisContext) ifTrue:[stackDelta := 1. ^ 144].

    self error:'invalid code symbol'.
    errorFlag := #Error
! !

!ByteCodeCompiler class methodsFor:'machine code constants'!

sharedCodeFunctionFor:aSymbol
    "return the address of a shared code-function;
     the code below looks ugly, but adds some speed to instvar-access
     methods"

    |codeSymbol|

    (aSymbol == #retSelf) ifTrue:[
%{
        extern OBJ __retSelf();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retSelf;
#endif
        RETURN ( _MKSMALLINT((int)__retSelf) );
%}
    ].
    (aSymbol == #retNil) ifTrue:[
%{
        extern OBJ __retNil();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retNil;
#endif
        RETURN ( _MKSMALLINT((int)__retNil) );
%}
    ].
    (aSymbol == #retTrue) ifTrue:[
%{
        extern OBJ __retTrue();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retTrue;
#endif
        RETURN ( _MKSMALLINT((int)__retTrue) );
%}
    ].
    (aSymbol == #retFalse) ifTrue:[
%{
        extern OBJ __retFalse();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retFalse;
#endif
        RETURN ( _MKSMALLINT((int)__retFalse) );
%}
    ].
    (aSymbol == #ret0) ifTrue:[
%{
        extern OBJ __ret0();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __ret0;
#endif
        RETURN ( _MKSMALLINT((int)__ret0) );
%}
    ].
    (aSymbol == #blockRet0) ifTrue:[
%{
        extern OBJ __bRet0();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __bRet0;
#endif
        RETURN ( _MKSMALLINT((int)__bRet0) );
%}
    ].
    (aSymbol == #blockRetNil) ifTrue:[
%{
        extern OBJ __bRetNil();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __bRetNil;
#endif
        RETURN ( _MKSMALLINT((int)__bRetNil) );
%}
    ].
    (aSymbol == #blockRetTrue) ifTrue:[
%{
        extern OBJ __bRetTrue();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __bRetTrue;
#endif
        RETURN ( _MKSMALLINT((int)__bRetTrue) );
%}
    ].
    (aSymbol == #blockRetFalse) ifTrue:[
%{
        extern OBJ __bRetFalse();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __bRetFalse;
#endif
        RETURN ( _MKSMALLINT((int)__bRetFalse) );
%}
    ].
    (aSymbol == #retInstVar1) ifTrue:[
%{
        extern OBJ __retInst0();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst0;
#endif
        RETURN ( _MKSMALLINT((int)__retInst0) );
%}
    ].
    (aSymbol == #retInstVar2) ifTrue:[
%{
        extern OBJ __retInst1();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst1;
#endif
        RETURN ( _MKSMALLINT((int)__retInst1) );
%}
    ].
    (aSymbol == #retInstVar3) ifTrue:[
%{
        extern OBJ __retInst2();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst2;
#endif
        RETURN ( _MKSMALLINT((int)__retInst2) );
%}
    ].
    (aSymbol == #retInstVar4) ifTrue:[
%{
        extern OBJ __retInst3();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst3;
#endif
        RETURN ( _MKSMALLINT((int)__retInst3) );
%}
    ].
    (aSymbol == #retInstVar5) ifTrue:[
%{
        extern OBJ __retInst4();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst4;
#endif
        RETURN ( _MKSMALLINT((int)__retInst4) );
%}
    ].
    (aSymbol == #retInstVar6) ifTrue:[
%{
        extern OBJ __retInst5();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst5;
#endif
        RETURN ( _MKSMALLINT((int)__retInst5) );
%}
    ].
    (aSymbol == #retInstVar7) ifTrue:[
%{
        extern OBJ __retInst6();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst6;
#endif
        RETURN ( _MKSMALLINT((int)__retInst6) );
%}
    ].
    (aSymbol == #retInstVar8) ifTrue:[
%{
        extern OBJ __retInst7();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst7;
#endif
        RETURN ( _MKSMALLINT((int)__retInst7) );
%}
    ].
    (aSymbol == #retInstVar9) ifTrue:[
%{
        extern OBJ __retInst8();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst8;
#endif
        RETURN ( _MKSMALLINT((int)__retInst8) );
%}
    ].
    (aSymbol == #retInstVar10) ifTrue:[
%{
        extern OBJ __retInst9();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst9;
#endif
        RETURN ( _MKSMALLINT((int)__retInst9) );
%}
    ].
    (aSymbol == #retInstVar11) ifTrue:[
%{
        extern OBJ __retInst10();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst10;
#endif
        RETURN ( _MKSMALLINT((int)__retInst10) );
%}
    ].
    (aSymbol == #retInstVar12) ifTrue:[
%{
        extern OBJ __retInst11();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst11;
#endif
        RETURN ( _MKSMALLINT((int)__retInst11) );
%}
    ].
    (aSymbol == #retInstVar13) ifTrue:[
%{
        extern OBJ __retInst12();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst12;
#endif
        RETURN ( _MKSMALLINT((int)__retInst12) );
%}
    ].
    (aSymbol == #retInstVar14) ifTrue:[
%{
        extern OBJ __retInst13();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst13;
#endif
        RETURN ( _MKSMALLINT((int)__retInst13) );
%}
    ].
    (aSymbol == #retInstVar15) ifTrue:[
%{
        extern OBJ __retInst14();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst14;
#endif
        RETURN ( _MKSMALLINT((int)__retInst14) );
%}
    ].
    (aSymbol == #retInstVar16) ifTrue:[
%{
        extern OBJ __retInst15();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst15;
#endif
        RETURN ( _MKSMALLINT((int)__retInst15) );
%}
    ].
    (aSymbol == #retInstVar17) ifTrue:[
%{
        extern OBJ __retInst16();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst16;
#endif
        RETURN ( _MKSMALLINT((int)__retInst16) );
%}
    ].
    (aSymbol == #retInstVar18) ifTrue:[
%{
        extern OBJ __retInst17();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst17;
#endif
        RETURN ( _MKSMALLINT((int)__retInst17) );
%}
    ].
    (aSymbol == #retInstVar19) ifTrue:[
%{
        extern OBJ __retInst18();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst18;
#endif
        RETURN ( _MKSMALLINT((int)__retInst18) );
%}
    ].
    (aSymbol == #retInstVar20) ifTrue:[
%{
        extern OBJ __retInst19();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst19;
#endif
        RETURN ( _MKSMALLINT((int)__retInst19) );
%}
    ].
    (aSymbol == #retInstVar21) ifTrue:[
%{
        extern OBJ __retInst20();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst20;
#endif
        RETURN ( _MKSMALLINT((int)__retInst20) );
%}
    ].
    (aSymbol == #retInstVar22) ifTrue:[
%{
        extern OBJ __retInst21();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst21;
#endif
        RETURN ( _MKSMALLINT((int)__retInst21) );
%}
    ].
    (aSymbol == #retInstVar23) ifTrue:[
%{
        extern OBJ __retInst22();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst22;
#endif
        RETURN ( _MKSMALLINT((int)__retInst22) );
%}
    ].
    (aSymbol == #retInstVar24) ifTrue:[
%{
        extern OBJ __retInst23();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst23;
#endif
        RETURN ( _MKSMALLINT((int)__retInst23) );
%}
    ].
    (aSymbol == #retInstVar25) ifTrue:[
%{
        extern OBJ __retInst24();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst24;
#endif
        RETURN ( _MKSMALLINT((int)__retInst24) );
%}
    ].
    (aSymbol == #retInstVar26) ifTrue:[
%{
        extern OBJ __retInst25();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst25;
#endif
        RETURN ( _MKSMALLINT((int)__retInst25) );
%}
    ].
    (aSymbol == #retInstVar27) ifTrue:[
%{
        extern OBJ __retInst26();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst26;
#endif
        RETURN ( _MKSMALLINT((int)__retInst26) );
%}
    ].
    (aSymbol == #retInstVar28) ifTrue:[
%{
        extern OBJ __retInst27();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst27;
#endif
        RETURN ( _MKSMALLINT((int)__retInst27) );
%}
    ].
    (aSymbol == #retInstVar29) ifTrue:[
%{
        extern OBJ __retInst28();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst28;
#endif
        RETURN ( _MKSMALLINT((int)__retInst28) );
%}
    ].
    (aSymbol == #retInstVar30) ifTrue:[
%{
        extern OBJ __retInst29();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst29;
#endif
        RETURN ( _MKSMALLINT((int)__retInst29) );
%}
    ].
    (aSymbol == #retInstVar31) ifTrue:[
%{
        extern OBJ __retInst30();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __retInst30;
#endif
        RETURN ( _MKSMALLINT((int)__retInst30) );
%}
    ].

    (aSymbol == #storeInstVar1) ifTrue:[
%{
        extern OBJ __setInst0();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst0;
#endif
        RETURN ( _MKSMALLINT((int)__setInst0) );
%}
    ].
    (aSymbol == #storeInstVar2) ifTrue:[
%{
        extern OBJ __setInst1();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst1;
#endif
        RETURN ( _MKSMALLINT((int)__setInst1) );
%}
    ].
    (aSymbol == #storeInstVar3) ifTrue:[
%{
        extern OBJ __setInst2();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst2;
#endif
        RETURN ( _MKSMALLINT((int)__setInst2) );
%}
    ].
    (aSymbol == #storeInstVar4) ifTrue:[
%{
        extern OBJ __setInst3();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst3;
#endif
        RETURN ( _MKSMALLINT((int)__setInst3) );
%}
    ].
    (aSymbol == #storeInstVar5) ifTrue:[
%{
        extern OBJ __setInst4();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst4;
#endif
        RETURN ( _MKSMALLINT((int)__setInst4) );
%}
    ].
    (aSymbol == #storeInstVar6) ifTrue:[
%{
        extern OBJ __setInst5();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst5;
#endif
        RETURN ( _MKSMALLINT((int)__setInst5) );
%}
    ].
    (aSymbol == #storeInstVar7) ifTrue:[
%{
        extern OBJ __setInst6();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst6;
#endif
        RETURN ( _MKSMALLINT((int)__setInst6) );
%}
    ].
    (aSymbol == #storeInstVar8) ifTrue:[
%{
        extern OBJ __setInst7();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst7;
#endif
        RETURN ( _MKSMALLINT((int)__setInst7) );
%}
    ].
    (aSymbol == #storeInstVar9) ifTrue:[
%{
        extern OBJ __setInst8();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst8;
#endif
        RETURN ( _MKSMALLINT((int)__setInst8) );
%}
    ].
    (aSymbol == #storeInstVar10) ifTrue:[
%{
        extern OBJ __setInst9();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst9;
#endif
        RETURN ( _MKSMALLINT((int)__setInst9) );
%}
    ].
    (aSymbol == #storeInstVar11) ifTrue:[
%{
        extern OBJ __setInst10();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst10;
#endif
        RETURN ( _MKSMALLINT((int)__setInst10) );
%}
    ].
    (aSymbol == #storeInstVar12) ifTrue:[
%{
        extern OBJ __setInst11();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst11;
#endif
        RETURN ( _MKSMALLINT((int)__setInst11) );
%}
    ].
    (aSymbol == #storeInstVar13) ifTrue:[
%{
        extern OBJ __setInst12();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst12;
#endif
        RETURN ( _MKSMALLINT((int)__setInst12) );
%}
    ].
    (aSymbol == #storeInstVar13) ifTrue:[
%{
        extern OBJ __setInst12();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst12;
#endif
        RETURN ( _MKSMALLINT((int)__setInst12) );
%}
    ].
    (aSymbol == #storeInstVar14) ifTrue:[
%{
        extern OBJ __setInst13();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst13;
#endif
        RETURN ( _MKSMALLINT((int)__setInst13) );
%}
    ].
    (aSymbol == #storeInstVar15) ifTrue:[
%{
        extern OBJ __setInst14();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst14;
#endif
        RETURN ( _MKSMALLINT((int)__setInst14) );
%}
    ].
    (aSymbol == #storeInstVar16) ifTrue:[
%{
        extern OBJ __setInst15();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst15;
#endif
        RETURN ( _MKSMALLINT((int)__setInst15) );
%}
    ].
    (aSymbol == #storeInstVar17) ifTrue:[
%{
        extern OBJ __setInst16();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst16;
#endif
        RETURN ( _MKSMALLINT((int)__setInst16) );
%}
    ].
    (aSymbol == #storeInstVar18) ifTrue:[
%{
        extern OBJ __setInst17();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst17;
#endif
        RETURN ( _MKSMALLINT((int)__setInst17) );
%}
    ].
    (aSymbol == #storeInstVar19) ifTrue:[
%{
        extern OBJ __setInst18();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst18;
#endif
        RETURN ( _MKSMALLINT((int)__setInst18) );
%}
    ].
    (aSymbol == #storeInstVar20) ifTrue:[
%{
        extern OBJ __setInst19();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst19;
#endif
        RETURN ( _MKSMALLINT((int)__setInst19) );
%}
    ].
    (aSymbol == #storeInstVar21) ifTrue:[
%{
        extern OBJ __setInst20();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst20;
#endif
        RETURN ( _MKSMALLINT((int)__setInst20) );
%}
    ].
    (aSymbol == #storeInstVar22) ifTrue:[
%{
        extern OBJ __setInst21();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst21;
#endif
        RETURN ( _MKSMALLINT((int)__setInst21) );
%}
    ].
    (aSymbol == #storeInstVar23) ifTrue:[
%{
        extern OBJ __setInst22();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst22;
#endif
        RETURN ( _MKSMALLINT((int)__setInst22) );
%}
    ].
    (aSymbol == #storeInstVar23) ifTrue:[
%{
        extern OBJ __setInst22();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst22;
#endif
        RETURN ( _MKSMALLINT((int)__setInst22) );
%}
    ].
    (aSymbol == #storeInstVar24) ifTrue:[
%{
        extern OBJ __setInst23();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst23;
#endif
        RETURN ( _MKSMALLINT((int)__setInst23) );
%}
    ].
    (aSymbol == #storeInstVar25) ifTrue:[
%{
        extern OBJ __setInst24();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst24;
#endif
        RETURN ( _MKSMALLINT((int)__setInst24) );
%}
    ].
    (aSymbol == #storeInstVar26) ifTrue:[
%{
        extern OBJ __setInst25();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst25;
#endif
        RETURN ( _MKSMALLINT((int)__setInst25) );
%}
    ].
    (aSymbol == #storeInstVar27) ifTrue:[
%{
        extern OBJ __setInst26();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst26;
#endif
        RETURN ( _MKSMALLINT((int)__setInst26) );
%}
    ].
    (aSymbol == #storeInstVar28) ifTrue:[
%{
        extern OBJ __setInst27();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst27;
#endif
        RETURN ( _MKSMALLINT((int)__setInst27) );
%}
    ].
    (aSymbol == #storeInstVar29) ifTrue:[
%{
        extern OBJ __setInst28();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst28;
#endif
        RETURN ( _MKSMALLINT((int)__setInst28) );
%}
    ].
    (aSymbol == #storeInstVar30) ifTrue:[
%{
        extern OBJ __setInst29();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst29;
#endif
        RETURN ( _MKSMALLINT((int)__setInst29) );
%}
    ].
    (aSymbol == #storeInstVar31) ifTrue:[
%{
        extern OBJ __setInst30();
#if defined(SYSV4) && defined(i386)
        OBJ (*dummy)() = __setInst30;
#endif
        RETURN ( _MKSMALLINT((int)__setInst30) );
%}
    ].
    ^  nil
! !

!ByteCodeCompiler methodsFor:'machine code generation'!

checkForSharedCode:symbolicCodeArray
    "if this method is a very simple one,
     we can use the shared compiled code"

    |codeSymbol nArgs index|

    symbolicCodeArray isNil ifTrue:[^ nil].
    codeSymbol := symbolicCodeArray at:1.
    nArgs := methodArgs size.
    (nArgs == 0) ifTrue:[
        (codeSymbol == #retSelf) ifTrue:[^ codeSymbol].
        (codeSymbol == #retTrue) ifTrue:[^ codeSymbol].
        (codeSymbol == #retFalse) ifTrue:[^ codeSymbol].
        (codeSymbol == #retNil) ifTrue:[^ codeSymbol].
        (codeSymbol == #ret0) ifTrue:[^ codeSymbol].
        ('retInstVar*' match:codeSymbol) ifTrue:[^ codeSymbol].

        (codeSymbol == #pushMethodArg1) ifTrue:[
            ((symbolicCodeArray at:2) == #storeInstVar) ifTrue:[
                index := symbolicCodeArray at:3.
                ((symbolicCodeArray at:4) == #retSelf) ifTrue:[
                    ^ ('storeInstVar' , index printString) asSymbol
                ].
                ^ nil
            ].
            ('storeInstVar*' match:(symbolicCodeArray at:2)) ifTrue:[
                ((symbolicCodeArray at:3) == #retSelf) ifTrue:[^ symbolicCodeArray at:2]
            ].
            ^ nil
        ].

        codeSymbol == #pushInstVar ifTrue:[
            index := symbolicCodeArray at:2.
            (symbolicCodeArray at:3) == #retTop ifTrue:[
                ^ ('retInstVar' , index printString) asSymbol
            ].
            ^ nil
        ]
    ].
    ^ nil
!

checkForMachineCode:symbolicCodeArray
    "if this method is a simple one,
     we can compile it into machine code"

    |code1 code2 code3 name|

    symbolicCodeArray isNil ifTrue:[^ nil].
    code1 := symbolicCodeArray at:1.
    (code1 == #retNum) ifTrue:[
        ^ self codeForRetNum:(symbolicCodeArray at:2)
    ].
    (code1 == #pushNum) ifTrue:[
        code2 := symbolicCodeArray at:3.
        (code2 == #retTop) ifTrue:[
            ^ self codeForRetNum:(symbolicCodeArray at:2)
        ].
        ^ nil
    ].
    (code1 == #pushMethodArg1) ifTrue:[
        code2 := symbolicCodeArray at:2.
        ((code2 == #storeGlobal)
        or:[code2 == #storeClassVar]) ifTrue:[
            code3 := symbolicCodeArray at:4.
            (code3 == #retSelf) ifTrue:[
                name := symbolicCodeArray at:3.
                ^ self codeForSetCell:name
            ]
        ].
        ^ nil
    ].

    (code1 == #pushGlobal) ifTrue:[
        code2 := symbolicCodeArray at:8.
        (code2 == #retTop) ifTrue:[
            name := symbolicCodeArray at:2.
            ^ self codeForRetCell:name
        ].
        ^ nil
    ].
    (code1 == #pushClassVar) ifTrue:[
        code2 := symbolicCodeArray at:8.
        (code2 == #retTop) ifTrue:[
            name := symbolicCodeArray at:2.
            ^ self codeForRetCell:name
        ].
        ^ nil
    ].
    (code1 == #pushLit) ifTrue:[
        code2 := symbolicCodeArray at:3.
        (code2 == #retTop) ifTrue:[
            ^ nil
        ].
        ^ nil
    ].
    ^ nil
!

codeForRetNum:value
     "^ number will be coded into machine code"

    |count b conIndex tagHi newCode|

    count := self codeProtoForRetNumEnd - self codeProtoForRetNum.

    b := ExternalBytes address:(self codeProtoForRetNum).

    "search for sequence 0x92345678"

    tagHi := false.
    1 to:count-3 do:[:index |
        (b at:index) == 16r92 ifTrue:[
            (b at:index+1) == 16r34 ifTrue:[
                (b at:index+2) == 16r56 ifTrue:[
                    (b at:index+3) == 16r78 ifTrue:[
                        conIndex := index.
                        tagHi := true
                    ]
                ]
            ]
        ]
    ].

    conIndex isNil ifTrue:["'search failed' printNewline. "^ nil].
    tagHi ifFalse:['low tag unsupported' printNewline. ^ nil].

    "allocate code ..."

    newCode := ExternalBytes newForText:count.
    newCode isNil ifTrue:[
        'alloc of text (size ' print. count print. ') failed' printNewline.
        ^ nil
    ].

    "copy from proto"
    1 to:count do:[:index |
        newCode at:index put:(b at:index)
    ].
    "put in ret-value"
    newCode at:conIndex   put:((value bitShift:-24) bitAnd:16rFF).
    newCode at:conIndex+1 put:((value bitShift:-16) bitAnd:16rFF).
    newCode at:conIndex+2 put:((value bitShift:-8) bitAnd:16rFF).
    newCode at:conIndex+3 put:(value bitAnd:16rFF).
    tagHi ifTrue:[
        newCode at:conIndex 
               put:((newCode at:conIndex) bitOr:16r80)
    ] ifFalse:[
    ].
'address is:' print. newCode address printNewline.
    ^ newCode address

    "ByteCodeCompiler new codeForRetNum:15"
!

codeForRetCell:aGlobalOrClassVariableSymbol
     "^ global will be coded into machine code"

    |cell count b conIndex newCode msbFirst|

    cell := Smalltalk cellAt:aGlobalOrClassVariableSymbol.
    cell isNil ifTrue:[^ nil].

    count := self codeProtoForRetCellEnd - self codeProtoForRetCell.

    b := ExternalBytes address:(self codeProtoForRetCell).

    msbFirst := true.

    "search for sequence 0x12345678 // 78563412"
    1 to:count - 3 do:[:index |
        (b at:index) == 16r12 ifTrue:[
            (b at:index+1) == 16r34 ifTrue:[
                (b at:index+2) == 16r56 ifTrue:[
                    (b at:index+3) == 16r78 ifTrue:[
                        conIndex := index
                    ]
                ]
            ]
        ].
        conIndex isNil ifTrue:[
            (b at:index) == 16r78 ifTrue:[
                (b at:index+1) == 16r56 ifTrue:[
                    (b at:index+2) == 16r34 ifTrue:[
                        (b at:index+3) == 16r12 ifTrue:[
                            conIndex := index.
                            msbFirst := false
                        ]
                    ]
                ]
            ]
        ]
    ].

    conIndex isNil ifTrue:["'search failed' printNewline. " ^ nil].

    "allocate code ..."

    newCode := ExternalBytes newForText:count.
    newCode isNil ifTrue:['alloc of text (size ' print. count print. ') failed' printNewline.^ nil].

    "copy from proto"
    1 to:count do:[:index |
        newCode at:index put:(b at:index)
    ].
    "put in cell address"
    msbFirst ifTrue:[
        newCode at:conIndex   put:((cell bitShift:-24) bitAnd:16rFF).
        newCode at:conIndex+1 put:((cell bitShift:-16) bitAnd:16rFF).
        newCode at:conIndex+2 put:((cell bitShift:-8) bitAnd:16rFF).
        newCode at:conIndex+3 put:(cell bitAnd:16rFF).
    ] ifFalse:[
        newCode at:conIndex+3 put:((cell bitShift:-24) bitAnd:16rFF).
        newCode at:conIndex+2 put:((cell bitShift:-16) bitAnd:16rFF).
        newCode at:conIndex+1 put:((cell bitShift:-8) bitAnd:16rFF).
        newCode at:conIndex   put:(cell bitAnd:16rFF).
    ].

'address is:' print. newCode address printNewline.
    ^ newCode address

    "ByteCodeCompiler new codeForRetCell:#Transcript"
!

codeForSetCell:aGlobalOrClassVariableSymbol
     "global := arg will be coded into machine code"

    |cell count b conIndex newCode|

    cell := Smalltalk cellAt:aGlobalOrClassVariableSymbol.
    cell isNil ifTrue:[^ nil].

    count := self codeProtoForSetCellEnd - self codeProtoForSetCell.

    b := ExternalBytes address:(self codeProtoForSetCell).

    "search for sequence 0x12345678"
    1 to:count - 3 do:[:index |
        (b at:index) == 16r12 ifTrue:[
            (b at:index+1) == 16r34 ifTrue:[
                (b at:index+2) == 16r56 ifTrue:[
                    (b at:index+3) == 16r78 ifTrue:[
                        conIndex := index
                    ]
                ]
            ]
        ]
    ].

    conIndex isNil ifTrue:["'search failed' printNewline." ^ nil].

    "allocate code ..."

    newCode := ExternalBytes newForData:count.
    newCode isNil ifTrue:['alloc of data (size ' print. count print. ') failed' printNewline.^ nil].

    "copy from proto"
    1 to:count do:[:index |
        newCode at:index put:(b at:index)
    ].
    "put in cell address"
    newCode at:conIndex   put:((cell bitShift:-24) bitAnd:16rFF).
    newCode at:conIndex+1 put:((cell bitShift:-16) bitAnd:16rFF).
    newCode at:conIndex+2 put:((cell bitShift:-8) bitAnd:16rFF).
    newCode at:conIndex+3 put:(cell bitAnd:16rFF).

'address is:' print. newCode address printNewline.
    ^ newCode address

    "ByteCodeCompiler new codeForSetCell:#xyz"
!

codeProtoForRetNum
%{   /* NOCONTEXT */
     extern OBJ __retNumProto();
#if defined(SYSV4) && defined(i386)
     OBJ (*dummy)() = __retNumProto;
#endif
     RETURN ( _MKSMALLINT((int)__retNumProto) );
%}
!

codeProtoForRetNumEnd
%{   /* NOCONTEXT */
     extern OBJ __retNumProtoEnd();
#if defined(SYSV4) && defined(i386)
     OBJ (*dummy)() = __retNumProtoEnd;
#endif
     RETURN ( _MKSMALLINT((int)__retNumProtoEnd) );
%}
!

codeProtoForRetCell
%{   /* NOCONTEXT */
     extern OBJ __retCellProto();
#if defined(SYSV4) && defined(i386)
     OBJ (*dummy)() = __retCellProto;
#endif
     RETURN ( _MKSMALLINT((int)__retCellProto) );
%}
!

codeProtoForRetCellEnd
%{   /* NOCONTEXT */
     extern OBJ __retCellProtoEnd();
#if defined(SYSV4) && defined(i386)
     OBJ (*dummy)() = __retCellProtoEnd;
#endif
     RETURN ( _MKSMALLINT((int)__retCellProtoEnd) );
%}
!

codeProtoForSetCell
%{   /* NOCONTEXT */
     extern OBJ __setCellProto();
#if defined(SYSV4) && defined(i386)
     OBJ (*dummy)() = __setCellProto;
#endif
     RETURN ( _MKSMALLINT((int)__setCellProto) );
%}
!

codeProtoForSetCellEnd
%{   /* NOCONTEXT */
     extern OBJ __setCellProtoEnd();
#if defined(SYSV4) && defined(i386)
     OBJ (*dummy)() = __setCellProtoEnd;
#endif
     RETURN ( _MKSMALLINT((int)__setCellProtoEnd) );
%}
! !