[squeak-dev] The Trunk: Kernel-fbs.770.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Jun 14 13:10:54 UTC 2013


Frank Shearar uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-fbs.770.mcz

==================== Summary ====================

Name: Kernel-fbs.770
Author: fbs
Time: 14 June 2013, 2:09:30.742 pm
UUID: 96386258-f4b8-4217-ad92-97749f3aba11
Ancestors: Kernel-fbs.769

Push the core (the actual kernel) of Exceptions-Kernel into Kernel-Exceptions, so that Kernel doesn't depend on Exceptions.

(I'd like to see domain specific exceptions pushed closer to their domains, rather than "cross-slicing" all exceptions together just because they're exceptions. Hence the new Kernel-Numbers-Exceptions category.)

=============== Diff against Kernel-fbs.769 ===============

Item was changed:
  SystemOrganization addCategory: #'Kernel-Chronology'!
  SystemOrganization addCategory: #'Kernel-Classes'!
+ SystemOrganization addCategory: #'Kernel-Exceptions'!
+ SystemOrganization addCategory: #'Kernel-Exceptions-Kernel'!
  SystemOrganization addCategory: #'Kernel-Methods'!
  SystemOrganization addCategory: #'Kernel-Models'!
  SystemOrganization addCategory: #'Kernel-Numbers'!
+ SystemOrganization addCategory: #'Kernel-Numbers-Exceptions'!
  SystemOrganization addCategory: #'Kernel-Objects'!
  SystemOrganization addCategory: #'Kernel-Processes'!
  SystemOrganization addCategory: #'Kernel-Processes-Variables'!

Item was added:
+ Error subclass: #ArithmeticError
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Numbers-Exceptions'!

Item was added:
+ Halt subclass: #AssertionFailure
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !AssertionFailure commentStamp: 'gh 5/2/2002 20:29' prior: 0!
+ AsssertionFailure is the exception signaled from Object>>assert: when the assertion block evaluates to false.!

Item was added:
+ Error subclass: #AttemptToWriteReadOnlyGlobal
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !AttemptToWriteReadOnlyGlobal commentStamp: 'gh 5/2/2002 20:26' prior: 0!
+ This is a resumable error you get if you try to assign a readonly variable a value.
+ Name definitions in the module system can be read only and are then created using instances of ReadOnlyVariableBinding instead of Association.
+ See also LookupKey>>beReadWriteBinding and LookupKey>>beReadOnlyBinding.
+ 
+ !

Item was added:
+ ----- Method: AttemptToWriteReadOnlyGlobal>>description (in category 'as yet unclassified') -----
+ description
+ 	"Return a textual description of the exception."
+ 
+ 	| desc mt |
+ 	desc := 'Error'.
+ 	^(mt := self messageText) == nil
+ 		ifTrue: [desc]
+ 		ifFalse: [desc, ': ', mt]!

Item was added:
+ ----- Method: AttemptToWriteReadOnlyGlobal>>isResumable (in category 'as yet unclassified') -----
+ isResumable
+ 	^true!

Item was added:
+ Error subclass: #BlockCannotReturn
+ 	instanceVariableNames: 'result deadHome'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !BlockCannotReturn commentStamp: '<historical>' prior: 0!
+ This class is private to the EHS implementation.  Its use allows for ensured execution to survive code such as:
+ 
+ [self doThis.
+ ^nil]
+ 	ensure: [self doThat]
+ 
+ Signaling or handling this exception is not recommended.!

Item was added:
+ ----- Method: BlockCannotReturn>>deadHome (in category 'accessing') -----
+ deadHome
+ 
+ 	^ deadHome!

Item was added:
+ ----- Method: BlockCannotReturn>>deadHome: (in category 'accessing') -----
+ deadHome: context
+ 
+ 	deadHome := context!

Item was added:
+ ----- Method: BlockCannotReturn>>defaultAction (in category 'exceptionDescription') -----
+ defaultAction
+ 
+ 	self messageText: 'Block cannot return'.
+ 	^super defaultAction!

Item was added:
+ ----- Method: BlockCannotReturn>>isResumable (in category 'exceptionDescription') -----
+ isResumable
+ 
+ 	^true!

Item was added:
+ ----- Method: BlockCannotReturn>>result (in category 'accessing') -----
+ result
+ 
+ 	^result!

Item was added:
+ ----- Method: BlockCannotReturn>>result: (in category 'accessing') -----
+ result: r
+ 
+ 	result := r!

Item was added:
+ Warning subclass: #Deprecation
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !Deprecation commentStamp: 'dew 5/21/2003 17:46' prior: 0!
+ This Warning is signalled by methods which are deprecated.
+ 
+ The use of Object>>#deprecatedExplanation: aString and Object>>#deprecated: aBlock explanation: aString is recommended.
+ 
+ Idiom: Imagine I want to deprecate the message #foo.
+ 
+ foo
+ 	^ 'foo'
+ 
+ I can replace it with:
+ 
+ foo
+ 	self deprecatedExplanation: 'The method #foo was not good. Use Bar>>newFoo instead.'
+ 	^ 'foo'
+ 
+ Or, for certain cases such as when #foo implements a primitive, #foo can be renamed to #fooDeprecated.
+ 
+ fooDeprecated
+ 	^ <primitive>
+ 
+ foo
+ 	^ self deprecated: [self fooDeprecated] explanation: 'The method #foo was not good. Use Bar>>newFoo instead.'
+ !

Item was added:
+ ArithmeticError subclass: #DomainError
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Numbers-Exceptions'!
+ 
+ !DomainError commentStamp: 'nice 4/20/2011 22:13' prior: 0!
+ A DomainError is an error occuring when a mathematical function is used outside its domain of validity.!

Item was added:
+ Error subclass: #DuplicateVariableError
+ 	instanceVariableNames: 'superclass variable'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !DuplicateVariableError commentStamp: 'ar 2/13/2010 15:05' prior: 0!
+ DuplicateVariableError is signaled when a (class or instance) variable name is used in both super and subclass.!

Item was added:
+ ----- Method: DuplicateVariableError>>isResumable (in category 'testing') -----
+ isResumable
+ 	^true!

Item was added:
+ ----- Method: DuplicateVariableError>>superclass (in category 'accessing') -----
+ superclass
+ 	"The superclass in which the variable is defined"
+ 	^superclass!

Item was added:
+ ----- Method: DuplicateVariableError>>superclass: (in category 'accessing') -----
+ superclass: aClass
+ 	"The superclass in which the variable is defined"
+ 	superclass := aClass!

Item was added:
+ ----- Method: DuplicateVariableError>>variable (in category 'accessing') -----
+ variable
+ 	"Name of the duplicate variable"
+ 	^variable!

Item was added:
+ ----- Method: DuplicateVariableError>>variable: (in category 'accessing') -----
+ variable: aString
+ 	"Name of the duplicate variable"
+ 	variable := aString!

Item was added:
+ Exception subclass: #Error
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions-Kernel'!
+ 
+ !Error commentStamp: '<historical>' prior: 0!
+ >From the ANSI standard:
+ This protocol describes the behavior of instances of class Error. These are used to represent error conditions that prevent the normal continuation of processing. Actual error exceptions used by an application may be subclasses of this class.
+ As Error is explicitly specified  to be subclassable, conforming implementations must implement its behavior in a non-fragile manner.
+ 
+ Additional notes:
+ Error>defaultAction uses an explicit test for the presence of the Debugger class to decide whether or not it is in development mode.  In the future, TFEI hopes to enhance the semantics of #defaultAction to improve support for pluggable default handlers.!

Item was added:
+ ----- Method: Error>>defaultAction (in category 'exceptionDescription') -----
+ defaultAction
+ 	"No one has handled this error, but now give them a chance to decide how to debug it.  If none handle this either then open debugger (see UnhandedError-defaultAction)"
+ 
+ 	UnhandledError signalForException: self!

Item was added:
+ ----- Method: Error>>isResumable (in category 'private') -----
+ isResumable
+ 	"Determine whether an exception is resumable."
+ 
+ 	^ false!

Item was added:
+ Object subclass: #Exception
+ 	instanceVariableNames: 'messageText tag signalContext handlerContext outerContext'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions-Kernel'!
+ 
+ !Exception commentStamp: '<historical>' prior: 0!
+ This is the main class used to implement the exception handling system (EHS).  It plays two distinct roles:  that of the exception, and that of the exception handler.  More specifically, it implements the bulk of the protocols laid out in the ANSI specification - those protocol names are reflected in the message categories.
+ 
+ Exception is an abstract class.  Instances should neither be created nor trapped.  In most cases, subclasses should inherit from Error or Notification rather than directly from Exception.
+ 
+ In implementing this EHS, The Fourth Estate Inc. incorporated some ideas and code from Craig Latta's EHS.  His insights were crucial in allowing us to implement BlockContext>>valueUninterruptably (and by extension, #ensure: and #ifCurtailed:), and we imported the following methods with little or no modification:
+ 
+ ContextPart>>terminateTo:
+ ContextPart>>terminate
+ MethodContext>>receiver:
+ MethodContext>>answer:
+ 
+ Thanks, Craig!!!

Item was added:
+ ----- Method: Exception class>>, (in category 'exceptionSelector') -----
+ , anotherException
+ 	"Create an exception set."
+ 
+ 	^ExceptionSet new
+ 		add: self;
+ 		add: anotherException;
+ 		yourself!

Item was added:
+ ----- Method: Exception class>>handles: (in category 'exceptionSelector') -----
+ handles: exception
+ 	"Determine whether an exception handler will accept a signaled exception."
+ 
+ 	^ exception isKindOf: self!

Item was added:
+ ----- Method: Exception class>>signal (in category 'exceptionInstantiator') -----
+ signal
+ 	"Signal the occurrence of an exceptional condition."
+ 
+ 	^ self new signal!

Item was added:
+ ----- Method: Exception class>>signal: (in category 'exceptionInstantiator') -----
+ signal: signalerText
+ 	"Signal the occurrence of an exceptional condition with a specified textual description."
+ 
+ 	^ self new signal: signalerText!

Item was added:
+ ----- Method: Exception>>defaultAction (in category 'priv handling') -----
+ defaultAction
+ 	"The default action taken if the exception is signaled."
+ 
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: Exception>>defaultResumeValue (in category 'defaults') -----
+ defaultResumeValue
+ 	"Answer the value that by default should be returned if the exception is resumed"
+ 	^nil!

Item was added:
+ ----- Method: Exception>>defaultReturnValue (in category 'defaults') -----
+ defaultReturnValue
+ 	"Answer the value that by default should be returned if the exception is returned"
+ 	^nil!

Item was added:
+ ----- Method: Exception>>description (in category 'printing') -----
+ description
+ 	"Return a textual description of the exception."
+ 
+ 	| desc mt |
+ 	desc := self class name asString.
+ 	^(mt := self messageText) == nil
+ 		ifTrue: [desc]
+ 		ifFalse: [desc, ': ', mt]!

Item was added:
+ ----- Method: Exception>>isNested (in category 'handling') -----
+ isNested
+ 	"Determine whether the current exception handler is within the scope of another handler for the same exception."
+ 
+ 	^ handlerContext nextHandlerContext canHandleSignal: self!

Item was added:
+ ----- Method: Exception>>isResumable (in category 'priv handling') -----
+ isResumable
+ 	"Determine whether an exception is resumable."
+ 
+ 	^ true!

Item was added:
+ ----- Method: Exception>>messageText (in category 'printing') -----
+ messageText
+ 	"Return an exception's message text."
+ 	^ messageText ifNil: [ String empty ]!

Item was added:
+ ----- Method: Exception>>messageText: (in category 'signaling') -----
+ messageText: signalerText
+ 	"Set an exception's message text."
+ 
+ 	messageText := signalerText!

Item was added:
+ ----- Method: Exception>>outer (in category 'handling') -----
+ outer
+ 	"Evaluate the enclosing exception action and return to here instead of signal if it resumes (see #resumeUnchecked:)."
+ 
+ 	| prevOuterContext |
+ 	self isResumable ifTrue: [
+ 		prevOuterContext := outerContext.
+ 		outerContext := thisContext contextTag.
+ 	].
+ 	self pass.
+ !

Item was added:
+ ----- Method: Exception>>pass (in category 'handling') -----
+ pass
+ 	"Yield control to the enclosing exception action for the receiver."
+ 
+ 	handlerContext nextHandlerContext handleSignal: self!

Item was added:
+ ----- Method: Exception>>printOn: (in category 'printing') -----
+ printOn: stream
+ 
+ 	stream nextPutAll: self description!

Item was added:
+ ----- Method: Exception>>privHandlerContext: (in category 'priv handling') -----
+ privHandlerContext: aContextTag
+ 
+ 	handlerContext := aContextTag!

Item was added:
+ ----- Method: Exception>>rearmHandlerDuring: (in category 'handling') -----
+ rearmHandlerDuring: aBlock
+ "Make the current error handler re-entrant while it is running aBlock. Only works in a closure-enabled image"
+ 
+ 	^ handlerContext rearmHandlerDuring: aBlock!

Item was added:
+ ----- Method: Exception>>receiver (in category 'printing') -----
+ receiver
+ 
+ 	^ self signalerContext receiver!

Item was added:
+ ----- Method: Exception>>resignalAs: (in category 'handling') -----
+ resignalAs: replacementException
+ 	"Signal an alternative exception in place of the receiver."
+ 
+ 	self resumeUnchecked: replacementException signal!

Item was added:
+ ----- Method: Exception>>resume (in category 'handling') -----
+ resume
+ 	"Return from the message that signaled the receiver."
+ 
+ 	self resume: self defaultResumeValue!

Item was added:
+ ----- Method: Exception>>resume: (in category 'handling') -----
+ resume: resumptionValue
+ 	"Return resumptionValue as the value of the signal message."
+ 
+ 	self isResumable ifFalse: [IllegalResumeAttempt signal].
+ 	self resumeUnchecked: resumptionValue!

Item was added:
+ ----- Method: Exception>>resumeUnchecked: (in category 'handling') -----
+ resumeUnchecked: resumptionValue
+ 	"Return resumptionValue as the value of #signal, unless this was called after an #outer message, then return resumptionValue as the value of #outer."
+ 
+ 	| ctxt |
+ 	outerContext ifNil: [
+ 		signalContext return: resumptionValue
+ 	] ifNotNil: [
+ 		ctxt := outerContext.
+ 		outerContext := ctxt tempAt: 1. "prevOuterContext in #outer"
+ 		ctxt return: resumptionValue
+ 	].
+ !

Item was added:
+ ----- Method: Exception>>retry (in category 'handling') -----
+ retry
+ 	"Abort an exception handler and re-evaluate its protected block."
+ 
+ 	handlerContext restart!

Item was added:
+ ----- Method: Exception>>retryUsing: (in category 'handling') -----
+ retryUsing: alternativeBlock
+ 	"Abort an exception handler and evaluate a new block in place of the handler's protected block."
+ 
+ 	handlerContext restartWithNewReceiver: alternativeBlock
+ !

Item was added:
+ ----- Method: Exception>>return (in category 'handling') -----
+ return
+ 	"Return nil as the value of the block protected by the active exception handler."
+ 
+ 	self return: self defaultReturnValue!

Item was added:
+ ----- Method: Exception>>return: (in category 'handling') -----
+ return: returnValue
+ 	"Return the argument as the value of the block protected by the active exception handler."
+ 
+ 	handlerContext return: returnValue!

Item was added:
+ ----- Method: Exception>>searchFrom: (in category 'handling') -----
+ searchFrom: aContext
+ 	" Set the context where the handler search will start. "
+ 
+ 	signalContext := aContext contextTag!

Item was added:
+ ----- Method: Exception>>signal (in category 'signaling') -----
+ signal
+ 	"Ask ContextHandlers in the sender chain to handle this signal.  The default is to execute and return my defaultAction."
+ 
+ 	signalContext := thisContext contextTag.
+ 	^ thisContext nextHandlerContext handleSignal: self!

Item was added:
+ ----- Method: Exception>>signal: (in category 'signaling') -----
+ signal: signalerText
+ 	"Signal the occurrence of an exceptional condition with a specified textual description."
+ 
+ 	self messageText: signalerText.
+ 	^ self signal!

Item was added:
+ ----- Method: Exception>>signalerContext (in category 'printing') -----
+ signalerContext
+ 	"Find the first sender of signal(:)"
+ 
+ 	^ signalContext findContextSuchThat: [:ctxt |
+ 		(ctxt receiver == self or: [ctxt receiver == self class]) not]!

Item was added:
+ ----- Method: Exception>>tag (in category 'exceptionDescription') -----
+ tag
+ 	"Return an exception's tag value."
+ 
+ 	^tag == nil
+ 		ifTrue: [self messageText]
+ 		ifFalse: [tag]!

Item was added:
+ ----- Method: Exception>>tag: (in category 'exceptionBuilder') -----
+ tag: t
+ 	"This message is not specified in the ANSI protocol, but that looks like an oversight because #tag is specified, and the spec states that the signaler may store the tag value."
+ 
+ 	tag := t!

Item was added:
+ Notification subclass: #ExceptionAboutToReturn
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions-Kernel'!
+ 
+ !ExceptionAboutToReturn commentStamp: '<historical>' prior: 0!
+ This class is private to the EHS implementation.  Its use allows for ensured execution to survive code such as:
+ 
+ [self doThis.
+ ^nil]
+ 	ensure: [self doThat]
+ 
+ Signaling or handling this exception is not recommended.  Not even slightly.!

Item was added:
+ Object subclass: #ExceptionSet
+ 	instanceVariableNames: 'exceptions'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !ExceptionSet commentStamp: '<historical>' prior: 0!
+ An ExceptionSet is a grouping of exception handlers which acts as a single handler.  Within the group, the most recently added handler will be the last handler found during a handler search (in the case where more than one handler in the group is capable of handling a given exception). !

Item was added:
+ ----- Method: ExceptionSet>>, (in category 'exceptionSelector') -----
+ , anException
+ 	"Return an exception set that contains the receiver and the argument exception. This is commonly used to specify a set of exception selectors for an exception handler."
+ 
+ 	self add: anException.
+ 	^self!

Item was added:
+ ----- Method: ExceptionSet>>add: (in category 'private') -----
+ add: anException
+ 
+ 	^exceptions add: anException!

Item was added:
+ ----- Method: ExceptionSet>>handles: (in category 'exceptionSelector') -----
+ handles: anException
+ 	"Determine whether an exception handler will accept a signaled exception."
+ 
+ 	exceptions do:
+ 		[:ex |
+ 		(ex handles: anException)
+ 			ifTrue: [^true]].
+ 	^false!

Item was added:
+ ----- Method: ExceptionSet>>initialize (in category 'private') -----
+ initialize
+ 
+ 	exceptions := OrderedCollection new!

Item was added:
+ ArithmeticError subclass: #FloatingPointException
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Numbers-Exceptions'!

Item was added:
+ Exception subclass: #Halt
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !Halt commentStamp: '<historical>' prior: 0!
+ Halt is provided to support Object>>halt.!

Item was added:
+ ----- Method: Halt>>defaultAction (in category 'priv handling') -----
+ defaultAction
+ 	"No one has handled this error, but now give them a chance to decide how to debug it.  If none handle this either then open debugger (see UnhandedError-defaultAction)"
+ 
+ 	UnhandledError signalForException: self!

Item was added:
+ ----- Method: Halt>>isResumable (in category 'description') -----
+ isResumable
+ 
+ 	^true!

Item was added:
+ Exception subclass: #IllegalResumeAttempt
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !IllegalResumeAttempt commentStamp: '<historical>' prior: 0!
+ This class is private to the EHS implementation.  An instance of it is signaled whenever an attempt is made to resume from an exception which answers false to #isResumable.!

Item was added:
+ ----- Method: IllegalResumeAttempt>>defaultAction (in category 'comment') -----
+ defaultAction
+ 	"No one has handled this error, but now give them a chance to decide how to debug it.  If none handle this either then open debugger (see UnhandedError-defaultAction)"
+ 
+ 	UnhandledError signalForException: self!

Item was added:
+ ----- Method: IllegalResumeAttempt>>isResumable (in category 'comment') -----
+ isResumable
+ 	
+ 	^ false!

Item was added:
+ ----- Method: IllegalResumeAttempt>>readMe (in category 'comment') -----
+ readMe
+ 
+ 	"Never handle this exception!!"!

Item was added:
+ Notification subclass: #InMidstOfFileinNotification
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!

Item was added:
+ ----- Method: InMidstOfFileinNotification>>defaultAction (in category 'as yet unclassified') -----
+ defaultAction
+ 
+ 	self resume: false!

Item was added:
+ NotImplemented subclass: #MessageNotUnderstood
+ 	instanceVariableNames: 'message receiver reachedDefaultHandler'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !MessageNotUnderstood commentStamp: '<historical>' prior: 0!
+ This exception is provided to support Object>>doesNotUnderstand:.!

Item was added:
+ ----- Method: MessageNotUnderstood>>defaultAction (in category 'exceptionDescription') -----
+ defaultAction
+ 	reachedDefaultHandler := true.
+ 	super defaultAction!

Item was added:
+ ----- Method: MessageNotUnderstood>>initialize (in category 'initialize-release') -----
+ initialize
+ 	super initialize.
+ 	reachedDefaultHandler := false!

Item was added:
+ ----- Method: MessageNotUnderstood>>isResumable (in category 'exceptionDescription') -----
+ isResumable
+ 	"Determine whether an exception is resumable."
+ 
+ 	^true!

Item was added:
+ ----- Method: MessageNotUnderstood>>message (in category 'exceptionDescription') -----
+ message
+ 	"Answer the selector and arguments of the message that failed."
+ 
+ 	^message!

Item was added:
+ ----- Method: MessageNotUnderstood>>message: (in category 'exceptionBuilder') -----
+ message: aMessage
+ 
+ 	message := aMessage!

Item was added:
+ ----- Method: MessageNotUnderstood>>messageText (in category 'exceptionBuilder') -----
+ messageText
+ 	"Return an exception's message text."
+ 
+ 	^messageText == nil
+ 		ifTrue:
+ 			[message == nil
+ 				ifTrue: [super messageText]
+ 				ifFalse: [message lookupClass printString, '>>', message selector asString]]
+ 		ifFalse: [messageText]!

Item was added:
+ ----- Method: MessageNotUnderstood>>reachedDefaultHandler (in category 'accessing') -----
+ reachedDefaultHandler
+ 	^reachedDefaultHandler!

Item was added:
+ ----- Method: MessageNotUnderstood>>receiver (in category 'exceptionDescription') -----
+ receiver
+ 	"Answer the receiver that did not understand the message"
+ 
+ 	^ receiver!

Item was added:
+ ----- Method: MessageNotUnderstood>>receiver: (in category 'exceptionBuilder') -----
+ receiver: obj
+ 
+ 	receiver := obj!

Item was added:
+ ArithmeticError subclass: #NaNError
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Numbers-Exceptions'!
+ 
+ !NaNError commentStamp: 'ar 12/14/2010 00:03' prior: 0!
+ NaNError is signaled by various operations that would either result in or operate on an NaN input.!

Item was added:
+ ----- Method: NaNError>>isResumable (in category 'testing') -----
+ isResumable
+ 	"NaNError is always resumable"
+ 	^true!

Item was added:
+ ----- Method: NaNError>>messageText (in category 'accessing') -----
+ messageText
+ 	"Return an exception's message text."
+ 
+ 	^messageText ifNil:['This operation would result in NaN ']!

Item was added:
+ Error subclass: #NonBooleanReceiver
+ 	instanceVariableNames: 'object'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!

Item was added:
+ ----- Method: NonBooleanReceiver>>isResumable (in category 'signaledException') -----
+ isResumable
+ 
+ 	^true!

Item was added:
+ ----- Method: NonBooleanReceiver>>object (in category 'accessing') -----
+ object
+ 	^object!

Item was added:
+ ----- Method: NonBooleanReceiver>>object: (in category 'accessing') -----
+ object: anObject
+ 	object := anObject!

Item was added:
+ Error subclass: #NotImplemented
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!

Item was added:
+ NotImplemented subclass: #NotYetImplemented
+ 	instanceVariableNames: 'receiverClass selector context'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !NotYetImplemented commentStamp: 'jcg 10/21/2009 01:20' prior: 0!
+ Sent by #notYetImplemented.  Better than the age-old behavior of opening a notifier window, because this can be caught and handled.
+ !

Item was added:
+ ----- Method: NotYetImplemented class>>signal (in category 'signaling') -----
+ signal
+ 	"Call only from #notYetImplemented.  Find the context that sent #nYI... this is the method that needs to be implemented."
+ 	| ctxt ex |
+ 	ctxt := thisContext sender sender.
+ 	ex := self new.
+ 	ex receiverClass: ctxt receiver class selector: ctxt selector.
+ 	ex messageText: ctxt printString.
+ 	ex signal.
+ 		!

Item was added:
+ ----- Method: NotYetImplemented>>receiverClass (in category 'accessing') -----
+ receiverClass
+ 	^receiverClass!

Item was added:
+ ----- Method: NotYetImplemented>>receiverClass:selector: (in category 'initialize') -----
+ receiverClass: cls selector: sel
+ 	receiverClass := cls.
+ 	selector := sel.!

Item was added:
+ ----- Method: NotYetImplemented>>selector (in category 'accessing') -----
+ selector
+ 	^selector!

Item was added:
+ Exception subclass: #Notification
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions-Kernel'!
+ 
+ !Notification commentStamp: '<historical>' prior: 0!
+ A Notification is an indication that something interesting has occurred.  If it is not handled, it will pass by without effect.!

Item was added:
+ ----- Method: Notification>>defaultAction (in category 'exceptionDescription') -----
+ defaultAction
+ 	"No action is taken. The value nil is returned as the value of the message that signaled the exception."
+ 
+ 	^nil!

Item was added:
+ ----- Method: Notification>>isResumable (in category 'exceptionDescription') -----
+ isResumable
+ 	"Answer true. Notification exceptions by default are specified to be resumable."
+ 
+ 	^true!

Item was added:
+ Error subclass: #NumberParserError
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Numbers-Exceptions'!

Item was added:
+ Error subclass: #OutOfMemory
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !OutOfMemory commentStamp: '<historical>' prior: 0!
+ OutOfMemory is signaled when an allocation fails due to not having enough memory. Its default action signals the low-space semaphore.!

Item was added:
+ ----- Method: OutOfMemory>>defaultAction (in category 'as yet unclassified') -----
+ defaultAction
+ 	Smalltalk signalLowSpace.!

Item was added:
+ ----- Method: OutOfMemory>>isResumable (in category 'as yet unclassified') -----
+ isResumable
+ 	^true!

Item was added:
+ Notification subclass: #ProvideAnswerNotification
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!

Item was added:
+ NotImplemented subclass: #SubclassResponsibility
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !SubclassResponsibility commentStamp: 'fbs 1/26/2013 00:20' prior: 0!
+ I am signalled when a subclass fails to implement an "abstract method" and something sends an instance of this subclass the unimplemented message.!

Item was added:
+ Notification subclass: #TimedOut
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !TimedOut commentStamp: 'brp 10/21/2004 17:47' prior: 0!
+ I am signalled by #duration:timeoutDo: if the receiving block takes too long to execute.
+ 
+ I am signalled by a watchdog process spawned by #duration:timeoutDo: and caught in the same method. 
+ 
+ I am not intended to be used elsewhere.!

Item was added:
+ Exception subclass: #UnhandledError
+ 	instanceVariableNames: 'exception'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!

Item was added:
+ ----- Method: UnhandledError class>>signalForException: (in category 'as yet unclassified') -----
+ signalForException: anError
+ 
+ 	^ self new
+ 		exception: anError;
+ 		signal!

Item was added:
+ ----- Method: UnhandledError>>defaultAction (in category 'priv handling') -----
+ defaultAction
+ 	"The current computation is terminated. The cause of the error should be logged or reported to the user. If the program is operating in an interactive debugging environment the computation should be suspended and the debugger activated."
+ 	^ToolSet debugError: exception.!

Item was added:
+ ----- Method: UnhandledError>>exception (in category 'as yet unclassified') -----
+ exception
+ 
+ 	^ exception!

Item was added:
+ ----- Method: UnhandledError>>exception: (in category 'as yet unclassified') -----
+ exception: anError
+ 
+ 	exception := anError!

Item was added:
+ ----- Method: UnhandledError>>isResumable (in category 'priv handling') -----
+ isResumable
+ 	
+ 	^ false!

Item was added:
+ Notification subclass: #Warning
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Exceptions'!
+ 
+ !Warning commentStamp: '<historical>' prior: 0!
+ A Warning is a Notification which by default should be brought to the attention of the user.!

Item was added:
+ ----- Method: Warning>>defaultAction (in category 'exceptionDescription') -----
+ defaultAction
+ 	"The user should be notified of the occurrence of an exceptional occurrence and given an option of continuing or aborting the computation. The description of the occurrence should include any text specified as the argument of the #signal: message."
+ 	ToolSet
+ 		debugContext: thisContext
+ 		label: 'Warning'
+ 		contents: self messageText, '\\Select Proceed to continue, or close this window to cancel the operation.' withCRs.
+ 	self resume.
+ !

Item was added:
+ ArithmeticError subclass: #ZeroDivide
+ 	instanceVariableNames: 'dividend'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Numbers-Exceptions'!
+ 
+ !ZeroDivide commentStamp: '<historical>' prior: 0!
+ ZeroDivide may be signaled when a mathematical division by 0 is attempted.!

Item was added:
+ ----- Method: ZeroDivide class>>dividend: (in category 'exceptionInstantiator') -----
+ dividend: argument
+ 	^self new dividend: argument; yourself!

Item was added:
+ ----- Method: ZeroDivide class>>signalWithDividend: (in category 'signaling') -----
+ signalWithDividend: aDividend
+ 
+ 	^(self dividend: aDividend) signal!

Item was added:
+ ----- Method: ZeroDivide>>dividend (in category 'exceptionDescription') -----
+ dividend
+ 	"Answer the number that was being divided by zero."
+ 
+ 	^dividend!

Item was added:
+ ----- Method: ZeroDivide>>dividend: (in category 'exceptionBuilder') -----
+ dividend: argument
+ 	"Specify the number that was being divided by zero."
+ 
+ 	dividend := argument!

Item was added:
+ ----- Method: ZeroDivide>>isResumable (in category 'exceptionDescription') -----
+ isResumable
+ 	"Determine whether an exception is resumable."
+ 
+ 	^true!



More information about the Squeak-dev mailing list