Context.st
author Claus Gittinger <cg@exept.de>
Wed, 15 Jan 1997 19:08:31 +0100
changeset 2173 01ad5ffe0c9d
parent 2157 436ad20004f4
child 2201 db0f6e86c8bb
permissions -rw-r--r--
checkin from browser

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

Object variableSubclass:#Context
	instanceVariableNames:'flags sender home receiver selector searchClass lineNr retvalTemp
		handle*'
	classVariableNames:'InvalidReturnSignal SingleStepInterruptRequest'
	poolDictionaries:''
	category:'Kernel-Methods'
!

!Context class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1988 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
"
    Contexts represent the stack frame objects, which keep the processing
    state of a method or block (i.e. its local variables, temporaries etc.)
    Every message send adds a context to a chain, which can be traced back via 
    the sender field. The context of the currently active method is always
    accessable via the pseuodoVariable called 'thisContext'.
    (The actual implementation uses the machines stack for this, building real 
     contexts on demand only).

    For both method- and block-contexts, the layout is the same. 
    For method contexts, the home-field is nil, while for block contexts the home-
    field is either the context of its surrounding block (i.e. the context of the
    block, in which the receiving block was created, if its a nested block) or of
    its home method. 

    Contexts of cheap blocks do not have a home context - their home field is 
    also nil.

    Currently, contexts do not contain a reference to the method or block which
    created it - this is not needed for program execution, but could get the debugger
    somewhat into trouble: it has to search the class hierarchy for receiver/selector
    combinations to find the method. This usually works, but fails in case of methods
    which are not anchored in any class - especially leading to problems with wrapper-
    and lazy methods. Also, Method>>valueWithReceiver - type of invocations cannot
    be easily debugged.
    Therefore, the implementation may be changed in the near future, to include a
    field for the method/block, and set it in the VM during program execution.
    (there may be some small performance penalty for this, though).

    LineNumbers vs. program counter:

    Due to the compilation to machine code, methods and/or block do not
    always (actually: do seldom) contain bytecodes. Thus, there is no such concept
    as a bytecode p-counter. To support debugging, the linenumber within the
    original source is instead remembered when a send or loop entry is performed.
    Since linenumbers are not always sufficient for debugging (multiple sends in one
    line), this may be changed in future versions to a character offset, giving
    the position of the selector in the source.

    Restartable / Returnable contexts:

    In previous versions (up to ST/X 2.10.5), every method stored enough
    information in the context for that one to be restartable later (for example,
    via the debuggers restart button). With 2.10.6, this is now an stc-compiler
    option, and the system as delivered is compiled to only create restartable
    contexts for those which contain blocks. This resulted in an overall speedup of
    roughly 10-20% percent, depending on the type of CPU. However, it makes most
    methods non-restartable (however, abort, signal handling and unwind blocks work
    as usual).
    In practice, this was reported to be not a severe limitation and all users were happy
    to trade the increased performance for that slight inconvenience.
    (during development, this is seldom a problem, since interpreted methods are always
     returnable and restartable)
    If you do not like this (and you are a happy owner of the full distribution), you
    should recompile all classes with stc's '-optContext' flag.

    Resuming contexts:

    Strictly speaking, ST/X does not support a context to be resumed. However,
    it does support a forced return (i.e. non-local-return) from a context.
    Thus, resume of a context is implemented by forcing a return from the context
    which was created by the method called from the first one. The effect is the same.

    Returning from a dead method:

    Blocksreturn from an outlived context (i.e. its home method has already returned)
    is now rewarded by an invalidReturn exception - it used to be a noop in previous
    releases (The blue book described this to be a noop, but other smalltalk implementations
    changed this to be an invalid operation -  good decision)


    [instance variables:]
        flags       <SmallInteger>          used by the VM; never touch.
                                            contains info about number of args, 
                                            locals and temporaries.

        sender      <Context>               the 'calling / sending' context

        home        <Context>               the context, where this block was 
                                            created, or nil if its a method context
                                            There are also cheap blocks, which do
                                            not need a reference to the home context,
                                            for those, its nil too.

        receiver    <Object>                the receiver of this message

        selector    <Symbol>                the selector of this message

        searchClass <Class>                 the class, where the message lookup started
                                            (for super sends) or nil, for regular sends.

        lineNr      <SmallInteger>          the position where the context left off
                                            (kind of p-counter). Only the low 16bits
                                             are valid.

        retValTemp  nil                     temporary - always nil, when you see the context
                                            (used in the VM as temporary)

        handle      *noObject*              used by the VM; not accessable, not an object

        <indexed>                           arguments of the send followed by
                                            locals of the method/block followed by
                                            temporaries.

    [class variables:]
        InvalidReturnSignal                 signal raised when a block tries
                                            to return ('^') from a method context
                                            which itself has already returned
                                            (i.e. there is no place to return to)
        
    WARNING: layout and size known by the compiler and runtime system - do not change.


    [author:]
        Claus Gittinger

    [see also:]
        Block Process Method
        ( contexts, stacks & unwinding : programming/contexts.html)
"
! !

!Context class methodsFor:'initialization'!

initialize
    InvalidReturnSignal isNil ifTrue:[
        InvalidReturnSignal := ErrorSignal newSignalMayProceed:true.
        InvalidReturnSignal nameClass:self message:#invalidReturnSignal.
        InvalidReturnSignal notifierString:'invalid return; method cannot return twice'.

        SingleStepInterruptRequest := QuerySignal new.
        SingleStepInterruptRequest nameClass:self message:#singleStepInterruptRequest.
        SingleStepInterruptRequest notifierString:'single step'.
    ]

    "Modified: 6.5.1996 / 16:46:03 / cg"
! !

!Context class methodsFor:'Signal constants'!

invalidReturnSignal
    "return the signal used when a method is tried to be returned twice
     or, when some dead context is unwound or restarted."

    ^ InvalidReturnSignal
!

singleStepInterruptRequest
    "return the dummy query signal to ask for single stepping"

    ^ SingleStepInterruptRequest

    "Created: 6.5.1996 / 16:46:32 / cg"
! !

!Context class methodsFor:'queries'!

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

    ^ true

    "Modified: 23.4.1996 / 15:58:00 / cg"
! !

!Context methodsFor:'accessing'!

argAt:n
    "return the n'th argument"

    n > self numArgs ifTrue:[
        ^ self error:'invalid arg access'
    ].
    ^ self at:n

    "Modified: 12.10.1996 / 21:44:28 / cg"
!

argAt:n put:value
    "set the n'th argument - useful when the receiver should be restarted"

    n > self numArgs ifTrue:[
        ^ self error:'invalid arg access'
    ].
    ^ self at:n put:value

    "Modified: 12.10.1996 / 21:44:32 / cg"
!

args
    "return an array filled with the arguments of this context"

    |n|

    n := self numArgs.
    ^ (Array new:n) replaceFrom:1 to:n with:self.
!

argsAndVars
    "return an array filled with the arguments and variables of this context"

    |n|

    n := self numArgs + self numVars.
    ^ (Array new:n) replaceFrom:1 to:n with:self.

    "Modified: 23.10.1996 / 16:19:41 / cg"
!

home
    "return the immediate home of the receiver.
     for block contexts, this is the methodcontext, where the block was created,
     for nested block contexts, its the surrounding blocks context.
     for method-contexts this is nil."

    ^ nil "home"
!

instVarAt:index
    "have to catch instVar access to retVal and handle - they are invalid.
     Notice, that one of the next ST/X versions will get some syntactic
     extension to get this automatically)."

    (index == 8) ifTrue:[^ nil].
    (index == 9) ifTrue:[^ nil].
    ^ super instVarAt:index
!

instVarAt:index put:value
    "have to catch instVar access to retVal and handle - they are invalid.
     Notice, that one of the next ST/X versions will get some syntactic
     extension to get this automatically)."

    (index == 8) ifTrue:[^ nil].
    (index == 9) ifTrue:[^ nil].
    ^ super instVarAt:index put:value
!

lineNumber
    "this returns the lineNumber within the methods source, where the context was
     interrupted or called another method. (currently, sometimes this information
     is not available - in this case 0 is returned)"

    lineNr isNil ifTrue:[^ nil].
    ^ lineNr bitAnd:16rFFFF
!

method
    "return the method for which the receiver was created.
     To save time during normal execution, this information is not held in the
     context, but computed here on request."

    |c|

    c := self searchClass.
    "
     the below cannot happen in normal circumstances
     (added to avoid recursive errors in case of a broken sender chain)
    "
    c isBehavior ifFalse:[
        'Context [error]: non class in searchClass' errorPrintCR.
        '      selector: ' errorPrint. selector errorPrint.
        ' receiver: ' errorPrint. receiver errorPrintCR.
        ^ nil
    ].

    c := c whichClassIncludesSelector:selector.
    c notNil ifTrue:[
        ^ c compiledMethodAt:selector
    ].

    "mhmh - seems to be a context for an unbound method;
     look in the senders context. Consider this a kludge.
     (maybe it was not too good of an idea to not keep the current
      method in the context ....
      future versions of ST/X's message lookup may store the method in
      the context.)
    "
    (sender notNil and:[sender selector startsWith:'valueWithReceiver:']) ifTrue:[
        ^ sender receiver
    ].

    ^ nil

    "Modified: 10.1.1997 / 17:34:48 / cg"
!

methodClass
    "return the class in which the method for which the receiver was created is."

    |cls m|

    cls := self searchClass.
    [cls notNil] whileTrue:[
        cls := cls whichClassIncludesSelector:selector.
        cls isNil ifTrue:[^ nil].

        m := cls compiledMethodAt:selector.
        m notNil ifTrue:[
            m isIgnored ifFalse:[^ cls].
        ].
        cls := cls superclass
    ].
    ^ cls

    "Modified: 10.6.1996 / 14:34:59 / cg"
!

methodHome
    "return the method-home - for method contexts this is the receiver"

    ^ self
!

ntemp
    "return the number of temporary variables of the Block/Method.
     (for debugging only).
     I dont like the name of this method; its here for compatibility."

    ^ self numTemps

    "Modified: 23.10.1996 / 16:19:06 / cg"
!

numArgs
    "return the number of arguments to the Block/Method"

%{  /* NOCONTEXT */

    RETURN ( __MKSMALLINT( (__intVal(__INST(flags)) >> __NARG_SHIFT) & __NARG_MASK) );
%}
!

numTemps
    "return the number of temporary variables of the Block/Method.
     (for debugging only)"

    ^ self size - self numArgs - self numVars

    "Created: 23.10.1996 / 16:19:10 / cg"
    "Modified: 23.10.1996 / 16:19:48 / cg"
!

numVars
    "return the number of local variables of the Block/Method"

%{  /* NOCONTEXT */

    RETURN ( __MKSMALLINT( (__intVal(__INST(flags)) >> __NVAR_SHIFT) & __NVAR_MASK) );
%}
!

nvars
    "return the number of local variables of the Block/Method.
     I dont like the name of this method; its here for compatibility."

    ^ self numVars

    "Modified: 23.10.1996 / 16:18:44 / cg"
!

receiver
    "return the receiver of the context"

    ^ receiver
!

searchClass
    "this is the class where the method-lookup started;
     for normal sends, it is nil (or sometimes the receivers class).
     For supersends, its the superclass of the one, in which the
     caller was defined."

    searchClass notNil ifTrue:[^ searchClass].
    ^ receiver class
!

selector
    "return the selector of the method for which the context was created"

    ^ selector
!

sender
    "return the sender of the context"

%{  /* NOCONTEXT */
    OBJ theContext;

    /*
     * this special nil test is for the very first context (startup-context);
     * actually, its cosmetics, to avoid a visible nil>>nil context in the debugger.
     */

    if (__isNonNilObject(theContext = __INST(sender))) {
	if (__isLazy(theContext)) {
	    /*
	     * this cannot happen
	     */
	    _PATCHUPCONTEXT(theContext);
	}
	/* 
	 * to be prepared for the worst situation 
	 * (the sender is not stored, so the trap wont catch it)
	 * make the writeBarrier trigger manually.
	 * We'll see, if this is really required.
	 */
	theContext->o_space |= CATCHMARK;
	_markNonLIFO(theContext);
    }
%}.
    ^ sender
!

setLineNumber:aNumber
    "private entry for uncompiledCodeObject ..."

    lineNr := aNumber
!

temporaries 
    "return an array filled with the temporaries of this context"

    |nonTemps mySize|

    nonTemps := self numArgs + self numVars.
    mySize := self numTemps.
    ^ (Array new:mySize) replaceFrom:1 to:mySize with:self startingAt:nonTemps+1

    "Modified: 23.10.1996 / 16:20:00 / cg"
!

unsafeSender
    "temporary: for debugging only"

    ^ sender
!

varAt:n
    "return the n'th local variable"

    ^ self at:(n + self numArgs)
!

varAt:n put:value
    "set the n'th local variable - useful when the receiver should be restarted
     or continued"

    self at:(n + self numArgs) put:value
!

vars 
    "return an array filled with the local variables of this context"

    |nonVars mySize|

    nonVars := self numArgs.
    mySize := self numVars.
    ^ (Array new:mySize) replaceFrom:1 to:mySize with:self startingAt:nonVars+1

    "Modified: 23.10.1996 / 16:20:06 / cg"
! !

!Context methodsFor:'copying'!

deepCopy
    "raise an error - deepCopy is not allowed for contexts"

    ^ self deepCopyError
! !

!Context methodsFor:'error handling'!

invalidReturn:returnValue
    "this message is sent by the VM, when a methods context
     which has already returned is about to return again.
     (i.e. about to execute a return from an already returned
      method in a block).
    We raise a signal here, to allow catching of that situation."

    "
     in previous versions of ST/X and ST-80, this was no error;
     (instead, a normal blockreturn was performed to the value-sender).
     From a note in comp.lang.smalltalk, I conclude that new ST-80 versions
     now raise an error if this happens.
     Comment out the raise below to get that (old) behavior
     BETTER REWRITE YOUR APPLICATION
    " 
"/ new behavior:

    ^ InvalidReturnSignal 
	raiseRequestWith:returnValue.

"/ old behavior:
"/  ^ returnValue
!

invalidReturnOrRestart:returnValue
    "this message is sent by the VM, when a methods context
     which was compiled non-returnable is about to return again.
     We raise a signal here, to allow catching of that situation."

    ^ InvalidReturnSignal
	raiseRequestWith:returnValue
	errorString:'method was compiled non-resumable'
!

invalidReturnOrRestartError:how with:value
    "common error reporter for restart/return errors"
    
    self canReturn ifTrue:[
	"
	 tried to return from/restart a context which is already dead
	 (i.e. the method/block has already executed a return)
	"
	^ InvalidReturnSignal 
	      raiseRequestWith:value
	      errorString:(how , ': context not on calling chain')
    ].
    "
     tried to return from/restart a context of a method which was compiled
     unrestartable or of a block (which is never restartable)
    "
    ^ InvalidReturnSignal 
	  raiseRequestWith:value
	  errorString:(how , ': context cannot be restarted/returned from')
! !

!Context methodsFor:'minidebugger printing'!

fullPrint
    "print the receiver, selector and args of the context 
     - used only for MiniDebuggers walkback print"

    self receiverPrintString print. ' ' print. selector print.
    self size ~~ 0 ifTrue: [
        ' ' print. self argsDisplayString print
    ].
    ' [' print. self lineNumber print. ']' printCR

    "
     thisContext fullPrint
    "

    "Modified: 20.5.1996 / 10:27:14 / cg"
!

fullPrintAll
    "print a full walkback starting at the receiver
     - used only for MiniDebuggers walkback print"

    |context|

    context := self.
    [context notNil] whileTrue: [
	context fullPrint.
	context := context sender
    ]

    "
     thisContext fullPrintAll
    "
!

fullPrintAllOn:aStream
    "print a full walkback starting at the receiver
     - used only for MiniDebuggers walkback print"

    |context|

    context := self.
    [context notNil] whileTrue: [
        context fullPrintOn:aStream.
        context := context sender
    ]

    "
     thisContext fullPrintAllOn:Transcript
    "

    "Created: 15.1.1997 / 18:09:05 / cg"
!

fullPrintOn:aStream
    "print the receiver, selector and args of the context 
     - used only for MiniDebuggers walkback print"

    self receiverPrintString printOn:aStream. ' ' printOn:aStream. selector printOn:aStream.
    self size ~~ 0 ifTrue: [
        ' ' printOn:aStream. self argsDisplayString printOn:aStream
    ].
    ' [' printOn:aStream. self lineNumber printOn:aStream. ']' printOn:aStream.
    aStream cr

    "
     thisContext fullPrintOn:Transcript
    "

    "Modified: 20.5.1996 / 10:27:14 / cg"
    "Created: 15.1.1997 / 18:09:06 / cg"
! !

!Context methodsFor:'non local control flow'!

restart
    "restart the receiver - i.e. the method is evaluated again.
     if the context to restart already died, trigger an error.
     This is a low level helper for unwindAndRestart.

     NOTICE: 
	 NO unwind actions are performed - this is usually not
	 what you want (see Context>>unwindAndRestart).

     LIMITATION: 
	 currently a context can only be restarted by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-restartable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    sender isNil ifTrue:[^ nil].
%{
    __RESUMECONTEXT__(SND_COMMA self, RESTART_VALUE, 0);
%}.
    "
     when we arrive here, something went wrong.
     debugging ...
    "
    ^ self invalidReturnOrRestartError:#restart with:nil
!

resume
    "resume execution in this context. I.e. as if the method called
     last by the receiver did a ^ nil.
     If the context has already returned, report an error.

     NOTICE:
	 NO unwind actions are performed (see Context>>unwind).

     LIMITATION: 
	 currently a context can only be resumed by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-resumable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    ^ self resume:nil
!

resume:value
    "resume the receiver - as if it got 'value' from whatever
     it called. This continues execution in the receivers method
     after the point where it did its last send.
     If the context has already returned - report an error. 

     NOTICE:
	 NO unwind actions are performed (see Context>>unwind:).

     LIMITATION: 
	 currently a context can only be resumed by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-resumable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    |theContext|

    "
     starting with this context, find the one below (i.e. the one that I
     have called) and return from it.
    "
    theContext := thisContext.
%{
    while ((theContext != nil) && (__ContextInstPtr(theContext)->c_sender != self)) {
	theContext = __ContextInstPtr(theContext)->c_sender;
    }
%}.

    theContext isNil ifTrue:[
	"
	 tried to resume in context which is already dead
	 (i.e. the method/block has already executed a return)
	"
	^ theContext invalidReturnOrRestartError:#resume with:value
    ].
    ^ theContext return:value
!

return
    "return from this context with nil. I.e. as if it did a ^ nil.
     NOTICE:
	 NO unwind actions are performed - this is usually not
	 what you want (See Context>>unwind).
	 This is a low level method - a helper for unwind.

     LIMITATION: 
	 currently a context can only be returned by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-returnable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    ^ self return:nil
!

return:value
    "return from this context as if it did a '^ value'.
     NOTICE:
	 NO unwind actions are performed - this is usually not
	 what you want (See Context>>unwind:).
	 This is a low level method - a helper for unwind.

     LIMITATION: 
	 currently a context can only be returned by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-returnable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    sender isNil ifTrue:[^ nil].
%{
    __RESUMECONTEXT__(SND_COMMA self, value, 0);

%}.
    "
     when we arrive here, something went wrong.
     debugging ...
    "
    ^ self invalidReturnOrRestartError:#return with:value
!

returnDoing:aBlock
    "return from this context as if it did a '^ aBlock value'.
     The block is evaluated as if called by the receiver context;
     NOT the true executing context.
     NOTICE:
	 NO unwind actions are performed - this is usually not
	 what you want (See Context>>unwindThenDo:).
	 This is a low level method - a helper for unwind.

     LIMITATION:
	 currently a context can only be returned by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-returnable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    sender isNil ifTrue:[^ nil].
%{
    __RESUMECONTEXT__(SND_COMMA self, aBlock, 2);
%}.
    "
     when we arrive here, something went wrong.
     debugging ...
    "
    ^ self invalidReturnOrRestartError:#return with:aBlock
!

unwind
    "return nil from the receiver - i.e. simulate a '^ nil'.
     If the context has already retruned, report an error.
     Evaluate all unwind-blocks as specified in Block>>valueNowOrOnUnwind:
     and Block>>valueOnUnwindDo: on the way.

     LIMITATION: 
	 currently a context can only be unwound by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-returnable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    ^ self unwind:nil
!

unwind:value
    "return value from the receiver - i.e. simulate a '^ value'.
     If the context has already returned , report an error.
     Evaluate all unwind-blocks as specified in Block>>valueNowOrOnUnwind:
     and Block>>valueOnUnwindDo: on the way.

     LIMITATION: 
	 currently a context can only be unwound by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-returnable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    |con unwindBlock|

    sender isNil ifTrue:[
	"
	 tried to return to a context which is already dead
	 (i.e. the method/block has already executed a return)
	"
	^ self invalidReturnOrRestartError:#unwind with:value
    ].

    "
     start with this context, moving up, looking for unwind actions
    "
    con := thisContext.
    [con notNil and:[con ~~ self]] whileTrue:[
	con isUnwindContext ifTrue:[
	    "/
	    "/ mhmh - hardwired knowledge about those methods (taking the 1st arg) 
	    "/
	    unwindBlock := con argAt:1.
	    con unmarkForUnwind.
	    unwindBlock value
	].
	con := con sender
    ].

    "oops, I am not on the calling chain
     (should we check for this situation first and NOT evaluate
      the unwind actions in this case ?)
    "
    con isNil ifTrue:[
	"
	 tried to return to a context which is already dead
	 (i.e. the method/block has already executed a return)
	"
	^ self invalidReturnOrRestartError:#unwind with:value
    ].
    "
     now, that all unwind-actions are done, I can use the
     low-level return ...
    "
    ^ self return:value
!

unwindAndRestart
    "restart the receiver - i.e. the method is evaluated again.
     if the context to restart already died report an error.
     Evaluate all unwind-blocks as specified in Block>>valueNowOrOnUnwind:
     and Block>>valueOnUnwindDo: before restarting.

     LIMITATION: 
	 currently a context can only be restarted by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-restartable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    |con unwindBlock|

    "
     start with this context, moving up, looking for unwind actions
    "
    con := thisContext.
    [con notNil and:[con ~~ self]] whileTrue:[
	con isUnwindContext ifTrue:[
	    "/
	    "/ mhmh - hardwired knowledge about those methods (taking the 1st arg) 
	    "/
	    unwindBlock := con argAt:1.
	    con unmarkForUnwind.
	    unwindBlock value
	].

	con := con sender
    ].

    "oops, I am not on the calling chain
     (should we check for this situation first and NOT evaluate
      the unwind actions in this case ?)
    "
    con isNil ifTrue:[
	"
	 tried to return to a context which is already dead
	 (i.e. the method/block has already executed a return)
	"
	^ self invalidReturnOrRestartError:#unwindAndRestart with:nil
    ].
    "
     now, that all unwind-actions are done, I can use the
     low-level restart ...
    "
    ^ self restart
!

unwindThenDo:aBlock 
    "return the value of aBlock from the receiver - i.e. simulate a '^ aBlock value'.
     If the context has already returned , report an error.
     Evaluate all unwind-blocks as specified in Block>>valueNowOrOnUnwind:
     and Block>>valueOnUnwindDo: on the way.
     The block is evaluated AFTER all unwind actions are performed
     (i.e. the blocks sender will be the receiving context, not the
      currently executing context)

     LIMITATION: 
	 currently a context can only be unwound by
	 the owning process - not from outside.
	 Also, the compiler has an option (+optcontext) to create
	 non-returnable contexts (which are faster).
	 If such a context is restarted, a runtime error is raised."

    |con unwindBlock|

    sender isNil ifTrue:[
	"
	 tried to return to a context which is already dead
	 (i.e. the method/block has already executed a return)
	"
	^ self invalidReturnOrRestartError:#unwind with:aBlock
    ].

    "
     start with this context, moving up, looking for unwind actions
    "
    con := thisContext.
    [con notNil and:[con ~~ self]] whileTrue:[
	con isUnwindContext ifTrue:[
	    "/
	    "/ mhmh - hardwired knowledge about those methods (taking the 1st arg) 
	    "/
	    unwindBlock := con argAt:1.
	    con unmarkForUnwind.
	    unwindBlock value
	].
	con := con sender
    ].

    "oops, I am not on the calling chain
     (should we check for this situation first and NOT evaluate
      the unwind actions in this case ?)
    "
    con isNil ifTrue:[
	"
	 tried to return to a context which is already dead
	 (i.e. the method/block has already executed a return)
	"
	^ self invalidReturnOrRestartError:#unwind with:aBlock
    ].
    "
     now, that all unwind-actions are done, I can use the
     low-level return ...
    "
    ^ self returnDoing:aBlock 
! !

!Context methodsFor:'printing & storing'!

argStringFor:someObject

    |name|
%{
    /*
     * special handling for (invalid) free objects.
     * these only appear if some primitiveCode does not correctly use SEND macros,
     * which may lead to sends to free objects. In normal operation, this 'cannot' happen.
     */ 
    if (__isNonNilObject(someObject) && (__qClass(someObject)==nil)) {
	name = __MKSTRING("FreeObject");
    }
%}.
    name notNil ifTrue:[^ name].
    ^ someObject displayString
!

argsDisplayString
    |fullString n "{ Class: SmallInteger }" |

    fullString := ''.
    n := self numArgs.
    1 to:n do:[:index |
	fullString := fullString , ' ' , (self argStringFor:(self at:index))
    ].
    ^ fullString
!

displayString
    "return a string describing the context - for display in Inspector" 

    ^ self class name , '(' , self printString , ')'
!

fullPrintString
    "return a string describing the context - this includes the linenumber,
     receiver printString and argument printString"

    |s|

    s := WriteStream on:String new.
    s nextPutAll:self receiverPrintString; space; nextPutAll:selector.
    self size ~~ 0 ifTrue: [
	s space.
	s nextPutAll:self argsDisplayString
    ].
    s nextPutAll:' ['; nextPutAll:self lineNumber printString; nextPutAll:']' .
    ^ s contents

    "
     thisContext fullPrintString
    "
!

methodPrintString
    "return a string describing the contexts method as 'implementorClass>>selector'" 

    |mthd who|

    mthd := self method.
    mthd notNil ifTrue:[
        who := mthd who.
        who notNil ifTrue:[
            ^ who methodClass name , '>>' , who methodSelector
        ]
    ].
    ^ mthd displayString.

    "
     thisContext methodPrintString 
     thisContext sender methodPrintString  
    "

    "Modified: 1.11.1996 / 16:21:49 / cg"
!

printOn:aStream
    "append a printed description of the receiver onto aStream"

    aStream nextPutAll:(self receiverPrintString).
    aStream space.
    self selector printOn:aStream
!

printString
    "return a string describing the context" 

    ^ self receiverPrintString , ' ' , self selector printString
!

receiverPrintString
    "return a string describing the receiver of the context" 

    |receiverClass receiverClassName newString implementorClass|

%{
    /*
     * special handling for (invalid) free objects.
     * these only appear if some primitiveCode does not correctly use SEND macros,
     * which may lead to sends to free objects. In normal operation, this 'cannot' happen.
     */ 
    if (__isNonNilObject(__INST(receiver)) && (__qClass(__INST(receiver))==nil)) {
        receiverClassName = __MKSTRING("FreeObject");
    }
%}.
    receiverClassName notNil ifTrue:[^ receiverClassName].

    receiverClass := receiver class.
    receiverClassName := receiverClass name.
    (receiverClass == SmallInteger) ifTrue:[
        newString := '(' , receiver printString , ') ' , receiverClassName
    ] ifFalse:[
        newString := receiverClassName
    ].

    selector notNil ifTrue:[
"/        implementorClass := self searchClass whichClassIncludesSelector:selector.

        "
         kludge to avoid slow search for containing class
        "
        (selector ~~ #doIt and:[selector ~~ #doIt:]) ifTrue:[
            implementorClass := self methodClass. 
        ].
        implementorClass notNil ifTrue: [
            (implementorClass ~~ receiverClass) ifTrue: [
                newString := newString , '>>>',
                             implementorClass name printString
            ]
        ] ifFalse:[
            self searchClass ~~ receiverClass ifTrue:[
                newString := newString , '>>>' , self searchClass name
            ].
            "
             kludge for doIt - these unbound methods are not
             found in the classes methodDictionary
            "
            (selector ~~ #doIt and:[selector ~~ #doIt:]) ifTrue:[
                newString := newString , '>>>**NONE**'
            ]
        ]
    ].

    ^ newString
! !

!Context methodsFor:'private accessing'!

markForInterrupt
    "set the interrupt flag.
     The VM needs this to know that some special action is to be performed with
     this context upon return - a highly internal mechanism and not for public use."

%{  /* NOCONTEXT */
     __markInterrupted(__ContextInstPtr(self));
%}
!

markForInterruptOnUnwind
    "set the interrupt-on-unwind flag in the receiver.
     The VM will generate a stepInterrupt, when this context returns or
     is unwound. This is used by the debugger for faster single-stepping;
     - a highly internal mechanism and not for public use."

%{  /* NOCONTEXT */
     __INST(flags) = (OBJ)((INT)__INST(flags) 
                     | __MASKSMALLINT(__IRQ_ON_UNWIND));
%}
!

markForUnwind
    "set the mark for unwind flag in the receiver.
     The VM needs this to know that some special action is to be performed with
     this context - a highly internal mechanism and not for public use."

%{  /* NOCONTEXT */
     __INST(flags) = (OBJ)((INT)__INST(flags) | __MASKSMALLINT(__UNWIND_MARK));
%}

    "Modified: 13.12.1995 / 19:05:22 / cg"
!

unmarkForUnwind
    "clear the mark for unwind flag in the receiver.
     The VM needs this to know that some special action is to be performed with
     this context - a highly internal mechanism and not for public use."

%{  /* NOCONTEXT */
    __INST(flags) = (OBJ)((INT)__INST(flags) & ~__MASKSMALLINT(__UNWIND_MARK));
%}
! !

!Context methodsFor:'special accessing'!

canReturn
    "return true, if the receiver allows returning through it.
     For normal method contexts, this returns true;
     for blocks, it (currently) always returns false.

     However, the system can be compiled (for production code), to create
     contexts which cannot be returned or restarted
     (except, if the method contains a returning block). 
     This saves some administrative work in every method
     invocation and makes overall execution faster. However, it limits
     the debugger, in that it cannot return from or restart those contexts.
     (unwinding and termination is not affected by this optimization)
     Currently, the system as delivered has this optimization disabled."

%{  /* NOCONTEXT */

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

hasStackToShow
    ^ false

    "Created: 28.6.1996 / 14:48:39 / cg"
!

isNonLifo
    "return true, if this is a nonLifo context"

%{  /* NOCONTEXT */
     RETURN ( ((INT)__INST(flags) & __MASKSMALLINT(__NONLIFO)) ? true : false );
%}
!

isOnMachineStack
    "return true, if this is a machine stack context as opposed to a 
     real heap context"

%{  /* NOCONTEXT */
     RETURN ( (__qSpace(self) >= STACKSPACE) ? true : false );
%}
!

isSpecial
    "return true, if this is either a nonLifo or interrupted context"

%{  /* NOCONTEXT */
     RETURN ( ((INT)__INST(flags) & __MASKSMALLINT(__SPECIAL)) ? true : false );
%}
!

isUnwindContext
    "return true, if this is an unwindContext"

%{  /* NOCONTEXT */
     RETURN ( ((INT)__INST(flags) & __MASKSMALLINT(__UNWIND_MARK)) ? true : false );
%}
! !

!Context methodsFor:'testing'!

isBlockContext
    "return true, iff the receiver is a BlockContext, false otherwise"

    ^ false
!

isContext
    "return true, iff the receiver is a Context, false otherwise"

    ^ true
!

isRecursive
    "return true, if this context is one of a recursive send of the same
     selector to the same receiver before.
     Here, different arguments are ignored - i.e. only the same method
     counts for recursiveness.
     Used to detect recursive errors or recursive printing - for example."

    |c rec "numArgs" "{Class: SmallInteger }"|

    rec := 0.
    c := self sender.
    [c notNil] whileTrue:[
        ((c selector == selector) 
        and:[(c receiver == receiver)]) ifTrue:[
            "
             stupid: the current ST/X context does not include
             the method, but the class, in which the search started ...
            "
"/            (c searchClass whichClassIncludesSelector:selector) == (self searchClass whichClassIncludesSelector:selector) ifTrue:[
              c methodClass == self methodClass ifTrue:[
"/              "
"/               finally, look for different arguments
"/              "
"/              numArgs := self numArgs.
"/              1 to:numArgs do:[:argIndex |
"/                  (self argAt:argIndex) == (c argAt:argIndex) ifFalse:[^ false]
"/              ]. 
              ^ true
            ]
        ].
        c := c sender.

        "
         this special test was added to get out after a while
         if the sender chain is corrupt - this gives us at least
         a chance to find those errors.
        "
        rec := rec + 1.
        rec >= 100000 ifTrue:[
            'Context [warning]: bad context chain' errorPrintCR.
            ^ true
        ]
    ].
    ^ false

    "Modified: 10.1.1997 / 17:34:26 / cg"
! !

!Context class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.70 1997-01-15 18:08:31 cg Exp $'
! !
Context initialize!