Signal.st
author claus
Fri, 28 Oct 1994 02:22:16 +0100
changeset 171 129f0e2e23df
parent 159 514c749165c3
child 214 2e4defd713f9
permissions -rw-r--r--
handling now in Exception

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

$Header: /cvs/stx/stx/libbasic/Signal.st,v 1.15 1994-10-28 01:22:16 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libbasic/Signal.st,v 1.15 1994-10-28 01:22:16 claus Exp $
"
!

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

!Signal class methodsFor:'initialization'!

initialize 
    "setup the signal used to handle unhandled signals"

    NoHandlerSignal isNil ifTrue:[
	Object initialize.

	NoHandlerSignal := Object 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 access'!

noHandlerSignal
    "return the signal used to handle unhandled signals"

    ^ NoHandlerSignal
! !

!Signal methodsFor:'instance creation'!

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
!

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

!Signal methodsFor:'copying'!

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

    ^ self deepCopyError
! !

!Signal methodsFor:'accessing'!

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
!

mayProceed:aBoolean
    "set/clear the signals ability to proceed.
     This flag is not checked in the current version of
     the debugger."

    mayProceed := aBoolean
!

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

    parent := aSignal
!

parent
    "return the parent-signal of the receiver"

    ^ parent
!

notifierString:aString
    "set the notifier string"

    notifierString := aString
!

notifierString
    "return the notifier string"

    ^ notifierString
!

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
!

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

!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:'save evaluation'!

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

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

ignore: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 AbortSignals, because continuing after an exception without any cleanup
      will often lead to followup-errors."

      ^ self handle:[:ex | ex proceed] do:aBlock.

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

!Signal methodsFor:'queries'!

accepts:aSignal
    "return true, if the receiver accepts the argument, aSignal.
     (i.e. the recevier is aSignal or a parent of it). False otherwise."

    |s|

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

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|

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

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

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

    |ex|

    ex := Exception new 
	      signal:self
	      parameter:nil 
	      errorString:notifierString
	      suspendedContext:thisContext sender.

    ^ ex raise
!

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

    |ex|

    ex := Exception new 
	      signal:self
	      parameter:aParameter 
	      errorString:notifierString
	      suspendedContext:thisContext sender.

    ^ ex raise
!

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

    |ex|

    ex := Exception new 
	      signal:self
	      parameter:nil
	      errorString:something printString
	      suspendedContext:thisContext sender.

    ^ ex raise
!

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

    |ex|

    ex := Exception new 
	      signal:self
	      parameter:aParameter 
	      errorString:aString
	      suspendedContext:thisContext sender.

    ^ ex raise
! !