Notification.st
author Claus Gittinger <cg@exept.de>
Tue, 17 Jun 2003 11:12:22 +0200
changeset 7385 852e84340d2b
parent 6451 f22b12c0349a
child 8516 14ec9e1d3b39
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1999 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


"{ Package: 'stx:libbasic' }"

Exception subclass:#Notification
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Exceptions'
!

!Notification class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1999 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

!

documentation
"    
    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 QuerySignal
"

!

examples 
"
  an up-notification from a deeply nested operation to a higher level:
                                                                        [exBegin]
    |zero|

    zero := 0.
    Notification handle:[:n |
        Transcript showCR:'Please note that: ' , n description.
        n 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 notify:'hello world'
                    ] value
                ]
            ] value
        ] value
    ]
                                                                        [exEnd]
"
! !

!Notification class methodsFor:'initialization'!

initialize

    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).
     ]
    "

    "
     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: / 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
    "return true, if this is a querySignal - always return true here"

    ^ true

    "Created: / 23.7.1999 / 14:59:50 / stefan"
!

notify:aMessageString
    "raise the query - return the handlers value, or the default
     value, if there is no handler."

    ^ self raiseRequestErrorString:aMessageString
!

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
    "the default action is to return the default value.
     Subclasses may redefine this"

    ^ self defaultResumeValue

    "Modified: / 23.7.1999 / 15:13:34 / stefan"
! !

!Notification class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Notification.st,v 1.12 2002-03-07 07:53:07 cg Exp $'
! !
Notification initialize!