Back: Number-truncation and round off
Up: Class reference
Forward: Object-built ins
 
Top: GNU Smalltalk User's Guide
Contents: Table of Contents
Index: Class index
About: About this document

6.105 Object

Defined in namespace Smalltalk
Category: Language-Implementation
I am the root of the Smalltalk class system. All classes in the system are subclasses of me.

6.105.1 Object: built ins  (instance)
6.105.2 Object: change and update  (instance)
6.105.3 Object: class type methods  (instance)
6.105.4 Object: copying  (instance)
6.105.5 Object: debugging  (instance)
6.105.6 Object: dependents access  (instance)
6.105.7 Object: error raising  (instance)
6.105.8 Object: finalization  (instance)
6.105.9 Object: printing  (instance)
6.105.10 Object: Relational operators  (instance)
6.105.11 Object: saving and loading  (instance)
6.105.12 Object: storing  (instance)
6.105.13 Object: syntax shortcuts  (instance)
6.105.14 Object: testing functionality  (instance)
6.105.15 Object: VM callbacks  (instance)


6.105.1 Object: built ins

= arg
Answer whether the receiver is equal to arg. The equality test is by default the same as that for equal objects. = must not fail; answer false if the receiver cannot be compared to arg

== arg
Answer whether the receiver is the same object as arg. This is a very fast test and is called 'identity'

addToBeFinalized
Add the object to the list of objects to be finalized when there are no more references to them

asOop
Answer the object index associated to the receiver. The object index doesn't change when garbage collection is performed.

at: anIndex
Answer the index-th indexed instance variable of the receiver

at: anIndex put: value
Store value in the index-th indexed instance variable of the receiver

basicAt: anIndex
Answer the index-th indexed instance variable of the receiver. This method must not be overridden, override at: instead

basicAt: anIndex put: value
Store value in the index-th indexed instance variable of the receiver This method must not be overridden, override at:put: instead

basicPrint
Print a basic representation of the receiver

basicSize
Answer the number of indexed instance variable in the receiver

become: otherObject
Change all references to the receiver into references to otherObject. Depending on the implementation, references to otherObject might or might not be transformed into the receiver (respectively, 'two-way become' and 'one-way become'). Implementations doing one-way become answer the receiver (so that it is not lost). Most implementations doing two-way become answer otherObject, but this is not assured - so do answer the receiver for consistency. GNU Smalltalk does two-way become and answers otherObject, but this might change in future versions: programs should not rely on the behavior and results of #become: .

changeClassTo: aBehavior
Mutate the class of the receiver to be aBehavior. Note: Tacitly assumes that the structure is the same for the original and new class!!

checkIndexableBounds: index
Private - Check the reason why an access to the given indexed instance variable failed

checkIndexableBounds: index put: object
Private - Check the reason why a store to the given indexed instance variable failed

class
Answer the class to which the receiver belongs

halt
Called to enter the debugger

hash
Answer an hash value for the receiver. This hash value is ok for objects that do not redefine ==.

identityHash
Answer an hash value for the receiver. This method must not be overridden

instVarAt: index
Answer the index-th instance variable of the receiver. This method must not be overridden.

instVarAt: index put: value
Store value in the index-th instance variable of the receiver. This method must not be overridden.

isReadOnly
Answer whether the object's indexed instance variables can be written

makeFixed
Avoid that the receiver moves in memory across garbage collections.

makeReadOnly: aBoolean
Set whether the object's indexed instance variables can be written

makeWeak
Make the object a 'weak' one. When an object is only referenced by weak objects, it is collected and the slots in the weak objects are changed to nils by the VM

mark: aSymbol
Private - use this method to mark code which needs to be reworked, removed, etc. You can then find all senders of #mark: to find all marked methods or you can look for all senders of the symbol that you sent to #mark: to find a category of marked methods.

nextInstance
Private - answer another instance of the receiver's class, or nil if the entire object table has been walked

notYetImplemented
Called when a method defined by a class is not yet implemented, but is going to be

perform: selectorOrMessageOrMethod
Send the unary message named selectorOrMessageOrMethod (if a Symbol) to the receiver, or the message and arguments it identifies (if a Message or DirectedMessage), or finally execute the method within the receiver (if a CompiledMethod). In the last case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden

perform: selectorOrMethod with: arg1
Send the message named selectorOrMethod (if a Symbol) to the receiver, passing arg1 to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden

perform: selectorOrMethod with: arg1 with: arg2
Send the message named selectorOrMethod (if a Symbol) to the receiver, passing arg1 and arg2 to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden

perform: selectorOrMethod with: arg1 with: arg2 with: arg3
Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the other arguments to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden

perform: selectorOrMethod withArguments: argumentsArray
Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the elements of argumentsArray as parameters, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden

primError: message
This might start the debugger... Note that we use #basicPrint 'cause #printOn: might invoke an error.

primitiveFailed
Called when a VM primitive fails

removeToBeFinalized
Remove the object from the list of objects to be finalized when there are no more references to them

shouldNotImplement
Called when objects belonging to a class should not answer a selector defined by a superclass

size
Answer the number of indexed instance variable in the receiver

specialBasicAt: index
Similar to basicAt: but without bounds checking. This method is used to support instance mutation when an instance's class definition is changed. This method must not be overriddent

subclassResponsibility
Called when a method defined by a class should be overridden in a subclass


6.105.2 Object: change and update

broadcast: aSymbol
Send the unary message aSymbol to each of the receiver's dependents

broadcast: aSymbol with: anObject
Send the message aSymbol to each of the receiver's dependents, passing anObject

broadcast: aSymbol with: arg1 with: arg2
Send the message aSymbol to each of the receiver's dependents, passing arg1 and arg2 as parameters

broadcast: aSymbol withArguments: anArray
Send the message aSymbol to each of the receiver's dependents, passing the parameters in anArray

broadcast: aSymbol withBlock: aBlock
Send the message aSymbol to each of the receiver's dependents, passing the result of evaluating aBlock with each dependent as the parameter

changed
Send update: for each of the receiver's dependents, passing them the receiver

changed: aParameter
Send update: for each of the receiver's dependents, passing them aParameter

update: aParameter
Default behavior is to do nothing. Called by #changed and #changed:


6.105.3 Object: class type methods

species
This method has no unique definition. Generally speaking, methods which always return the same type usually don't use #class, but #species. For example, a PositionableStream's species is the class of the collection on which it is streaming (used by upTo:, upToAll:, upToEnd). Stream uses species for obtaining the class of next:'s return value, Collection uses it in its #copyEmpty: message, which in turn is used by all collection-re- turning methods. An Interval's species is Array (used by collect:, select:, reject:, etc.).

yourself
Answer the receiver


6.105.4 Object: copying

copy
Returns a shallow copy of the receiver (the instance variables are not copied). The shallow copy receives the message postCopy and the result of postCopy is passed back.

deepCopy
Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables)

postCopy
Performs any changes required to do on a copied object. This is the place where one could, for example, put code to replace objects with copies of the objects

shallowCopy
Returns a shallow copy of the receiver (the instance variables are not copied)


6.105.5 Object: debugging

breakpoint: context return: return
Called back by the system. Must return the value passed through the second parameter

inspect
Print all the instance variables of the receiver on the Transcript

validSize
Answer how many elements in the receiver should be inspected


6.105.6 Object: dependents access

addDependent: anObject
Add anObject to the set of the receiver's dependents. Important: if an object has dependents, it won't be garbage collected.

dependents
Answer a collection of the receiver's dependents.

release
Remove all of the receiver's dependents from the set and allow the receiver to be garbage collected.

removeDependent: anObject
Remove anObject to the set of the receiver's dependents. No problem if anObject is not in the set of the receiver's dependents.


6.105.7 Object: error raising

doesNotUnderstand: aMessage
Called by the system when a selector was not found. message is a Message containing information on the receiver

error: message
Display a walkback for the receiver, with the given error message. Signal an `Error' exception (you can trap it the old way too, with `ExError'

halt: message
Display a walkback for the receiver, with the given error message. Signal an `Halt' exception (you can trap it the old way too, with `ExHalt')


6.105.8 Object: finalization

finalize
Do nothing by default


6.105.9 Object: printing

basicPrintNl
Print a basic representation of the receiver, followed by a new line.

basicPrintOn: aStream
Print a represention of the receiver on aStream

display
Print a represention of the receiver on the Transcript (stdout the GUI is not active). For most objects this is simply its #print representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped.

displayNl
Print a represention of the receiver, then put a new line on the Transcript (stdout the GUI is not active). For most objects this is simply its #printNl representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped.

displayOn: aStream
Print a represention of the receiver on aStream. For most objects this is simply its #printOn: representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped.

displayString
Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped.

print
Print a represention of the receiver on the Transcript (stdout the GUI is not active)

printNl
Print a represention of the receiver on stdout, put a new line the Transcript (stdout the GUI is not active)

printOn: aStream
Print a represention of the receiver on aStream

printString
Answer a String representing the receiver


6.105.10 Object: Relational operators

~= anObject
Answer whether the receiver and anObject are not equal

~~ anObject
Answer whether the receiver and anObject are not the same object


6.105.11 Object: saving and loading

binaryRepresentationObject
This method must be implemented if PluggableProxies are used with the receiver's class. The default implementation raises an exception.

postLoad
Called after loading an object; must restore it to the state before `preStore' was called. Do nothing by default

postStore
Called after an object is dumped; must restore it to the state before `preStore' was called. Call #postLoad by default

preStore
Called before dumping an object; it must *change* it (it must not answer a new object) if necessary. Do nothing by default

reconstructOriginalObject
Used if an instance of the receiver's class is returned as the #binaryRepresentationObject of another object. The default implementation raises an exception.


6.105.12 Object: storing

store
Put a String of Smalltalk code compiling to the receiver on the Transcript (stdout the GUI is not active)

storeNl
Put a String of Smalltalk code compiling to the receiver, followed by a new line, on the Transcript (stdout the GUI is not active)

storeOn: aStream
Put Smalltalk code compiling to the receiver on aStream

storeString
Answer a String of Smalltalk code compiling to the receiver


6.105.13 Object: syntax shortcuts

-> anObject
Creates a new instance of Association with the receiver being the key and the argument becoming the value


6.105.14 Object: testing functionality

ifNil: nilBlock
Evaluate nilBlock if the receiver is nil, else answer self

ifNil: nilBlock ifNotNil: notNilBlock
Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver.

ifNotNil: notNilBlock
Evaluate notNiilBlock if the receiver is not nil, passing the receiver. Else answer nil.

ifNotNil: notNilBlock ifNil: nilBlock
Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver.

isArray
Answer `false'.

isBehavior
Answer `false'.

isCharacter
Answer `false'.

isCharacterArray
Answer `false'.

isClass
Answer `false'.

isFloat
Answer `false'.

isInteger
Answer `false'.

isKindOf: aClass
Answer whether the receiver's class is aClass or a subclass of aClass

isMemberOf: aClass
Returns true if the receiver is an instance of the class 'aClass'

isMeta
Same as isMetaclass

isMetaclass
Answer `false'.

isMetaClass
Same as isMetaclass

isNamespace
Answer `false'.

isNil
Answer whether the receiver is nil

isNumber
Answer `false'.

isSmallInteger
Answer `false'.

isString
Answer `false'.

isSymbol
Answer `false'.

notNil
Answer whether the receiver is not nil

respondsTo: aSymbol
Returns true if the receiver understands the given selector


6.105.15 Object: VM callbacks

badReturnError
Called back when a block performs a bad return

mustBeBoolean
Called by the system when ifTrue:*, ifFalse:*, and: or or: are sent to anything but a boolean

noRunnableProcess
Called back when all processes are suspended

userInterrupt
Called back when the user presses Ctrl-Break




This document was generated on May, 12 2002 using texi2html