Query.st
author Stefan Vogel <sv@exept.de>
Wed, 28 Jul 1999 09:53:29 +0200
changeset 4464 cec93c942c14
parent 4446 4da4e51fc1ab
child 4466 9cba6f4ecec4
permissions -rw-r--r--
Use context flag for exception handling instead of searching for selectors.

'From Smalltalk/X, Version:3.5.3 on 26-jul-1999 at 00:02:41'                    !

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

!Query class methodsFor:'documentation'!

documentation
"    
    Query ist an abstract superclass of all query exceptions in the system

    [author:]
        Stefan Vogel

    [see also:]
        Signal QuerySignal
"

!

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

    zero := 0.
    Query 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'.
                        (Query 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]
    Query answer:true do:[
        'nesting'.
        [
            [
                (Query 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'.
                        (Query 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]
"

!

history
    "Created: / 23.7.1999 / 14:16:16 / stefan"
! !

!Query 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."

      thisContext markForHandle.
      aBlock value.

      "
       Query answer:true do:[
          Transcript showCR:'query answers: ' , (Query query printString).
       ]
      "

      "
       Query 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"
! !

!Query 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|

    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 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 := thisContext sender.
    [con notNil] whileTrue:[
        con := con findSpecialHandle:true raise:true.
        con notNil ifTrue:[
            (con selector == #answer:do:) ifFalse:[
                ^ super raiseRequest
            ].
            (s := con receiver) == self ifTrue:[
                ^ con argAt:1
            ] ifFalse:[
                (s accepts:self) ifTrue:[
                    ^ super raiseRequest
                ]
            ]
        ]
    ].
    "/ 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"
! !

!Query methodsFor:'default actions'!

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

    ^ nil

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

!Query class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Query.st,v 1.2 1999-07-28 07:53:26 stefan Exp $'
! !