Exception.st
changeset 2208 cc55b9f5b47e
parent 2204 0ec2bd49dd82
child 2219 0e7ba134fa8d
--- a/Exception.st	Mon Jan 20 12:49:30 1997 +0100
+++ b/Exception.st	Mon Jan 20 12:52:22 1997 +0100
@@ -40,22 +40,22 @@
     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
+	reject          - dont handle this signal;
+			  another handler will be searched for, 
+			  upper in the calling hierarchy
 
-        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
 
-        returnWith:val  - same, but return val from Signal>>handle:do:
-                          (this is also the handlers default, 
-                           if it falls through; taking the handlerBlocks value
-                           as return value)
+	returnWith:val  - same, but return val from Signal>>handle:do:
+			  (this is also the handlers default, 
+			   if it falls through; taking the handlerBlocks value
+			   as return value)
 
-        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
@@ -63,22 +63,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.
@@ -86,31 +86,31 @@
     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,
-                                    the same signal is raised again.
+	RecursiveExceptionSignal
+			 <Signal>   raised when within a handler for some signal,
+				    the same signal is raised again.
 
 
     [see also:]
-        Signal  SignalSet QuerySignal
-        Context Block
-        Object DebugView
-        (``Exception handling and signals'': programming/exceptions.html)
+	Signal  SignalSet QuerySignal
+	Context Block
+	Object DebugView
+	(``Exception handling and signals'': programming/exceptions.html)
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 !
 
@@ -126,33 +126,33 @@
     (especially, the mailingHandler is fun).
 
     Define a handler:
-                                                                [exBegin]
-        Exception emergencyHandler:(Exception abortingEmergencyHandler)
-                                                                [exEnd]
+								[exBegin]
+	Exception emergencyHandler:(Exception abortingEmergencyHandler)
+								[exEnd]
 
 
     try some exception (for demonstration, in some other process):
-                                                                [exBegin]
-        [
-            #(1 2 3) at:4
-        ] fork.
-                                                                [exEnd]
+								[exBegin]
+	[
+	    #(1 2 3) at:4
+	] fork.
+								[exEnd]
 
     cleanup:
-                                                                [exBegin]
-        Exception emergencyHandler:nil
-                                                                [exEnd]
+								[exBegin]
+	Exception emergencyHandler:nil
+								[exEnd]
 
 
     A handler which dumps information to a file (watch the file 'errorTrace.stx'):
-                                                                [exBegin]
-        Exception emergencyHandler:(Exception dumpingEmergencyHandler)
-                                                                [exEnd]
+								[exBegin]
+	Exception emergencyHandler:(Exception dumpingEmergencyHandler)
+								[exEnd]
 
     A handler which sends you mail:
-                                                                [exBegin]
-        Exception emergencyHandler:(Exception mailingEmergencyHandler)
-                                                                [exEnd]
+								[exBegin]
+	Exception emergencyHandler:(Exception mailingEmergencyHandler)
+								[exEnd]
 "
 ! !
 
@@ -217,15 +217,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
@@ -243,14 +243,14 @@
      (I prefer to get right into the debugger, though)
 
      Exception
-        emergencyHandler:
-            [:ex | self errorNotify:ex errorString ]
+	emergencyHandler:
+	    [:ex | self errorNotify:ex errorString ]
     "
 
     "ST-X behavior of going right into the debugger:
 
      Exception
-        emergencyHandler:nil
+	emergencyHandler:nil
     "
 
     "automatically aborting current operation, on error:
@@ -258,15 +258,15 @@
       you have abortSignal handlers at appropriate places)
 
      Exception
-        emergencyHandler:
-            [:ex | Object abortSignal raise. ex return. ]
+	emergencyHandler:
+	    [:ex | Object abortSignal raise. ex return. ]
     "
 
     "finally, traditional language system behavior; dump core ;-)
 
      Exception
-        emergencyHandler:
-            [:ex | Smalltalk exitWithCoreDump. ]
+	emergencyHandler:
+	    [:ex | Smalltalk exitWithCoreDump. ]
     "
 
     "Modified: 15.1.1997 / 20:49:06 / cg"
@@ -280,7 +280,7 @@
      This is useful for endUser applications"
 
     ^ [:ex | self warn:'Error: ' , ex errorString.
-             AbortSignal raise 
+	     AbortSignal raise 
       ]
 
     "test with (try a few halts or CTRL-C's):
@@ -305,54 +305,54 @@
      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|
+	     |str printedException|
 
-             ex signal == Signal noHandlerSignal ifTrue:[
-                printedException := ex parameter.
-             ] ifFalse:[
-                printedException := ex
-             ].
+	     ex signal == Signal noHandlerSignal 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.
+	     "/ 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 proceed
-             ].
+	     printedException signal == Object userInterruptSignal ifTrue:[
+		  (self confirm:'abort current action ?') ifTrue:[
+		      AbortSignal raise
+		  ].
+		  ex proceed
+	     ].
 
-             "/
-             "/ dump it to 'errorTrace.stx'
-             "/
-             str := 'errorTrace.stx' asFilename appendingWriteStream.
+	     "/
+	     "/ dump it to 'errorTrace.stx'
+	     "/
+	     str := 'errorTrace.stx' asFilename appendingWriteStream.
 
-             str nextPutLine:('******************************* '
-                              , AbsoluteTime now printString
-                              , ' *******************************').
-             str cr.
+	     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 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.
+	     printedException suspendedContext fullPrintAllOn:str.
+	     str cr.
+	     str cr.
+	     str close.
 
-             self warn:printedException errorString.
-             AbortSignal raise 
+	     self warn:printedException errorString.
+	     AbortSignal raise 
       ]
 
     "test with (try a few halts or CTRL-C's):
@@ -375,78 +375,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|
+	    |str printedException doMail emergencyMailReceiver pipe|
 
-            ex signal == Signal noHandlerSignal ifTrue:[
-               printedException := ex parameter.
-            ] ifFalse:[
-               printedException := ex
-            ].
+	    ex signal == Signal noHandlerSignal 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.
+	     "/ 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 proceed
-             ].
+	     printedException signal == Object userInterruptSignal ifTrue:[
+		  (self confirm:'abort current action ?') ifTrue:[
+		      AbortSignal raise
+		  ].
+		  ex proceed
+	     ].
 
-            "/ somehow get the name of the guy to receive the mail
-            "/ you have to implement that yourself.
+	    "/ somehow get the name of the guy to receive the mail
+	    "/ you have to implement that yourself.
 
-            "/ emergencyMailReceiver := OneOfYourClass getEmergencyMailReceiver.
-            emergencyMailReceiver := OperatingSystem getLoginName.
+	    "/ 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.
+	    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:('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.
+		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.
+		printedException suspendedContext fullPrintAllOn:str.
+		str cr;cr.
 
-                str close.
+		str close.
 
-                pipe := PipeStream 
-                            writingTo:'mail ', emergencyMailReceiver.
-                pipe notNil ifTrue:[
-                    pipe nextPutLine:'Subject: automatic error report'.
-                    pipe nextPutAll:str contents.
-                    pipe cr.
-                    pipe 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 
+	     AbortSignal raise 
       ]
 
     "test with (try a few halts or CTRL-C's):
@@ -628,14 +628,14 @@
 
     |con block noHandlerSignal any msg sel conArg1
      theSignal c ex1 activeHandlers inHandler rejected
-     lastHandler h|
+     lastHandler h raiseReceiver|
 
     con := thisContext sender.  "the raise/raiseRequest-context"
     con := con sender.          "the signal raise context"
 
     theSignal := con receiver.
     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.
@@ -651,128 +651,108 @@
     "/ the code below collects active handlers ...
 
     [c notNil] whileTrue:[
-        sel := c selector.
-        sel == #doRaise ifTrue:[
-            ex1 := c receiver.
-            ex1 species == self species ifTrue:[
-                c := c sender.
-                (c notNil and:[c receiver == ex1]) ifTrue:[
-                    c := c sender.
-                    c notNil ifTrue:[
-                        "/ the common case (really ?) first
-                        (c receiver == theSignal) ifTrue:[
-                            (c selector startsWith:'raise') ifTrue:[
-                                h := ex1 handlerContext.
-                                h notNil ifTrue:[
-                                    activeHandlers isNil ifTrue:[
-                                        activeHandlers := OrderedCollection new
-                                    ].
-                            
-                                    lastHandler := h.
-                                    activeHandlers add:lastHandler.
-                                    inHandler := true.
-                                    c := lastHandler.
-"/ 'skip over active handler: ' print. c displayString printCR.
-                                ]
-                            ]
-                        ] ifFalse:[
-                            c receiver isSignal ifTrue:[
-                                (c selector startsWith:'raise') ifTrue:[
-                                    h := ex1 handlerContext.
-                                    h notNil ifTrue:[
-                                        (h receiver accepts:theSignal) ifTrue:[
+	c := c findContextWithSelector:#doRaise or:nil.
+	c notNil ifTrue:[
+
+	    ex1 := c receiver.
+	    ((ex1 class == self class)
+	    or:[ex1 species == self species]) ifTrue:[
+		c := c sender.
+		(c notNil and:[c receiver == ex1]) ifTrue:[
+		    c := c sender.
+		    c notNil ifTrue:[
+
+			"/ the common case (really ?) first
+			((raiseReceiver := c receiver) == theSignal) ifTrue:[
+			    (c selector startsWith:'raise') ifTrue:[
+				h := ex1 handlerContext.
+				h notNil ifTrue:[
+				    activeHandlers isNil ifTrue:[
+					activeHandlers := OrderedCollection new
+				    ].
 
-                                        activeHandlers isNil ifTrue:[
-                                            activeHandlers := OrderedCollection new
-                                        ].
-                                        lastHandler := h.
-                                        activeHandlers add:lastHandler.
-                                        inHandler := true.
-                                        c := lastHandler.
-"/ 'skip2 over active handler: ' print. h displayString printCR.
-                                        ]
-                                    ]    
-                                ]    
-                            ]    
-                        ]
-                    ]
-                ]
-            ].
-        ].
-        c := c sender.
+				    lastHandler := h.
+				    activeHandlers add:lastHandler.
+				    inHandler := true.
+				    c := lastHandler.
+				]
+			    ]
+			] ifFalse:[
+			    raiseReceiver isSignal ifTrue:[
+				(c selector startsWith:'raise') ifTrue:[
+				    h := ex1 handlerContext.
+				    h notNil ifTrue:[
+					(h receiver accepts:theSignal) ifTrue:[
+
+					    activeHandlers isNil ifTrue:[
+						activeHandlers := OrderedCollection new
+					    ].
+					    lastHandler := h.
+					    activeHandlers add:lastHandler.
+					    inHandler := true.
+					    c := lastHandler.
+					]
+				    ]    
+				]    
+			    ]    
+			]
+		    ]
+		]
+	    ].
+	    c := c sender.
+	]
     ].
 
+    "/ now, start searching for a handler,
+    "/ start search above the last active handler
+
     lastHandler notNil ifTrue:[
-"/        'skip over last active handler: ' print. lastHandler displayString printCR.
-        con := lastHandler sender.
+	con := lastHandler sender.
     ].
 
     any := false.
     [con notNil] whileTrue:[
-        con isBlockContext ifFalse:[
+	con isBlockContext ifFalse:[
+
+	    sel := con selector.
 
-            "/ new behavior:
-            (activeHandlers notNil
-             and:[activeHandlers includesIdentical:con]) ifTrue:[
-                'skip activeHandler: ' print. con displayString printCR.
+	    ((sel == #'handle:do:') 
+	    or:[((sel == #'handle:from:do:') 
+		and:[(con argAt:2) == originator])]) ifTrue:[
 
-            ] ifFalse:[
-                sel := con selector.
+		"/ new behavior:
+		(activeHandlers notNil
+		 and:[activeHandlers includesIdentical:con]) ifTrue:[
+		    'skip activeHandler: ' print. con displayString printCR.
 
-                ((sel == #'handle:do:') 
-                or:[((sel == #'handle:from:do:') 
-                    and:[(con argAt:2) == originator])]) 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"
+		] ifFalse:[
+		    "
+		     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"
 
-                        conArg1 := con argAt:1.
+			conArg1 := con argAt:1.
 
-                        handlerContext := con.
-                        any := true.
+			handlerContext := con.
+			any := true.
 
-                        self doCallHandler:conArg1.
+			self doCallHandler:conArg1.
 
-                        "if the handler rejects, we arrive here"
-                        "continue search for another handler"
-                        rejected := true.
-                    ].
-                ]
-            ]
-        ].
-        con := con sender
+			"if the handler rejects, we arrive here"
+			"continue search for another handler"
+			rejected := true.
+		    ].
+		]
+	    ]
+	].
+	con := con sender
     ].
 
     activeHandlers := nil.
 
-"/    (inHandler "and:[rejected ~~ true]") ifTrue:[
-"/        "
-"/         mhmh - an error while in a handler
-"/         here, we do not fall back to the noHandlerSignal/staticHandler
-"/         (makes debugging easier)
-"/
-"/         Should we ?
-"/        "
-"/        ((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 , ')')
-"/    ].
-
     "
      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).
@@ -781,52 +761,52 @@
      try per signal handler
     "
     (block := signal handlerBlock) isNil ifTrue:[
-        "/
-        "/ if its a querySignal, ignore it
-        "/
-        signal isQuerySignal ifTrue:[^ nil].
+	"/
+	"/ if its a querySignal, ignore it
+	"/
+	signal isQuerySignal ifTrue:[^ nil].
 
-        "/
-        "/ if it is not the NoHandlerSignal, raise it ...
-        "/ passing the receiver as parameter.
-        "/
-        signal ~~ (noHandlerSignal := Signal noHandlerSignal) ifTrue:[
-            noHandlerSignal notNil ifTrue:[
-                any ifTrue:[
-                    msg := 'unhandled (rejected)'
-                ] ifFalse:[
-                    msg := 'unhandled'
-                ].
-                msg := msg , ' exception: (' , errorString , ')'.
-                ^ noHandlerSignal 
-                      raiseRequestWith:self 
-                           errorString:msg
-                                    in:self suspendedContext
-            ].
-            "/
-            "/ mhmh - an error during early startup; noHandlerSignal is
-            "/ not yet defined.
-            "/
-            ^ MiniDebugger enterWithMessage:errorString
-        ].
+	"/
+	"/ if it is not the NoHandlerSignal, raise it ...
+	"/ passing the receiver as parameter.
+	"/
+	signal ~~ (noHandlerSignal := Signal noHandlerSignal) ifTrue:[
+	    noHandlerSignal notNil ifTrue:[
+		any ifTrue:[
+		    msg := 'unhandled (rejected)'
+		] ifFalse:[
+		    msg := 'unhandled'
+		].
+		msg := msg , ' exception: (' , errorString , ')'.
+		^ noHandlerSignal 
+		      raiseRequestWith:self 
+			   errorString:msg
+				    in:self suspendedContext
+	    ].
+	    "/
+	    "/ 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
-            ].
-        ].
+	"
+	 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.
@@ -838,7 +818,7 @@
 raise
     "actually raise a non-proceedable exception.
      CAVEAT:
-         For now, in ST/X all signals are proceedable."
+	 For now, in ST/X all signals are proceedable."
 
     resumeBlock := [:value | ^ value].
     ^ self doRaise
@@ -871,6 +851,6 @@
 !Exception class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.45 1997-01-18 18:37:26 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.46 1997-01-20 11:52:22 cg Exp $'
 ! !
 Exception initialize!