handling now in Exception
authorclaus
Fri, 28 Oct 1994 02:22:16 +0100
changeset 171 129f0e2e23df
parent 170 40ea50c7b9fe
child 172 52750f9c44de
handling now in Exception
Exception.st
Signal.st
--- a/Exception.st	Fri Oct 28 02:21:37 1994 +0100
+++ b/Exception.st	Fri Oct 28 02:22:16 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -11,20 +11,20 @@
 "
 
 Object subclass:#Exception
-         instanceVariableNames:'signal parameter errorString
-                                suspendedContext handlerContext
-                                rejected
-                                resumeBlock rejectBlock'
-         classVariableNames:'EmergencyHandler'
-         poolDictionaries:''
-         category:'Kernel-Exceptions'
+	 instanceVariableNames:'signal parameter errorString
+				suspendedContext handlerContext
+				rejected
+				resumeBlock rejectBlock'
+	 classVariableNames:'EmergencyHandler RecursiveExceptionSignal'
+	 poolDictionaries:''
+	 category:'Kernel-Exceptions'
 !
 
 Exception comment:'
 COPYRIGHT (c) 1993 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.12 1994-08-23 23:09:12 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.13 1994-10-28 01:22:06 claus Exp $
 '!
 
 !Exception class methodsFor:'documentation'!
@@ -32,7 +32,7 @@
 copyright
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -45,7 +45,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.12 1994-08-23 23:09:12 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.13 1994-10-28 01:22:06 claus Exp $
 "
 !
 
@@ -55,20 +55,20 @@
     The handler block may perform various actions by sending corresponding messages
     to the exception object. The following actions are possible:
 
-        reject          - dont handle this signal;
-                          another handler will be searched for, 
-                          upper in the calling hierarchy
-                          (this is also the handlers default, if it falls through)
+	reject          - dont handle this signal;
+			  another handler will be searched for, 
+			  upper in the calling hierarchy
+			  (this is also the handlers default, if it falls through)
 
-        proceed         - return from the Signal>>raise, with nil as value
+	proceed         - return from the Signal>>raise, with nil as value
 
-        proceedWith:val - same, but return val from Signal>>raise
+	proceedWith:val - same, but return val from Signal>>raise
 
-        return          - return from the Signal>>handle:do:, with nil as value
+	return          - return from the Signal>>handle:do:, with nil as value
 
-        return:val      - same, but return val from Signal>>handle:do:
+	return:val      - same, but return val from Signal>>handle:do:
 
-        restart         - restart the Signal>>handle:do:, after repairing
+	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
@@ -76,22 +76,22 @@
     parameter can be passed - the use is signal specific.:
 
     instance variables:
-        signal           <Signal>     the signal which caused the exception
+	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)
+	parameter        <Object>     a parameter (if any) which was passed when raising
+				      the signal (only if raised with #raiseWith:aParameter)
 
-        errorString      <String>     an errorString 
-                                      (usually the signals own errorString, but sometimes
-                                       changed explicitely in #raiseWith:errorString:)
+	errorString      <String>     an errorString 
+				      (usually the signals own errorString, but sometimes
+				       changed explicitely in #raiseWith:errorString:)
 
-        suspendedContext <Context>    the context in which the raise occured
+	suspendedContext <Context>    the context in which the raise occured
 
-        handlerContext   <Context>    the context of the handler (if any)
+	handlerContext   <Context>    the context of the handler (if any)
 
-        resumeBlock      <Block>      private to the exception; needed to perform resume action
+	resumeBlock      <Block>      private to the exception; needed to perform resume action
 
-        rejectBlock      <Block>      private to the exception; needed to perform reject action
+	rejectBlock      <Block>      private to the exception; needed to perform reject action
 
     In case of an unhandled signal raise, Exceptions EmergenyHandler will be evaluated. 
     The default emergeny handler will enter the debugger.
@@ -99,19 +99,46 @@
     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]
+	Exception emergencyHandler:[:ex | Smalltalk exitWithCoreDump]
 
     Class variables:
-        EmergencyHandler <Block>    this block is evaluated, if no handler was defined
-                                    for a signal (i.e. this one is responsible for the
-                                    unhandled exception debugger).
-                                    Having this being a block allows to globally catch
-                                    these errors - even when no enclosing handler-scope
-                                    around the erronous code exists.
-                                    (as the catch/through does).
+
+	EmergencyHandler <Block>    this block is evaluated, if no handler was defined
+				    for a signal (i.e. this one is responsible for the
+				    unhandled exception debugger).
+				    Having this being a block allows to globally catch
+				    these errors - even when no enclosing handler-scope
+				    around the erronous code exists.
+				    (as the catch/through does).
+
+	RecursiveExceptionSignal
+			 <Signal>   raised when within a handler for some signal,
+				    th same signal is raised again.
 "
 ! !
 
+!Exception class methodsFor:'initialization'!
+
+initialize 
+    "setup the signal used to handle unhandled signals"
+
+    RecursiveExceptionSignal isNil ifTrue:[
+	Object initialize.
+
+	RecursiveExceptionSignal := Object errorSignal newSignalMayProceed:false.
+	RecursiveExceptionSignal nameClass:self message:#recursiveExceptionSignal.
+	RecursiveExceptionSignal notifierString:'recursive signal raise in handler'
+    ]
+! !
+
+!Exception class methodsFor:'signal access'!
+
+recursiveExceptionSignal
+    "return the signal used to handle recursive signals in the handlers"
+
+    ^ RecursiveExceptionSignal
+! !
+
 !Exception class methodsFor:'defaults'!
 
 emergencyHandler
@@ -121,15 +148,15 @@
      set it up, when called the first time
     "
     EmergencyHandler isNil ifTrue:[
-        EmergencyHandler := [:ex |
-            "
-             sending it to the signal allows per-signal specific
-             debuggers to be implemented in the future
-             (for example, segv in primitive code could show things 
-              on the C-level ..)
-            "
-            (ex signal) enterDebuggerWith:ex message:(ex errorString).
-        ]
+	EmergencyHandler := [:ex |
+	    "
+	     sending it to the signal allows per-signal specific
+	     debuggers to be implemented in the future
+	     (for example, segv in primitive code could show things 
+	      on the C-level ..)
+	    "
+	    (ex signal) enterDebuggerWith:ex message:(ex errorString).
+	]
     ].
 
     ^ EmergencyHandler
@@ -176,8 +203,10 @@
 !
 
 rejected
-    "return true, if the exception handler rejected.
-     (only valid after handler execution)"
+    "return true, if the exception handler rejected 
+     (in contrast to a handler falling through).
+     Uncertain, if thais is really interresting to anybody.
+     Notice: this is only valid immediately after handler execution."
 
     ^ rejected
 ! !
@@ -192,26 +221,127 @@
     parameter := aParameter.
     errorString := aString.
     suspendedContext := sContext.
-!
+! !
+
+!Exception methodsFor:'raising '!
 
-handlerContext:aContext
-    "set the context of the handler.
-     - only to be sent from the signal when raising"
+raise
+    "actually raise an exception"
 
-    handlerContext := aContext
+    resumeBlock := [:value | ^ value].
+    self evaluateHandler
 !
 
-rejectBlock:aBlock
-    "this is meant to be sent by Signal only"
+evaluateHandler
+    "search through the context-calling chain for a 'handle:do:'-context 
+     to the raising signal a parent of it or a SignalSet which includes 
+     the raising signal.
+     If found, take the contexts 2nd argument (the handler) and evaluate
+     it with the receiver exception as argument.
+     If none found, just return."
+
+    |con block noHandlerSignal|
+
+    con := thisContext sender.  "the raise-context"
+    con := con sender.          "the signal raise context"
+    con isRecursive ifTrue:[
+	"
+	 mhmh - an error while in a handler
+	"
+	((signal == RecursiveExceptionSignal)
+	or:[RecursiveExceptionSignal isNil]) ifTrue:[
+	    "
+	     ... either while handling RecursiveExceptionSignal
+	     or at startup when RecursiveExceptionSignal is not yet
+	     created -
+	     - go immediately into the debugger.
+	    "
+	    ^ self enterDebuggerWith:self
+			     message:'recursive signal raise'
+	].
+	^ RecursiveExceptionSignal 
+	    raiseRequestWith:self 
+		 errorString:('recursive signal raise: ' , errorString)
+    ].
+
+    [con notNil] whileTrue:[
+	(con selector == #'handle:do:') ifTrue:[
+	    "
+	     if this is the Signal>>handle:do: context
+	     or a SignalSet>>handle:do: context with self in it,
+	     call the handler
+	    "
+	    (con receiver accepts:signal) ifTrue:[
+		"call the handler"
+
+		handlerContext := con.
+		self doCallHandler:(con args at:1).
 
-    rejected := false.
-    rejectBlock := aBlock
+		"if the handler rejects or falls through we arrive here"
+		"continue search for another handler"
+	    ].
+	].
+	con := con sender
+    ].
+
+    "
+     we arrive here, if either no handler was found, or none of the
+     handlers did a return (i.e. every handler rejected or fell through).
+    "
+    "
+     try per signal handler
+    "
+    (block := signal handlerBlock) notNil ifTrue:[
+	^ block value:self.
+    ].
+
+    "
+     if it is not the NoHandlerSignal, raise it ...
+     passing the recevier as parameter.
+    "
+    signal ~~ (noHandlerSignal := Signal noHandlerSignal) ifTrue:[
+	noHandlerSignal notNil ifTrue:[
+	    ^ noHandlerSignal 
+		  raiseRequestWith:self 
+		       errorString:('unhandled exception: ' , errorString)
+	].
+	"
+	 mhmh - an error during early startup; noHandlerSignal is
+	 not yet defined.
+	"
+	^ MiniDebugger enterWithMessage:errorString
+    ].
+
+    "
+     mhmh - smells like trouble - there is no handler and
+     no per-signal handler block.
+     Look for either a per-process emergencyHandlerBlock 
+     or the global emergencyHandler (from Exception) ...
+    "
+    Processor notNil ifTrue:[ 
+	"care for signal during startup (Processor not yet created)"
+	block := Processor activeProcess emergencySignalHandler.
+    ].
+    block isNil ifTrue:[
+	block := Exception emergencyHandler
+    ].
+    block isNil ifTrue:[
+	"care for error during startup (Exception not yet initialized)"
+	^ MiniDebugger enterWithMessage:errorString
+    ].
+
+    "... and call it"
+    ^ block value:self.
 !
 
-resumeBlock:aBlock
-    "this is meant to be sent by Signal only"
+doCallHandler:aHandler
+    "call the handler proper - needed an extra method
+     to have a separate returnContext for the rejectBlock.
+     (which is historical, and actually no longer needed)"
 
-    resumeBlock := aBlock
+    rejectBlock := [^ self]. "this will return on reject"
+    aHandler value:self.
+    "handler fall through - is just like a reject"
 ! !
 
 !Exception methodsFor:'handler actions'!
--- a/Signal.st	Fri Oct 28 02:21:37 1994 +0100
+++ b/Signal.st	Fri Oct 28 02:22:16 1994 +0100
@@ -13,7 +13,7 @@
 Object subclass:#Signal
 	 instanceVariableNames:'mayProceed notifierString nameClass message
 				handlerBlock parent'
-	 classVariableNames:'NoHandlerSignal RecursiveRaiseSignal'
+	 classVariableNames:'NoHandlerSignal'
 	 poolDictionaries:''
 	 category:'Kernel-Exceptions'
 !
@@ -22,7 +22,7 @@
 COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/Signal.st,v 1.14 1994-10-10 00:28:19 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Signal.st,v 1.15 1994-10-28 01:22:16 claus Exp $
 '!
 
 !Signal class methodsFor:'documentation'!
@@ -43,7 +43,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/Signal.st,v 1.14 1994-10-10 00:28:19 claus Exp $
+$Header: /cvs/stx/stx/libbasic/Signal.st,v 1.15 1994-10-28 01:22:16 claus Exp $
 "
 !
 
@@ -66,9 +66,11 @@
     And, finally there is a very special SignalSet which allows catching
     any signal (SignalSet>>anySignal).
 
-    This Signal implementation has been modeled after what some PD
-    programs seem to expect - it may not be perfect currently
-    (especially, I dont know what nameClass and message are for).
+    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:
 
@@ -77,11 +79,11 @@
     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, a NoHandler-Signal will be raised instead,
+    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 NoHandler-signal can be handled just like any other signal.
-    (therefore, it is possible to catch any error by catching the NoHandler
-     signal).
+    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.
@@ -94,7 +96,7 @@
     or per-process signal handling to be added. Even to code which was never
     planned to handle signals.
 
-    See samples in doc/coding.
+    See samples in 'doc/coding' and actual raise code in Exception.
 
     Instance variables:
 
@@ -102,24 +104,30 @@
 					proceed (currently not honored by the
 					debugger)
 
-	notifierString  <String>        eror message to be output 
+	notifierString  <String>        error message to be output 
 
-	nameClass       <???>           I dont know what this is for 
-					(included for ST-80 compatibility)
+	nameClass       <Class>         for the printOn-implementation; nameClass
+					is the class, to which message (below) 
+					should be sent to create the receiver.
 
-	message         <???>           I dont know what this is for
-					(included for ST-80 compatibility)
+	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.
+					object as argument. This will play the role
+					of an on-stack handler.
+
+    Class variables:
 
-    Notice:
-    Part of the implementation is a left-over from old times when the 
-    resume/restart things in context did not work properly. Now, with the 
-    handler- and suspendedContext at hand, the exception can do it using 
-    other mechanisms. This might be cleaned up ...
+	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).
 "
 ! !
 
@@ -135,9 +143,6 @@
 	NoHandlerSignal nameClass:self message:#noHandlerSignal.
 	NoHandlerSignal notifierString:'unhandled exception'.
 
-	RecursiveRaiseSignal := Object errorSignal newSignalMayProceed:false.
-	RecursiveRaiseSignal nameClass:self message:#recursiveRaiseSignal.
-	RecursiveRaiseSignal notifierString:'recursive signal raise'
     ]
 ! !
 
@@ -155,12 +160,6 @@
     "return the signal used to handle unhandled signals"
 
     ^ NoHandlerSignal
-!
-
-recursiveRaiseSignal
-    "return the signal used to handle recursive signal raises"
-
-    ^ RecursiveRaiseSignal
 ! !
 
 !Signal methodsFor:'instance creation'!
@@ -240,6 +239,13 @@
      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'!
@@ -348,10 +354,16 @@
      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 := thisContext.
-    con := con sender.
+    con := aContext.
     [con notNil] whileTrue:[
 	(con selector == #handle:do:) ifTrue:[
 	    "
@@ -376,11 +388,7 @@
      and call the handler with this as argument.
      The signals notifierString is used as errorString."
 
-    "This could have been defined using 'raiseRequestWith:', 
-     but is not - to not add too many contexts to the backtrace 
-     (thus making things cleaner in the debugger-walkback eventually)"
-
-    |ex block|
+    |ex|
 
     ex := Exception new 
 	      signal:self
@@ -388,40 +396,7 @@
 	      errorString:notifierString
 	      suspendedContext:thisContext sender.
 
-    ex resumeBlock:[:value | ^ value].
-    self evaluateHandlerWith:ex.
-
-    (block := handlerBlock) isNil ifTrue:[
-	"
-	 if I am not the NoHandlerSignal, raise it ...
-	 passing the exception as parameter.
-	"
-	self == NoHandlerSignal ifFalse:[
-	    ^ NoHandlerSignal 
-		  raiseRequestWith:ex
-		       errorString:('unhandled exception: ' , ex errorString)
-	].
-
-	"
-	 otherwise,
-	 take either a per-process emergencyHandlerBlock 
-	 or the global emergencyHandler (from Exception) ...
-	"
-	Processor notNil ifTrue:[ 
-	    "care for signal during startup (Processor not yet created)"
-	    block := Processor activeProcess emergencySignalHandler.
-	].
-	block isNil ifTrue:[
-	    block := Exception emergencyHandler
-	].
-	block isNil ifTrue:[
-	    "care for error during startup (Exception not yet initialized)"
-	    ^ MiniDebugger enterWithMessage:ex errorString
-	]
-    ].
-
-    "... and call it"
-    ^ block value:ex.
+    ^ ex raise
 !
 
 raiseRequestWith:aParameter
@@ -429,11 +404,7 @@
      and call the handler with this as argument..
      The signals notifierString is used as errorString."
 
-    "This could have been defined using 'raiseRequestWith:', 
-     but is not - to not add too many contexts to the backtrace 
-     (thus making things cleaner in the debugger-walkback eventually)"
-
-    |ex block|
+    |ex|
 
     ex := Exception new 
 	      signal:self
@@ -441,49 +412,16 @@
 	      errorString:notifierString
 	      suspendedContext:thisContext sender.
 
-    ex resumeBlock:[:value | ^ value].
-    self evaluateHandlerWith:ex.
-
-    (block := handlerBlock) isNil ifTrue:[
-	"
-	 if I am not the NoHandlerSignal, raise it ...
-	 passing the exception as parameter.
-	"
-	self == NoHandlerSignal ifFalse:[
-	    ^ NoHandlerSignal 
-		  raiseRequestWith:ex
-		       errorString:('unhandled exception: ' , ex errorString)
-	].
-
-	"
-	 otherwise,
-	 take either a per-process emergencyHandlerBlock 
-	 or the global emergencyHandler (from Exception) ...
-	"
-	Processor notNil ifTrue:[ 
-	    "care for signal during startup (Processor not yet created)"
-	    block := Processor activeProcess emergencySignalHandler.
-	].
-	block isNil ifTrue:[
-	    block := Exception emergencyHandler
-	].
-	block isNil ifTrue:[
-	    "care for error during startup (Exception not yet initialized)"
-	    ^ MiniDebugger enterWithMessage:ex errorString
-	]
-    ].
-
-    "... and call it"
-    ^ block value:ex.
+    ^ 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, something is used as errorString.
+     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 block|
+    |ex|
 
     ex := Exception new 
 	      signal:self
@@ -491,40 +429,7 @@
 	      errorString:something printString
 	      suspendedContext:thisContext sender.
 
-    ex resumeBlock:[:value | ^ value].
-    self evaluateHandlerWith:ex.
-
-    (block := handlerBlock) isNil ifTrue:[
-	"
-	 if I am not the NoHandlerSignal, raise it ...
-	 passing the exception as parameter.
-	"
-	self == NoHandlerSignal ifFalse:[
-	    ^ NoHandlerSignal 
-		  raiseRequestWith:ex
-		       errorString:('unhandled exception: ' , ex errorString)
-	].
-
-	"
-	 otherwise,
-	 take either a per-process emergencyHandlerBlock 
-	 or the global emergencyHandler (from Exception) ...
-	"
-	Processor notNil ifTrue:[ 
-	    "care for signal during startup (Processor not yet created)"
-	    block := Processor activeProcess emergencySignalHandler.
-	].
-	block isNil ifTrue:[
-	    block := Exception emergencyHandler
-	].
-	block isNil ifTrue:[
-	    "care for error during startup (Exception not yet initialized)"
-	    ^ MiniDebugger enterWithMessage:ex errorString
-	]
-    ].
-
-    "... and call it"
-    ^ block value:ex.
+    ^ ex raise
 !
 
 raiseRequestWith:aParameter errorString:aString
@@ -532,7 +437,7 @@
      and call the handler with this as argument..
      The argument, aString is used as errorString."
 
-    |ex block|
+    |ex|
 
     ex := Exception new 
 	      signal:self
@@ -540,108 +445,5 @@
 	      errorString:aString
 	      suspendedContext:thisContext sender.
 
-    ex resumeBlock:[:value | ^ value].
-    self evaluateHandlerWith:ex.
-
-    (block := handlerBlock) isNil ifTrue:[
-	"
-	 if I am not the NoHandlerSignal, raise it ...
-	 passing the exception as parameter.
-	"
-	self == NoHandlerSignal ifFalse:[
-	    ^ NoHandlerSignal 
-		  raiseRequestWith:ex
-		       errorString:('unhandled exception: ' , ex errorString)
-	].
-
-	"
-	 otherwise,
-	 take either a per-process emergencyHandlerBlock 
-	 or the global emergencyHandler (from Exception) ...
-	"
-	Processor notNil ifTrue:[ 
-	    "care for signal during startup (Processor not yet created)"
-	    block := Processor activeProcess emergencySignalHandler.
-	].
-	block isNil ifTrue:[
-	    block := Exception emergencyHandler
-	].
-	block isNil ifTrue:[
-	    "care for error during startup (Exception not yet initialized)"
-	    ^ MiniDebugger enterWithMessage:ex errorString
-	]
-    ].
-
-    "... and call it"
-    ^ block value:ex.
+    ^ ex raise
 ! !
-
-!Signal methodsFor:'private'!
-
-evaluateHandlerWith:ex
-    "search through the context-calling chain for a 'handle:do:'-context 
-     to the receiver or a parent of the receiver or a SignalSet which includes 
-     the receiver.
-     If found, take its 2nd argument (the handler) and evaluate
-     it with the exception as argument.
-     If none found, just return."
-
-    |con|
-
-    con := thisContext.
-    con := con sender.
-    con isRecursive ifTrue:[
-	"
-	 mhmh - an error while in a handler
-	"
-	((self == RecursiveRaiseSignal)
-	or:[RecursiveRaiseSignal isNil]) ifTrue:[
-	    "
-	     ... either while handling RecursiveSignal
-	     or at startup when RecursiveSignal is not yet
-	     created -
-	     - go immediately into the debugger.
-	    "
-	    ^ self enterDebuggerWith:ex
-			     message:'recursive signal raise'
-	].
-	^ RecursiveRaiseSignal 
-	    raiseRequestWith:ex
-		 errorString:('recursive signal raise: ' , ex errorString)
-    ].
-
-    [con notNil] whileTrue:[
-	(con selector == #'handle:do:') ifTrue:[
-	    "
-	     if this is the Signal>>handle:do: context
-	     or a SignalSet>>handle:do: context with self in it,
-	     call the handler
-	    "
-	    (con receiver accepts:self) ifTrue:[
-		"call the handler"
-
-		ex handlerContext:con.
-		self doCallHandler:(con args at:1) with:ex.
-
-		"if the handler rejects or falls through we arrive here"
-		"continue search for another handler"
-	    ].
-	].
-	con := con sender
-    ].
-
-    "
-     we arrive here, if either no handler was found, or none of the
-     handlers did a return (i.e. every handler rejected or fell through).
-    "
-!
-
-doCallHandler:aHandler with:ex
-    "call the handler proper - needed an extra method
-     to have a separate returnContext for the rejectBlock.
-     (which is historical, and actually no longer needed)"
-
-    ex rejectBlock:[^ self]. "this will return on reject"
-    aHandler value:ex.
-    "handler return - is just like a reject"
-! !