Notification.st
changeset 4550 66adee5e8491
parent 4525 999e680a29ca
child 4554 db264efac2c0
--- a/Notification.st	Wed Aug 04 18:26:42 1999 +0200
+++ b/Notification.st	Wed Aug 04 18:31:44 1999 +0200
@@ -11,6 +11,8 @@
 "
 
 
+'From Smalltalk/X, Version:3.5.3 on 4-aug-1999 at 06:30:17 pm'                  !
+
 Exception subclass:#Notification
 	instanceVariableNames:''
 	classVariableNames:''
@@ -37,22 +39,150 @@
 
 documentation
 "    
-    Notification is an abstract superclass of all notification 
-    exceptions in the system
+    Notification is the superclass of all notification exceptions in the system.
+    These notifications are ignored, if no handler is present.
+    In this case a default value is returned.
 
     [author:]
         Stefan Vogel
 
     [see also:]
-        Signal
+        Signal QuerySignal
 "
+
 !
 
-examples
+examples 
 "
-                                                            [exBegin]
-    Notification raiseRequest
-                                                            [exEnd]
+  an up-query from a deeply nested operation to a higher level:
+                                                                        [exBegin]
+    |zero|
+
+    zero := 0.
+    Notification handle:[:ex |
+        Transcript showCR:'query'.
+        ex proceedWith:true
+    ] do:[
+        'nesting'.
+        [
+            [
+                Object errorSignal handle:[:ex |
+                    Transcript showCR:'some error: ' , ex errorString.
+                    ex proceed
+                ] do:[
+                    [
+                        1 // zero.  'an error which is caught in the handler'.
+                        (Notification query) == true ifTrue:[
+                            Transcript showCR:'query says: ok'.
+                        ] ifFalse:[
+                            Transcript showCR:'query says: no'
+                        ]
+                    ] value
+                ]
+            ] value
+        ] value
+    ]
+                                                                        [exEnd]
+  for lazy typists, a more compact interface is also provided
+  (which is also easier to read):
+                                                                        [exBegin]
+    Notification answer:true do:[
+        'nesting'.
+        [
+            [
+                (Notification query) == true ifTrue:[
+                    Transcript showCR:'query says: ok'.
+                ] ifFalse:[
+                    Transcript showCR:'query says: no'
+                ]
+            ] value
+        ] value
+    ]
+                                                                        [exEnd]
+  an up-query from a deeply nested operation, for which there
+  is no handler:
+  (notice, this would not work with normal signals, which would raise
+   another unhandled exception-exception;
+   also notice the == check #raise's return value being true,
+   instead of a simple ifTrue; this handles a nil-value from
+   the unhandled query)
+                                                                        [exBegin]
+    |zero|
+
+    zero := 0.
+    [
+        'nesting'.
+        [
+            [
+                Object errorSignal handle:[:ex |
+                    Transcript showCR:'some error: ' , ex errorString.
+                    ex proceed
+                ] do:[
+                    [
+                        1 // zero.  'an error which is caught in the handler'.
+                        (Notification raise) == true ifTrue:[
+                            Transcript showCR:'query says: ok'.
+                        ] ifFalse:[
+                            Transcript showCR:'query says: no'
+                        ]
+                    ] value
+                ]
+            ] value
+        ] value
+    ] value
+                                                                         [exEnd]
+  counter-example, just to show that things would not work this way
+  with regular signals:
+                                                                        [exBegin]
+    |signal|
+
+    signal := Signal new.
+    'nesting deeply'.
+    [
+        [
+            [
+                [
+                    [
+                        (signal raise) == true ifTrue:[
+                            Transcript showCR:'query says: ok'.
+                        ] ifFalse:[
+                            Transcript showCR:'query says: no'
+                        ]
+                    ] value
+                ] value
+            ] value
+        ] value
+    ] value
+                                                                         [exEnd]
+
+   except, by handling the unhandled exception
+   (but we think, that querySignals are easier to use and
+    better document the intent):
+                                                                        [exBegin]
+    |signal|
+
+    signal := Signal new.
+    'nesting deeply'.
+    [
+        [
+            [
+                [
+                    [
+                        Signal noHandlerSignal handle:[:ex |
+                            ex proceedWith:nil
+                        ] do:[
+                            (signal raise) == true ifTrue:[
+                                Transcript showCR:'query says: ok'.
+                            ] ifFalse:[
+                                Transcript showCR:'query says: no'
+                            ]
+                        ]
+                    ] value
+                ] value
+            ] value
+        ] value
+    ] value
+                                                                         [exEnd]
 "
 
 ! !
@@ -61,46 +191,164 @@
 
 initialize
 
-    NotifierString := 'Notification'.
+    NotifierString := 'Notification:'
+! !
+
+!Notification class methodsFor:'answering queries'!
+
+answer:someAnswer do:aBlock
+    "evaluate the argument, aBlock.
+     If the receiver is queried during evaluation, answer with someAnswer.
+     This is a wrapper for #handle:do: for lazy typists; no new functionality."
+
+    <exception: #handle>
+
+    "/ thisContext markForHandle. -- same as above pragma
+    aBlock value.  "the real logic is in Exception>>doRaise"
+
+    "
+     Notification answer:true do:[
+        Transcript showCR:'query answers: ' , (Query query printString).
+     ]
+    "
 
     "
-     self initialize
+     Notification answer:false do:[
+        Transcript showCR:'first query answers: ' , (Query query printString).
+        Query answer:true do:[
+            Transcript showCR:'second query answers: ' , (Query query printString).
+        ]
+     ]
     "
 
-    "Created: / 23.7.1999 / 15:31:44 / stefan"
+    "Created: / 10.7.1996 / 15:08:20 / cg"
+    "Modified: / 14.10.1996 / 16:59:18 / cg"
+    "Modified: / 25.7.1999 / 23:12:19 / stefan"
+! !
+
+!Notification class methodsFor:'queries'!
+
+accepts:aSignal
+    "return true, if the receiver accepts the argument, aSignal.
+     (i.e. the receiver is aSignal or a parent of it). False otherwise."
+
+    |s|
+
+    self == aSignal ifTrue:[^ true].
+    aSignal isQuerySignal ifFalse:[^ false].
+
+    s := aSignal.
+    [s notNil] whileTrue:[
+        self == s ifTrue:[^ true].
+        s := s parent
+    ].
+    ^ false
+
+    "Modified: / 22.3.1999 / 12:45:32 / stefan"
+    "Created: / 23.7.1999 / 15:18:00 / stefan"
+!
+
+defaultAnswer
+    "Return the default answer to the Query. This method is called,
+     if nobody catches the signal.
+
+     Subclasses may redefine this method."
+
+    "Calling raiseRequest here will execute the exception's action method"    
+
+    ^ super raiseRequest
+
+    "Created: / 23.7.1999 / 15:16:03 / stefan"
+!
+
+handlerForSignal:signal context:theContext originator:originator
+    "answer the handler block for the signal from originator.
+     The block is retrieved from aContext.
+     Answer nil if the signal is not handled"
+
+    |arg|
+
+    theContext selector == #'answer:do:' ifTrue:[
+        (self == signal or:[self accepts:signal]) ifTrue:[
+            arg := theContext argAt:1.
+            ^ [:ex| ex proceedWith:arg].
+        ]
+    ] ifFalse:[
+        ^ super handlerForSignal:signal context:theContext originator:originator.
+    ].
+
+    ^ nil
+
+    "Created: / 25.7.1999 / 23:11:55 / stefan"
+!
+
+isQuerySignal
+
+    ^ true
+
+    "Created: / 23.7.1999 / 14:59:50 / stefan"
+!
+
+query
+    "raise the query - return the handlers value, or the default
+     value, if there is no handler.
+     Invoking the handler is exactly the functionality of Signal>>raiseRequest,
+     but we can do it faster here."
+
+    |con s|
+
+    con := Context findFirstSpecialHandle:true raise:false.
+    [con notNil] whileTrue:[
+        (con selector == #answer:do:) ifFalse:[
+            ^ super raiseRequest
+        ].
+        (s := con receiver) == self ifTrue:[
+            ^ con argAt:1
+        ].
+        (s == self or:[s accepts:self]) ifTrue:[
+            ^ super raiseRequest
+        ].
+        con := con findSpecialHandle:true raise:false.
+    ].
+
+    "/ no handler found - return the default value
+    ^ self defaultAnswer
+
+    "Modified: / 15.6.1998 / 21:27:37 / cg"
+    "Modified: / 25.7.1999 / 23:15:16 / stefan"
+!
+
+raise
+    "QuerySignals are proceedable by definition,
+     so they should be raised with #query or #raiseRequest"
+
+    ^ self shouldNotImplement
+
+    "Created: / 23.7.1999 / 15:19:17 / stefan"
+!
+
+raiseRequest
+    "redefined to use #query"
+
+    ^ self query
+
+    "Created: / 25.7.1999 / 23:25:59 / stefan"
 ! !
 
 !Notification methodsFor:'default actions'!
 
 defaultAction
-    "Default action for notifications: open a info box with errorString"
-
-    |text|
-
-    text := self errorString.
+    "the default action is to return the default value.
+     Subclasses may redefine this"
 
-    (Smalltalk isInitialized and:[Dialog notNil]) ifTrue:[
-        Dialog notify:text.
-    ] ifFalse:[
-        "
-         on systems without GUI, simply show
-         the message on the Transcript.
-        "
-        Transcript showCR:text.
-    ].
-    self proceed.
+    ^ nil
 
-
-    "
-      Notification raiseRequestWith:self errorString:' abc'
-    "
-
-    "Modified: / 3.8.1999 / 14:06:55 / stefan"
+    "Modified: / 23.7.1999 / 15:13:34 / stefan"
 ! !
 
 !Notification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Notification.st,v 1.5 1999-08-04 14:12:07 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Notification.st,v 1.6 1999-08-04 16:31:44 stefan Exp $'
 ! !
 Notification initialize!