[FIX] Exception>>isNested, take 2

Paul McDonough paulm at 4thEstate.com
Wed Jan 12 23:40:56 UTC 2000


Just for fun, I thought I'd attach the file this time ...
Paul
-------------- next part --------------
'From Squeak2.7 of 7 January 2000 [latest update: #1762] on 10 January 2000 at 6:24:35 pm'!

!Exception methodsFor: 'private' stamp: 'tfei 1/10/2000 18:20'!
findHandlerFrom: startCtx

       | ctx handler |
       ctx := startCtx.
       [ctx == nil]
               whileFalse:
                       [ctx isHandlerContext
                               ifTrue:
                                       [handler := ctx tempAt: 1. "the first argument"
                                       ((handler handles: self) and: [(ctx tempAt: 2) sender == nil])
                                               ifTrue: [^ctx]].
                       ctx := ctx sender].
       ^nil! !

!Exception methodsFor: 'private' stamp: 'tfei 1/10/2000 18:22'!
setHandlerFrom: startCtx

	handlerContext := self findHandlerFrom: startCtx.
	^handlerContext! !

!Exception methodsFor: 'signaledException' stamp: 'tfei 1/10/2000 18:19'!
isNested
	"Determine whether the current exception handler is within the scope of another handler for the same exception."

	^(self findHandlerFrom: handlerContext sender) ~~ nil! !

!Exception methodsFor: 'signaledException' stamp: 'tfei 1/10/2000 18:22'!
outer
	"Evaluate the enclosing exception action for the receiver and return."

	self isResumable
		ifTrue:
			[self setHandlerFrom: handlerContext sender.
			handlerContext == nil
				ifTrue: [self defaultAction]
				ifFalse: [self handlerAction]]
		ifFalse: [self pass]! !

!Exception methodsFor: 'signaledException' stamp: 'tfei 1/10/2000 18:23'!
pass
	"Yield control to the enclosing exception action for the receiver."

	self setHandlerFrom: handlerContext sender.
	handlerContext == nil
		ifTrue:
			[self defaultAction.
			self isResumable
				ifTrue: [self resume]
				ifFalse: [IllegalResumeAttempt signal]]
		ifFalse: [self handlerAction]! !

!Exception methodsFor: 'exceptionSignaler' stamp: 'tfei 1/10/2000 18:23'!
signal
	"Signal the occurrence of an exceptional condition."

	| result |
	initialContext == nil ifTrue: [initialContext := thisContext sender].
	resignalException := nil.
	(self setHandlerFrom: initialContext) == nil
		ifTrue: [^self defaultAction].
	result := self handlerAction.
	^resignalException == nil
		ifTrue: [result]
		ifFalse: [resignalException signal]! !


!Warning methodsFor: 'private-exceptionSignaler' stamp: 'tfei 1/10/2000 18:23'!
signal
	"Signal the occurrence of an exceptional condition."
	"Warning is overriding this and marking it private in order to get around an apparent contradiction within the ANSI specification:
		Warning>>defaultAction must give the user the option to 'abort the computation'.
		Warning is resumable.
		Exception>>signal must return to its caller if it reaches a defaultAction in the case of a resumable exception.
		Therefore, Warning needs to invoke a handler action from its defaultAction; that handler action would seem to be return:, but according to the spec, 'It is erroneous to directly or indirectly send this message from within a #defaultAction method  to the receiver of the #defaultAction method.'

We have chosen to support the apparently intended behavior of Warning, at the expense of introducing a mildly unpleasant hack - in case of an unhandled Warning, we determine whether the user has elected to continue or not.  In the latter case, this process needs to terminate immediately, without returning to the sender of #signal.  To accomplish this, we nil out the sender on the call stack, and then use MethodContext>>cannotReturn: to open a notifier and allow the environment to continue in use."

	| result |
	initialContext == nil ifTrue: [initialContext := thisContext sender].
	resignalException := nil.
	(self setHandlerFrom: initialContext) == nil
		ifTrue:
			[self defaultAction.
			"if user elected to continue the computation, execution did not reach this line"
			initialContext unwindTo: nil.
			thisContext terminateTo: nil]
		ifFalse:
			[result := self handlerAction.
			^resignalException == nil
				ifTrue: [result]
				ifFalse: [resignalException signal]]! !




More information about the Squeak-dev mailing list