Signal.st
author Claus Gittinger <cg@exept.de>
Tue, 30 Apr 1996 17:39:28 +0200
changeset 1321 52e043fb7eaf
parent 1292 89497fff7f87
child 1326 60ea3687ee49
permissions -rw-r--r--
checkin from browser

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

!Signal class methodsFor:'initialization'!

initialize 
    "setup the signal used to handle unhandled signals"

    NoHandlerSignal isNil ifTrue:[
	NoHandlerSignal := ErrorSignal newSignalMayProceed:true.
	NoHandlerSignal nameClass:self message:#noHandlerSignal.
	NoHandlerSignal notifierString:'unhandled exception'.
    ]
! !

!Signal class methodsFor:'instance creation'!

new
    "return a new signal"

    ^ (self basicNew) notifierString:'signal'
! !

!Signal class methodsFor:'Signal constants'!

noHandlerSignal
    "return the signal used to handle unhandled signals"

    ^ NoHandlerSignal
! !

!Signal methodsFor:'accessing'!

errorString
    "return the notifier string"

    ^ notifierString
!

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

!Signal methodsFor:'copying'!

deepCopy
    "raise an error - deepCopy is not allowed for signals"

    ^ self deepCopyError
! !

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

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

    |newSignal|

    newSignal := (self copy) mayProceed:aBoolean.
    newSignal parent:self.
    ^ newSignal
! !

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

errorStringFor:template
    "used when raising with a given error string; if the given
     errorString starts with a space, it is appended to the receivers
     notifier string; if it ends with a space, it is prepended.
     Otherwise, the errorString is returned."

    (template startsWith:' ') ifTrue:[
	^ notifierString , template
    ].
    (template endsWith:' ') ifTrue:[
	^ template , notifierString
    ].
    ^ template
! !

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

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
!

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 cought 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 sel|

    con := aContext.
    [con notNil] whileTrue:[
	(((sel := con selector) == #handle:do:) 
	or:[sel == #handle:from:do:]) ifTrue:[
	    "
	     is this is a #handle:do: or a #handle:from:do: context
	     with self in it ?
	    "
	    (con receiver accepts:self) ifTrue:[
		"found a handler context"

		^ true
	    ].
	].
	con := con sender
    ].
    ^ false
!

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

raise
    "raise a signal - create an Exception object
     and call the handler with this as argument.
     The signals notifierString is used as errorString."

    ^ (Exception  
	      signal:self
	      parameter:nil 
	      errorString:notifierString
	      suspendedContext:thisContext sender) raise.
!

raiseErrorString:aString
    "raise a signal - create an Exception object
     and call the handler with this as argument.
     The argument is used as errorString."

    ^ (Exception  
	      signal:self
	      parameter:nil 
	      errorString:(self errorStringFor:aString)
	      suspendedContext:thisContext sender) raise.
!

raiseFrom:something
    "raise a signal - create an Exception object with aParameter
     and call the handler with this as argument..
     The argument, something is passed both as parameter and originator.
     XXX: I am not certain, if this is the correct behavior (seen in remoteInvocation-goodie)"

    ^ (Exception 
	      signal:self
	      parameter:something 
	      errorString:notifierString
	      suspendedContext:thisContext sender
	      originator:something) raise.
!

raiseIn:aContext
    "raise a signal - create an Exception object
     and call the handler with this as argument.
     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."

    ^ (Exception 
	      signal:self
	      parameter:nil 
	      errorString:notifierString
	      suspendedContext:aContext) raise.
!

raiseRequest
    "raise a signal - create an Exception object
     and call the handler with this as argument.
     The signals notifierString is used as errorString."

    ^ (Exception  
	      signal:self
	      parameter:nil 
	      errorString:notifierString
	      suspendedContext:thisContext sender) raiseRequest.
!

raiseRequestWith:aParameter
    "raise a signal - create a proceedable Exception object with aParameter
     and look for handlers .
     The signals notifierString is used as errorString."

    ^ (Exception 
	      signal:self
	      parameter:aParameter 
	      errorString:notifierString
	      suspendedContext:thisContext sender) raiseRequest.
!

raiseRequestWith:aParameter errorString:aString
    "raise a signal - create an Exception object with aParameter
     and call the handler with this as argument..
     The argument, aString is used as errorString."

    ^ (Exception 
	      signal:self
	      parameter:aParameter 
	      errorString:(self errorStringFor:aString)
	      suspendedContext:thisContext sender) raiseRequest
!

raiseRequestWith:aParameter errorString:aString in:aContext
    "raise a signal - create an Exception object with aParameter
     and call the handler with this as argument..
     The argument, aString is used as errorString.
     The additional context is passed as the context responsible for the raise."

    ^ (Exception 
	      signal:self
	      parameter:aParameter 
	      errorString:(self errorStringFor:aString)
	      suspendedContext:aContext) raiseRequest
!

raiseRequestWith:aParameter in:aContext
    "raise a signal - create an Exception object with aParameter
     and call the handler with this as argument..
     The signals notifierString is used as errorString.
     The additional context is passed as the context responsible for the raise."

    ^ (Exception 
	      signal:self
	      parameter:aParameter 
	      errorString:notifierString
	      suspendedContext:aContext) raiseRequest.
!

raiseWith:aParameter
    "raise a signal - create an Exception object with aParameter
     and call the handler with this as argument..
     The argument, aParameter is passed as parameter.
     XXX: I am not certain, if this is the correct behavior (seen in remoteInvocation-goodie)"

    ^ (Exception 
	      signal:self
	      parameter:aParameter 
	      errorString:notifierString
	      suspendedContext:thisContext sender) raise.
!

raiseWith:aParameter errorString:aString
    "raise a signal - create an Exception object with aParameter
     and call the handler with this as argument..
     The argument, aString is used as errorString, aParameter is passed
     as exception parameter."

    ^ (Exception 
	      signal:self
	      parameter:aParameter 
	      errorString:(self errorStringFor:aString)
	      suspendedContext:thisContext sender) raise.
! !

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

     ^ aBlock value  "the real logic is in raise/Exception"

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

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

     ^ aBlock value  "the real logic is in raise/Exception"

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

       |o1 o2|

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

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.34 1996-04-25 16:47:02 cg Exp $'
! !
Signal initialize!