CompiledCode.st
author Stefan Vogel <sv@exept.de>
Thu, 13 Jun 1996 00:11:10 +0200
changeset 1461 dd25bb1e9973
parent 1293 02fb05148c98
child 1493 33e226c7d187
permissions -rw-r--r--
Use methodDictionary instead of selector/method arrays. Still backward compatible if UseMethodDictionary in Behavior is set to false.

"
 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.
"

'From Smalltalk/X, Version:2.10.9 on 11-jun-1996 at 16:33:14'                   !

ExecutableFunction subclass:#CompiledCode
	instanceVariableNames:'flags byteCode literals'
	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
      literals    <Array>           the block/methods literal array


    [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:'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"
! !

!CompiledCode methodsFor:'accessing'!

byteCode
    "return the bytecode (a ByteArray)"

    ^ byteCode
!

literals
    "return the literal array"

    ^ literals
! !

!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
    "this error is triggered, if a non array is passed to 
     #valueWithReceiver:.. methods"

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

badLiteralTable
    "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 block/methods
     literal table or the GC is broken and corrupted it."

    ^ BadLiteralsSignal raise.
!

invalidByteCode
    "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 block/method."

    ^ InvalidByteCodeSignal raise.
!

invalidInstruction
    "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 the block/methods code."

    ^ InvalidInstructionSignal raise.
!

noByteCode
    "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,
	someone played around with a block/method, 
	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.
!

receiverNotBoolean:anObject
    "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."

    ^ NonBooleanReceiverSignal raise.
!

tooManyArguments
    "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."

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

!CompiledCode methodsFor:'private accessing'!

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

    byteCode := aByteArray
!

dynamic
    "return the flag stating that the machine code was created
     dynamically (from bytecode)."

%{  /* NOCONTEXT */

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

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

dynamic:aBoolean
    "set/clear the flag bit stating that the machine code was created
     dynamically and should be flushed on image-restart.
     Obsolete - now done in VM"

%{  /* NOCONTEXT */

    int newFlags = __intVal(__INST(flags));

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

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

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

    literals := aLiteralArray
!

markFlag
    "return the mark bits value as a boolean"

%{  /* NOCONTEXT */

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

    RETURN ((__intVal(__INST(flags)) & 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:'queries'!

decompileTo:aStream
    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: 16.4.1996 / 20:31:26 / 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"
!

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.
    literals notNil ifTrue:[
	literals do: [ :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 
    "
!

referencesGlobal:aGlobalSymbol
    "return true, if this method references the global
     bound to aGlobalSymbol."

    |lits|

    (lits := self literals) isNil ifTrue:[^ false].
    ^ (lits identityIndexOf:aGlobalSymbol startingAt:1) ~~ 0

    "Created: 16.4.1996 / 16:36:32 / cg"
! !

!CompiledCode class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/CompiledCode.st,v 1.30 1996-06-12 22:10:44 stefan Exp $'
! !
CompiledCode initialize!