stc doesn't grok lowercase class instvars
authorStefan Vogel <sv@exept.de>
Sat, 24 Jul 1999 12:53:55 +0200
changeset 4449 c8e195e21aab
parent 4448 3cb121baa9f7
child 4450 5a8cc3958be2
stc doesn't grok lowercase class instvars
Exception.st
--- a/Exception.st	Sat Jul 24 12:53:11 1999 +0200
+++ b/Exception.st	Sat Jul 24 12:53:55 1999 +0200
@@ -52,22 +52,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
@@ -75,22 +75,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.
@@ -98,31 +98,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
 "
 !
 
@@ -141,52 +141,52 @@
     block and pass it to the #emergencyHandler: method.
 
     BTW: the Launchers 'source & debugger' settings menu allows you
-         to install either a default or the notifying handler.
+	 to install either a default or the notifying handler.
 
 
     A handler which shows a box, then aborts - (no more debuggers):
-                                                                [exBegin]
-        Exception emergencyHandler:(Exception abortingEmergencyHandler)
-                                                                [exEnd]
+								[exBegin]
+	Exception emergencyHandler:(Exception abortingEmergencyHandler)
+								[exEnd]
 
 
     A handler which aborts - (no box, no debugger):
-                                                                [exBegin]
-        Exception emergencyHandler:[:ex | AbortSignal raise]
-                                                                [exEnd]
+								[exBegin]
+	Exception emergencyHandler:[:ex | AbortSignal raise]
+								[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 (switch back to the regular handler, which enters the debugger):
-                                                                [exBegin]
-        Exception emergencyHandler:nil
-                                                                [exEnd]
+								[exBegin]
+	Exception emergencyHandler:nil
+								[exEnd]
 
 
     A handler which shows a warnBox and asks for debugging:
-                                                                [exBegin]
-        Exception emergencyHandler:(Exception notifyingEmergencyHandler)
-                                                                [exEnd]
+								[exBegin]
+	Exception emergencyHandler:(Exception notifyingEmergencyHandler)
+								[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]
 "
 ! !
 
@@ -245,14 +245,14 @@
      the parents notifier string"
 
     NotifierString isNil ifTrue:[
-        ^ self parent errorString
+	^ self parent errorString
     ] ifFalse:[
-        (NotifierString size > 0 
-         and:[NotifierString first == (Character space)]) ifTrue:[
-            ^ self parent errorString, NotifierString
-        ] ifFalse:[
-            ^ NotifierString
-        ].
+	(NotifierString size > 0 
+	 and:[NotifierString first == (Character space)]) ifTrue:[
+	    ^ self parent errorString, NotifierString
+	] ifFalse:[
+	    ^ NotifierString
+	].
     ]
 
     "
@@ -272,21 +272,21 @@
     |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
+	    ]
+	].
     ].
     ^ t.
 
@@ -327,8 +327,8 @@
 
     s := aSignal.
     [s notNil] whileTrue:[
-        self == s ifTrue:[^ true].
-        s := s parent
+	self == s ifTrue:[^ true].
+	s := s parent
     ].
     ^ false
 
@@ -365,20 +365,20 @@
 
     con := aContext.
     [con notNil] whileTrue:[
-        con := con findNextContextWithSelector:#'handle:do:' or:#'handle:from:do:' or:nil.
-        con notNil ifTrue:[
-            "
-             is this is a #handle:do: or a #handle:from:do: context
-             with self in it ?
-            "
+	con := con findNextContextWithSelector:#'handle:do:' or:#'handle:from:do:' or:nil.
+	con notNil ifTrue:[
+	    "
+	     is this is a #handle:do: or a #handle:from:do: context
+	     with self in it ?
+	    "
 
-            ((r := con receiver) notNil
-            and:[r accepts:self]) ifTrue:[
-                "found a handler context"
+	    ((r := con receiver) notNil
+	    and:[r accepts:self]) ifTrue:[
+		"found a handler context"
 
-                ^ true
-            ]
-        ]
+		^ true
+	    ]
+	]
     ].
     ^ false
 
@@ -419,10 +419,10 @@
      existing Signals."
 
     self == Exception ifTrue:[
-        ^ nil
+	^ nil
     ].
 
-    ^ superclass
+    ^ self superclass
 
     "Created: / 23.7.1999 / 14:01:29 / stefan"
     "Modified: / 23.7.1999 / 16:15:38 / stefan"
@@ -477,11 +477,11 @@
      allowing a raise to mimicri the exception happened somewhere else."
 
     ^ (self newException   
-              signal:self
-              parameter:nil 
-              errorString:aString
-              suspendedContext:aContext
-              originator:nil) raise.
+	      signal:self
+	      parameter:nil 
+	      errorString:aString
+	      suspendedContext:aContext
+	      originator:nil) raise.
 
     "Modified: / 26.7.1996 / 16:42:47 / cg"
     "Modified: / 12.3.1998 / 15:43:43 / stefan"
@@ -550,8 +550,8 @@
      The argument, aString is used as errorString."
 
     ^ (self newException 
-              parameter:aParameter; 
-              errorString:aString
+	      parameter:aParameter; 
+	      errorString:aString
       ) raiseRequest
 
     "Modified: / 9.5.1996 / 15:13:35 / cg"
@@ -566,9 +566,9 @@
      allowing a raise to mimicri the exception happened somewhere else."
 
     ^ (self newException 
-              parameter:aParameter; 
-              errorString:aString;
-              suspendedContext:aContext) raiseRequest
+	      parameter:aParameter; 
+	      errorString:aString;
+	      suspendedContext:aContext) raiseRequest
 
     "Modified: / 26.7.1996 / 16:29:27 / cg"
     "Modified: / 12.3.1998 / 15:18:34 / stefan"
@@ -582,8 +582,8 @@
      allowing a raise to mimicri the exception happened somewhere else."
 
     ^ (self newException 
-              parameter:aParameter; 
-              suspendedContext:aContext) raiseRequest.
+	      parameter:aParameter; 
+	      suspendedContext:aContext) raiseRequest.
 
     "Modified: / 26.7.1996 / 16:29:33 / cg"
     "Modified: / 12.3.1998 / 15:18:55 / stefan"
@@ -607,8 +607,8 @@
      as exception parameter."
 
     ^ (self newException 
-              parameter:aParameter;
-              errorString:aString) raise.
+	      parameter:aParameter;
+	      errorString:aString) raise.
 
     "Modified: / 9.5.1996 / 15:14:32 / cg"
     "Modified: / 12.3.1998 / 15:19:40 / stefan"
@@ -624,9 +624,9 @@
 
 
     ^ (self newException 
-              parameter:aParameter; 
-              errorString:aString;
-              suspendedContext:aContext) raise.
+	      parameter:aParameter; 
+	      errorString:aString;
+	      suspendedContext:aContext) raise.
 
     "Modified: / 26.7.1996 / 16:29:42 / cg"
     "Modified: / 12.3.1998 / 15:20:12 / stefan"
@@ -638,7 +638,7 @@
      The argument, aParameter is passed as parameter."
 
     ^ (self newException parameter:aParameter;
-                         suspendedContext:aContext) raise.
+			 suspendedContext:aContext) raise.
 
     "Modified: / 9.5.1996 / 15:14:24 / cg"
     "Modified: / 12.3.1998 / 15:34:51 / stefan"
@@ -662,7 +662,7 @@
 
       "
        Object messageNotUnderstoodSignal catch:[
-          123 size open   
+	  123 size open   
        ]
       "
 
@@ -682,10 +682,10 @@
 
       "
        Object messageNotUnderstoodSignal handle:[:ex |
-          'oops' printNL.
-          ex return
+	  'oops' printNL.
+	  ex return
        ] do:[
-          123 size open   
+	  123 size open   
        ]
       "
 
@@ -694,10 +694,10 @@
 
        num := 0.
        Number divisionByZeroSignal handle:[:ex |
-          'oops' printNL.
-          ex return
+	  'oops' printNL.
+	  ex return
        ] do:[
-          123 / num   
+	  123 / num   
        ]
       "
 
@@ -725,17 +725,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
+		]
       "
 
     "Modified: / 2.3.1998 / 14:28:05 / stefan"
@@ -754,7 +754,7 @@
 
       "
        Object messageNotUnderstoodSignal ignoreIn:[
-          123 size open   
+	  123 size open   
        ]
       "
 
@@ -777,8 +777,8 @@
      setting the parent of the new signal to the receiver."
 
     ^ (Signal basicNew) mayProceed:proceed;
-                    notifierString:NotifierString;
-                            parent:self
+		    notifierString:NotifierString;
+			    parent:self
 
     "Created: / 23.7.1999 / 20:12:43 / stefan"
 ! !
@@ -886,58 +886,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|
+	     |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.
 
-             "/ send a line to stdErr
+	     "/ send a line to stdErr
 
-             ('[warning]: ignored error: ' , printedException errorString) errorPrintCR.
-             ('[warning]:    error information appended to ''errorTrace.stx''') errorPrintCR.
+	     ('[warning]: ignored error: ' , printedException errorString) errorPrintCR.
+	     ('[warning]:    error information appended to ''errorTrace.stx''') errorPrintCR.
 
-             AbortSignal raise 
+	     AbortSignal raise 
       ]
 
     "test with (try a few halts or CTRL-C's):
@@ -1195,52 +1195,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:[
-                handlerContext notNil ifTrue:[
-                    msg := 'unhandled (rejected)'
-                ] ifFalse:[
-                    msg := 'unhandled'
-                ].
-                msg := msg , ' exception: (' , self errorString , ')'.
-                ^ noHandlerSignal 
-                      raiseRequestWith:self 
-                           errorString:msg
-                                    in:self suspendedContext
-            ].
-            "/
-            "/ mhmh - an error during early startup; noHandlerSignal is
-            "/ not yet defined.
-            "/
-            ^ MiniDebugger enterWithMessage:self errorString
-        ].
+	"/
+	"/ if it is not the NoHandlerSignal, raise it ...
+	"/ passing the receiver as parameter.
+	"/
+	signal ~~ (noHandlerSignal := Signal noHandlerSignal) ifTrue:[
+	    noHandlerSignal notNil ifTrue:[
+		handlerContext notNil ifTrue:[
+		    msg := 'unhandled (rejected)'
+		] ifFalse:[
+		    msg := 'unhandled'
+		].
+		msg := msg , ' exception: (' , self errorString , ')'.
+		^ noHandlerSignal 
+		      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
-            ].
-        ].
+	"
+	 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"
     ^ block value:self.
@@ -1268,26 +1268,26 @@
     |b|
 
     resumeBlock isNil ifTrue:[
-        "signal raiser does not want us to proceed"
-        Signal proceedErrorSignal raiseWith:self.
+	"signal raiser does not want us to proceed"
+	Signal proceedErrorSignal raiseWith:self.
     ] ifFalse:[
-        proceedable ifFalse:[
-            ('WARNING: signal <', signal printString, '> has been raised nonproceedable') errorPrintCR.
-            ('         by: ', suspendedContext printString) errorPrintCR.
-            ('         ', thisContext sender printString , ' tries to proceed.') errorPrintCR.
-            ('         This will be an error in future ST/X versions.') errorPrintCR.
-        ].
-        b := resumeBlock.
-        resumeBlock := rejectBlock := handlerContext := suspendedContext := nil.
-        b value:nil
+	proceedable ifFalse:[
+	    ('WARNING: signal <', signal printString, '> has been raised nonproceedable') errorPrintCR.
+	    ('         by: ', suspendedContext printString) errorPrintCR.
+	    ('         ', thisContext sender printString , ' tries to proceed.') errorPrintCR.
+	    ('         This will be an error in future ST/X versions.') errorPrintCR.
+	].
+	b := resumeBlock.
+	resumeBlock := rejectBlock := handlerContext := suspendedContext := nil.
+	b value:nil
     ]
 
     "
-        Object errorSignal handle:[:ex|
-            ex proceed
-        ] do:[
-            Object errorSignal raise
-        ].
+	Object errorSignal handle:[:ex|
+	    ex proceed
+	] do:[
+	    Object errorSignal raise
+	].
     "
 
     "Modified: / 27.3.1997 / 16:44:39 / cg"
@@ -1300,18 +1300,18 @@
     |b|
 
     resumeBlock isNil ifTrue:[
-        "signal raiser does not want us to proceed"
-        Signal proceedErrorSignal raiseWith:self.
+	"signal raiser does not want us to proceed"
+	Signal proceedErrorSignal raiseWith:self.
     ] ifFalse:[
-        proceedable ifFalse:[
-            ('WARNING: signal <', signal printString, '> has been raised nonproceedable') errorPrintCR.
-            ('         by: ', suspendedContext printString) errorPrintCR.
-            ('         ', thisContext sender printString , ' tries to proceed.') errorPrintCR.
-            ('         This will be an error in future ST/X versions.') errorPrintCR.
-        ].
-        b := resumeBlock.
-        resumeBlock := rejectBlock := handlerContext := suspendedContext := nil.
-        b value:value
+	proceedable ifFalse:[
+	    ('WARNING: signal <', signal printString, '> has been raised nonproceedable') errorPrintCR.
+	    ('         by: ', suspendedContext printString) errorPrintCR.
+	    ('         ', thisContext sender printString , ' tries to proceed.') errorPrintCR.
+	    ('         This will be an error in future ST/X versions.') errorPrintCR.
+	].
+	b := resumeBlock.
+	resumeBlock := rejectBlock := handlerContext := suspendedContext := nil.
+	b value:value
     ]
 
     "Modified: / 27.3.1997 / 16:45:57 / cg"
@@ -1346,10 +1346,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
@@ -1439,7 +1439,7 @@
      ATTENTION: the code below depends on being called by #raise or
      #raiseRequest for proper operation (it skips the sending context)."
 
-    |theContext block noHandlerSignal conArg1
+    |theContext conArg1
      theSignal c ex1 activeHandlers inHandler 
      lastHandler h r firstHandler|
 
@@ -1447,19 +1447,19 @@
     "/ 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.
 
     inHandler := false.
     c := thisContext sender sender.    "the raise/raiseRequest-context"
-                                       "the signal raise context"
+				       "the signal raise context"
 
     "/ since the exceptionHandler is evaluated onTop of the
     "/ contextChain, we must skip active handlers before searching.
@@ -1475,40 +1475,40 @@
     firstHandler := nil.
 
     [c notNil] whileTrue:[
-        firstHandler isNil ifTrue:[
-            c := c findNextContextWithSelector:#doRaise or:#'handle:do:' or:#'handle:from:do:'.
-        ] ifFalse:[
-            c := c findNextContextWithSelector:#doRaise or:nil or:nil.
-        ].
-        c notNil ifTrue:[
-            (c selector == #doRaise) ifTrue:[
+	firstHandler isNil ifTrue:[
+	    c := c findNextContextWithSelector:#doRaise or:#'handle:do:' or:#'handle:from:do:'.
+	] ifFalse:[
+	    c := c findNextContextWithSelector:#doRaise or:nil or:nil.
+	].
+	c notNil ifTrue:[
+	    (c selector == #doRaise) ifTrue:[
 
-                ex1 := c receiver.
+		ex1 := c receiver.
 
-                ((ex1 class == self class)
-                or:[ex1 species == self species]) ifTrue:[
-                    (ex1 signal == theSignal) ifTrue:[
-                        h := ex1 handlerContext.
-                        h notNil ifTrue:[
-                            r := h receiver.
-                            (r notNil and:[r accepts:theSignal]) ifTrue:[
-                                activeHandlers isNil ifTrue:[
-                                    activeHandlers := OrderedCollection new
-                                ].
+		((ex1 class == self class)
+		or:[ex1 species == self species]) ifTrue:[
+		    (ex1 signal == theSignal) ifTrue:[
+			h := ex1 handlerContext.
+			h notNil ifTrue:[
+			    r := h receiver.
+			    (r notNil and:[r accepts:theSignal]) ifTrue:[
+				activeHandlers isNil ifTrue:[
+				    activeHandlers := OrderedCollection new
+				].
 
-                                lastHandler := h.
-                                activeHandlers add:lastHandler.
-                                inHandler := true.
-                                c := lastHandler.
-                            ]
-                        ]
-                    ]
-                ]
-            ] ifFalse:[
-                "/ must be a #handle:do context ...
-                firstHandler := c.
-            ]
-        ]
+				lastHandler := h.
+				activeHandlers add:lastHandler.
+				inHandler := true.
+				c := lastHandler.
+			    ]
+			]
+		    ]
+		]
+	    ] ifFalse:[
+		"/ must be a #handle:do context ...
+		firstHandler := c.
+	    ]
+	]
     ].
 
     "/ now, start searching for a handler,
@@ -1522,39 +1522,39 @@
 "/        theContext := lastHandler.
 "/        theContext := lastHandler findNextContextWithSelector:#'handle:do:' or:#'handle:from:do:' or:nil.
 "/    ] ifFalse:[
-        theContext := firstHandler.
+	theContext := firstHandler.
 "/    ].
 
     [theContext notNil] whileTrue:[
-        (theContext selector == #'handle:do:'
-        or:[(theContext argAt:2) == originator]) 
-        ifTrue:[
-            (activeHandlers notNil
-             and:[activeHandlers includesIdentical:theContext]) ifTrue:[
+	(theContext selector == #'handle:do:'
+	or:[(theContext argAt:2) == originator]) 
+	ifTrue:[
+	    (activeHandlers notNil
+	     and:[activeHandlers includesIdentical:theContext]) ifTrue:[
 "/                'skip activeHandler: ' print. theContext displayString printCR.
 
-            ] ifFalse:[
-                "
-                 if this is the Signal>>handle:do: context
-                 or a SignalSet>>handle:do: context with self in it,
-                 call the handler
-                "
-                r := theContext receiver.
-                (r notNil and:[r 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
+		"
+		r := theContext receiver.
+		(r notNil and:[r accepts:signal]) ifTrue:[
+		    "call the handler"
 
-                    conArg1 := theContext argAt:1.
+		    conArg1 := theContext argAt:1.
 
-                    handlerContext := theContext.
+		    handlerContext := theContext.
 
-                    self doCallHandler:conArg1.
+		    self doCallHandler:conArg1.
 
-                    "/ if the handler rejects, we arrive here
-                    "/ continue search for another handler
-                ].
-            ]
-        ].
-        theContext := theContext findNextContextWithSelector:#'handle:do:' or:#'handle:from:do:' or:nil.
+		    "/ if the handler rejects, we arrive here
+		    "/ continue search for another handler
+		].
+	    ]
+	].
+	theContext := theContext findNextContextWithSelector:#'handle:do:' or:#'handle:from:do:' or:nil.
     ].
 
     activeHandlers := nil.
@@ -1583,12 +1583,12 @@
      In the next release, this will raise a signal, so fix your code"
 
     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
     ].
 
     "/ remove the next 2 lines to make proceeding from non-proceedable signals an error.
@@ -1605,17 +1605,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
-        Signal wrongProceedabilitySignal raiseRequestWith:signal in:suspendedContext
+	"/ proceeding from wrongProceedabilitySignal grants the raiseRequest
+	Signal wrongProceedabilitySignal raiseRequestWith:signal in:suspendedContext
     ].
     proceedable := true.
     resumeBlock := [:value | ^ value].
@@ -1651,6 +1651,6 @@
 !Exception class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.69 1999-07-23 18:13:00 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.70 1999-07-24 10:53:55 stefan Exp $'
 ! !
 Exception initialize!