GenericException.st
changeset 4521 946e1a02b158
parent 4519 fb4904d6787b
child 4527 2ddbe34bab87
--- a/GenericException.st	Wed Aug 04 09:08:53 1999 +0200
+++ b/GenericException.st	Wed Aug 04 09:58:10 1999 +0200
@@ -13,7 +13,7 @@
 Object subclass:#GenericException
 	instanceVariableNames:'signal parameter errorString suspendedContext handlerContext
 		rejected originator proceedable handlingException'
-	classVariableNames:'EmergencyHandler RecursiveExceptionSignal'
+	classVariableNames:'EmergencyHandler'
 	poolDictionaries:''
 	category:'Kernel-Exceptions'
 !
@@ -325,32 +325,32 @@
     |t|
 
     (self inheritsFrom:Object userNotificationSignal) ifTrue:[
-        "/ all userNotifications pass the extraString unchanged.
-        ^ extraString
+	"/ all userNotifications pass the extraString unchanged.
+	^ extraString
     ].
 
     extraString isNil ifTrue:[
-        t := self errorString
+	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 := extraString.
+	(extraString endsWith:Character space) ifTrue:[
+	    t := extraString, self errorString
+	] ifFalse:[
+	    (extraString startsWith:Character space) ifTrue:[
+		t := self errorString, extraString
+	    ]
+	].
     ].
 
     aParameter isNil ifTrue:[
-        ^ t.
+	^ t.
     ].
 
     (t startsWith:' ') ifTrue:[
-        ^ aParameter printString , t.
+	^ aParameter printString , t.
     ].
     (t endsWith:' ') ifTrue:[
-        ^ t , aParameter printString.
+	^ t , aParameter printString.
     ].
     ^ t
 
@@ -397,9 +397,9 @@
 
     (theContext selector ~~ #'handle:from:do:'
      or:[(theContext argAt:2) == originator]) ifTrue:[
-        (self == signal or:[self accepts:signal]) ifTrue:[
-            ^ theContext argAt:1
-        ]
+	(self == signal or:[self accepts:signal]) ifTrue:[
+	    ^ theContext argAt:1
+	]
     ].
 
     ^ nil
@@ -412,7 +412,7 @@
 
     (theContext selector == #'handle:from:do:'
      or:[theContext selector == #'handle:do:']) ifTrue:[
-        ^ theContext receiver
+	^ theContext receiver
     ].
 
     ^ nil
@@ -448,13 +448,13 @@
 
     con := Context findFirstSpecialHandle:true raise:false.
     [con notNil] whileTrue:[
-        ((r := con receiver) notNil
-         and:[(r handlerForSignal:self context:con originator:nil) notNil]
-        ) ifTrue:[
-            "found a handler context"
-            ^ true
-        ].
-        con := con findSpecialHandle:true raise:false.
+	((r := con receiver) notNil
+	 and:[(r handlerForSignal:self context:con originator:nil) notNil]
+	) ifTrue:[
+	    "found a handler context"
+	    ^ true
+	].
+	con := con findSpecialHandle:true raise:false.
     ].
     ^ false
 
@@ -748,7 +748,7 @@
 
     "
      Object messageNotUnderstoodSignal catch:[
-        123 size open   
+	123 size open   
      ]
     "
 
@@ -771,10 +771,10 @@
 
     "
      Object messageNotUnderstoodSignal handle:[:ex |
-        'oops' printNL.
-        ex return
+	'oops' printNL.
+	ex return
      ] do:[
-        123 size open   
+	123 size open   
      ]
      "
 
@@ -783,10 +783,10 @@
 
       num := 0.
       Number divisionByZeroSignal handle:[:ex |
-          'oops' printNL.
-          ex return
+	  'oops' printNL.
+	  ex return
       ] do:[
-          123 / num   
+	  123 / num   
       ]
      "
 
@@ -817,17 +817,17 @@
      o1 := 123.
      o2 := nil.
      Object messageNotUnderstoodSignal 
-         handle:
-                [:ex |
-                    'oops' printNL.
-                    ex proceed
-                ] 
-         from:o1
-         do:
-                [
-                    o1 open.
-                    o2 open
-                ]
+	 handle:
+		[:ex |
+		    'oops' printNL.
+		    ex proceed
+		] 
+	 from:o1
+	 do:
+		[
+		    o1 open.
+		    o2 open
+		]
     "
 
     "Created: / 23.7.1999 / 14:06:26 / stefan"
@@ -846,7 +846,7 @@
 
     "
      Object messageNotUnderstoodSignal ignoreIn:[
-        123 size open   
+	123 size open   
      ]
     "
 
@@ -978,58 +978,58 @@
      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)"
+	 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)"
 
     ^ [: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:[
-                      AbortSignal raise
-                  ].
-                  ex proceedWith:nil
-             ].
-
-             "/
-             "/ dump it to 'errorTrace.stx'
-             "/
-             str := 'errorTrace.stx' asFilename appendingWriteStream.
-
-             str nextPutLine:('******************************* '
-                              , AbsoluteTime now printString
-                              , ' *******************************').
-             str cr.
-
-             str nextPutLine:('** Error: ' , printedException errorString).
-             str nextPutLine:('** Signal: ' , printedException signal printString).
-             str nextPutLine:('** Parameter: ' , printedException parameter printString).
-             str nextPutLine:('** Process: ' , Processor activeProcess printString).
-             str nextPutLine:('** Backtrace:').
-             str cr.
+	     |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:[
+		      AbortSignal raise
+		  ].
+		  ex proceedWith:nil
+	     ].
+
+	     "/
+	     "/ dump it to 'errorTrace.stx'
+	     "/
+	     str := 'errorTrace.stx' asFilename appendingWriteStream.
+
+	     str nextPutLine:('******************************* '
+			      , AbsoluteTime now printString
+			      , ' *******************************').
+	     str cr.
+
+	     str nextPutLine:('** Error: ' , printedException errorString).
+	     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 errorString) errorPrintCR.
-             ('[warning]:    error information appended to ''errorTrace.stx''') errorPrintCR.
-
-             AbortSignal raise 
+	     printedException suspendedContext fullPrintAllOn:str.
+	     str cr.
+	     str cr.
+	     str close.
+
+	     "/ send a line to stdErr
+
+	     ('[warning]: ignored error: ' , printedException errorString) errorPrintCR.
+	     ('[warning]:    error information appended to ''errorTrace.stx''') errorPrintCR.
+
+	     AbortSignal raise 
       ]
 
     "test with (try a few halts or CTRL-C's):
@@ -1053,78 +1053,78 @@
      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."
+	     for your particular environment ...
+	     ... but please: copy the code and modify there;
+	     leave the stuff below as it is."
 
     ^ [: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 == Object userInterruptSignal ifTrue:[
-                  (self confirm:'abort current action ?') ifTrue:[
-                      AbortSignal 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 errorString 
-                           , '\\No mailing to service people possible.') withCRs.
-                doMail := false.
-            ] ifFalse:[
-                doMail := self confirm:(printedException errorString 
-                                        , '\\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: ' , AbsoluteTime now printString).
-                str nextPutLine:('Error: ', printedException errorString).
-                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.
-                ]
-             ].
-
-             AbortSignal raise 
+	    |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 == Object userInterruptSignal ifTrue:[
+		  (self confirm:'abort current action ?') ifTrue:[
+		      AbortSignal 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 errorString 
+			   , '\\No mailing to service people possible.') withCRs.
+		doMail := false.
+	    ] ifFalse:[
+		doMail := self confirm:(printedException errorString 
+					, '\\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: ' , AbsoluteTime now printString).
+		str nextPutLine:('Error: ', printedException errorString).
+		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.
+		]
+	     ].
+
+	     AbortSignal raise 
       ]
 
     "test with (try a few halts or CTRL-C's):
@@ -1311,52 +1311,52 @@
      try per signal handler
     "
     (block := signal handlerBlock) isNil ifTrue:[
-        "/
-        "/ if its a querySignal, ignore it
-        "/
-        signal isQuerySignal ifTrue:[^ nil].
-
-        "/
-        "/ if it is not the NoHandlerSignal, raise it ...
-        "/ passing the receiver as parameter.
-        "/
-        signal ~~ NoHandlerError ifTrue:[
-            NoHandlerError notNil ifTrue:[
-                handlerContext notNil ifTrue:[
-                    msg := 'unhandled (rejected)'
-                ] ifFalse:[
-                    msg := 'unhandled'
-                ].
-                msg := msg , ' exception: (' , self errorString , ')'.
-                ^ NoHandlerError 
-                      raiseRequestWith:self 
-                      errorString:msg
-                      in:self suspendedContext
-            ].
-            "/
-            "/ mhmh - an error during early startup; noHandlerSignal is
-            "/ not yet defined.
-            "/
-            ^ MiniDebugger enterWithMessage:self 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:self errorString
-            ].
-        ].
+	"/
+	"/ if its a querySignal, ignore it
+	"/
+	signal isQuerySignal ifTrue:[^ nil].
+
+	"/
+	"/ if it is not the NoHandlerSignal, raise it ...
+	"/ passing the receiver as parameter.
+	"/
+	signal ~~ NoHandlerError ifTrue:[
+	    NoHandlerError notNil ifTrue:[
+		handlerContext notNil ifTrue:[
+		    msg := 'unhandled (rejected)'
+		] ifFalse:[
+		    msg := 'unhandled'
+		].
+		msg := msg , ' exception: (' , self errorString , ')'.
+		^ NoHandlerError 
+		      raiseRequestWith:self 
+		      errorString:msg
+		      in:self suspendedContext
+	    ].
+	    "/
+	    "/ mhmh - an error during early startup; noHandlerSignal is
+	    "/ not yet defined.
+	    "/
+	    ^ MiniDebugger enterWithMessage:self 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:self errorString
+	    ].
+	].
     ].
 
     "... and call it"
@@ -1383,17 +1383,17 @@
     "Continue after the raise - the raise returns nil"
 
     proceedable ifFalse:[
-        "proceed from ProceedError to recover from this error"
-        ProceedError raiseRequestWith:self in:thisContext sender.
-        proceedable := true.
+	"proceed from ProceedError to recover from this error"
+	ProceedError raiseRequestWith:self in:thisContext sender.
+	proceedable := true.
     ].
     self proceedWith:nil.
 
     "
      Object errorSignal handle:[:ex|
-         ex proceed
+	 ex proceed
      ] do:[
-         Object errorSignal raiseRequest
+	 Object errorSignal raiseRequest
      ].
     "
 
@@ -1407,16 +1407,16 @@
     |con|
 
     proceedable ifFalse:[
-        "proceed from ProceedError to recover from this error"
-        ProceedError raiseRequestWith:self in:thisContext sender.
-        proceedable := true.
+	"proceed from ProceedError to recover from this error"
+	ProceedError raiseRequestWith:self in:thisContext sender.
+	proceedable := true.
     ].
 
     "/ find my raise context
     con := Context findFirstSpecialHandle:false raise:true.
     [con notNil 
      and:[con receiver ~~ self]] whileTrue:[
-        con := con findSpecialHandle:false raise:true.
+	con := con findSpecialHandle:false raise:true.
     ].
     "/ now, have the doCallXXX context at-hand
     con := con sender.
@@ -1439,7 +1439,7 @@
     con := Context findFirstSpecialHandle:false raise:true.
     [con notNil 
      and:[con receiver ~~ self]] whileTrue:[
-        con := con findSpecialHandle:false raise:true.
+	con := con findSpecialHandle:false raise:true.
     ].
     "/ now, have the doCallXXX context at-hand
 
@@ -1448,15 +1448,15 @@
 
     "
      Object errorSignal handle:[:ex |
-        '1' printCR.
-        ex reject
+	'1' printCR.
+	ex reject
      ] do:[
-        Object errorSignal handle:[:ex |
-            '2' printCR.
-            ex reject
-        ] do:[
-            #() at:1
-        ]
+	Object errorSignal handle:[:ex |
+	    '2' printCR.
+	    ex reject
+	] do:[
+	    #() at:1
+	]
      ]
     "
 !
@@ -1475,11 +1475,11 @@
      |rslt n|
 
      Object errorSignal handle:[:ex |
-        'fixing divisor ...' printCR.
-        n := 1.
-        ex restart.
+	'fixing divisor ...' printCR.
+	n := 1.
+	ex restart.
      ] do:[
-        rslt := 5 / n.
+	rslt := 5 / n.
      ].
      rslt
     "
@@ -1494,7 +1494,7 @@
     con := handlerContext.
 
     con selector == #'handle:do:' ifFalse:[
-        self error:'unimplemented feature'.
+	self error:'unimplemented feature'.
     ].
 
 "/    handlerContext unwindThenDo:[
@@ -1512,10 +1512,10 @@
      sig := Signal new.
 
      sig handle:[:ex |
-        ex restartDo:[ rslt := 999 ]
+	ex restartDo:[ rslt := 999 ]
      ] do:[
-        rslt := 0.
-        sig raise
+	rslt := 0.
+	sig raise
      ].
      Transcript showCR:rslt
     "
@@ -1524,9 +1524,9 @@
      |sig rslt|
 
      Object errorSignal handle:[:ex |
-        ex restartDo:[ rslt := 999 ]
+	ex restartDo:[ rslt := 999 ]
      ] do:[
-        rslt := nil foo.
+	rslt := nil foo.
 
      ].
      Transcript showCR:rslt
@@ -1536,9 +1536,9 @@
      |sig rslt|
 
      Object errorSignal handle:[:ex |
-        ex restartDo:[ 'handler' printCR. rslt := nil foo ]
+	ex restartDo:[ 'handler' printCR. rslt := nil foo ]
      ] do:[
-        rslt := nil foo.
+	rslt := nil foo.
 
      ].
      Transcript showCR:rslt
@@ -1658,12 +1658,12 @@
     "/ instanceVariable to record the originator setting.
 
     originator isNil ifTrue:[
-        originator := suspendedContext homeReceiver
+	originator := suspendedContext homeReceiver
     ].
 
     theSignal := signal.
     theSignal isSignal ifFalse:[
-        self halt:'unexpected non-Signal in calling context'.
+	self halt:'unexpected non-Signal in calling context'.
     ].
 
 "/ 'search handler for: ' print. theSignal displayString printCR.
@@ -1685,42 +1685,42 @@
     c := Context findFirstSpecialHandle:searchForHandle raise:true.
 
     [c notNil] whileTrue:[
-        (c isRaiseContext) ifTrue:[
-            ex1 := c receiver.
-            ((ex1 class == self class)
-            or:[ex1 species == self species]) ifTrue:[
-                h := ex1 handlerContext.
-                h notNil ifTrue:[
-                    ((ex1 signal == theSignal)
-
-                    "/ mhmh - if not ==, the raised signal there is not ours, 
-                    "/ but the handler could still be for a signalSet, parentSig
-                    "/ or other thingy which accepts our signal.
-                    "/ If we omit that check, a signalSet-handler gets invoked
-                    "/ again by an exception occuring inside its handler.
-
-                    "/ to avoid overhead, only do it if the
-                    "/ handlers receiver is not of the signals class...
-                    "/ ...i.e. knowing that most are r handle:do: contexts,
-                    "/ where the receiver is the handling signal.
-                    or:[h receiver ~~ ex1 signal
-                        and:[ex1 handlingException accepts:theSignal]]) ifTrue:[
-                        activeHandlers isNil ifTrue:[
-                            activeHandlers := OrderedCollection new
-                        ].
-
-                        activeHandlers add:h.
-                        "/ lastHandler := h.
-                        c := h.
-                    ]
-                ]
-            ]
-        ] ifFalse:[
-            "/ must be a handle context ...
-            firstHandler := c.
-            searchForHandle := false.
-        ].
-        c := c findSpecialHandle:searchForHandle raise:true.
+	(c isRaiseContext) ifTrue:[
+	    ex1 := c receiver.
+	    ((ex1 class == self class)
+	    or:[ex1 species == self species]) ifTrue:[
+		h := ex1 handlerContext.
+		h notNil ifTrue:[
+		    ((ex1 signal == theSignal)
+
+		    "/ mhmh - if not ==, the raised signal there is not ours, 
+		    "/ but the handler could still be for a signalSet, parentSig
+		    "/ or other thingy which accepts our signal.
+		    "/ If we omit that check, a signalSet-handler gets invoked
+		    "/ again by an exception occuring inside its handler.
+
+		    "/ to avoid overhead, only do it if the
+		    "/ handlers receiver is not of the signals class...
+		    "/ ...i.e. knowing that most are r handle:do: contexts,
+		    "/ where the receiver is the handling signal.
+		    or:[h receiver ~~ ex1 signal
+			and:[ex1 handlingException accepts:theSignal]]) ifTrue:[
+			activeHandlers isNil ifTrue:[
+			    activeHandlers := OrderedCollection new
+			].
+
+			activeHandlers add:h.
+			"/ lastHandler := h.
+			c := h.
+		    ]
+		]
+	    ]
+	] ifFalse:[
+	    "/ must be a handle context ...
+	    firstHandler := c.
+	    searchForHandle := false.
+	].
+	c := c findSpecialHandle:searchForHandle raise:true.
     ].
 
     h := nil.
@@ -1737,41 +1737,41 @@
 "/        theContext := lastHandler.
 "/        theContext := lastHandler findNextHandleContext
 "/    ] ifFalse:[
-        theContext := firstHandler.
+	theContext := firstHandler.
 "/    ].
     firstHandler := nil.
 
     [theContext notNil] whileTrue:[
-        "/
-        "/  ask the Signal instance/Exception class for the handler.
-        "/  nil is returned, if the signal is not accepted
-        "/
-        r := theContext receiver.
-        (r notNil and:[(handler := r handlerForSignal:signal 
-                                     context:theContext 
-                                     originator:originator) notNil]
-        ) ifTrue:[
-            (activeHandlers notNil
-             and:[activeHandlers includesIdentical:theContext]) ifTrue:[
+	"/
+	"/  ask the Signal instance/Exception class for the handler.
+	"/  nil is returned, if the signal is not accepted
+	"/
+	r := theContext receiver.
+	(r notNil and:[(handler := r handlerForSignal:signal 
+				     context:theContext 
+				     originator:originator) notNil]
+	) ifTrue:[
+	    (activeHandlers notNil
+	     and:[activeHandlers includesIdentical:theContext]) ifTrue:[
 "/                'skip activeHandler: ' print. theContext displayString printCR.
 
-            ] ifFalse:[
-                "call the handler"
-
-                handlerContext := theContext.
-                "/ remember the handling signal, sigSet, or exception
-                "/ for the #accepts: check above
-                handlingException := r handlingExceptionInContext:theContext.
-                theContext := nil.
-                self doCallHandler:handler.
-
-                "/ if the handler rejects, we arrive here
-                "/ continue search for another handler
-                theContext := handlerContext.
-                handlerContext := nil.
-            ].
-        ].
-        theContext := theContext findSpecialHandle:true raise:false.
+	    ] ifFalse:[
+		"call the handler"
+
+		handlerContext := theContext.
+		"/ remember the handling signal, sigSet, or exception
+		"/ for the #accepts: check above
+		handlingException := r handlingExceptionInContext:theContext.
+		theContext := nil.
+		self doCallHandler:handler.
+
+		"/ if the handler rejects, we arrive here
+		"/ continue search for another handler
+		theContext := handlerContext.
+		handlerContext := nil.
+	    ].
+	].
+	theContext := theContext findSpecialHandle:true raise:false.
     ].
 
     "/ help GC a bit, by clearing things we no longer need
@@ -1795,12 +1795,12 @@
     "actually raise a non-proceedable exception"
 
     suspendedContext isNil ifTrue:[
-        "Call chain:
-           (origin)>>someMethod         sender
-           Signal>>raise                sender
-           Exception>>raise             thisContext
-        "
-        suspendedContext := thisContext sender sender
+	"Call chain:
+	   (origin)>>someMethod         sender
+	   Signal>>raise                sender
+	   Exception>>raise             thisContext
+	"
+	suspendedContext := thisContext sender sender
     ].
 
     proceedable := false.
@@ -1814,17 +1814,17 @@
     "actually raise a proceedable exception."
 
     suspendedContext isNil ifTrue:[
-        "Call chain:
-           (origin)>>someMethod         sender
-           Signal>>raise                sender
-           Exception>>raise             thisContext
-        "
-        suspendedContext := thisContext sender sender
+	"Call chain:
+	   (origin)>>someMethod         sender
+	   Signal>>raise                sender
+	   Exception>>raise             thisContext
+	"
+	suspendedContext := thisContext sender sender
     ].
 
     self mayProceed ifFalse:[
-        "/ proceeding from wrongProceedabilitySignal grants the raiseRequest
-        WrongProceedabilityError raiseRequestWith:signal in:suspendedContext
+	"/ proceeding from wrongProceedabilitySignal grants the raiseRequest
+	WrongProceedabilityError raiseRequestWith:signal in:suspendedContext
     ].
 
     proceedable := true.
@@ -1937,10 +1937,10 @@
     The parameter is the exception which tried to proceed.
 
     NOTE: In the past ST/X didn't distinguish between proceedable
-          and non-proceedable exceptions. To make transistion easier,
-          this exception is a warning for now. In a future release of
-          ST/X, this exception will be changed to be an error.
-          Please fix your code.
+	  and non-proceedable exceptions. To make transistion easier,
+	  this exception is a warning for now. In a future release of
+	  ST/X, this exception will be changed to be an error.
+	  Please fix your code.
 "
 
 ! !
@@ -1982,15 +1982,15 @@
 
     "
       Object errorSignal handle:[:ex|
-         ex proceedWith:nil
+	 ex proceedWith:nil
       ] do:[
-         Object errorSignal raise
+	 Object errorSignal raise
       ].
 
       Object errorSignal handle:[:ex|
-         ex proceed
+	 ex proceed
       ] do:[
-         Object errorSignal raise
+	 Object errorSignal raise
       ].
     "
 
@@ -2037,6 +2037,6 @@
 !GenericException class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/GenericException.st,v 1.13 1999-08-04 07:07:05 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/GenericException.st,v 1.14 1999-08-04 07:58:10 stefan Exp $'
 ! !
 GenericException initialize!