GenericException.st
author Claus Gittinger <cg@exept.de>
Sat, 25 Sep 1999 15:20:37 +0200
changeset 4814 7825b9141f01
parent 4758 91b5a25f29c5
child 4936 bc943fef0d96
permissions -rw-r--r--
changes to allow compilation under win32 (does not like strings beginning with a cr - how comes this ?)

"
 COPYRIGHT (c) 1993 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 subclass:#GenericException
	instanceVariableNames:'signal parameter errorString suspendedContext handlerContext
		rejected originator proceedable handlingException'
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Exceptions'
!

GenericException class instanceVariableNames:'NotifierString'

"
 The following class instance variables are inherited by this class:

	Object - 
"
!

!GenericException class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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
"
    GenericException and its subclasses implement the same protocol as Signal.
    So class based exceptions may be implemented as subclasses of GenericException.

    Instances of Exception are passed to a Signal handling block as argument.
    The handler block may perform various actions by sending corresponding messages
    to the exception object. The following actions are possible:

        reject          - don't handle this signal;
                          another handler will be searched for, 
                          upper in the calling hierarchy

        proceed         - return from the Signal>>raise, with nil as value

        proceedWith:val - same, but return val from Signal>>raise

        return          - return from the Signal>>handle:do:, with nil as value

        returnWith:val  - same, but return val from Signal>>handle:do:
                          (this is also the handlers default, 
                           if it falls through; taking the handlerBlocks value
                           as return value)

        restart         - restart the Signal>>handle:do:, after repairing

    Via the Exception object, the handler can also query the state of execution:
    where the Signal was raised, where the handler is, the signal which caused
    the error and the errorString passed when the signal was raised. Also, an optional
    parameter can be passed - the use is signal specific.

    [instance variables:]
        signal           <Signal>     the signal which caused the exception

        parameter        <Object>     a parameter (if any) which was passed when raising
                                      the signal (only if raised with #raiseWith:aParameter)

        errorString      <String>     an errorString 
                                      (usually the signals own errorString, but sometimes
                                       changed explicitely in #raiseWith:errorString:)

        suspendedContext <Context>    the context in which the raise occured

        handlerContext   <Context>    the context of the handler (if any)

    In case of an unhandled signal raise, Exceptions EmergenyHandler will be evaluated. 
    The default emergeny handler will enter the debugger.

    For applications, which do not want Debuggers to come up, other handlers are
    possible.
    For example, to get the typical C++ behavior, use:
        Exception emergencyHandler:[:ex | Smalltalk exitWithCoreDump]

    [see also:]
        Signal  SignalSet QuerySignal
        Context Block
        Object DebugView
        (``Exception handling and signals'': programming/exceptions.html)

    [author:]
        Claus Gittinger
"
!

examples
"
    Examples on Exception-raising & handling are found in the doc/coding
    section (CodingExamples).

    The emergencyHandler stuff is very useful, to prevent endUser applications
    from entering the debugger. See the examples in NoHandlerError.
"
! !

!GenericException class methodsFor:'initialization'!

initialize 

    NotifierString := 'unknown exception'.

    "Modified: / 4.8.1999 / 09:06:26 / stefan"
! !

!GenericException class methodsFor:'instance creation'!

signal:aSignal originator:origin
    "create a new instance and set the fields in preparation for a raise.
     - only to be sent from the signal when raising"

    "{ Pragma: +inlineNew }"

    ^ (self basicNew) signal:aSignal originator:origin.

    "Created: / 23.7.1999 / 13:40:45 / stefan"
!

signal:aSignal parameter:aParameter errorString:aString suspendedContext:sContext originator:origin
    "create a new instance and set the fields in preparation for a raise.
     - only to be sent from the signal when raising"

    "{ Pragma: +inlineNew }"

    ^ (self basicNew)
        signal:aSignal 
        parameter:aParameter 
        errorString:aString 
        suspendedContext:sContext 
        originator:origin.
! !

!GenericException class methodsFor:'Signal constants'!

noHandlerError

    ^ NoHandlerError

    "Created: / 4.8.1999 / 08:33:35 / stefan"
!

proceedError

    ^ ProceedError

    "Created: / 4.8.1999 / 08:34:30 / stefan"
!

recursiveExceptionError
    "return the signal used to handle recursive signals in the handlers"

    ^ RecursiveExceptionError

    "Created: / 4.8.1999 / 09:05:06 / stefan"
!

recursiveExceptionSignal
    "return the signal used to handle recursive signals in the handlers.
     This is for backward compatinility. Use recursiveExceptionError"

    ^ RecursiveExceptionError

    "Modified: / 4.8.1999 / 09:05:59 / stefan"
!

wrongProceedabilityError

    ^ WrongProceedabilityError

    "Created: / 4.8.1999 / 08:34:19 / stefan"
! !

!GenericException class methodsFor:'accessing'!

notifierString:aString

    NotifierString := aString
! !

!GenericException class methodsFor:'compatibility - accessing'!

errorString
    "#errorString is deprecated, use description instead"

    ^ self description
!

handlerBlock
    "Compatibility with Signal. Class based exeptions do not have a handler
     block. They redefine the #action method instead"

    ^ nil

    "Created: / 23.7.1999 / 14:43:18 / stefan"
    "Modified: / 24.7.1999 / 20:52:10 / stefan"
! !

!GenericException class methodsFor:'compatibility - defaults'!

emergencyHandler

    ^ NoHandlerError emergencyHandler.
!

emergencyHandler:aOneArgBlock
    "set the handler used for unhandled exceptions.
     The default (a nil-handler) leads to a debugger to be shown."

    ^ NoHandlerError emergencyHandler:aOneArgBlock.

    "ST-80 behavior of first showing a notifier:
     (I prefer to get right into the debugger, though)

     Exception
        emergencyHandler:
            [:ex | self errorNotify:ex errorString ]
    "

    "ST-X behavior of going right into the debugger:

     Exception
        emergencyHandler:nil
    "

    "automatically aborting current operation, on error:
     (may be useful for end-user apps; make certain, 
      you have abortSignal handlers at appropriate places)

     Exception
        emergencyHandler:
            [:ex | Object abortSignal raise. ex return. ]
    "

    "finally, traditional language system behavior; dump core ;-)

     Exception
        emergencyHandler:
            [:ex | Smalltalk exitWithCoreDump. ]
    "

    "Modified: 15.1.1997 / 20:49:06 / cg"

! !

!GenericException class methodsFor:'compatibility - queries'!

accepts:aSignal
    "return true, if the receiver accepts the argument, aSignal.
     (i.e. the receiver is aSignal or a parent of it). False otherwise."

    |s|

    self == aSignal ifTrue:[^ true].
    aSignal isQuerySignal ifTrue:[^ false].

    s := aSignal.
    [s notNil] whileTrue:[
        self == s ifTrue:[^ true].
        s := s parent
    ].
    ^ false

    "Created: / 23.7.1999 / 14:00:47 / stefan"
!

exception:anExceptionOrSignal isHandledIn:aContext
    "return true, if there is a handler for the receiver signal in the 
     contextChain starting with aContext."

    |con r|

    con := Context findFirstSpecialHandle:true raise:false.
    [con notNil] whileTrue:[
        ((r := con receiver) notNil
         and:[(r handlerForSignal:anExceptionOrSignal context:con originator:nil) notNil]
        ) ifTrue:[
            "found a handler context"
            ^ true
        ].
        con := con findSpecialHandle:true raise:false.
    ].
    ^ false

!

handlerForSignal:signal context:theContext originator:originator
    "answer the handler block for the signal from originator.
     The block is retrieved from aContext.
     Answer nil if the signal is not handled"


    (theContext selector ~~ #'handle:from:do:'
     or:[(theContext argAt:2) == originator]) ifTrue:[
        (self == signal or:[self accepts:signal]) ifTrue:[
            ^ theContext argAt:1
        ]
    ].

    ^ nil

    "Created: / 25.7.1999 / 19:52:58 / stefan"
!

handlerProtectedBlock:doBlock inContext:context
    "set the handlerProtectedBlock in context"

    context selector == #handle:do: ifTrue:[
        context argAt:2 put:doBlock.
    ] ifFalse:[context selector == #handle:from:do: ifTrue:[
        context argAt:3 put:doBlock.
    ]].

!

handlingExceptionInContext:theContext
    "answer the handling exception from aContext."

    (theContext selector == #'handle:from:do:'
     or:[theContext selector == #'handle:do:']) ifTrue:[
        ^ theContext receiver
    ].

    ^ nil
!

inheritsFrom:anotherSignal
    "return true, if the receiver is a child of anotherSignal
     (i.e. if handling anotherSignal also handles the receiver)
     This is almost the same as accepts, but returns false, if
     the receiver is identical to anotherSignal."

    self == anotherSignal ifTrue:[^ false].
    ^ anotherSignal accepts:self

    "Created: / 23.7.1999 / 13:59:51 / stefan"
!

isHandled
    "return true, if there is a handler for the receiver signal.
     Raising an unhandled signal will usually lead into the debugger,
     but can be caught globally by setting Exceptions EmergencyHandler."

    ^ self exception:self isHandledIn:(thisContext sender).

    "Created: / 23.7.1999 / 14:03:50 / stefan"
!

isHandledIn:aContext
    "return true, if there is a handler for the receiver signal in the 
     contextChain starting with aContext."

    ^ self exception:self isHandledIn:aContext
!

isQuerySignal
    "return true, if this is a querySignal - always return false here"

    ^ false

    "Created: / 23.7.1999 / 13:50:16 / stefan"
!

isSignal
    "return true, if the receiver is some kind of signal;
     true returned here - the method is redefined from Object."

    ^ true

    "Created: / 23.7.1999 / 13:49:59 / stefan"
!

mayProceed
    "return true, if the exception handler is allowed to proceed
     the execution where the exception occured.

     Subclasses may redefine this."

    ^ true

    "Modified: / 23.7.1999 / 14:50:11 / stefan"
!

parent
    "return the parent Signal/Exception of myself.
     Subclasses may redefine this to install themself as child of
     existing Signals."

    self == GenericException ifTrue:[
        ^ nil
    ].

    ^ self superclass

    "Created: / 23.7.1999 / 14:01:29 / stefan"
    "Modified: / 23.7.1999 / 16:15:38 / stefan"
! !

!GenericException class methodsFor:'compatibility - raising'!

new
    "{ Pragma: +inlineNew }"

    ^ self basicNew signal:self.

    "Modified: / 23.7.1999 / 13:53:12 / stefan"
    "Created: / 24.7.1999 / 13:21:13 / stefan"
!

newException

    ^ self new

    "Created: / 23.7.1999 / 13:45:49 / stefan"
    "Modified: / 24.7.1999 / 13:21:25 / stefan"
!

newExceptionFrom:originator
    "answer a new exception object for this signal.
     Set the originator.
     Subclasses may redefine this method"

    ^ self new originator:originator

    "Created: / 23.7.1999 / 13:47:07 / stefan"
!

raise
    "raise a signal nonproceedable.
     The signals notifierString is used as errorString."

    <context: #return>

    ^ self newException 
        suspendedContext:thisContext sender;
        raise

    "Modified: / 2.5.1996 / 16:36:23 / cg"
    "Modified: / 5.3.1998 / 16:44:36 / stefan"
    "Created: / 23.7.1999 / 14:07:17 / stefan"
!

raiseErrorString:aString
    "raise a signal nonproceedable.
     The argument is used as errorString."

    <context: #return>

    ^ self newException 
        suspendedContext:thisContext sender;
        errorString:aString;
        raise.

    "Modified: / 9.5.1996 / 15:17:59 / cg"
    "Modified: / 12.3.1998 / 15:15:22 / stefan"
    "Created: / 23.7.1999 / 14:07:33 / stefan"
!

raiseFrom:something
    "raise a signal nonproceedable.
     The argument, something is passed both as parameter and originator."

    <context: #return>

    ^ (self newExceptionFrom:something) 
        suspendedContext:thisContext sender;
        parameter:something;
        raise

    "Modified: / 2.5.1996 / 16:36:38 / cg"
    "Modified: / 5.3.1998 / 16:49:55 / stefan"
    "Created: / 23.7.1999 / 14:07:59 / stefan"
!

raiseRequest
    "raise a signal proceedable.
     The signals notifierString is used as errorString."

    <context: #return>

    ^ self newException 
        suspendedContext:thisContext sender;
        raiseRequest.

    "Modified: / 2.5.1996 / 16:36:52 / cg"
    "Modified: / 5.3.1998 / 16:50:46 / stefan"
    "Created: / 23.7.1999 / 14:08:24 / stefan"
!

raiseRequestErrorString:aString
    "raise a signal proceedable.
     The argument, aString is used as errorString."

    <context: #return>

    ^ self newException 
        suspendedContext:thisContext sender;
        errorString:aString;
        raiseRequest
!

raiseRequestFrom:something
    "raise a signal proceedable.
     The argument, something is passed both as parameter and originator."

    <context: #return>

    ^ (self newExceptionFrom:something) 
        suspendedContext:thisContext sender;
        parameter:something;
        raiseRequest.

    "Modified: / 2.5.1996 / 16:36:38 / cg"
    "Modified: / 5.3.1998 / 16:52:46 / stefan"
    "Created: / 23.7.1999 / 14:08:36 / stefan"
!

raiseRequestWith:aParameter
    "raise a signal proceedable.
     The signals notifierString is used as errorString."

    <context: #return>

    ^ self newException 
        suspendedContext:thisContext sender;
        parameter:aParameter;
        raiseRequest.

    "Modified: / 9.5.1996 / 15:13:20 / cg"
    "Modified: / 12.3.1998 / 15:16:57 / stefan"
    "Created: / 23.7.1999 / 14:08:48 / stefan"
!

raiseRequestWith:aParameter errorString:aString
    "raise a signal proceedable.
     The argument, aString is used as errorString."

    <context: #return>

    ^ self newException 
        suspendedContext:thisContext sender;
        parameter:aParameter; 
        errorString:aString;
        raiseRequest

    "Modified: / 9.5.1996 / 15:13:35 / cg"
    "Modified: / 12.3.1998 / 15:17:52 / stefan"
    "Created: / 23.7.1999 / 14:08:57 / stefan"
!

raiseRequestWith:aParameter errorString:aString in:aContext
    "raise a signal proceedable.
     The argument, aString is used as errorString.
     The additional context is passed as the context responsible for the raise,
     allowing a raise to mimicri the exception happened somewhere else."

    ^ self newException 
        parameter:aParameter; 
        errorString:aString;
        suspendedContext:aContext;
        raiseRequest

    "Modified: / 26.7.1996 / 16:29:27 / cg"
    "Modified: / 12.3.1998 / 15:18:34 / stefan"
    "Created: / 23.7.1999 / 14:09:07 / stefan"
!

raiseWith:aParameter
    "raise a signal nonproceedable.
     The argument, aParameter is passed as parameter."

    <context: #return>

    ^ self newException 
        suspendedContext:thisContext sender;
        parameter:aParameter;
        raise.

    "Modified: / 9.5.1996 / 15:14:24 / cg"
    "Modified: / 12.3.1998 / 15:19:11 / stefan"
    "Created: / 23.7.1999 / 14:09:27 / stefan"
!

raiseWith:aParameter errorString:aString
    "raise a signal nonproceedable.
     The argument, aString is used as errorString, aParameter is passed
     as exception parameter."

    <context: #return>

    ^ self newException 
        suspendedContext:thisContext sender;
        parameter:aParameter;
        errorString:aString;
        raise.

    "Modified: / 9.5.1996 / 15:14:32 / cg"
    "Modified: / 12.3.1998 / 15:19:40 / stefan"
    "Created: / 23.7.1999 / 14:09:36 / stefan"
!

raiseWith:aParameter errorString:aString in:aContext
    "raise a signal nonproceedable.
     The argument, aString is used as errorString, aParameter is passed
     as exception parameter.
     The additional context is passed as the context responsible for the raise,
     allowing a raise to mimicri the exception happened somewhere else."

    ^ self newException 
          parameter:aParameter; 
          errorString:aString;
          suspendedContext:aContext; 
          raise.

    "Modified: / 26.7.1996 / 16:29:42 / cg"
    "Modified: / 12.3.1998 / 15:20:12 / stefan"
    "Created: / 23.7.1999 / 14:09:46 / stefan"
! !

!GenericException class methodsFor:'compatibility - save evaluation'!

catch:aBlock
    "evaluate the argument, aBlock.
     If the receiver-signal is raised during evaluation, abort
     the evaluation and return true; otherwise return false. 
     This is the catch & throw mechanism found in other languages,
     where the returned value indicates if an exception occured."

    |raiseOccurred|

    raiseOccurred := false.
    self handle:[:ex | raiseOccurred := true. ex return] do:aBlock.
    ^ raiseOccurred

    "
     Object messageNotUnderstoodSignal catch:[
        123 size open   
     ]
    "

    "Created: / 23.7.1999 / 14:06:01 / stefan"
!

handle:handleBlock do:aBlock
    "evaluate the argument, aBlock.
     If the receiver-signal is raised during evaluation,
     evaluate the handleBlock passing it an Exception argument.
     The handler may decide how to react to the signal by sending
     a corresponding message to the exception (see there).
     If the signal is not raised, return the value of evaluating
     aBlock."

    <context: #return>
    <exception: #handle>

    "/ thisContext markForHandle. -- same as above pragma
    ^ aBlock value  "the real logic is in Exception>>doRaise"

    "
     Object messageNotUnderstoodSignal handle:[:ex |
        'oops' printNL.
        ex return
     ] do:[
        123 size open   
     ]
     "

     "
      |num|

      num := 0.
      Number divisionByZeroSignal handle:[:ex |
          'oops' printNL.
          ex return
      ] do:[
          123 / num   
      ]
     "

    "Created: / 23.7.1999 / 14:06:13 / stefan"
    "Modified: / 25.7.1999 / 19:44:05 / stefan"
!

handle:handleBlock from:anObject do:aBlock
    "evaluate the argument, aBlock.
     If the receiver-signal is raised during evaluation,
     and the exception originated from anObject,
     evaluate the handleBlock passing it an Exception argument.
     The handler may decide how to react to the signal by sending
     a corresponding message to the exception (see there).
     If the signal is not raised, return the value of evaluating
     aBlock."

    <context: #return>
    <exception: #handle>

    "/ thisContext markForHandle. -- same as above pragma
    ^ aBlock value  "the real logic is in Exception>>doRaise"

    "
     the first open will be caught; the second not:

     |o1 o2|

     o1 := 123.
     o2 := nil.
     Object messageNotUnderstoodSignal 
         handle:
                [:ex |
                    'oops' printNL.
                    ex proceed
                ] 
         from:o1
         do:
                [
                    o1 open.
                    o2 open
                ]
    "

    "Created: / 23.7.1999 / 14:06:26 / stefan"
    "Modified: / 25.7.1999 / 19:44:13 / stefan"
!

ignoreIn:aBlock
    "evaluate the argument, aBlock.
     Ignore the receiver-signal during evaluation - i.e. simply
     continue. 
     This makes only sense for some signals, such as UserInterrupt
     or AbortSignal, because continuing after an exception without any cleanup
     often leads to followup-errors."

    ^ self handle:[:ex | ex proceedWith:nil] do:aBlock.

    "
     Object messageNotUnderstoodSignal ignoreIn:[
        123 size open   
     ]
    "

    "Created: / 23.7.1999 / 14:06:40 / stefan"
! !

!GenericException class methodsFor:'compatibility - signal creation'!

newSignal
    "create a new signal, using the receiver as a prototype and
     setting the parent of the new signal to the receiver."

    ^ self newSignalMayProceed:self mayProceed

    "Created: / 23.7.1999 / 20:13:23 / stefan"
!

newSignalMayProceed:proceed
    "create a new signal, using the receiver as a prototype and
     setting the parent of the new signal to the receiver."

    ^ (Signal basicNew) mayProceed:proceed;
                    notifierString:NotifierString;
                            parent:self

    "Created: / 23.7.1999 / 20:12:43 / stefan"
! !

!GenericException class methodsFor:'printing'!

description
    "return the notifier string.
     If the notifier string starts with space, prepend
     the parents notifier string.
     Subclasses may redefine this method."

    NotifierString isNil ifTrue:[
        ^ self name asString
    ].
    (NotifierString startsWith:Character space) ifTrue:[
        ^ self parent description, NotifierString
    ].
    ^ NotifierString

    "
     Object errorSignal description
    "

    "Created: / 23.7.1999 / 14:22:25 / stefan"
! !

!GenericException methodsFor:'accessing'!

creator
    "return the creator of the exception"

    ^ signal
!

errorString 
    "return the errorString passsed with the signal raise
     (or nil, if there was none).
     #errorString is deprecated, use description instead"


    ^ self description

    "Modified: / 12.3.1998 / 15:13:28 / stefan"
!

errorString:aString 
    "set the errorString.
     If it starts with a space, the signals errorString is prepended,
     if it ends with a space, it is appended.
     #errorString: is deprecated, use messageText: instead"

    errorString := aString

    "Created: / 5.3.1998 / 16:45:29 / stefan"
    "Modified: / 12.3.1998 / 15:30:45 / stefan"
!

handlerContext
    "return the context of the handler"

    ^ handlerContext
!

handlingException
    "return the handling exception (or signalSet or Exception).
     This is only valid during handler evaluation, and answers
     the object which accepted the actual signal.
     (i.e. the parent or signalSet or handlerCollection)"

    ^ handlingException
!

isResumable
    "return true, if the exception is resumable"

    ^ proceedable

    "Modified: / 2.3.1998 / 12:20:43 / stefan"
!

messageText:aString 
    "set the messageText.
     If it starts with a space, the signals errorString is prepended,
     if it ends with a space, it is appended."

    errorString := aString

    "Created: / 5.3.1998 / 16:45:29 / stefan"
    "Modified: / 12.3.1998 / 15:30:45 / stefan"
!

originator 
    "return the originator passsed with the signal raise
     (or nil, if there was none)"

    ^ originator
!

originator:anObject 
    "set the originator"

    originator := anObject

    "Created: / 5.3.1998 / 16:34:56 / stefan"
!

parameter
    "return the parameter passsed with the signal raise
     (or nil, if there was none)"

    ^ parameter
!

parameter:anObject
    "set the parameter of the exception"

    parameter := anObject

    "Created: / 5.3.1998 / 16:34:22 / stefan"
!

rejected
    "return true, if any other of the exceptions handlers has rejected 
     Uncertain, if this is really interesting to anybody.
     This is only valid during handler execution.
     (i.e. an outer handler can find out, if any other handler has already
     rejected).
     Currently only used to change the 'unhandled-exception' errorString 
     into 'rejected-exception' for information).
    "

    ^ rejected == true
!

signal
    "return the signal, that caused the exception"

    ^ signal
!

signal:aSignal
    "set the signal, that caused the exception"

    signal := aSignal

    "Created: / 5.3.1998 / 16:02:46 / stefan"
!

suspendedContext
    "return the context in which the raise occured"

    ^ suspendedContext
!

suspendedContext:something
    "set the value of the instance variable 'suspendedContext' (automatically generated)"

    suspendedContext := something.

    "Created: / 2.3.1998 / 12:43:20 / stefan"
!

willProceed
    "return true, if the exception is proceedable"

    ^ self isResumable

    "Modified: / 2.3.1998 / 12:20:43 / stefan"
! !

!GenericException methodsFor:'copying'!

postCopy
    "set the internal state to nil"

    suspendedContext := handlerContext := rejected := nil

    "Created: / 2.3.1998 / 12:30:06 / stefan"
! !

!GenericException methodsFor:'default actions'!

defaultAction
    "perform a action for the exception if it hasn't been catched
     We arrive here, if either no handler was found, or none of the
     handlers did a return (i.e. every handler rejected).

     The default is to evaluate the signal's handlerBlock or 
     to raise the noHandlerSignal.
     Subclasses may redefine this."

    |handlerBlock|

    "
     try per signal handler
    "
    (handlerBlock := signal handlerBlock) notNil ifTrue:[
        "... and call it"
        ^ handlerBlock value:self.
    ].

    "/ if its a querySignal, ignore it
    signal isQuerySignal ifTrue:[^ nil].
    ^ self noHandler.

    "Created: / 23.7.1999 / 14:38:03 / stefan"
    "Modified: / 4.8.1999 / 08:11:05 / stefan"
!

mayProceed
    "return true, if the exception handler is allowed to proceed
     the execution where the exception occured.

     Subclasses may redefine this."

    ^ signal mayProceed

    "Created: / 23.7.1999 / 14:48:26 / stefan"
!

noHandler
    "raise the NoHandlerError.
     NohandlerError redefines this method to avoid recursive invocations"

    <context: #return>

    |msg|

    rejected == true ifTrue:[
        msg := 'unhandled (rejected)'
    ] ifFalse:[
        msg := 'unhandled'
    ].
    msg := msg , ' exception: (' , self errorString , ')'.
    self mayProceed ifTrue:[
        ^ NoHandlerError 
              raiseRequestWith:self 
              errorString:msg
              in:suspendedContext.
    ].
    NoHandlerError 
          raiseWith:self 
          errorString:msg
          in:suspendedContext.

! !

!GenericException methodsFor:'handler actions'!

proceed
    "Continue after the raise - the raise returns nil"

    self proceedWith:nil.

    "cg: a strange example: 
        there are two cought errors here - can you spot them ?

     Object errorSignal handle:[:ex|
         'proceeding' printCR.
         ex proceed
     ] do:[
         Object errorSignal raiseRequest
     ].
    "

    "Modified: / 27.3.1997 / 16:44:39 / cg"
    "Modified: / 4.8.1999 / 08:42:12 / stefan"
!

proceedWith:value
    "Continue after the raise - the raise returns value"

    |con|

    proceedable ifFalse:[
        "proceed from ProceedError to recover from this error"
        ProceedError raiseRequestWith:self.
        proceedable := true.
    ].

    thisContext evaluateUnwindActionsUpTo:suspendedContext.
    suspendedContext resumeIgnoringErrors:value.

    "/ arrive here, if suspended context is not resumable -
    "/ sigh; resume our raise context ...
    "/ ... consider this a fallBack kludge, for the case that
    "/ a raising context is not returnable.

    "/ find my raise context
    con := Context findFirstSpecialHandle:false raise:true.
    [con notNil 
     and:[con receiver ~~ self]] whileTrue:[
        con := con findSpecialHandle:false raise:true.
    ].
    "/ now, have the doCallXXX context at-hand
    con := con sender.
    "/ now, have the doRaise context at-hand
    con := con sender.
    "/ now, have the raise context at-hand

    handlerContext := suspendedContext := nil.
    con resume:value.

    "Modified: / 27.3.1997 / 16:45:57 / cg"
    "Modified: / 4.8.1999 / 08:42:17 / stefan"
!

reject
    "handler decided not to handle this signal -
     system will look for another handler"

    |con|

    "/ find my raise context
    con := Context findFirstSpecialHandle:false raise:true.
    [con notNil 
     and:[con receiver ~~ self]] whileTrue:[
        con := con findSpecialHandle:false raise:true.
    ].
    "/ now, have the doCallXXX context at-hand

    rejected := true.
    con unwind:nil.

    "
     Object errorSignal handle:[:ex |
        '1' printCR.
        ex reject
     ] do:[
        Object errorSignal handle:[:ex |
            '2' printCR.
            ex reject
        ] do:[
            #() at:1
        ]
     ]
    "
!

resignalAs:anotherException
    "resignal anotherException, as if it was raised in the first place"

    |con|

    con := suspendedContext.

"/    "/ find my raise context
"/    con := Context findFirstSpecialHandle:false raise:true.
"/    [con notNil 
"/     and:[con receiver ~~ self]] whileTrue:[
"/        con := con findSpecialHandle:false raise:true.
"/    ].
"/    "/ now, have the doCallXXX context at-hand
"/    con := con sender.
"/    "/ now, have the doRaise context at-hand
"/    con := con sender.
"/    "/ now, have the raise* context at-hand
"/    con := con sender.
"/    "/ now, have the raising context at-hand

    handlerContext := suspendedContext := nil.
    con unwindThenDo:[anotherException mayProceed ifTrue:[
                          anotherException raiseRequest
                      ] ifFalse:[
                          anotherException raise
                      ]
                     ]

    "
     |rslt n|

     Object messageNotUnderstoodSignal handle:[:ex |
        ex resignalAs:Number divisionByZeroSignal
     ] do:[
        rslt := 5 foo
     ].
     rslt
    "
!

restart
    "restart the handle:do: - usually after some repair work is done
     in the handler"

    |con|

    con := handlerContext.
    handlerContext := suspendedContext := nil.
    con unwindAndRestart

    "
     |rslt n|

     Object errorSignal handle:[:ex |
        'fixing divisor ...' printCR.
        n := 1.
        ex restart.
     ] do:[
        rslt := 5 / n.
     ].
     rslt
    "
!

restartDo:aBlock
    "restart the handle:do: but execute the argument, aBlock instead of the
     original do-block - usually after some repair work is done in handler"

    |con|

    con := handlerContext.

"/    handlerContext unwindThenDo:[
"/        handlerContext receiver 
"/            handle:(handlerContext argAt:1)
"/            do:aBlock
"/    ].
    handlerContext := suspendedContext := nil.
    con receiver handlerProtectedBlock:aBlock inContext:con.
    con unwindAndRestart

    "
     |sig rslt|

     sig := Signal new.

     sig handle:[:ex |
        ex restartDo:[ rslt := 999 ]
     ] do:[
        rslt := 0.
        sig raise
     ].
     Transcript showCR:rslt
    "

    "
     |sig rslt|

     Object errorSignal handle:[:ex |
        ex restartDo:[ rslt := 999 ]
     ] do:[
        rslt := nil foo.

     ].
     Transcript showCR:rslt
    "

    "
     |sig rslt|

     Object errorSignal handle:[:ex |
        ex restartDo:[ 'handler' printCR. rslt := nil foo ]
     ] do:[
        rslt := nil foo.

     ].
     Transcript showCR:rslt
    "

    "Modified: / 8.11.1997 / 18:52:28 / cg"
!

resume
    "Continue after the raise - the raise returns nil
     obsolete (use #proceed), retained for backwards compatibility"

    self obsoleteMethodWarning:'use #proceed'.
    ^ self proceedWith:nil

    "Modified: / 2.3.1998 / 10:51:55 / stefan"
!

resumeWith:value
    "Continue after the raise - the raise returns value
     obsolete (use #proceedWith:), retained for backwards compatibility"

    self obsoleteMethodWarning:'use #proceedWith:'.
    ^ self proceedWith:value

    "Modified: / 2.3.1998 / 10:51:48 / stefan"
!

return
    "Continue after the handle:do: - the handle:do: returns nil"

    |con|

    con := handlerContext.
    handlerContext := suspendedContext := nil.
    con unwind:nil

    "Modified: 27.3.1997 / 16:46:39 / cg"
!

returnDoing:aBlock
    "Continue after the handle:do: - the handle:do: returns aBlock value
     Be careful when debugging. You cannot see the context with #returnDoing:
     in the debugger if aBlock raises a signal"

    |con|

    con := handlerContext.
    handlerContext := suspendedContext := nil.
    con unwindThenDo:aBlock
!

returnWith:value
    "Continue after the handle:do: - the handle:do: returns value"

    |con|

    con := handlerContext.
    handlerContext := suspendedContext := nil.
    con unwind:value

    "Modified: 27.3.1997 / 16:46:51 / cg"
! !

!GenericException methodsFor:'printing'!

description
    "return the description string of the signal"

    errorString isNil ifTrue:[
        ^ signal description
    ].
    (errorString startsWith:Character space) ifTrue:[
        ^ signal description, errorString.
    ].
    (errorString endsWith:Character space) ifTrue:[
        ^ errorString, signal description.
    ].

    ^ errorString

    "
      (Error new messageText:'bla') description
      (Error new messageText:' bla') description
      (Error new messageText:'bla ') description
    "

    "Modified: / 12.3.1998 / 15:13:28 / stefan"
! !

!GenericException methodsFor:'private'!

doCallAction
    "call the action proper 
     - needed an extra method to have a raise-marked context around
       ( see implementation of #reject and #proceed)."

    <context: #return>
    <exception: #raise>

    "/ thisContext markForRaise. -- same as above pragma
    ^ self defaultAction
!

doCallHandler:aHandlerBlock
    "call the handler proper 
     - needed an extra method to have a raise-marked context around.
       ( see implementation of #reject and #proceed)."

    <context: #return>
    <exception: #raise>

    |val|

    "/ thisContext markForRaise. -- same as above pragma

    val := aHandlerBlock value:self.
    "
     handler fall through - is just like a returnWith:blocks-value
    "
    self returnWith:val

    "Modified: / 26.7.1999 / 14:41:55 / stefan"
!

doRaise
    "search through the context-calling chain for a handle-context 
     to the raising signal, a parent of it, or a SignalSet which includes 
     the raising signal.
     If found, ask the receiver for the handler and evaluate
     it with the receiver exception as argument.
     If no handler is found, perform the default #action method.

     ATTENTION: the code below depends on being called by #raise or
     #raiseRequest for proper operation (it skips the sending context)."

    <context: #return>

    |theContext handler
     theSignal c ex1 activeHandlers 
     "lastHandler" h r firstHandler searchForHandle|


    "/ is nil a valid originator? If so, we need an extra
    "/ instanceVariable to record the originator setting.

    originator isNil ifTrue:[
        originator := suspendedContext homeReceiver
    ].

    theSignal := signal.
    theSignal isSignal ifFalse:[
        self halt:'unexpected non-Signal in calling context'.
    ].

"/ 'search handler for: ' print. theSignal displayString printCR.

    "/ since the exceptionHandler is evaluated on top of the
    "/ contextChain, we must skip active handlers before searching.
    "/ otherwise, we get into trouble, when re-raising an exception
    "/ from within a handler (which would lead to re-executing the
    "/ same handler)
    "/ the code below collects active handlers ...

    "/ on the fly, look for the first handle - context,
    "/ and remember it (as firstHandler) to avoid walking the context chain twice
    "/ in most cases ...

    firstHandler := nil.
    searchForHandle := true.

    c := Context findFirstSpecialHandle:searchForHandle raise:true.

    [c notNil] whileTrue:[
        (c isRaiseContext) ifTrue:[
            ex1 := c receiver.
            ((ex1 class == self class)
            or:[ex1 species == self species]) ifTrue:[
                h := ex1 handlerContext.
                h notNil ifTrue:[
                    ((ex1 signal == theSignal)

                    "/ mhmh - if not ==, the raised signal there is not ours, 
                    "/ but the handler could still be for a signalSet, parentSig
                    "/ or other thingy which accepts our signal.
                    "/ If we omit that check, a signalSet-handler gets invoked
                    "/ again by an exception occuring inside its handler.

                    "/ to avoid overhead, only do it if the
                    "/ handlers receiver is not of the signals class...
                    "/ ...i.e. knowing that most are r handle:do: contexts,
                    "/ where the receiver is the handling signal.
                    or:[h receiver ~~ ex1 signal
                        and:[ex1 handlingException accepts:theSignal]]) ifTrue:[
                        activeHandlers isNil ifTrue:[
                            activeHandlers := OrderedCollection new
                        ].

                        activeHandlers add:h.
                        "/ lastHandler := h.
                        c := h.
                    ]
                ]
            ]
        ] ifFalse:[
            "/ must be a handle context ...
            firstHandler := c.
            searchForHandle := false.
        ].
        c := c findSpecialHandle:searchForHandle raise:true.
    ].

    h := nil.
    c := nil.

    "/ now, start searching for a handler,
    "/ start search above the last active handler.
    "/ Or start with the first handle context, if one
    "/ was found as a side effect of the previous handler search.
    "/ If nil, then there is no handler and we can directly proceed
    "/ to the unhandled code below.

"/    lastHandler notNil ifTrue:[
"/        theContext := lastHandler.
"/        theContext := lastHandler findNextHandleContext
"/    ] ifFalse:[
        theContext := firstHandler.
"/    ].
    firstHandler := nil.

    [theContext notNil] whileTrue:[
        "/
        "/  ask the Signal instance/Exception class for the handler.
        "/  nil is returned, if the signal is not accepted
        "/
        r := theContext receiver.
        (r notNil and:[(handler := r handlerForSignal:signal 
                                     context:theContext 
                                     originator:originator) notNil]
        ) ifTrue:[
            (activeHandlers notNil
             and:[activeHandlers includesIdentical:theContext]) ifTrue:[
"/                'skip activeHandler: ' print. theContext displayString printCR.

            ] ifFalse:[
                "call the handler"

                handlerContext := theContext.
                "/ remember the handling signal, sigSet, or exception
                "/ for the #accepts: check above
                handlingException := r handlingExceptionInContext:theContext.
                theContext := nil.
                self doCallHandler:handler.

                "/ if the handler rejects, we arrive here
                "/ continue search for another handler
                theContext := handlerContext.
                handlerContext := nil.
            ].
        ].
        theContext := theContext findSpecialHandle:true raise:false.
    ].

    "/ help GC a bit, by clearing things we no longer need
    "/ (especially useful for contexts ...)
    activeHandlers := handler := ex1 := firstHandler := nil.

    "
     we arrive here, if either no handler was found, 
     or every handler rejected.
    "
    ^ self doCallAction

    "Created: / 12.5.1996 / 15:09:39 / cg"
    "Modified: / 9.11.1997 / 14:48:44 / cg"
    "Modified: / 3.8.1999 / 11:20:41 / stefan"
! !

!GenericException methodsFor:'raising'!

raise
    "actually raise a non-proceedable exception"

    <context: #return>

    suspendedContext isNil ifTrue:[
        suspendedContext := thisContext sender
    ].

    proceedable := false.
    ^ self doRaise

    "Modified: / 12.5.1996 / 15:09:47 / cg"
    "Modified: / 3.8.1999 / 13:33:01 / stefan"
!

raiseRequest
    "actually raise a proceedable exception."

    <context: #return>

    suspendedContext isNil ifTrue:[
        suspendedContext := thisContext sender
    ].

    self mayProceed ifFalse:[
        "/ proceeding from wrongProceedabilitySignal grants the raiseRequest
        WrongProceedabilityError raiseRequestWith:signal
    ].

    proceedable := true.
    ^ self doRaise

    "Modified: / 12.5.1996 / 15:09:44 / cg"
    "Modified: / 4.8.1999 / 08:05:12 / stefan"
! !

!GenericException methodsFor:'setup'!

signal:aSignal originator:origin
    "set the fields usable for inspection by the handler
     - only to be sent from the signal when raising"

    signal := aSignal.
    originator := origin.

    "Created: / 23.7.1999 / 13:39:35 / stefan"
!

signal:aSignal parameter:aParameter errorString:aString suspendedContext:sContext originator:origin
    "set the fields usable for inspection by the handler
     - only to be sent from the signal when raising"

    signal := aSignal.
    parameter := aParameter.
    errorString := aString.
    suspendedContext := sContext.
    originator := origin.
! !

!GenericException class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/GenericException.st,v 1.27 1999-09-17 17:01:24 cg Exp $'
! !
GenericException initialize!