GenericException.st
changeset 4527 2ddbe34bab87
parent 4521 946e1a02b158
child 4533 f386b6e072a2
--- a/GenericException.st	Wed Aug 04 16:13:11 1999 +0200
+++ b/GenericException.st	Wed Aug 04 16:13:32 1999 +0200
@@ -27,34 +27,6 @@
 "
 !
 
-Error subclass:#WrongProceedabilityError
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:GenericException
-!
-
-Error subclass:#NoHandlerError
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:GenericException
-!
-
-Warning subclass:#ProceedError
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:GenericException
-!
-
-Error subclass:#RecursiveExceptionError
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:GenericException
-!
-
 !GenericException class methodsFor:'documentation'!
 
 copyright
@@ -377,12 +349,13 @@
 
     |s|
 
+    self == aSignal ifTrue:[^ true].
     aSignal isQuerySignal ifTrue:[^ false].
 
     s := aSignal.
     [s notNil] whileTrue:[
-	self == s ifTrue:[^ true].
-	s := s parent
+        self == s ifTrue:[^ true].
+        s := s parent
     ].
     ^ false
 
@@ -878,52 +851,28 @@
 !GenericException class methodsFor:'defaults'!
 
 emergencyHandler
-    "return the handler used for unhandled exceptions.
 
-     If no EmergencyHandler has been set, a handler which enters the 
-     debugger is returned.
-     The debugger is opened by asking the signal for a debug action,
-     this allows to provide other debuggers in specialized (subclass-instances)
-     of Signal (if that is ever needed)"
-
-    "
-     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
-
-    "Modified: 15.1.1997 / 20:50:37 / cg"
+    ^ NoHandlerError emergencyHandler.
 !
 
 emergencyHandler:aOneArgBlock
     "set the handler used for unhandled exceptions.
      The default (a nil-handler) leads to a debugger to be shown."
 
-    EmergencyHandler := aOneArgBlock
+    ^ NoHandlerError emergencyHandler:aOneArgBlock.
 
     "ST-80 behavior of first showing a notifier:
      (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:
@@ -931,231 +880,19 @@
       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"
-! !
 
-!GenericException class methodsFor:'useful handlers'!
-
-abortingEmergencyHandler
-    "return a block (usable as an emergency handler), 
-     which aborts after showing a warnBox.
-     This is useful for endUser applications"
-
-    ^ [:ex | self warn:'Error: ' , ex errorString.
-	     AbortSignal raise 
-      ]
-
-    "test with (try a few halts or CTRL-C's):
-     Exception emergencyHandler:(Exception abortingEmergencyHandler)
-    "
-
-    "back with:
-     Exception emergencyHandler:(Exception notifyingEmergencyHandler)
-     Exception emergencyHandler:nil
-    "
-
-    "Created: 15.1.1997 / 20:13:06 / cg"
-    "Modified: 15.1.1997 / 20:15:02 / cg"
-!
-
-dumpingEmergencyHandler
-    "return a block (usable as an emergency handler), 
-     which dumps the stackBacktrace to a trace file and
-     aborts after showing a warnBox.
-     This is useful, for endUser application, which are still being
-     debugged (i.e. the programmers may have a look at the traceFile
-     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)"
-
-    ^ [: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.
-        
-	     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):
-     Exception emergencyHandler:(Exception dumpingEmergencyHandler)
-    "
-
-    "back with:
-     Exception emergencyHandler:(Exception notifyingEmergencyHandler)
-     Exception emergencyHandler:nil
-    "
-
-    "Created: / 15.1.1997 / 20:14:52 / cg"
-    "Modified: / 24.1.1997 / 20:36:21 / cg"
-    "Modified: / 4.8.1999 / 08:11:20 / stefan"
-!
-
-mailingEmergencyHandler
-    "return a block (usable as an emergency handler), 
-     which shows a warnBox and optionally mails a stackBacktrace to a maintainer.
-     This is useful, for endUser application, which are still being
-     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."
-
-    ^ [: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 
-      ]
-
-    "test with (try a few halts or CTRL-C's):
-     Exception emergencyHandler:(Exception mailingEmergencyHandler)
-    "
-
-    "back with:
-     Exception emergencyHandler:(Exception notifyingEmergencyHandler)
-     Exception emergencyHandler:nil
-    "
-
-    "Created: / 15.1.1997 / 20:14:52 / cg"
-    "Modified: / 15.1.1997 / 21:10:28 / cg"
-    "Modified: / 4.8.1999 / 08:11:26 / stefan"
-!
-
-notifyingEmergencyHandler
-    "return a block (usable as an emergency handler for exceptions), 
-     which does errorNotification before going into the debugger."
-
-    ^ [:ex | nil errorNotify:ex errorString from:ex suspendedContext ]
-
-    "test with (try a few halts or CTRL-C's):
-     Exception emergencyHandler:(Exception notifyingEmergencyHandler)
-    "
-
-    "back with:
-     Exception emergencyHandler:nil
-    "
-
-    "Modified: 15.1.1997 / 20:15:12 / cg"
 ! !
 
 !GenericException methodsFor:'accessing'!
@@ -1294,15 +1031,13 @@
 
 !GenericException methodsFor:'default actions'!
 
-action
+defaultAction
     "perform a action for the exception if it hasn't been catched
      We arrive here, if either no handler was found, or none of the
      handlers did a return (i.e. every handler rejected).
 
      The default is to evaluate the signal's handlerBlock or the
      per process handler (if its the noHandlerSignal).
-     Finally fall back to Exceptions emergencyHandler, which is always
-     available and enters the debugger.
      Subclasses may redefine this."
 
     |block msg|
@@ -1311,52 +1046,28 @@
      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 ~~ 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 it is not the NoHandlerSignal, raise it ...
+        "/ passing the receiver as parameter.
+        "/
+        signal ~~ NoHandlerError ifTrue:[
+            handlerContext notNil ifTrue:[
+                msg := 'unhandled (rejected)'
+            ] ifFalse:[
+                msg := 'unhandled'
+            ].
+            msg := msg , ' exception: (' , self errorString , ')'.
+            ^ NoHandlerError 
+                  raiseRequestWith:self 
+                  errorString:msg
+                  in:self suspendedContext
+        ].
+        ^ MiniDebugger enterWithMessage:self errorString
     ].
 
     "... and call it"
@@ -1612,7 +1323,7 @@
     <exception: #raise>
 
     "/ thisContext markForRaise. -- same as above pragma
-    ^ self action
+    ^ self defaultAction
 !
 
 doCallHandler:aHandlerBlock
@@ -1857,186 +1568,9 @@
     originator := origin.
 ! !
 
-!GenericException::WrongProceedabilityError class methodsFor:'documentation'!
-
-documentation
-"    
-    WrongProceedabilityError is raised to indicate that someone tries
-    to raise a nonproceedable exception proceedable.
-
-    The parameter is the unproceedable signal.
-"
-
-! !
-
-!GenericException::WrongProceedabilityError class methodsFor:'initialization'!
-
-initialize
-
-    NotifierString := 'attempt to raise a nonproceedable signal proceedable'.
-
-    "
-     self initialize
-    "
-
-    "Created: / 4.8.1999 / 08:02:32 / stefan"
-    "Modified: / 4.8.1999 / 08:02:54 / stefan"
-! !
-
-!GenericException::WrongProceedabilityError class methodsFor:'queries'!
-
-mayProceed
-
-    ^ true
-
-    "Created: / 4.8.1999 / 08:02:32 / stefan"
-! !
-
-!GenericException::NoHandlerError class methodsFor:'documentation'!
-
-documentation
-"
-    NoHandlerError is raised, if there is no exception handler
-    or default action for an exception.
-
-    The parameter is the unhandled exception.
-"
-
-! !
-
-!GenericException::NoHandlerError class methodsFor:'initialization'!
-
-initialize
-
-    NotifierString := 'unhandled exception'.
-
-    "
-     self initialize
-    "
-
-    "Created: / 4.8.1999 / 08:07:30 / stefan"
-    "Modified: / 4.8.1999 / 08:08:05 / stefan"
-! !
-
-!GenericException::NoHandlerError class methodsFor:'queries'!
-
-mayProceed
-
-    ^ true
-
-    "Created: / 4.8.1999 / 08:07:30 / stefan"
-! !
-
-!GenericException::ProceedError class methodsFor:'documentation'!
-
-documentation
-"
-    ProceedError is raised to indicate that a handler tried to
-    proceed an exception marked as nonproceedable.
-
-    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.
-"
-
-! !
-
-!GenericException::ProceedError class methodsFor:'initialization'!
-
-initialize
-
-    NotifierString := 'handler tried to proceed from nonproceedable exception'.
-
-    "
-     self initialize
-    "
-
-    "Created: / 4.8.1999 / 07:36:14 / stefan"
-! !
-
-!GenericException::ProceedError class methodsFor:'queries'!
-
-mayProceed
-
-    ^ true
-
-    "Created: / 4.8.1999 / 07:35:07 / stefan"
-! !
-
-!GenericException::ProceedError methodsFor:'handler actions'!
-
-action
-    "make proceeding from a non-proceedable raise a warning for now.
-     This will change in future revisions"
-
-    ('WARNING: signal <', parameter signal printString, '> has been raised nonproceedable') errorPrintCR.
-    ('         by: ', parameter suspendedContext printString) errorPrintCR.
-    ('         ', suspendedContext printString , ' tries to proceed.') errorPrintCR.
-    ('         This will be an error in future ST/X versions.') errorPrintCR.
-
-    self proceedWith:nil.
-
-    "
-      Object errorSignal handle:[:ex|
-	 ex proceedWith:nil
-      ] do:[
-	 Object errorSignal raise
-      ].
-
-      Object errorSignal handle:[:ex|
-	 ex proceed
-      ] do:[
-	 Object errorSignal raise
-      ].
-    "
-
-    "Created: / 4.8.1999 / 07:48:49 / stefan"
-    "Modified: / 4.8.1999 / 08:43:53 / stefan"
-! !
-
-!GenericException::RecursiveExceptionError class methodsFor:'documentation'!
-
-documentation
-"
-    RecursiveExceptionError is raised, if the same exception is raised
-    again in an exception handler.
-
-    The parameter is the recursive exception.
-"
-
-! !
-
-!GenericException::RecursiveExceptionError class methodsFor:'initialization'!
-
-initialize
-
-    NotifierString := 'recursive exception raise in handler'.
-
-    "
-     self initialize
-    "
-
-    "Created: / 4.8.1999 / 09:00:47 / stefan"
-    "Modified: / 4.8.1999 / 09:04:09 / stefan"
-! !
-
-!GenericException::RecursiveExceptionError class methodsFor:'queries'!
-
-mayProceed
-
-    ^ false
-
-    "Created: / 4.8.1999 / 09:00:47 / stefan"
-    "Modified: / 4.8.1999 / 09:04:27 / stefan"
-! !
-
 !GenericException class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/GenericException.st,v 1.14 1999-08-04 07:58:10 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/GenericException.st,v 1.15 1999-08-04 14:13:27 stefan Exp $'
 ! !
 GenericException initialize!