Exception.st
author Claus Gittinger <cg@exept.de>
Sat, 18 Jan 1997 19:37:26 +0100
changeset 2204 0ec2bd49dd82
parent 2174 3c6300f27f74
child 2208 cc55b9f5b47e
permissions -rw-r--r--
comment

"
 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:#Exception
	instanceVariableNames:'signal parameter errorString suspendedContext handlerContext
		rejected originator resumeBlock rejectBlock'
	classVariableNames:'EmergencyHandler RecursiveExceptionSignal'
	poolDictionaries:''
	category:'Kernel-Exceptions'
!

!Exception 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
"
    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          - dont 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)

        resumeBlock      <Block>      private to the exception; needed to perform resume action

        rejectBlock      <Block>      private to the exception; needed to perform reject action

    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]


    [Class variables:]
        EmergencyHandler <Block>    this block is evaluated, if no handler was defined
                                    for a signal (i.e. this one is responsible for the
                                    unhandled exception debugger).
                                    Having this being a block allows to globally catch
                                    these errors - even when no enclosing handler-scope
                                    around the erronous code exists.
                                    (as the catch/through does).

        RecursiveExceptionSignal
                         <Signal>   raised when within a handler for some signal,
                                    the same signal is raised again.


    [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.
    Some commonly used (useful) emergency handlers are provided in the
    'useful handlers' section; try them to learn more
    (especially, the mailingHandler is fun).

    Define a handler:
                                                                [exBegin]
        Exception emergencyHandler:(Exception abortingEmergencyHandler)
                                                                [exEnd]


    try some exception (for demonstration, in some other process):
                                                                [exBegin]
        [
            #(1 2 3) at:4
        ] fork.
                                                                [exEnd]

    cleanup:
                                                                [exBegin]
        Exception emergencyHandler:nil
                                                                [exEnd]


    A handler which dumps information to a file (watch the file 'errorTrace.stx'):
                                                                [exBegin]
        Exception emergencyHandler:(Exception dumpingEmergencyHandler)
                                                                [exEnd]

    A handler which sends you mail:
                                                                [exBegin]
        Exception emergencyHandler:(Exception mailingEmergencyHandler)
                                                                [exEnd]
"
! !

!Exception class methodsFor:'initialization'!

initialize 
    "setup the signal used to handle unhandled signals"

    RecursiveExceptionSignal isNil ifTrue:[
	RecursiveExceptionSignal := ErrorSignal newSignalMayProceed:false.
	RecursiveExceptionSignal nameClass:self message:#recursiveExceptionSignal.
	RecursiveExceptionSignal notifierString:'recursive signal raise in handler'
    ]
! !

!Exception class methodsFor:'instance creation'!

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

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

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"

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

!Exception class methodsFor:'Signal constants'!

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

    ^ RecursiveExceptionSignal
! !

!Exception class methodsFor:'defaults'!

emergencyHandler
    "return the handler used for unhandled exceptions.

     If no EmergencyHandler has been set, a handler which enters the 
     debugger is returned.
     The debugger is opened by asking the signal for a debug action,
     this allows to provide other debuggers in specialized (subclass-instances)
     of Signal (if that is ever needed)"

    "
     set it up, when called the first time
    "
    EmergencyHandler isNil ifTrue:[
        EmergencyHandler := [:ex |
            "
             sending it to the signal allows per-signal specific
             debuggers to be implemented in the future
             (for example, segv in primitive code could show things 
              on the C-level ..)
            "
            (ex signal) enterDebuggerWith:ex message:(ex errorString).
        ]
    ].

    ^ EmergencyHandler

    "Modified: 15.1.1997 / 20:50:37 / cg"
!

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

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

!Exception class methodsFor:'useful handlers'!

abortingEmergencyHandler
    "return a block (usable as an emergency handler), 
     which aborts after showing a warnBox.
     This is useful for endUser applications"

    ^ [:ex | self warn:'Error: ' , ex errorString.
             AbortSignal raise 
      ]

    "test with (try a few halts or CTRL-C's):
     Exception emergencyHandler:(Exception abortingEmergencyHandler)
    "

    "back with:
     Exception emergencyHandler:(Exception notifyingEmergencyHandler)
     Exception emergencyHandler:nil
    "

    "Created: 15.1.1997 / 20:13:06 / cg"
    "Modified: 15.1.1997 / 20:15:02 / cg"
!

dumpingEmergencyHandler
    "return a block (usable as an emergency handler), 
     which dumps the stackBacktrace to a trace file and
     aborts after showing a warnBox.
     This is useful, for endUser application, which are still being
     debugged (i.e. the programmers may have a look at the traceFile
     from time to time).

     Notice:
         The code below is just an example; you may want to change the
         name of the error-file in your application
         (but please: copy the code; do not modify here)"

    ^ [:ex | 
             |str printedException|

             ex signal == Signal noHandlerSignal ifTrue:[
                printedException := ex parameter.
             ] ifFalse:[
                printedException := ex
             ].

             "/ user interruption is handled specially:
             "/ allow user to choose between proceeding or aborting
             "/ but never dump that information to the file.

             printedException signal == Object userInterruptSignal ifTrue:[
                  (self confirm:'abort current action ?') ifTrue:[
                      AbortSignal raise
                  ].
                  ex proceed
             ].

             "/
             "/ dump it to 'errorTrace.stx'
             "/
             str := 'errorTrace.stx' asFilename appendingWriteStream.

             str nextPutLine:('******************************* '
                              , AbsoluteTime now printString
                              , ' *******************************').
             str cr.

             str nextPutLine:('** Error: ' , printedException errorString).
             str nextPutLine:('** Signal: ' , printedException signal printString).
             str nextPutLine:('** Parameter: ' , printedException parameter printString).
             str nextPutLine:('** Process: ' , Processor activeProcess printString).
             str nextPutLine:('** Backtrace:').
             str cr.
        
             printedException suspendedContext fullPrintAllOn:str.
             str cr.
             str cr.
             str close.

             self warn:printedException errorString.
             AbortSignal raise 
      ]

    "test with (try a few halts or CTRL-C's):
     Exception emergencyHandler:(Exception dumpingEmergencyHandler)
    "

    "back with:
     Exception emergencyHandler:(Exception notifyingEmergencyHandler)
     Exception emergencyHandler:nil
    "

    "Created: 15.1.1997 / 20:14:52 / cg"
    "Modified: 15.1.1997 / 21:07:14 / cg"
!

mailingEmergencyHandler
    "return a block (usable as an emergency handler), 
     which shows a warnBox and optionally mails a stackBacktrace to a maintainer.
     This is useful, for endUser application, which are still being
     debugged (i.e. the programmers may have a look at the errors).

     Notice: the stuff here is a demonstration only; it should be modified
             for your particular environment ...
             ... but please: copy the code and modify there;
             leave the stuff below as it is."

    ^ [:ex | 
            |str printedException doMail emergencyMailReceiver pipe|

            ex signal == Signal noHandlerSignal ifTrue:[
               printedException := ex parameter.
            ] ifFalse:[
               printedException := ex
            ].

             "/ user interruption is handled specially:
             "/ allow user to choose between proceeding or aborting
             "/ but never dump that information to the file.

             printedException signal == Object userInterruptSignal ifTrue:[
                  (self confirm:'abort current action ?') ifTrue:[
                      AbortSignal raise
                  ].
                  ex proceed
             ].

            "/ somehow get the name of the guy to receive the mail
            "/ you have to implement that yourself.

            "/ emergencyMailReceiver := OneOfYourClass getEmergencyMailReceiver.
            emergencyMailReceiver := OperatingSystem getLoginName.

            emergencyMailReceiver isNil ifTrue:[
                self warn:(printedException errorString 
                           , '\\No mailing to service people possible.') withCRs.
                doMail := false.
            ] ifFalse:[
                doMail := self confirm:(printedException errorString 
                                        , '\\Mail error information to the service people (' 
                                        , emergencyMailReceiver , ') ?') withCRs
            ].
            doMail ifTrue:[
                str := '' writeStream.

                str nextPutLine:('Error notification from '
                                , OperatingSystem getLoginName
                                , '@'
                                , OperatingSystem getHostName).
                str cr.

                str nextPutLine:('Time: ' , AbsoluteTime now printString).
                str nextPutLine:('Error: ', printedException errorString).
                str nextPutLine:('Signal: ', printedException signal printString).
                str nextPutLine:('Parameter: ', printedException parameter printString).
                str nextPutLine:('Process: ', Processor activeProcess printString).
                str nextPutLine:'Backtrace:'.
                str cr.

                printedException suspendedContext fullPrintAllOn:str.
                str cr;cr.

                str close.

                pipe := PipeStream 
                            writingTo:'mail ', emergencyMailReceiver.
                pipe notNil ifTrue:[
                    pipe nextPutLine:'Subject: automatic error report'.
                    pipe nextPutAll:str contents.
                    pipe cr.
                    pipe close.
                ]
             ].

             AbortSignal raise 
      ]

    "test with (try a few halts or CTRL-C's):
     Exception emergencyHandler:(Exception mailingEmergencyHandler)
    "

    "back with:
     Exception emergencyHandler:(Exception notifyingEmergencyHandler)
     Exception emergencyHandler:nil
    "

    "Created: 15.1.1997 / 20:14:52 / cg"
    "Modified: 15.1.1997 / 21:10:28 / cg"
!

notifyingEmergencyHandler
    "return a block (usable as an emergency handler for exceptions), 
     which does errorNotification before going into the debugger."

    ^ [:ex | nil errorNotify:ex errorString from:ex suspendedContext ]

    "test with (try a few halts or CTRL-C's):
     Exception emergencyHandler:(Exception notifyingEmergencyHandler)
    "

    "back with:
     Exception emergencyHandler:nil
    "

    "Modified: 15.1.1997 / 20:15:12 / cg"
! !

!Exception methodsFor:'accessing'!

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

    ^ errorString
!

handlerContext
    "return the context of the handler"

    ^ handlerContext
!

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

    ^ originator
!

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

    ^ parameter
!

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

    ^ rejected
!

signal
    "return the signal, that caused the exception"

    ^ signal
!

suspendedContext
    "return the context in which the raise occured"

    ^ suspendedContext
!

willProceed
    "return true, if the exception is proceedable"

    ^ resumeBlock notNil
! !

!Exception methodsFor:'handler actions'!

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

    resumeBlock notNil ifTrue:[resumeBlock value:nil]
!

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

    resumeBlock notNil ifTrue:[resumeBlock value:value]
!

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

    rejected := true.
    rejectBlock value
!

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

    handlerContext unwindAndRestart
!

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

    resumeBlock notNil ifTrue:[resumeBlock value:nil]
!

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

    resumeBlock notNil ifTrue:[resumeBlock value:value]
!

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

    handlerContext unwind
!

returnDoing:aBlock
    "Continue after the handle:do: - the handle:do: returns aBlock value"

    handlerContext unwindThenDo:aBlock
!

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

    handlerContext unwind:value
! !

!Exception methodsFor:'raising'!

doCallHandler:aHandler
    "call the handler proper - needed an extra method
     to have a separate returnContext for the rejectBlock.
     (which is historical, and actually no longer needed)"

    |val|

    rejectBlock := [^ self]. "this will return on reject"
    val := aHandler value:self.
    "
     handler fall through - is just like a returnWith:blocks-value
    "
    self returnWith:val
!

doRaise
    "search through the context-calling chain for a 'handle:do:'-context 
     to the raising signal, a parent of it, or a SignalSet which includes 
     the raising signal.
     If found, take the contexts 2nd argument (the handler) and evaluate
     it with the receiver exception as argument.
     If no handler is found, try per signal handler, or
     per process handler (if its the noHandlerSignal).
     Finally fall back to Exceptions emergencyHandler, which is always
     available and enters the debugger.
     ATTENTION: the code below depends on being called by #raise or
     #raiseRequest for proper operation (it skips the sending context)."

    |con block noHandlerSignal any msg sel conArg1
     theSignal c ex1 activeHandlers inHandler rejected
     lastHandler h|

    con := thisContext sender.  "the raise/raiseRequest-context"
    con := con sender.          "the signal raise context"

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

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

    inHandler := false.
    c := con sender.

    "/ since the exceptionHandler is evaluated onTop 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 ...

    [c notNil] whileTrue:[
        sel := c selector.
        sel == #doRaise ifTrue:[
            ex1 := c receiver.
            ex1 species == self species ifTrue:[
                c := c sender.
                (c notNil and:[c receiver == ex1]) ifTrue:[
                    c := c sender.
                    c notNil ifTrue:[
                        "/ the common case (really ?) first
                        (c receiver == theSignal) ifTrue:[
                            (c selector startsWith:'raise') ifTrue:[
                                h := ex1 handlerContext.
                                h notNil ifTrue:[
                                    activeHandlers isNil ifTrue:[
                                        activeHandlers := OrderedCollection new
                                    ].
                            
                                    lastHandler := h.
                                    activeHandlers add:lastHandler.
                                    inHandler := true.
                                    c := lastHandler.
"/ 'skip over active handler: ' print. c displayString printCR.
                                ]
                            ]
                        ] ifFalse:[
                            c receiver isSignal ifTrue:[
                                (c selector startsWith:'raise') ifTrue:[
                                    h := ex1 handlerContext.
                                    h notNil ifTrue:[
                                        (h receiver accepts:theSignal) ifTrue:[

                                        activeHandlers isNil ifTrue:[
                                            activeHandlers := OrderedCollection new
                                        ].
                                        lastHandler := h.
                                        activeHandlers add:lastHandler.
                                        inHandler := true.
                                        c := lastHandler.
"/ 'skip2 over active handler: ' print. h displayString printCR.
                                        ]
                                    ]    
                                ]    
                            ]    
                        ]
                    ]
                ]
            ].
        ].
        c := c sender.
    ].

    lastHandler notNil ifTrue:[
"/        'skip over last active handler: ' print. lastHandler displayString printCR.
        con := lastHandler sender.
    ].

    any := false.
    [con notNil] whileTrue:[
        con isBlockContext ifFalse:[

            "/ new behavior:
            (activeHandlers notNil
             and:[activeHandlers includesIdentical:con]) ifTrue:[
                'skip activeHandler: ' print. con displayString printCR.

            ] ifFalse:[
                sel := con selector.

                ((sel == #'handle:do:') 
                or:[((sel == #'handle:from:do:') 
                    and:[(con argAt:2) == originator])]) ifTrue:[
                    "
                     if this is the Signal>>handle:do: context
                     or a SignalSet>>handle:do: context with self in it,
                     call the handler
                    "
                    (con receiver accepts:signal) ifTrue:[
                        "call the handler"

                        conArg1 := con argAt:1.

                        handlerContext := con.
                        any := true.

                        self doCallHandler:conArg1.

                        "if the handler rejects, we arrive here"
                        "continue search for another handler"
                        rejected := true.
                    ].
                ]
            ]
        ].
        con := con sender
    ].

    activeHandlers := nil.

"/    (inHandler "and:[rejected ~~ true]") ifTrue:[
"/        "
"/         mhmh - an error while in a handler
"/         here, we do not fall back to the noHandlerSignal/staticHandler
"/         (makes debugging easier)
"/
"/         Should we ?
"/        "
"/        ((signal == RecursiveExceptionSignal)
"/        or:[RecursiveExceptionSignal isNil]) ifTrue:[
"/            "
"/             ... either while handling RecursiveExceptionSignal
"/             or at startup when RecursiveExceptionSignal is not yet
"/             created -
"/             - go immediately into the debugger.
"/            "
"/            ^ self enterDebuggerWith:self
"/                             message:'recursive signal raise'
"/        ].
"/        ^ RecursiveExceptionSignal 
"/            raiseRequestWith:self 
"/                 errorString:('recursive signal raise: (' , errorString , ')')
"/    ].

    "
     we arrive here, if either no handler was found, or none of the
     handlers did a return (i.e. every handler rejected or fell through).
    "
    "
     try per signal handler
    "
    (block := signal handlerBlock) isNil ifTrue:[
        "/
        "/ if its a querySignal, ignore it
        "/
        signal isQuerySignal ifTrue:[^ nil].

        "/
        "/ if it is not the NoHandlerSignal, raise it ...
        "/ passing the receiver as parameter.
        "/
        signal ~~ (noHandlerSignal := Signal noHandlerSignal) ifTrue:[
            noHandlerSignal notNil ifTrue:[
                any ifTrue:[
                    msg := 'unhandled (rejected)'
                ] ifFalse:[
                    msg := 'unhandled'
                ].
                msg := msg , ' exception: (' , errorString , ')'.
                ^ noHandlerSignal 
                      raiseRequestWith:self 
                           errorString:msg
                                    in:self suspendedContext
            ].
            "/
            "/ mhmh - an error during early startup; noHandlerSignal is
            "/ not yet defined.
            "/
            ^ MiniDebugger enterWithMessage:errorString
        ].

        "
         mhmh - smells like trouble - there is no handler and
         no per-signal handler block.
         Look for either a per-process emergencyHandlerBlock 
         or the global emergencyHandler (from Exception) ...
        "
        Processor notNil ifTrue:[ 
            "care for signal during startup (Processor not yet created)"
            block := Processor activeProcess emergencySignalHandler.
        ].
        block isNil ifTrue:[
            block := Exception emergencyHandler.
            block isNil ifTrue:[
                "care for error during startup (Exception not yet initialized)"
                ^ MiniDebugger enterWithMessage:errorString
            ].
        ].
    ].
    "... and call it"
    ^ block value:self.

    "Created: 12.5.1996 / 15:09:39 / cg"
    "Modified: 9.11.1996 / 17:04:28 / cg"
!

raise
    "actually raise a non-proceedable exception.
     CAVEAT:
         For now, in ST/X all signals are proceedable."

    resumeBlock := [:value | ^ value].
    ^ self doRaise

    "Modified: 12.5.1996 / 15:09:47 / cg"
!

raiseRequest
    "actually raise a proceedable exception."

    resumeBlock := [:value | ^ value].
    ^ self doRaise

    "Modified: 12.5.1996 / 15:09:44 / cg"
! !

!Exception methodsFor:'setup'!

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

!Exception class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.45 1997-01-18 18:37:26 cg Exp $'
! !
Exception initialize!