Signal.st
author Claus Gittinger <cg@exept.de>
Sat, 31 Jul 1999 14:43:43 +0200
changeset 4473 793078981f01
parent 4466 9cba6f4ecec4
child 4476 696ac99f2a52
permissions -rw-r--r--
added #handlingSignalInContext: (see Exception-doRaise)

"
 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:#Signal
	instanceVariableNames:'mayProceed notifierString nameClass message handlerBlock parent'
	classVariableNames:'NoHandlerSignal GenericSignal ProceedErrorSignal
		WrongProceedabilitySignal'
	poolDictionaries:''
	category:'Kernel-Exceptions'
!

!Signal 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
"
    Signal and Exception provide a framework for exception handling.

    A Signal object is usually defined somewhere up in the calling chain
    and associated with some abnormal event. Many signals are also
    created at startup time and reused.

    When the event is raised (by Signal>>raise) the control will be either 
    given to a debugger or - if a handler was defined - to the handler. 
    The handler will get a description of what (and where) happened in an 
    Exception object and can decide how to react on the situation (i.e. 
    proceed, return or restart).

    There is also a companion class called SignalSet, which allows handling
    multiple signals with one handler (for example all arithmetic signals).
    And, finally there is a very special SignalSet which allows catching
    any signal (SignalSet>>anySignal).

    Since there is no official documentation on signal handling (i.e. none
    of the books describes it), this Signal implementation has been modeled
    after what some PD programs seem to expect and what alpha/beta testers told
    me it should look like.
    It may not be perfect and undergo minor changes.

    special:

    In addition to the nested catch & throw mechanism, signals can also be
    used when no such handler scope exists. To support this, signals can be 
    assigned a handlerBlock, which gets evaluated with the exception as argument 
    in case no handler was found (on the stack).

    If no handler was found (i.e. neither a handler context on the stack, nor
    a static handler block), the NoHandlerSignal will be raised instead,
    passing it the original exception in its exception-parameter.
    This NoHandlerSignal can be handled just like any other signal.
    (therefore, it is possible to catch any error by catching NoHandlerSignal.

    When the NoHandler signal is raised, and neither a handler-context, nor 
    a handler block is defined for it, an emergencyHandler(-block) is evaluated.
    This block is either provided by the current process 
    (see Process>>emergencySignalHandler) or as a global default by the Exception
    class (see Exception>>emergencyHandler).
    The default emergencyHandlerBlock (from Exception) will bring up a debugger.

    HandlerBlocks allow a global (if its the EmergencyHandler in Exception)
    or per-process signal handling to be added. Even to code which was never
    planned to handle signals.

    See samples in 'doc/coding' and actual raise code in Exception.

    [Instance variables:]

	mayProceed      <Boolean>       hint for the debugger - program may 
					proceed (currently not honored by the
					debugger)

	notifierString  <String>        error message to be output 

	nameClass       <Class>         for the printOn-implementation; nameClass
					is the class, to which message (below) 
					should be sent to create the receiver.

	message         <Symbol>        for the printOn-implementation; message
					is the selector, which should be sent to 
					nameClass (above) to create the receiver.

	handlerBlock    <Block>         if nonNil, a 1-arg block to be 
					evaluated when no handler context is 
					found. The block gets the exception
					object as argument. This will play the role
					of an on-stack handler.

    [Class variables:]

	NoHandlerSignal <Signal>        signal raised when no handler for a signal
					was found in raise.
					If this one is not handled either,
					Exceptions emergencyHandler will be evaluated
					instead (or a per-proces handler, if there
					is one).

    [author:]
	Claus Gittinger

    [see also:]
	Exception 
	SignalSet QuerySignal
	Object
	(``Exception handling and signals'': programming/exceptions.html)
"
! !

!Signal class methodsFor:'initialization'!

initGenericSignal 
    "setup the parent of all signals."

    GenericSignal isNil ifTrue:[
        GenericSignal := self basicNew notifierString: 'unknown Signal with: '.
        GenericSignal nameClass:self message:#genericSignal.
        GenericSignal mayProceed:true.
    ].

    "Modified: / 8.10.1997 / 11:58:01 / cg"
    "Modified: / 27.2.1998 / 14:17:20 / stefan"
!

initialize 
    "setup the signal used to handle unhandled signals"

    GenericSignal isNil ifTrue:[
        self initGenericSignal.
    ].

    NoHandlerSignal isNil ifTrue:[
        NoHandlerSignal := ErrorSignal newSignal.
        NoHandlerSignal nameClass:self message:#noHandlerSignal.
        NoHandlerSignal notifierString:'unhandled exception'.
        ProceedErrorSignal := ErrorSignal newSignal.
        ProceedErrorSignal nameClass:self message:#proceedErrorSignal.
        ProceedErrorSignal notifierString:'handler tried to proceed from nonproceedable signal'.
        WrongProceedabilitySignal := ErrorSignal newSignal.
        WrongProceedabilitySignal nameClass:self message:#wrongProceedabilitySignal.
        WrongProceedabilitySignal notifierString:'attempt to raise a nonproceedable signal proceedable'.
    ]

    "Modified: / 8.10.1997 / 11:48:40 / cg"
    "Modified: / 27.2.1998 / 14:17:59 / stefan"
! !

!Signal class methodsFor:'instance creation'!

new
    "return a new signal"

    ^ (self basicNew) notifierString:'signal'; mayProceed:true

    "
     Signal new
    "

    "Modified: 8.10.1997 / 11:51:39 / cg"
! !

!Signal class methodsFor:'Signal constants'!

genericSignal
    "return the generic signal - thats the parent of all signals
     in the system."

    ^ GenericSignal

    "Created: 8.10.1997 / 11:46:28 / cg"
    "Modified: 8.10.1997 / 11:47:08 / cg"
!

noHandlerSignal
    "return the signal used to handle unhandled signals"

    ^ NoHandlerSignal
!

proceedErrorSignal
    "return the signal used to indicate that a handler tried to
     proceed a signal marked as nonproceedable.
     The parameter for the exception raised by this signal is
     the exception which tried to proceed."

    ^ ProceedErrorSignal

    "Modified: / 27.2.1998 / 14:22:13 / stefan"
    "Created: / 27.2.1998 / 14:36:15 / stefan"
!

wrongProceedabilitySignal
    "return the signal used to indicate that a signaler wants
     to raise a nonproceedable signal proceedable.
     proceed a signal marked as nonproceedable.
     The parameter for the exception raised by this signal is
     the unproceedable signal."

    ^ WrongProceedabilitySignal

    "Created: / 27.2.1998 / 14:24:19 / stefan"
! !

!Signal methodsFor:'accessing'!

errorString
    "return the notifier string.
     If the notifier string starts with space, prepend
     the parents notifier string"

    notifierString isNil ifTrue:[
        ^ parent errorString
    ] ifFalse:[
        (notifierString size > 0 
         and:[notifierString first == (Character space)]) ifTrue:[
            ^ parent errorString, notifierString
        ] ifFalse:[
            ^ notifierString
        ].
    ]

    "
      Object errorSignal errorString
    "

    "Modified: / 12.3.1998 / 15:04:41 / stefan"
!

errorStringExtra:extraString with:aParameter
    "used when raising with a given error string and/or parameter; 
     if the errorString starts with a space, it is appended to the receivers
     notifier string; if it ends with a space, it is prepended.
     Otherwise, the extraString is returned.
     If no extraString is given, use the signals default errorString."

    |t|

    (self inheritsFrom:Object userNotificationSignal) ifTrue:[
        "/ all userNotifications pass the extraString unchanged.
        ^ extraString
    ].

    extraString isNil ifTrue:[
        t := self errorString
    ] ifFalse:[
        t := extraString.
        (extraString endsWith:Character space) ifTrue:[
            t := extraString, self errorString
        ] ifFalse:[
            (extraString startsWith:Character space) ifTrue:[
                t := self errorString, extraString
            ]
        ].
    ].
    ^ t.

"/    aParameter isNil ifTrue:[
"/        ^ t
"/    ].
"/
"/    (t startsWith:' ') ifTrue:[
"/        ^ aParameter printString , t
"/    ].
"/    (t endsWith:' ') ifTrue:[
"/        ^ t , aParameter printString
"/    ].
"/    ^ t

    "Modified: / 25.3.1997 / 12:12:37 / cg"
    "Created: / 12.3.1998 / 15:11:31 / stefan"
!

handlerBlock
    "return the handlerblock - if non-nil, this will be evaluated with the exception 
     object as argument, if no #handle:do: context was found on the stack."

    ^ handlerBlock
!

handlerBlock:aOneArgBlock
    "set the handlerblock - this will be evaluated with the exception 
     object as argument, if no #handle:do: context was found on the stack."

    handlerBlock := aOneArgBlock
!

mayProceed
    "return the signals ability to proceed.
     This flag is (currently) not checked by the system;
     be prepared for changes here, to eventually have nonProceedable
     signals refuse to let you continue execution."

    ^ mayProceed
!

mayProceed:aBoolean
    "set/clear the signals ability to proceed.
     This flag is (currently) not checked by the system;
     be prepared for changes here, to eventually have nonProceedable
     signals refuse to let you continue execution."

    mayProceed := aBoolean
!

nameClass:aClass message:aSelector
    "this sets the class & selector of a method which returns
     that signal - this is simply for documentation purposes -
     see Signal>>printOn: implementation.
     (took me a while to find that one out ;-)"

    nameClass := aClass.
    message := aSelector
!

notifierString
    "return the notifier string"

    ^ notifierString
!

notifierString:aString
    "set the notifier string"

    notifierString := aString
!

parent
    "return the parent-signal of the receiver"

    ^ parent
!

parent:aSignal 
    "set the parent-signal of the receiver."

    parent := aSignal
!

parent:aSignal mayProceed:aBoolean
    "set the parent-signal and the mayProceed flag of the receiver."

    parent := aSignal.
    mayProceed := aBoolean.

    "Modified: 8.10.1997 / 11:56:11 / cg"
! !

!Signal methodsFor:'copying'!

deepCopyUsing:aDictionary
    "raise an error - deepCopy is not allowed for signals"

    ^ self deepCopyError

    "Created: / 31.3.1998 / 15:43:01 / cg"
! !

!Signal methodsFor:'instance creation'!

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

    ^ (self copy) parent:self

    "Modified: 8.10.1997 / 11:53:06 / cg"
!

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

    ^ (self copy) parent:self mayProceed:aBoolean

    "Modified: 8.10.1997 / 11:57:13 / cg"
! !

!Signal methodsFor:'printing'!

printOn:aStream
    "append a printed representation of the receiver on aStream"

    nameClass notNil ifTrue:[
	aStream nextPutAll:nameClass name.
	aStream space.
	aStream nextPutAll:message.
	^ self
    ].
    ^ super printOn:aStream
! !

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

    aSignal isQuerySignal ifTrue:[^ false].

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

    "Modified: / 22.3.1999 / 12:45:42 / stefan"
!

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 accepts:signal) ifTrue:[
            ^ theContext argAt:1
        ]
    ].

    ^ nil

    "Created: / 25.7.1999 / 19:55:43 / stefan"
!

handlingSignalInContext:theContext
    "answer the handling signal from aContext."

    ^ self
!

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

    "Modified: / 6.6.1998 / 20:37:47 / cg"
!

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 isHandledIn:(thisContext sender).
!

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

    |con r|

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

    "Created: / 23.7.1999 / 14:03:34 / stefan"
    "Modified: / 26.7.1999 / 15:24:34 / stefan"
!

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

    ^ false

    "Modified: 22.4.1996 / 13:45:06 / cg"
!

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

    ^ true
! !

!Signal methodsFor:'raising'!

newException
    "answer a new exception object for this signal.
     Subclasses may redefine this method"

    ^ Exception signal:self originator:nil

    "Created: / 26.2.1998 / 19:53:56 / stefan"
    "Modified: / 23.7.1999 / 13:41:00 / stefan"
!

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

    ^ Exception signal:self originator:originator

    "Created: / 27.2.1998 / 09:17:00 / stefan"
    "Modified: / 23.7.1999 / 13:41:15 / stefan"
!

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

    ^ self newException raise

    "Modified: / 2.5.1996 / 16:36:23 / cg"
    "Modified: / 5.3.1998 / 16:44:36 / stefan"
!

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

    ^ (self newException errorString:aString) raise.

    "Modified: / 9.5.1996 / 15:17:59 / cg"
    "Modified: / 12.3.1998 / 15:15:22 / stefan"
!

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

    ^ (self newException   
              signal:self
              parameter:nil 
              errorString:aString
              suspendedContext:aContext
              originator:nil) raise.

    "Created: / 26.7.1996 / 16:42:32 / cg"
    "Modified: / 26.7.1996 / 16:42:47 / cg"
    "Modified: / 12.3.1998 / 15:43:43 / stefan"
!

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

    ^ ((self newExceptionFrom:something) parameter:something) raise

    "Modified: / 2.5.1996 / 16:36:38 / cg"
    "Modified: / 5.3.1998 / 16:49:55 / stefan"
!

raiseIn:aContext
    "raise a signal nonproceedable.
     The signals notifierString is used as errorString.
     The additional context is passed as the context responsible for the raise,
     allowing a raise to mimicri the exception happened somewhere else."

    ^ (self newException suspendedContext:aContext) raise.

    "Modified: / 2.5.1996 / 16:36:44 / cg"
    "Modified: / 5.3.1998 / 16:50:21 / stefan"
!

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

    ^ self newException raiseRequest.

    "Modified: / 2.5.1996 / 16:36:52 / cg"
    "Modified: / 5.3.1998 / 16:50:46 / stefan"
!

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

    ^ ((self newExceptionFrom:something) parameter:something) raiseRequest.

    "Modified: / 2.5.1996 / 16:36:38 / cg"
    "Modified: / 5.3.1998 / 16:52:46 / stefan"
!

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

    ^ (self newException parameter:aParameter) raiseRequest.

    "Modified: / 9.5.1996 / 15:13:20 / cg"
    "Modified: / 12.3.1998 / 15:16:57 / stefan"
!

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

    ^ (self newException 
              parameter:aParameter; 
              errorString:aString
      ) raiseRequest

    "Modified: / 9.5.1996 / 15:13:35 / cg"
    "Modified: / 12.3.1998 / 15:17:52 / stefan"
!

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

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

    "Modified: / 26.7.1996 / 16:29:27 / cg"
    "Modified: / 12.3.1998 / 15:18:34 / stefan"
!

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

    ^ (self newException 
              parameter:aParameter; 
              suspendedContext:aContext) raiseRequest.

    "Modified: / 26.7.1996 / 16:29:33 / cg"
    "Modified: / 12.3.1998 / 15:18:55 / stefan"
!

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

    ^ (self newException parameter:aParameter) raise.

    "Modified: / 9.5.1996 / 15:14:24 / cg"
    "Modified: / 12.3.1998 / 15:19:11 / stefan"
!

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

    ^ (self newException 
              parameter:aParameter;
              errorString:aString) raise.

    "Modified: / 9.5.1996 / 15:14:32 / cg"
    "Modified: / 12.3.1998 / 15:19:40 / stefan"
!

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


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

    "Created: / 2.5.1996 / 16:37:25 / cg"
    "Modified: / 26.7.1996 / 16:29:42 / cg"
    "Modified: / 12.3.1998 / 15:20:12 / stefan"
!

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

    ^ (self newException parameter:aParameter;
                         suspendedContext:aContext) raise.

    "Modified: / 9.5.1996 / 15:14:24 / cg"
    "Created: / 4.1.1998 / 14:38:15 / cg"
    "Modified: / 12.3.1998 / 15:34:51 / stefan"
! !

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

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

     thisContext markForHandle.
     ^ 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   
       ]
      "

    "Modified: / 25.7.1999 / 19:43:01 / 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."

     thisContext markForHandle.
     ^ 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
                ]
      "

    "Modified: / 25.7.1999 / 19:43:40 / 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 proceed] do:aBlock.

      "
       Object messageNotUnderstoodSignal ignoreIn:[
	  123 size open   
       ]
      "
! !

!Signal class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Signal.st,v 1.56 1999-07-31 12:43:26 cg Exp $'
! !
Signal initialize!