ExceptionHandlerSet.st
author Claus Gittinger <cg@exept.de>
Mon, 02 Aug 1999 15:42:45 +0200
changeset 4491 5041cae5651c
parent 4476 696ac99f2a52
child 4513 b16770982c62
permissions -rw-r--r--
use new pragma to flag exception frames.

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


IdentityDictionary subclass:#ExceptionHandlerSet
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Exceptions'
!

!ExceptionHandlerSet 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
"
    A ExceptionHandlerSet allows a group of unrelated signals to be handled
    by individual handlers - their evaluation is equivalent to a corresponding
    number of nested signal handlers, but more efficient and
    somwehat easier to program.

    [author:]
        Stefan Vogel

    [see also:]
        Exception Signal SignalSet
"
!

examples
"
    examples to be added.
                                                                [exBegin]
         |h num|

         h := ExceptionHandlerSet new.
         h on:(Number divisionByZeroSignal)
           handle:[:ex | 'division by zero' printNL. ex proceed].

         h on:(Object haltSignal)
           handle:[:ex | 'halt encountered ' printNL. ex proceed].

         h on:(Float domainErrorSignal)
           handle:[:ex | 'domain error  ' printNL. ex proceed].

         h handleDo:[
            num := 0.

            'now dividing' printNL.
            1 // num.

            'now doing bad arcSin' printNL.
            num := 50.
            num arcSin.

            'now halting' printNL.
            self halt.
         ]
                                                                [exEnd]

                                                                [exBegin]
         |h num|

         h := ExceptionHandlerSet new.
         h on:(Number divisionByZeroSignal)
           handle:[:ex | 'division by zero' printNL. ex proceed].

         h on:(Object haltSignal)
           handle:[:ex | 'halt encountered ' printNL. ex proceed].

         h on:(Float domainErrorSignal)
           handle:[:ex | 'domain error  ' printNL. ex proceed].

         [
            num := 0.

            'now dividing' printNL.
            1 // num.

            'now doing bad arcSin' printNL.
            num := 50.
            num arcSin.

            'now halting' printNL.
            self halt.
         ] valueWithExceptionHandler:h
                                                                [exEnd]
"
! !

!ExceptionHandlerSet methodsFor:'adding'!

on:aSignal handle:aHandler
    "add a handler for aSignal to the set"

    self at:aSignal put:aHandler

    "Created: / 26.7.1999 / 09:51:37 / stefan"
! !

!ExceptionHandlerSet methodsFor:'queries'!

accepts:aSignal
    "return true, if the receiver accepts the argument, aSignal.
     (i.e. if any of the receivers elements is aSignal or a parent of it)."

    self keysDo:[:sig | (sig accepts:aSignal) ifTrue:[^ true]].
    ^ false

    "Created: / 26.7.1999 / 09:53:09 / stefan"
!

handlerForSignal:signal
    "answer the handler block for signal"

    self keysAndValuesDo:[:sig :handler|
        (sig accepts:signal) ifTrue:[
            ^ handler.
        ].
    ].

    ^ nil

    "Modified: / 26.7.1999 / 09:59:43 / stefan"
    "Created: / 26.7.1999 / 11:29:29 / 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"


    (theContext selector ~~ #'handleDo:from:'
     or:[(theContext argAt:2) == originator]) ifTrue:[
        self keysAndValuesDo:[:sig :handler|
            (sig accepts:signal) ifTrue:[
                ^ handler.
            ].
        ].
    ].

    ^ nil

    "Created: / 26.7.1999 / 09:53:28 / stefan"
    "Modified: / 26.7.1999 / 09:59:43 / stefan"
!

handlingExceptionInContext:theContext
    "answer the handling exceptionHandlerSet from aContext."

    ^ self
! !

!ExceptionHandlerSet methodsFor:'save evaluation'!

handleDo:aBlock
    "evaluate the argument, aBlock.
     If any of the signals in the receiver is raised during evaluation,
     evaluate the handleBlock passing it an Exception argument.
     The handler may decide how to react to the signal by sending
     a corresponding message to the exception (see there).
     If the signal is not raised, return the value of evaluating
     aBlock."

    <exception: #handle>

    "/ thisContext markForHandle. -- same as above pragma
    ^ aBlock value  "the real logic is in Exception>>doRaise"

   "
    |h num|

    h := ExceptionHandlerSet new.
    h on:(Number divisionByZeroSignal)
      handle:[:ex | 'division by zero' printNL. ex proceed].

    h on:(Object haltSignal)
      handle:[:ex | 'halt encountered ' printNL. ex proceed].

    h on:(Float domainErrorSignal)
      handle:[:ex | 'domain error  ' printNL. ex proceed].

    h handleDo:[
       num := 0.

       'now dividing' printNL.
       1 // num.

       'now doing bad arcSin' printNL.
       num := 50.
       num arcSin.

       'now halting' printNL.
       self halt.
    ]
    "

    "Created: / 26.7.1999 / 09:56:44 / stefan"
    "Modified: / 26.7.1999 / 11:01:53 / stefan"
!

handleDo:aBlock from:originator
    "evaluate the argument, aBlock.
     If any of the signals in the receiver is raised during evaluation,
     evaluate the handleBlock passing it an Exception argument.
     The handler may decide how to react to the signal by sending
     a corresponding message to the exception (see there).
     If the signal is not raised, return the value of evaluating
     aBlock."

    <exception: #handle>

    "/ thisContext markForHandle. -- same as above pragma
    ^ aBlock value  "the real logic is in Exception>>doRaise"

   "
    |h num|

    h := ExceptionHandlerSet new.
    h on:(Number divisionByZeroSignal)
      handle:[:ex | 'division by zero' printNL. ex proceed].

    h on:(Object haltSignal)
      handle:[:ex | 'halt encountered ' printNL. ex proceed].

    h on:(Float domainErrorSignal)
      handle:[:ex | 'domain error  ' printNL. ex proceed].

    h handleDo:[
       'now halting' printNL.
       self halt.

       'the following exceptions are not handled.
        A debugger is opened' printNL.

       'now dividing' printNL.
       num := 0.
       1 // num.

       'now doing bad arcSin' printNL.
       num := 50.
       num arcSin.
    ] from:self
    "

    "Created: / 26.7.1999 / 09:56:44 / stefan"
    "Modified: / 26.7.1999 / 11:36:47 / stefan"
! !

!ExceptionHandlerSet class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/ExceptionHandlerSet.st,v 1.5 1999-08-02 13:42:02 cg Exp $'
! !