Exception.st
author claus
Sat, 22 Jul 1995 21:25:26 +0200
changeset 362 4131e87e79ec
parent 345 cf2301210c47
child 367 a2114577b799
permissions -rw-r--r--
.

"
 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 comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.22 1995-07-22 19:22:18 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.22 1995-07-22 19:22:18 claus Exp $
"
!

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,
				    th same signal is raised again.
"
! !

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

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

emergencyHandler:aOneArgBlock
    "set the handler used for unhandled exceptions"

    EmergencyHandler := aOneArgBlock

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

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

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

!Exception class methodsFor:'instance creation'!

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

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

!Exception methodsFor:'accessing'!

signal
    "return the signal, that caused the exception"

    ^ signal
!

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

    ^ parameter
!

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

    ^ errorString
!

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

    ^ originator
!

handlerContext
    "return the context of the handler"

    ^ handlerContext
!

suspendedContext
    "return the context in which the raise occured"

    ^ suspendedContext
!

rejected
    "return true, if any other of the exceptions handlers has rejected 
     Uncertain, if this is really interresting 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
!

willProceed
    "return true, if the exception is proceedable"

    ^ resumeBlock notNil
! !

!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 methodsFor:'raising'!

raise
    "actually raise a nonproceedable exception.
     For now, same as #raiseRequest (always proceedable)."

    resumeBlock := [:value | ^ value].
    ^ self evaluateHandler
!

raiseRequest
    "actually raise a proceedable exception."

    resumeBlock := [:value | ^ value].
    ^ self evaluateHandler
!

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

    |con block noHandlerSignal any msg sel|

    con := thisContext sender.  "the raise-context"
    con := con sender.          "the signal raise context"
    con isRecursive ifTrue:[
	"
	 mhmh - an error while in a handler
	"
	((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)
    ].

    any := false.
    [con notNil] whileTrue:[
	con isBlockContext ifFalse:[
	    (((sel := con selector) == #'handle:do:') 
	    or:[((sel == #'handle:from:do:')
		and:[(con args at: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"

		    handlerContext := con.
		    any := true.
		    self doCallHandler:(con args at:1).

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

    "
     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) notNil ifTrue:[
	^ block value:self.
    ].

    "
     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'
	    ].
	    ^ noHandlerSignal 
		  raiseRequestWith:self 
		       errorString:(msg , ' exception: ' , errorString)
				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.
!

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

!Exception methodsFor:'handler actions'!

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

    rejected := true.
    rejectBlock value
!

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

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

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

    handlerContext unwind
!

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

    handlerContext unwind:value
!

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

    handlerContext unwindThenDo:aBlock
!

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

    handlerContext unwindAndRestart
! !