Notification.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 23 Apr 2013 14:27:19 +0100
branchjv
changeset 18050 131d0413b25b
parent 18040 a11a12546f23
parent 15114 77142b5c937a
child 18062 014678b4657a
permissions -rw-r--r--
Merged 5b83e8406d5d and 6278efcd484d (branch default - CVS HEAD)

"
 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' }"

GenericException subclass:#Notification
	instanceVariableNames:'tag'
	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 signals in the system.
    contrast to regular exceptions, Notifications are ignored, if no handler is present
    and a default value is returned from the raise.
    When a handler finishes, the do-block is proceeded with the exception handlers value
    (an Exception does a return in this case.).

    Thanks to proceedable exceptions, Notifications allow for non-GUI model code to provide
    user notifications which are optionally shown.
    Very useful, for example to provide progress information from a method which can be
    invoked both from a GUI-Tool (where notifications are wanted) and also from the system,
    where such notifications are not desired.

    [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'.
        [
            [
                Error 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 and proceed with someAnswer.
     This is a wrapper for #handle:do: for lazy typists; no new functionality."

    <context: #return>
    <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:'misc ui support'!

iconInBrowserSymbol
    <resource: #programImage>

    ^ #notificationClassBrowserIcon
! !

!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 parent.
    [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"
!

handles:anException
    "return true, if the receiver handles the argument, anException.
     (i.e. the receiver is anExceptions signal or a parent of it)"

    |signal|

    signal := anException creator.

    self == signal ifTrue:[^ true].               "quick check"
    anException isNotification ifFalse:[^ false]. "speed up non-queries by not traversing the parent chain"

    [(signal := signal parent) notNil] whileTrue:[
        self == signal ifTrue:[^ true].
    ].
    ^ false
!

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 (avoiding the construction of an exception instance)."

    |con signal|

    con := Context findFirstSpecialHandle:true raise:false.
    [con notNil] whileTrue:[
        (con selector ~~ #answer:do:) ifTrue:[
            "there is another handler block, maybe it will return the answer.
             Call it via raiseRequest"
            ^ super raiseRequest
        ].
        signal := con receiver.
        signal == self ifTrue:[
            ^ con argAt:1
        ].
        signal isNil ifTrue:[
            self error:'nil receiver in #answer:do: - send'.
        ].
        (signal accepts:self) ifTrue:[
            ^ con argAt:1
        ].
        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:'accessing'!

tag
    "for squeak compatibility"

    ^ tag

    "Modified (comment): / 11-09-2011 / 16:40:54 / cg"
!

tag:aSzmbol
    "for squeak compatibility"

    tag := aSzmbol.

    "Modified (format): / 11-09-2011 / 16:41:01 / cg"
! !

!Notification methodsFor:'default actions'!

defaultAction
    "the default action is to return the default value.
     Subclasses may redefine this"

    |handlerBlock|

    "try per signal handler.
     I may have been created from a QuerySignal"

    (handlerBlock := signal handlerBlock) notNil ifTrue:[
        "... and call it"
        ^ handlerBlock value:self.
    ].
    ^ self defaultResumeValue

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

!Notification methodsFor:'helpers'!

hasDialog
    "answer true, if we can use a Dialog window"

    (Smalltalk isInitialized 
     and:[Dialog notNil
     and:[Screen notNil
     and:[Screen current notNil
     and:[Screen current isOpenAndDispatching
    ]]]]) ifTrue:[
        Dialog autoload.        "in case its autoloaded"
        ^ true.
    ].
    ^ false
! !

!Notification methodsFor:'private'!

LATERdoCallHandler:aHandlerBlock
"SV: Have to think about..."
    "call the handler proper
     - an extra method is needed to have a raise-marked context around.
       (see implementation of #reject and #proceed).
     Redefined from GenericException to do a proceed here"

    <context: #return>
    <exception: #raise>

    |val|

    aHandlerBlock argumentCount == 0 ifTrue:[
        "/ 0-arg handler - not interested in the ex - object
        val := aHandlerBlock value
    ] ifFalse:[
        "/ 1-arg handler - pass myself as exception argument
        val := aHandlerBlock value:self.
    ].

    "handler fall through - is just like a #proceedWith:(aHandlerBlock value)"

    self proceedWith:val
! !

!Notification methodsFor:'queries'!

query
    "notice the implementation on the class-side: if no additional parameters are to be passed,
     we do not even arrive here, because query has inlined the raiseRequest code"

    ^ self raiseRequest
! !

!Notification methodsFor:'testing'!

isNotification
    ^ true
! !

!Notification class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Notification.st,v 1.29 2013-04-19 08:41:19 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/Notification.st,v 1.29 2013-04-19 08:41:19 cg Exp $'
! !


Notification initialize!