GenericException.st
author Stefan Vogel <sv@exept.de>
Wed, 22 Sep 2004 16:42:22 +0200
changeset 8586 a38e882affa5
parent 8509 b62464d549f5
child 8617 5fb5a717deff
permissions -rw-r--r--
take care of time-wrap in #millisecondsToRun:

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

"{ Package: 'stx:libbasic' }"

Object subclass:#GenericException
	instanceVariableNames:'signal parameter messageText suspendedContext handlerContext
		rejected originator proceedable handlingException'
	classVariableNames:'StrictRaising'
	poolDictionaries:''
	category:'Kernel-Exceptions'
!

GenericException class instanceVariableNames:'NotifierString'

"
 No other class instance variables are inherited by this class.
"
!

!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
"
    Note: 
	The instance based Signal framework is being replaced by
	class based exceptions.
	I.e. what used to be instances of Signal/QuerySignal is beeing
	rewritten into subclasses of Exception/Error/Query and Warning.
	Although the functionality is basically unchanged, the new
	class based exceptions are easier to instanciate (no need for
	creation in a classes initialize method), easier to use (no real
	need for SIgnal-constant accessors) and allow for easier parameter
	passing (not only a single parameter, but allows for individual
	exception subclasses to add additional state).

    GenericException and its subclasses implement the same protocol as Signal.
    So class based exceptions may be implemented as subclasses of GenericException.

    Normally all exceptions are subclasses of Exception. Exceptions, that are
    used for debugging or that are signalling errors in the exception system itself
    are direct 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 messageText 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)

	messageText      <String>     an messageText 
				      (usually the signals own messageText, 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]


    Raising:
	two different raising messages are to be used, 
	depending on whether the exception is proceedable or not

	For some stupid reason, someone decided that the raise-code checks if
	the raising messages matches to what the signal thinks is its proceedability.
	(i.e. not only do both the sender and the signal itself specify proceedability,
	 this is checked by the raise code and a warning is generated if there is a mismatch)
	This used to be even worse (WrongProceedabilityError), but we relaxed this to
	a message sent to stderr.

	That means, that PROCEEDABLE signals must be raised with:
	    raiseRequest
	and NON-PROCEEDABLE signals must be raised with:
	    raise

	If you dont know/care as a raiser, you can use
	    raiseSignal
	which checks for proceedability and sends the appropriate message.
	(sigh)

    all of the 3 messages above come in various flavours:
	raiseXXX                - do not pass any additional parameter;
				  default messageText

	raiseXXXWith:           - pass additional parameter;
				  default messageText

	raiseXXXErrorString:    - do not pass any additional parameter;
				  given errorString

	raiseXXXWith:errorString:
				- pass any additional parameter;
				  AND given errorString


    [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'.
    StrictRaising := false.     "set to true to check weather a signal may be raised proceedable"

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

!GenericException class methodsFor:'instance creation'!

new
    "{ Pragma: +inlineNew }"

    ^ self basicNew setSignal: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"
!

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:'Compatibility-ANSI'!

raiseSignal:errorMessage 
    "raise a signal (proceedable or not, whatever the proceedability is).
     The argument, errorMessage is used as messageText."
    
    <context: #return>

    ^ (self newException 
        suspendedContext:thisContext sender
        errorString:errorMessage) raiseSignal.

    "Modified: / 07-08-2004 / 19:24:00 / stefan"
!

raiseSignal:errorMessage with:aParameter
    "raise a signal (proceedable or not, whatever the proceedability is).
     The argument, errorMessage is used as messageText."

    <context: #return>

    ^ (self newException 
        suspendedContext:thisContext sender
        errorString:errorMessage;
        parameter:aParameter)
            raiseSignal.

    "Modified: / 07-08-2004 / 19:10:40 / stefan"
!

signalWith:messageText
    self raiseErrorString:messageText
! !

!GenericException class methodsFor:'Compatibility-Dolphin'!

signal:messageText
    "raise a signal proceedable or nonproceedable (whichever is right).
     The argument is used as messageText."

    <context: #return>

    ^ (self newException 
	suspendedContext:thisContext sender
	errorString:messageText)
	    raiseSignal.
! !

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

    <resource:#obsolete>

    ^ 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 description ]
    "

    "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:anExceptionHandler isHandledIn:aContext
    "return true, if there is a handler for the receiver signal in the 
     contextChain starting with aContext."

    |theContext|

    theContext := aContext findExceptional.
    [theContext notNil] whileTrue:[
        theContext isRaiseContext ifTrue:[ |ex1 con1|
            "skip all the contexts between the raise and the sender of #handle:do"
            ex1 := theContext receiver.              "exception, that has been raised"
            con1 := ex1 handlerContext.              "the context of the #handle:do:"
            con1 notNil ifTrue:[
                "handlerContext may be nil, if this is a default action"
                theContext := con1.
            ].
            ex1 := con1 := nil.
        ] ifFalse:[ |r|
            ((r := theContext receiver) notNil
             and:[(r handlerForSignal:anExceptionHandler context:theContext originator:nil) notNil]
            ) ifTrue:[
                "found a handler context"
                ^ true
            ].
        ].
        theContext notNil ifTrue:[
            theContext := theContext findSpecialHandle:true raise:true.
        ].
    ].

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

    |sel|

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

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

    |sel|

    sel := theContext selector.
    (sel == #'handle:from:do:'
     or:[sel == #'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"
!

isExceptionCreator
    "return true, if the receiver can create exceptions,
     this includes #raise, #raiseRequest as well as the behavior of
     an exception handler, such as the #accepts: and #handles: messages"

    ^ true
!

isExceptionHandler
    "return true, if the receiver responds to the exception handler protocol,
     especially to the #accepts: and #handles: messages"

    ^ true

    "Created: / 23.7.1999 / 13:49:59 / 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"
!

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

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

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

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

raiseErrorString:aString in:aContext
    "raise a signal nonproceedable.
     The argument is used as messageText."

    <context: #return>

    ^ (self newException 
	suspendedContext:aContext
	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 messageText."

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

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

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

    <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 messageText.
     The additional context is passed as the context responsible for the raise,
     allowing a raise to mimicri the exception happened somewhere else."

    ^ (self newException 
	suspendedContext:aContext
	parameter:aParameter  
	errorString:aString)
	    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"
!

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

    ^ (self newException 
	suspendedContext:aContext
	parameter:aParameter) 
	    raiseRequest
!

raiseSignal
    "raise a signal (proceedable or not, whatever the proceedability is).
     The signals notifierString is used as messageText."

    <context: #return>

    ^ (self newException 
	suspendedContext:thisContext sender)
	    raiseSignal

    "Modified: / 10.11.2001 / 15:13:34 / cg"
!

raiseSignalErrorString:aString
    "raise a signal (proceedable or not, whatever the proceedability is).
     The argument, aString is used as messageText."

    <context: #return>

    ^ (self newException 
	suspendedContext:thisContext sender
	errorString:aString)
	    raiseSignal.
!

raiseSignalWith:aParameter
    "raise a signal (proceedable or not, whatever the proceedability is).
     The argument, aParameter is passed as parameter."

    <context: #return>

    ^ (self newException 
	suspendedContext:thisContext sender
	parameter:aParameter)
	    raiseSignal.
!

raiseSignalWith:aParameter errorString:aString
    "raise a signal (proceedable or not, whatever the proceedability is).
     The argument, aString is used as messageText, 
     aParameter is passed as exception parameter."

    <context: #return>

    ^ (self newException 
	suspendedContext:thisContext sender
	parameter:aParameter
	errorString:aString)
	    raiseSignal.
!

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 messageText, 
     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 messageText, 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 
	  suspendedContext:aContext 
	  parameter:aParameter 
	  errorString:aString)
	      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"
!

deferAfter:aBlock
    "evaluate the argument, aBlock.
     Ignore the receiver-signal during evaluation - i.e. simply continue,
     but remember if the signal was raised.
     After the block evaluation, finally raise the signal - if it was raised in the block.
     If the signal is raised multiple times, only the first raises parameter is remembered,
     and only a single raise is performed after the blocks evaluation.

     Deferring makes sense for some signals, such as UserInterrupt or AbortSignal, 
     which must occasionally be delayed temporarily until a save place is reached 
     (especially when packages are sent across a communication channel, and you dont want
      partial packages to be generated by user interruptions)."

    |coughtException result|

    self handle:[:ex |
	coughtException isNil ifTrue:[
	    coughtException := ex.
	].
	ex proceedWith:nil
    ] do:[
	result := aBlock value.
    ].
    coughtException notNil ifTrue:[
	coughtException suspendedContext:thisContext.

	"/ the exception was raised during the execution of aBlock above. 
	"/ Raise it now (delayed).
	coughtException raiseSignal.
    ].
    ^ result

    "
     UserInterrupt deferAfter:[
	 Transcript showCR:'1 - now raising, but will be deferred.'.
	 UserInterrupt raiseRequestWith:'hello'.
	 Transcript showCR:'2 - after the raise, deferred exception will be handled soon.'.
     ].
     Transcript showCR:'3 - here after the protected block.'.
    "
!

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:mayProceedBoolean
    "create a new signal, using the receiver as a prototype and
     setting the parent of the new signal to the receiver."

    |sig|

    self isQuerySignal ifTrue:[
	sig := QuerySignal basicNew.
	mayProceedBoolean ifFalse:[
	    'Exception [warning]: nonProceedable Queries do not make sense' infoPrintCR.
	].
    ] ifFalse:[
	sig := Signal basicNew.
    ].
    ^ sig 
	mayProceed:mayProceedBoolean;
	notifierString:NotifierString;
	parent:self

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

!GenericException class methodsFor:'converting'!

, anExceptionHandler
    "return a SignalSet with myself and anExceptionHandler"

    ^ SignalSet with:self with:anExceptionHandler
! !

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

    |parent|

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

    "
     Object errorSignal description
    "

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

!GenericException class methodsFor:'queries'!

isControlInterrupt
    ^ false

    "Created: / 16.11.2001 / 16:11:54 / cg"
! !

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

     WARNING: this method belongs to NoHandlerError, and may eventually be
     moved there - it is (for now) left here for backward compatibility."

    ^ [:ex | self warn:'Error: ' , ex description.
             AbortOperationRequest raise 
      ]

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

    "back with:
     NoHandlerError emergencyHandler:(NoHandlerError notifyingEmergencyHandler)
     NoHandlerError 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)

     WARNING: this method belongs to NoHandlerError, and may eventually be
     moved there - it is (for now) left here for backward compatibility."

    ^ [:ex | 
             |str printedException|

             ex signal == NoHandlerError 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:[
                      AbortOperationRequest raise
                  ].
                  ex proceedWith:nil
             ].

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

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

             str nextPutLine:('** Error: ' , printedException description).
             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.

             "/ send a line to stdErr

             ('[warning]: ignored error: ' , printedException description) errorPrintCR.
             ('[warning]:    error information appended to ''errorTrace.stx''') errorPrintCR.

             AbortOperationRequest raise 
      ]

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

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

    "Created: / 15.1.1997 / 20:14:52 / cg"
    "Modified: / 24.1.1997 / 20:36:21 / cg"
    "Modified: / 4.8.1999 / 08:11:20 / stefan"
!

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.

     WARNING: this method belongs to NoHandlerError, and may eventually be
     moved there - it is (for now) left here for backward compatibility."

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

            ex signal == NoHandlerError 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 == UserInterrupt ifTrue:[
                  (self confirm:'abort current action ?') ifTrue:[
                      AbortOperationRequest raise
                  ].
                  ex proceedWith:nil
             ].

            "/ 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 description 
                           , '\\No mailing to service people possible.') withCRs.
                doMail := false.
            ] ifFalse:[
                doMail := self confirm:(printedException description 
                                        , '\\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: ' , Timestamp now printString).
                str nextPutLine:('Error: ', printedException description).
                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.
                ]
             ].

             AbortOperationRequest raise.
             "not reached"
      ]

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

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

    "Created: / 15.1.1997 / 20:14:52 / cg"
    "Modified: / 15.1.1997 / 21:10:28 / cg"
    "Modified: / 4.8.1999 / 08:11:26 / stefan"
!

notifyingEmergencyHandler
    "return a block (usable as an emergency handler for exceptions), 
     which does errorNotification before going into the debugger.
     Halts and breakpoints go directly into the debugger (without asking)

     WARNING: this method belongs to NoHandlerError, and may eventually be
     moved there - it is (for now) left here for backward compatibility."

    ^ [:ex | 
        (ex signal == NoHandlerError 
        and:[ex parameter signal inheritsFrom:ControlInterrupt]) ifTrue:[
            "/ go directly into the debugger ...
            ^ Debugger 
                enter:ex suspendedContext 
                withMessage:ex description
                mayProceed:true
        ] ifFalse:[
            "/ ask, and maybe go into the debugger ...
            ^ nil 
                errorNotify:ex description 
                from:ex suspendedContext 
                allowDebug:true 
        ]
      ]

    "test with (NOTE: halt, breakpoints or CTRL-C's still go straight into the debugger):
     NoHandlerError emergencyHandler:(NoHandlerError notifyingEmergencyHandler).
     Object bla.
    "

    "back with:
     NoHandlerError emergencyHandler:nil
    "

    "Modified: / 16.11.2001 / 16:07:05 / cg"
!

notifyingEmergencyHandlerForUserProcesses
    "return a block (usable as an emergency handler for exceptions), 
     which does errorNotification before going into the debugger,
     but only for exceptions occurring in user processes;
     systemProcesses are not debugged.
     Halts and breakpoints go directly into the debugger (without asking)

     WARNING: this method belongs to NoHandlerError, and may eventually be
     moved there - it is (for now) left here for backward compatibility."

    ^ [:ex | 

        |theException|

        Processor activeProcessIsSystemProcess ifTrue:[
            'EmergencyHandler [info]: exception cought: ' errorPrint.
            ex signal == NoHandlerError ifTrue:[
                theException := ex parameter.
            ] ifFalse:[
                theException := ex
            ].
            theException description errorPrintCR.
            AbortOperationRequest raise.
        ] ifFalse:[
            (ex signal == NoHandlerError 
            and:[ex parameter signal inheritsFrom:ControlInterrupt]) ifTrue:[
                "/ go directly into the debugger ...
                ^ Debugger 
                    enter:ex suspendedContext 
                    withMessage:ex description
                    mayProceed:true
            ] ifFalse:[
                "/ ask, and maybe go into the debugger ...
                ^ nil 
                    errorNotify:ex description 
                    from:ex suspendedContext
                    allowDebug:true
            ]
        ]
      ]

    "test with:
     NoHandlerError emergencyHandler:(NoHandlerError notifyingEmergencyHandlerForUserProcesses)
     Object bla.
    "

    "back with:
     NoHandlerError emergencyHandler:nil
    "

    "Modified: / 16.11.2001 / 16:06:54 / cg"
! !

!GenericException methodsFor:'Compatibility-ANSI'!

pass
    ^ self reject
!

retry
    "same as #restart - ANSI & VW compatibility"

    self restart

    "Created: / 7.9.2001 / 13:31:02 / cg"
!

retryUsing: alternativeBlock
    "Abort an exception handler and evaluate a new block in place of the handler's protected block."

    "/ self mustBeHandled ifFalse: [ ^self ].

    ^ self restartDo:alternativeBlock
!

signalWith:messageText
    ^ self raiseErrorString:messageText
! !

!GenericException methodsFor:'accessing'!

creator
    "return the creator of the exception"

    signal == nil ifTrue:[ 
	^ self class 
    ].
    ^ signal
!

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

    <resource:#obsolete>

    ^ self description

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

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

    <resource:#obsolete>

    messageText := 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"
!

isResumable:aBoolean
    proceedable := aBoolean
!

messageText
    "return the explicit given messageText - nil, if signaler did not provide one."

    ^ messageText
!

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

    messageText := 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"
!

proceedable:aBoolean
    proceedable := aBoolean
!

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' messageText 
     into 'rejected-exception' for information).
    "

    ^ rejected == true
!

searchFrom:raisingContext 
    suspendedContext := raisingContext
!

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

    proceedable notNil ifTrue:[^ proceedable].
    signal notNil ifTrue:[^ signal mayProceed].
    ^ self class 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 description , ')'.
    self mayProceed ifTrue:[
        ^ NoHandlerError 
              raiseRequestWith:self 
              errorString:msg
              in:suspendedContext.
    ].
    ^ NoHandlerError 
          raiseWith:self 
          errorString:msg
          in:suspendedContext.
! !

!GenericException methodsFor:'default values'!

defaultResumeValue
    ^ nil
!

defaultReturnValue
    ^ nil
! !

!GenericException methodsFor:'handler actions'!

exit
    "either resume or return - depending on the receivers resumability.
     VW compatibility."

    self isResumable ifTrue:[
	self resume:(self defaultResumeValue)
    ] ifFalse:[
	self return:(self defaultReturnValue)
    ]

    "Modified: / 7.9.2001 / 13:28:54 / cg"
!

exit:value
    "either resume or return - depending on the receivers resumability.
     VW compatibility."

    self isResumable ifTrue:[
	self resume:value
    ] ifFalse:[
	self return:value
    ]

    "Created: / 7.9.2001 / 13:29:55 / cg"
    "Modified: / 7.9.2001 / 13:30:00 / cg"
!

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

    self proceedWith:(self defaultResumeValue).

    "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: / 4.8.1999 / 08:42:12 / stefan"
    "Modified: / 7.9.2001 / 13:29:08 / cg"
!

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.
    con canReturn ifFalse:[
	"the context that triggered the exception cannot return.
	 This is a fallback: return the the context of the raise*.
	 We know, that this context is returnable"

	con := Context findFirstSpecialHandle:false raise:true.
	[con notNil and:[con receiver ~~ self]] whileTrue:[
	    con := con findSpecialHandle:false raise:true.
	].
	[con notNil and:[con sender ~~ suspendedContext]] whileTrue:[
	    con := con sender.
	].
    ].
    handlerContext := suspendedContext := nil.
    con unwindThenDo:[anotherException raiseSignal].

    "
     |rslt|

     ZeroDivide handle:[:ex |
	ex resignalAs:Number domainErrorSignal
     ] do:[
	rslt := 5 // 0
     ].
     rslt
    "

    "
     |rslt|

     MessageNotUnderstood handle:[:ex |
	ex resignalAs:Number domainErrorSignal
     ] do:[
	rslt := 1 perform:#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"
    "/ no - ANSI defines #resume - sigh
    "/ <resource:#obsolete>
    "/
    "/ self obsoleteMethodWarning:'use #proceed'.

    ^ self proceedWith:(self defaultResumeValue)

    "Modified: / 2.3.1998 / 10:51:55 / stefan"
    "Modified: / 7.9.2001 / 13:28:34 / cg"
!

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

    ^ self proceedWith:value

    "Modified: / 7.9.2001 / 13:28:49 / cg"
!

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

    "/ obsolete (use #proceedWith:), retained for backwards compatibility
    "/ no - ANSI defines #resume: - sigh
    "/<resource:#obsolete>
    "/
    "/ self obsoleteMethodWarning:'use #proceedWith:'.   
    ^ self proceedWith:value

    "Modified: / 2.3.1998 / 10:51:48 / stefan"
    "Modified: / 7.9.2001 / 13:29:26 / cg"
!

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

    |con|

    con := handlerContext.
    handlerContext := suspendedContext := nil.
    con unwind:(self defaultReturnValue)

    "Modified: / 7.9.2001 / 13:29:34 / cg"
!

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

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"

    self return:value
! !

!GenericException methodsFor:'printing & storing'!

description
    "return the description string of the signal"

    |sigDescr|

    sigDescr := signal description.
    (messageText isNil or:[ messageText isString not])
    ifTrue:[
	^ sigDescr
    ].
    (messageText startsWith:Character space) ifTrue:[
	^ sigDescr, messageText.
    ].
    (messageText endsWith:Character space) ifTrue:[
	^ messageText, sigDescr.
    ].

    ^ messageText

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

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

printOn:aStream

    super printOn:aStream.
    aStream nextPut:$(; nextPutAll:self description; nextPut:$)
! !

!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
    aHandlerBlock numArgs == 0 ifTrue:[
        "/ 0-arg handler - not interested in the ex - object
        val := aHandlerBlock value
    ] ifFalse:[
        "/ 1-arg handler - pass myself as exception argument
        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>

    |currentContext|

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

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

    signal isExceptionCreator ifFalse:[
        "there is something rotten in the state of denmark"
        GenericException raiseWith:signal errorString:'unexpected non-ExceptionCreator in calling context'.
    ].

    "now, start searching for a handler.
     Start search above the last active handler.
     Skip raise contexts.
     If nil, then there is no handler and we can directly proceed
     to the unhandled code below."

    currentContext := suspendedContext findExceptional.
    [currentContext notNil] whileTrue:[
        (currentContext isRaiseContext) ifTrue:[ 
            |ex1 con1|

            "skip all the contexts between the raise and the sender of #handle:do"
            ex1 := currentContext receiver.     "exception, that has been raised"
            con1 := ex1 handlerContext.         "the context of the #handle:do:"

            con1 isNil ifTrue:[ 
                "the handlerContext is nil if an exception's default action is performed.
                 Start search at the sending context.
                 Maybe we should better treat a default action like a #handle:do:
                 at the outest level. But the DebugView currently can't handle this,
                 because it tries to raise e.g. AbortOperationRequest even if it has bee invoked
                 by e.g. NoHandlerError"   

                (ex1 signal == signal) ifTrue:[
                    "the same exception that has been cought by a default action is raised again.
                     don't recurse"
                    ^ self noHandler.
                ].
            ] ifFalse:[
                "skip to the raised exception's handleContext"
                currentContext := con1.
            ].
            ex1 := con1 := nil.
        ] ifFalse:[ "currentContext is a handleContext"
            |r handler|
    
            "ask the the receiver of the #handle:do: or #on:do: or whatever- message for the handler.
             nil is returned, if the signal is not accepted"
            r := currentContext receiver.     "receiver of #handle:do: or #on:do:"
            (r notNil and:[(handler := r handlerForSignal:signal 
                                         context:currentContext 
                                         originator:originator) notNil]
            ) ifTrue:[
                "call the handler"

                "remember the handling signal, sigSet, exception or whatever"
                handlingException := r handlingExceptionInContext:currentContext.
                handlerContext := currentContext.
                currentContext := nil.
                self doCallHandler:handler.

                "if the handler rejects, we arrive here
                 continue search for another handler"
                currentContext := handlerContext.
                handler := handlerContext := nil.
            ].
            r := handler := nil.
        ].
        currentContext notNil ifTrue:[
            currentContext := currentContext findSpecialHandle:true raise:true. "search starts at currentContext sender"
        ].
    ].

    "
     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:[ 
	StrictRaising ifTrue:[
	    "/ proceeding from wrongProceedabilitySignal grants the raiseRequest
	    WrongProceedabilityError raiseRequestWith:signal
	] ifFalse:[
	    'Exception [warning]: raised with wrong proceedability: ' infoPrint.
	    self class name infoPrintCR.
	]
    ].

    proceedable := true.
    ^ self doRaise

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

raiseSignal
    "actually raise an exception (whatever the proceedability is)."

    <context: #return>

    self mayProceed ifFalse:[
	^ self raise
    ].
    ^ self raiseRequest
! !

!GenericException methodsFor:'setup'!

setSignal:aSignal
    "set the fields usable for inspection by the handler
     - only to be sent from the signal when raising.
     CG: added this one to avoid confusion with dolphin signal: (which raises the ex)"

    signal := aSignal.
!

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.
    messageText := aString.
    suspendedContext := sContext.
    originator := origin.
!

suspendedContext:sContext errorString:aString
    "set required fields 
     - only to be sent from the signal when raising"

    messageText := aString.
    suspendedContext := sContext.
!

suspendedContext:sContext parameter:aParameter
    "set required fields 
     - only to be sent from the signal when raising"

    parameter := aParameter.
    suspendedContext := sContext.
!

suspendedContext:sContext parameter:aParameter errorString:aString
    "set required fields 
     - only to be sent from the signal when raising"

    parameter := aParameter.
    messageText := aString.
    suspendedContext := sContext.
! !

!GenericException methodsFor:'testing'!

isError
    ^ false
!

isException
    ^ true

    "Created: / 17.11.2001 / 18:37:27 / cg"
! !

!GenericException class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/GenericException.st,v 1.91 2004-09-01 16:32:37 stefan Exp $'
! !

GenericException initialize!