CompCode.st
author Claus Gittinger <cg@exept.de>
Mon, 12 Jan 1998 14:23:21 +0100
changeset 3165 b6bde90005a8
parent 3145 35167e4ad9a5
child 3218 78255e232c66
permissions -rw-r--r--
also try package-subdir of source-dir for classes source

"
 COPYRIGHT (c) 1994 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.
"

ExecutableFunction variableSubclass:#CompiledCode
	instanceVariableNames:'flags byteCode'
	classVariableNames:'NoByteCodeSignal InvalidByteCodeSignal InvalidInstructionSignal
		BadLiteralsSignal NonBooleanReceiverSignal ArgumentSignal'
	poolDictionaries:''
	category:'Kernel-Methods'
!

!CompiledCode class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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.
"
!

documentation
"
    This is an abstract class, to merge common attributes of Blocks and
    Methods i.e. describe all objects consisting of either compiled or 
    interpreted code.

    Instances of CompiledCode are not to be created by user code
    (the compilers create Blocks, Methods etc.)


    [Instance variables:]

      flags       <SmallInteger>    special flag bits coded in a number
      byteCode    <ByteArray>       bytecode if its an interpreted codeobject

      The block/methods literals are stored in the indexed instance variables.
      If there is only one indexed instvar, it contains a reference to an
      Object containing the literals.


    [Class variables:]

      NoByteCodeSignal              raised if a codeObject is about to be executed
                                    which has neither code nor byteCode (i.e. both are nil)
      InvalidByteCodeSignal         raised if byteCode is not an instance of ByteArray
      InvalidInstructionSignal      raised if an invalid instruction opcode is encountered
      BadLiteralsSignal             raised if literalArray is not an array
      NonBooleanReceiverSignal      raised for conditional jumps where receiver is not a boolean
      ArgumentSignal                raised if argument count is not what the codeObject expects

    all of these signals are children of ExecutionErrorSignal.

    NOTICE: layout known by runtime system and compiler - do not change

    [author:]
        Claus Gittinger
"
! !

!CompiledCode class methodsFor:'initialization'!

initialize
    "create signals raised by various errors"

    NoByteCodeSignal isNil ifTrue:[
        NoByteCodeSignal := ExecutionErrorSignal newSignalMayProceed:true.
        NoByteCodeSignal nameClass:self message:#noByteCodeSignal.
        NoByteCodeSignal notifierString:'nil byteCode in code-object - not executable'.

        InvalidByteCodeSignal := ExecutionErrorSignal newSignalMayProceed:true.
        InvalidByteCodeSignal nameClass:self message:#invalidByteCodeSignal.
        InvalidByteCodeSignal notifierString:'invalid byteCode in code-object - not executable'.

        InvalidInstructionSignal := ExecutionErrorSignal newSignalMayProceed:true.
        InvalidInstructionSignal nameClass:self message:#invalidInstructionSignal.
        InvalidInstructionSignal notifierString:'invalid instruction in code-object - not executable'.

        BadLiteralsSignal := ExecutionErrorSignal newSignalMayProceed:true.
        BadLiteralsSignal nameClass:self message:#badLiteralsSignal.
        BadLiteralsSignal notifierString:'bad literal table in code-object - should not happen'.

        NonBooleanReceiverSignal := ExecutionErrorSignal newSignalMayProceed:true.
        NonBooleanReceiverSignal nameClass:self message:#nonBooleanReceiverSignal.
        NonBooleanReceiverSignal notifierString:'if/while on non-boolean receiver'.

        ArgumentSignal := ExecutionErrorSignal newSignalMayProceed:true.
        ArgumentSignal nameClass:self message:#argumentSignal.
        ArgumentSignal notifierString:'bad argument(s)'.
    ]

    "Modified: 22.4.1996 / 16:33:38 / cg"
! !

!CompiledCode class methodsFor:'instance creation'!

new
    "create a new method with an inirect literal array
     stored in the first and only indexed instvar"

    ^ self basicNew:1.

    "Created: 24.6.1996 / 17:21:46 / stefan"
!

new:numberOfLiterals
    "create a new method with numberOfLiterals.
     Implementation note:
        If (self size) == 1, the only literal is an indirect literal
        containing an array of literals. Otherwise the literals
        are stored in self.
    "

    |nlits|

    nlits := numberOfLiterals.
    nlits <= 1 ifTrue:[
        nlits := nlits + 1.
    ].
    ^ self basicNew:nlits.

    "Created: 24.6.1996 / 17:20:13 / stefan"
    "Modified: 25.6.1996 / 14:25:14 / stefan"
! !

!CompiledCode class methodsFor:'Signal constants'!

argumentSignal
    "return the signal raised when something's wrong with the
     arguments"

    ^ ArgumentSignal
!

executionErrorSignal
    "return the parent-signal of all execution errors"

    ^ ExecutionErrorSignal
! !

!CompiledCode class methodsFor:'queries'!

isBuiltInClass
    "return true if this class is known by the run-time-system.
     Here, true is returned for myself, false for subclasses."

    ^ self == CompiledCode

    "Modified: 23.4.1996 / 15:57:03 / cg"
!

maxNumberOfArguments
    "return the maximum number of arguments a method can have.
     This is a limit in the VM, which may be removed in one of 
     the next versions ..."

%{  /* NOCONTEXT */
    RETURN (__MKSMALLINT(MAX_METHOD_ARGS));
%}
! !

!CompiledCode methodsFor:'ST-80 compatibility'!

getSource
    "return the code objects source code, nil if none is available"

    ^ self source.

    "Created: 19.6.1997 / 16:32:15 / cg"
!

getSourceForUserIfNone:aBlock
    "return the code objects source code.
     If none is available, return the result from evaluating aBlock."

    |src| 

    Screen current shiftDown ifTrue:[^ aBlock value].
    src := self source.
    src isNil ifTrue:[^ aBlock value].
    ^ src withoutTrailingSeparators

    "Modified: 19.6.1997 / 16:31:53 / cg"
!

withAllBlockMethodsDo:aBlock
    aBlock value:self

    "Created: 18.4.1997 / 20:42:07 / cg"
! !

!CompiledCode methodsFor:'accessing'!

allLiterals
    "return a collection of all literals (includes all block literals)"

    ^ self literals ? #()

    "Modified: 19.6.1997 / 17:37:52 / cg"
!

allSymbolLiterals
    "return a collection of all symbol-literals"

    ^ self allLiterals select:[:lit | lit isSymbol]

    "Modified: / 19.6.1997 / 17:37:52 / cg"
    "Created: / 1.11.1997 / 13:14:44 / cg"
!

byteCode
    "return the bytecode (a ByteArray)"

    ^ byteCode
!

changeLiteral:aLiteral to:newLiteral
    "change aLiteral to newLiteral"

    |lits nLits "{ Class: SmallInteger }" |

    self size == 1 ifTrue:[
        lits := self at:1.
    ] ifFalse:[
        lits := self.
    ].

    nLits := lits size.
    1 to:nLits do:[:i|
        (lits at:i) == aLiteral ifTrue:[
            lits at:i put:newLiteral.
            ^ true.
        ].
    ].
    ^ false.

    "Created: 24.6.1996 / 15:08:11 / stefan"
    "Modified: 24.6.1996 / 17:07:56 / stefan"
    "Modified: 4.7.1996 / 11:12:39 / cg"
!

decompiler
    ^ Decompiler

    "Created: 30.7.1997 / 16:36:40 / cg"
!

do:aBlock
    "same as #literalsDo:, in order to get common protocol with Array"

    ^ self literalsDo:aBlock

    "Modified: 25.6.1996 / 22:16:44 / stefan"
!

literals
    "return the literal array"

    |lits numLits "{ Class: SmallInteger }"|

    (numLits := self size) == 1 ifTrue:[
        ^ self at:1.
    ].

    lits := Array new:numLits.
    1 to:numLits do:[:i|
        lits at:i put:(self at:i).
    ].
    ^ lits.

    "
     (CompiledCode compiledMethodAt:#literals) literals
    "

    "Modified: 24.6.1996 / 17:12:06 / stefan"
    "Modified: 30.1.1997 / 17:09:06 / cg"
!

literalsDetect:aBlock ifNone:exceptionBlock
    "execute a one arg block for each of our literals.
     return the first literal for which aBlock returns true"

    |lits theLit numLits "{Class: SmallInteger }"|

    self size == 1 ifTrue:[
        lits := self at:1.
    ] ifFalse:[
        lits := self.
    ].

    numLits := lits size.
    1 to:numLits do:[:i |
        theLit := lits at:i.
        (aBlock value:theLit) ifTrue:[
            ^ theLit.
        ].
    ].
    ^ exceptionBlock value.

    "Created: 24.6.1996 / 14:27:35 / stefan"
    "Modified: 24.6.1996 / 17:13:02 / stefan"
    "Modified: 30.1.1997 / 16:24:04 / cg"
!

literalsDo:aBlock
    "execute a one arg block for each of our literals"

    |lits numLits "{ Class: SmallInteger }" |

    self size == 1 ifTrue:[
        lits := self at:1.
    ] ifFalse:[
        lits := self.
    ].

    numLits := lits size.
    1 to:numLits do:[:i |
        aBlock value:(lits at:i)
    ].

    "Created: 24.6.1996 / 14:17:12 / stefan"
    "Modified: 24.6.1996 / 17:13:28 / stefan"
    "Modified: 30.1.1997 / 17:08:05 / cg"
!

mclass
    "return the class of the receivers home method.
     Thats the class of the method where the block was compiled."

    ^ self homeMethod mclass

    "Modified: 19.6.1997 / 16:24:58 / cg"
    "Created: 19.6.1997 / 16:27:34 / cg"
! !

!CompiledCode methodsFor:'converting'!

makeRealMethod
    "by default, we are a real method.
     Subclasses (e.g. LazyMethod) may redefine this"

    ^ self

    "Created: 7.6.1996 / 12:45:50 / stefan"
! !

!CompiledCode methodsFor:'error handling'!

badArgumentArray
    "{ Pragma: +optSpace }"

    "this error is triggered, if a non array is passed to 
     #valueWithReceiver:.. type of methods"

    ^ ArgumentSignal
        raiseRequestWith:self
        errorString:'argumentArray must be an Array'

    "Modified: 4.11.1996 / 22:46:52 / cg"
!

badLiteralTable
    "{ Pragma: +optSpace }"

    "this error is triggered, when a block/method is called with a bad literal
     array (i.e. non-array) - this can only happen, if the
     compiler is broken or someone played around with a blocks/methods
     literal table or the GC is broken and corrupted it."

    ^ BadLiteralsSignal raise.

    "Modified: 4.11.1996 / 22:46:55 / cg"
!

invalidByteCode
    "{ Pragma: +optSpace }"

    "this error is triggered when the interpreter tries to execute a
     code object, where the byteCode is nonNil, but not a ByteArray.
     Can only happen when Compiler/runtime system is broken or
     someone played around with a blocks/methods code."

    ^ InvalidByteCodeSignal raise.

    "Modified: 4.11.1996 / 22:46:59 / cg"
!

invalidInstruction
    "{ Pragma: +optSpace }"

    "this error is triggered when the bytecode-interpreter tries to
     execute an invalid bytecode instruction.
     Can only happen when Compiler/runtime system is broken or
     someone played around with a blocks/methods code."

    ^ InvalidInstructionSignal raise.

    "Modified: 4.11.1996 / 22:47:03 / cg"
!

noByteCode
    "{ Pragma: +optSpace }"

    "this error is triggered when the interpreter tries to execute a
     code object, where both the code and byteCode instances are nil.
     This can happen if:
        - the Compiler/runtime system is broken, (should not happen)

        - someone played around with a block/method, (you should not do this)

        - compilation of a lazy method failed
          (i.e. the lazy method contains an error or
           it contains primitive code and there is no stc compiler available)

        - an unloaded object modules method is called for.

     Only the first case is to be considered serious 
     - it should not happen if the system is used correctly."

    ^ NoByteCodeSignal raise.

    "Modified: 4.11.1996 / 22:47:07 / cg"
!

receiverNotBoolean:anObject
    "{ Pragma: +optSpace }"

    "this error is triggered when the bytecode-interpreter tries to
     execute ifTrue:/ifFalse or whileTrue: - type of expressions where the
     receiver is neither true nor false.
     Machine compiled code does not detect this, and may behave undeterministec."

    ^ NonBooleanReceiverSignal raise.

    "Modified: 4.11.1996 / 22:47:11 / cg"
!

tooManyArguments
    "{ Pragma: +optSpace }"

    "this error is triggered, when a method/block tries to perform a send with
     more arguments than supported by the interpreter. 
     This can only happen, if the compiler has been changed without 
     updating the VM, since the compiler checks for allowed number of
     arguments."

    ^ ArgumentSignal
        raiseRequestWith:self
        errorString:'too many args in send'

    "Modified: 4.11.1996 / 22:47:14 / cg"
!

wrongNumberOfArguments:numberGiven
    "{ Pragma: +optSpace }"

    "this error is triggered by the VM, if a method is called with a wrong number
     of arguments. 
     This only applies to #valueWithReceiverXXX and #perform:withArguments: - sends.
     With a normal send, this error cannot happen."

    ^ ArgumentSignal
        raiseRequestWith:self
        errorString:(self class name ,
                     ' got ' , numberGiven printString ,
                     ' arg(s) where ' , self numArgs printString , ' expected')

    "Modified: 1.8.1997 / 00:23:10 / cg"
! !

!CompiledCode methodsFor:'executing'!

valueWithReceiver:anObject arguments:argArray
    "low level call of a methods code - BIG DANGER ALERT.
     Perform the receiver-method on anObject as receiver and argArray as
     arguments. This does NO message lookup at all and mimics a
     traditional function call.
     This method is provided for debugging- and breakpoint-support 
     (replacing a method by a stub and recalling the original), or to implement
     experimental MI implementations - it is not for general use. 

     The receiver must be a method compiled in anObjects class or one of its 
     superclasses and also, the number of arguments given must match the methods
     expectations -
     - otherwise strange things (and also strange crashes) can occur.
     The system is NOT always detecting a wrong method/receiver combination.
     YOU HAVE BEEN WARNED."

    ^ self 
        valueWithReceiver:anObject 
        arguments:argArray 
        selector:nil 
        search:nil
        sender:nil

    "Modified: 4.4.1997 / 23:33:56 / cg"
    "Created: 30.7.1997 / 12:04:52 / cg"
!

valueWithReceiver:anObject arguments:argArray selector:aSymbol
    "low level call of a methods code - BIG DANGER ALERT.
     Perform the receiver-method on anObject as receiver and argArray as
     arguments. This does NO message lookup at all and mimics a
     traditional function call.
     This method is provided for debugging- and breakpoint-support 
     (replacing a method by a stub and recalling the original), or to implement
     experimental MI implementations - it is not for general use. 

     The receiver must be a method compiled in anObjects class or one of its 
     superclasses and also, the number of arguments given must match the methods
     expectations -
     - otherwise strange things (and also strange crashes) can occur.
     The system is NOT always detecting a wrong method/receiver combination.
     YOU HAVE BEEN WARNED."

    ^ self 
        valueWithReceiver:anObject 
        arguments:argArray 
        selector:aSymbol 
        search:nil
        sender:nil

    "Modified: 4.4.1997 / 23:34:08 / cg"
    "Created: 30.7.1997 / 12:04:49 / cg"
!

valueWithReceiver:anObject arguments:argArray selector:aSymbol search:aClass
    "low level call of a methods code - BIG DANGER ALERT.
     Perform the receiver-method on anObject as receiver and argArray as
     arguments. This does NO message lookup at all and mimics a
     traditional function call.
     This method is provided for debugging- and breakpoint-support 
     (replacing a method by a stub and recalling the original), or to implement
     experimental MI implementations - it is not for general use. 

     The receiver must be a method compiled in anObjects class or one of its 
     superclasses and also, the number of arguments given must match the methods
     expectations -
     - otherwise strange things (and also strange crashes) can occur.
     The system is NOT always detecting a wrong method/receiver combination.
     YOU HAVE BEEN WARNED."

    ^ self 
        valueWithReceiver:anObject 
        arguments:argArray 
        selector:aSymbol 
        search:nil
        sender:nil

    "Modified: 4.4.1997 / 23:34:19 / cg"
    "Created: 30.7.1997 / 12:04:46 / cg"
!

valueWithReceiver:anObject arguments:argArray selector:aSymbol search:aClass sender:virtualSender
    "low level call of a methods code - BIG DANGER ALERT.
     Perform the receiver-method on anObject as receiver and argArray as
     arguments. This does NO message lookup at all and mimics a
     traditional function call.
     This method is provided for debugging- and breakpoint-support 
     (replacing a method by a stub and recalling the original), or to implement
     experimental MI implementations - it is not for general use. 

     The receiver must be a method compiled in anObjects class or one of its 
     superclasses and also, the number of arguments given must match the methods
     expectations -
     - otherwise strange things (and also strange crashes) can occur.
     The system is NOT always detecting a wrong method/receiver combination.
     YOU HAVE BEEN WARNED."

%{
    OBJFUNC code;
    OBJ searchClass;
    static struct inlineCache dummy = _DUMMYILC0;
    int nargs;
    OBJ *ap;

    /*
     * args must be an array, or nil
     */
    if (__isArray(argArray)) {
        nargs = __arraySize(argArray);
        ap = __ArrayInstPtr(argArray)->a_element;
    } else {
        if (argArray != nil) {
            goto badArgs;
        }
        nargs = 0;
    }

#ifdef F_NARGS
    if (((__intVal(__INST(flags)) & F_NARGS) >> F_NARGSHIFT) == nargs) 
#endif
    {
        code = __MethodInstPtr(self)->m_code;
        if (aClass == nil) {
            searchClass = dummy.ilc_class = __Class(anObject);
        } else {
            searchClass = dummy.ilc_class = aClass;
        }

        if (nargs <= 15) {
	  OBJ rslt;
#ifdef CONTEXT_DEBUG
	  OBJ sav = __thisContext;
#endif

          /*
           * add virtual sender (unwinding) here later,
           * to allow hiding contexts in lazy methods.
           * (this is cosmetics only; therefore its done later)
           */
          if (code) {
            /* compiled code */
            switch (nargs) {
                case 0:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy);
		    break;

                case 1:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, ap[0]);
		    break;

                case 2:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, ap[0], ap[1]);
		    break;

                case 3:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, ap[0], ap[1], ap[2]);
		    break;

                case 4:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3]);
		    break;

                case 5:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4]);
		    break;

                case 6:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5]);
		    break;

                case 7:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6]);
		    break;

                case 8:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6], ap[7]);
		    break;

                case 9:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6], ap[7], ap[8]);
		    break;

                case 10:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6], ap[7], ap[8], 
                                 ap[9]);
		    break;

                case 11:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6], ap[7], ap[8], 
                                 ap[9], ap[10]);
		    break;

                case 12:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6], ap[7], ap[8], 
                                 ap[9], ap[10], ap[11]);
		    break;

                case 13:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6], ap[7], ap[8], 
                                 ap[9], ap[10], ap[11], ap[12]);
		    break;

                case 14:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6], ap[7], ap[8], 
                                 ap[9], ap[10], ap[11], ap[12], ap[13]);
		    break;

                case 15:
                    rslt = (*code)(anObject, aSymbol, searchClass, &dummy, 
                                 ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6], ap[7], ap[8], 
                                 ap[9], ap[10], ap[11], ap[12], ap[13], ap[14]);
		    break;
            }
          } else {
            /* interpreted code */
#ifdef PASS_ARG_POINTER
            rslt = __interpret(self, nargs, anObject, aSymbol, searchClass, &dummy, ap);
#else
            switch (nargs) {
                case 0:
                    rslt = __interpret(self, 0, anObject, aSymbol, searchClass, &dummy);
		    break;

                case 1:
                    rslt = __interpret(self, 1, anObject, aSymbol, searchClass, &dummy,
                                   ap[0]);
		    break;

                case 2:
                    rslt = __interpret(self, 2, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1]);
		    break;

                case 3:
                    rslt = __interpret(self, 3, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2]);
		    break;

                case 4:
                    rslt = __interpret(self, 4, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3]);
		    break;

                case 5:
                    rslt = __interpret(self, 5, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4]);
		    break;

                case 6:
                    rslt = __interpret(self, 6, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5]);
		    break;

                case 7:
                    rslt = __interpret(self, 7, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6]);
		    break;

                case 8:
                    rslt = __interpret(self, 8, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6],
                                   ap[7]);
		    break;

                case 9:
                    rslt = __interpret(self, 9, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6],
                                   ap[7], ap[8]);
		    break;

                case 10:
                    rslt = __interpret(self, 10, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6],
                                   ap[7], ap[8], ap[9]);
		    break;

                case 11:
                    rslt = __interpret(self, 11, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6],
                                   ap[7], ap[8], ap[9], ap[10]);
		    break;

                case 12:
                    rslt = __interpret(self, 12, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6],
                                   ap[7], ap[8], ap[9], ap[11]);
		    break;

                case 13:
                    rslt = __interpret(self, 13, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6],
                                   ap[7], ap[8], ap[9], ap[11], ap[12]);
		    break;

                case 14:
                    rslt = __interpret(self, 14, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6],
                                   ap[7], ap[8], ap[9], ap[11], ap[12], ap[13]);
		    break;

                case 15:
                    rslt = __interpret(self, 15, anObject, aSymbol, searchClass, &dummy,
                                   ap[0], ap[1], ap[2], ap[3], ap[4], ap[5], ap[6],
                                   ap[7], ap[8], ap[9], ap[11], ap[12], ap[13], ap[14]);
		    break;
            }
#endif
          }
#ifdef CONTEXT_DEBUG
	  if (sav != __thisContext) {
	      if (code) {
	          printf("CONTEXT BOTCH after execution of %x\n", code);
	      } else {
	          printf("CONTEXT BOTCH after execution of interpreted method\n");
	          printf("code now: %x\n", __MethodInstPtr(self)->m_code);
	      }
	      printf("context before:\n");
	      __dumpObject__(sav);
	      printf("context now:\n");
	      __dumpObject__(__thisContext);
	  }
#endif
	  RETURN (rslt);
        }
    }
    badArgs: ;
%}.
    (argArray isMemberOf:Array) ifFalse:[
        "
         arguments must be either nil or an array
        "
        ^ self badArgumentArray
    ].

    (argArray size ~~ self numArgs) ifTrue:[
        "
         the method expects a different number of arguments
        "
        ^ self wrongNumberOfArguments:argArray size
    ].
    
    "/ the VM only supports a limited number of arguments in sends
    "/ (currently, 15)
    
    ^ self tooManyArguments

    "
     (Float compiledMethodAt:#+) 
        valueWithReceiver:1.0 arguments:#(2.0)

     'the next example is a wrong one - which is detected by True's method ...'.
     (True compiledMethodAt:#printString) 
        valueWithReceiver:false arguments:nil

     'the next example is a wrong one - it is nowhere detected
      and a wrong value returned ...'.
     (Point compiledMethodAt:#x) 
        valueWithReceiver:(1->2) arguments:nil

     'the next example is VERY bad one - it is nowhere detected
      and may crash the system WARNING: save your work before doing this ...'.
     (Point compiledMethodAt:#x) 
        valueWithReceiver:(Object new) arguments:nil

     'the next example is a wrong one - which is detected here ...'.
     (Object compiledMethodAt:#printOn:)
        valueWithReceiver:false arguments:nil

     'the next example is a wrong one - which is detected here ...'.
     (Object compiledMethodAt:#printOn:)
        valueWithReceiver:false arguments:#() 
    "
! !

!CompiledCode methodsFor:'private accessing'!

byteCode:aByteArray
    "set the bytecode field - DANGER ALERT"

    byteCode := aByteArray
!

checked:aBoolean
    "set/clear the flag bit stating that this method has already been checked
     by the just-in-time compiler. Setting the flag prevents it from
     trying any compilation.
     Not for public use - for VM debugging only."

%{  /* NOCONTEXT */

    INT newFlags = __intVal(__INST(flags));

    /* made this a primitive to get define in stc.h */
    if (aBoolean == true)
        newFlags |= F_CHECKED;
    else
        newFlags &= ~F_CHECKED;

    __INST(flags) = __MKSMALLINT(newFlags);
%}
!

dynamic
    "return the flag stating that the machine code was created
     dynamically (from bytecode) or loaded dynamically from an objectFile
     (i.e. has machineCode, but is not in the executable)."

%{  /* NOCONTEXT */

    /* made this a primitive to get define in stc.h */

    RETURN (( (INT)(__INST(flags)) & __MASKSMALLINT(F_DYNAMIC)) ? true : false);
%}
!

literals:aLiteralArray 
    "set the literal array for evaluation - DANGER ALERT"

    |i|

    aLiteralArray isNil ifTrue:[
        ^ self.
    ].

    self size == 1 ifTrue:[
        self at:1 put:aLiteralArray.
    ] ifFalse:[
        i := 1.
        aLiteralArray do:[:literal|
            self at:i put:literal.
            i := i + 1.
        ].
    ].

    "Modified: 25.6.1996 / 22:13:08 / stefan"
!

markFlag
    "return the mark bits value as a boolean"

%{  /* NOCONTEXT */

    /* made this a primitive to get define in stc.h */

    RETURN (( (INT)(__INST(flags)) & __MASKSMALLINT(F_MARKBIT)) ? true : false);
%}
!

markFlag:aBoolean
    "set/clear the mark flag bit.
     This bit is not used by the VM, but instead free to mark codeObjects
     for any (debugging/tracing) use. For example, the coverage test uses
     these to mark reached methods. (inspired by a note in c.l.s)"

%{  /* NOCONTEXT */

    INT newFlags = __intVal(__INST(flags));

    /* made this a primitive to get define in stc.h */
    if (aBoolean == true)
	newFlags |= F_MARKBIT;
    else
	newFlags &= ~F_MARKBIT;

    __INST(flags) = __MKSMALLINT(newFlags);
%}
! !

!CompiledCode methodsFor:'private-compiler interface'!

flags:newFlags
    "set the flags (number of method variables, stacksize).
     WARNING: for internal use by the compiler only.
              playing around here with incorrect values 
              may crash smalltalk badly.

     Dont depend on the values in the flag field - its interpretations
     may change without notice."

    "/ protect myself a bit - putting in an object would crash me ...

    (newFlags isMemberOf:SmallInteger) ifTrue:[
        flags := newFlags
    ]

    "Modified: 8.3.1996 / 13:26:05 / cg"
    "Created: 13.4.1997 / 00:01:11 / cg"
!

numberOfArgs:aNumber
    "set the number of arguments, the codeObject expects.
     WARNING: for internal use by the compiler only.     
              playing around here with incorrect values 
              may (will ?)  crash smalltalk badly.

     The limitation in the max. number of arguments is due to the
     missing SENDxx functions in the VM and cases in #perform. This too 
     will be removed in a later release, allowing any number of arguments."

    (aNumber between:0 and:self class maxNumberOfArguments) ifFalse:[
        self error:('ST/X only supports up to a maximum of ' ,
                    self class maxNumberOfArguments printString ,
                    ' method arguments').
        ^ self
    ].
%{
    /* made this a primitive to get define in stc.h */
#ifdef F_NARGS
    __INST(flags) = __MKSMALLINT( (__intVal(__INST(flags)) & ~F_NARGS) | (__intVal(aNumber) << F_NARGSHIFT) );
#endif
%}


!

numberOfVars:aNumber
    "set the number of local variables - for use by compiler only.
     WARNING: for internal use by the compiler only.     
              playing around here with incorrect values 
              may (will ?)  crash smalltalk badly."

%{  /* NOCONTEXT */
    INT f = __intVal(__INST(flags));

    /* made this a primitive to get define in stc.h */
    if (__isSmallInteger(aNumber)) {
        f = (f & ~F_NVARS) | (__intVal(aNumber) << F_NVARSHIFT);
        __INST(flags) = __MKSMALLINT(f);
    }
%}


!

stackSize
    "return thedepth of the local stack in the context.

     WARNING: for internal use by ST/X debuggers only.
              This method may be removed without notice."

%{  /* NOCONTEXT */
    int n = (__intVal(__INST(flags)) & F_NSTACK) >> F_NSTACKSHIFT;

    /* made this a primitive to get define in stc.h */
    RETURN (__MKSMALLINT(n));
%}

!

stackSize:aNumber
    "set the depth of the local stack.

     WARNING: for internal use by the compiler only.
              playing around here with incorrect values 
              may crash smalltalk badly.
              (if the runtime library was compiled with DEBUG, 
               a bad stack will be detected and triggers an error)"

%{  /* NOCONTEXT */
    INT f = __intVal(__INST(flags));

    /* made this a primitive to get define in stc.h */
    if (__isSmallInteger(aNumber)) {
        f = (f & ~F_NSTACK) | (__intVal(aNumber) << F_NSTACKSHIFT);
        __INST(flags) = __MKSMALLINT(f);
    }
%}

! !

!CompiledCode methodsFor:'queries'!

decompileTo:aStream
    |decompiler|

    decompiler := self decompiler.
    decompiler notNil ifTrue:[
        Autoload autoloadFailedSignal handle:[:ex |
            ex return
        ] do:[
            decompiler autoload.
        ].
    ].
    (decompiler isNil or:[decompiler isLoaded not]) ifTrue:[
        ^ false
    ].

    decompiler decompile:self to:aStream.
    ^ true

    "Created: 16.4.1996 / 20:25:40 / cg"
    "Modified: 30.7.1997 / 16:37:14 / cg"
!

isExecutable
    "return true, if this method is executable.
     I.e. neither an invalidated nor an unloaded method"

    self isInvalid ifTrue:[^ false].
    ^ self byteCode notNil or:[self code notNil]

    "Created: 16.4.1996 / 17:52:16 / cg"
!

isUnloaded
    "return true, if the methods machine code has been unloaded
     from the system (i.e. it is not executable)."

    ^ (self code isNil and:[self byteCode isNil])

    "Created: 16.4.1996 / 17:51:47 / cg"
!

numArgs
    "return the number of arguments, the method expects." 

%{  /* NOCONTEXT */
    /* made this a primitive to get define in stc.h */

    RETURN (__MKSMALLINT((__intVal(__INST(flags)) & F_NARGS) >> F_NARGSHIFT));
%}.
    "
     The old implementation simply counted the arguments from
     the methods source - new versions include this information
     in the flag instVar, for more security in #perform:
    "

    "
     (Method compiledMethodAt:#source) numArgs  
     (Method compiledMethodAt:#source:) numArgs 
    "
!

messages
    "return a Set of all symbols referenced by this thingy.
     (this is more than the message selectors, since also global names
     and symbols found in immediate arrays are included)."

    |symbolSet|

    symbolSet := IdentitySet new.
    self literalsDo: [ :lit |
        lit isSymbol ifTrue: [
            symbolSet add: lit
        ] ifFalse: [
            lit isArray ifTrue: [
                lit traverse: [ :el |
                    el isSymbol ifTrue: [symbolSet add: el]
                ]
            ]
        ]
    ].
    ^ symbolSet

    "
     (CompiledCode compiledMethodAt:#messages) messages 
    "

    "Modified: 25.6.1996 / 22:24:20 / stefan"
!

numVars
    "return the number of block local variables. 
     Do not depend on the returned value - future optimizations
     may change things here (i.e. when moving locals into
     surrounding context for inlining).
     - for debugging only."

%{  /* NOCONTEXT */
    /* made this a primitive to get define in stc.h */

    RETURN (__MKSMALLINT((__intVal(__INST(flags)) & F_NVARS) >> F_NVARSHIFT));
%}



!

referencesGlobal:aGlobalSymbol
    "return true, if this method references the global
     bound to aGlobalSymbol.
     For now, this is the same as #referencesLiteral:,
     but this might change in the future to perform a deeper
     analyzes on the bytecodes, to detect implizit global
     refs (as done by some special bytecodes)"

    ^ self referencesLiteral:aGlobalSymbol

    "
     (CompiledCode compiledMethodAt:#referencesGlobal:) referencesGlobal:#literalsDetect:ifNone:
     (CompiledCode compiledMethodAt:#referencesGlobal:) referencesGlobal:#bla
    "

    "Modified: / 24.6.1996 / 15:41:59 / stefan"
    "Modified: / 28.10.1997 / 13:11:11 / cg"
!

referencesLiteral:aLiteral
    "return true, if this method references the given literal."

    ^ (self literalsDetect:[:lit| lit == aLiteral] ifNone:[false]) ~~ false.

    "
     (CompiledCode compiledMethodAt:#referencesLiteral:) referencesGlobal:#literalsDetect:ifNone:
     (CompiledCode compiledMethodAt:#referencesLiteral:) referencesGlobal:#bla
    "

    "Modified: / 24.6.1996 / 15:41:59 / stefan"
    "Created: / 28.10.1997 / 13:09:40 / cg"
!

resources
    ^ nil

    "Created: / 3.11.1997 / 09:09:01 / cg"
! !

!CompiledCode class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Attic/CompCode.st,v 1.60 1998-01-05 17:21:31 cg Exp $'
! !
CompiledCode initialize!