|
|
6.8 Behavior
- Defined in namespace Smalltalk
- Category: Language-Implementation
- I am the parent class of all "class" type methods. My instances know
about the subclass/superclass relationships between classes, contain
the description that instances are created from, and hold the method
dictionary that's associated with each class. I provide methods for
compiling methods, modifying the class inheritance hierarchy, examining the
method dictionary, and iterating over the class hierarchy.
6.8.1 Behavior class: C interface
- defineCFunc: cFuncNameString
- withSelectorArgs: selectorAndArgs
forClass: aClass
returning: returnTypeSymbol
args: argsArray
Lookup the part on the C interface in this manual -- it is too complex to describe it here ;-) Anyway this is private and kept for backward com- patibility. You should use defineCFunc:withSelectorArgs:returning:args:.
6.8.2 Behavior: accessing class hierarchy
- allSubclasses
- Answer the direct and indirect subclasses of the receiver in a Set
- allSuperclasses
- Answer all the receiver's superclasses in a collection
- subclasses
- Answer the direct subclasses of the receiver in a Set
- superclass
- Answer the receiver's superclass (if any, otherwise answer nil)
- withAllSubclasses
- Answer a Set containing the receiver together with its direct and indirect subclasses
- withAllSuperclasses
- Answer the receiver and all of its superclasses in a collection
6.8.3 Behavior: accessing instances and variables
- allClassVarNames
- Return all the class variables understood by the receiver
- allInstances
- Returns a set of all instances of the receiver
- allInstVarNames
- Answer the names of every instance variables the receiver contained in the receiver's instances
- allSharedPools
- Return the names of the shared pools defined by the class and any of its superclasses
- classPool
- Answer the class pool dictionary. Since Behavior does not support classes with class variables, we answer an empty one; adding variables to it results in an error.
- classVarNames
- Answer all the class variables for instances of the receiver
- instanceCount
- Return a count of all the instances of the receiver
- instVarNames
- Answer an Array containing the instance variables defined by the receiver
- sharedPools
- Return the names of the shared pools defined by the class
- subclassInstVarNames
- Answer the names of the instance variables the receiver inherited from its superclass
6.8.4 Behavior: accessing the methodDictionary
- >> selector
- Return the compiled method associated with selector, from the local method dictionary. Error if not found.
- allSelectors
- Answer a Set of all the selectors understood by the receiver
- compiledMethodAt: selector
- Return the compiled method associated with selector, from the local method dictionary. Error if not found.
- selectorAt: method
- Return selector for the given compiledMethod
- selectors
- Answer a Set of the receiver's selectors
- sourceCodeAt: selector
- Answer source code (if available) for the given compiledMethod
- sourceMethodAt: selector
- This is too dependent on the original implementation
6.8.5 Behavior: browsing
- getAllMethods
- Answer the receiver's complete method dictionary - including inherited and not overridden methods. Each value in the dictionary is an Association, whose key is the class which defines the method, and whose value is the actual CompiledMethod
- getDirectMethods
- Answer the receiver's method dictionary; each value in the dictionary is not a CompiledMethod, but an Association, whose key is the class which defines the method (always the receiver), and whose value is the actual CompiledMethod
- getIndirectMethods
- Answer a dictionary of the receiver's inherited and not overridden methods. Each value in the dictionary is an Association, whose key is the class which defines the method, and whose value is the actual CompiledMethod
- getMethods
- Answer the receiver's complete method dictionary - including inherited and not overridden methods
- getMethodsFor: aSelector
- Get a dictionary with all the definitions of the given selector along the hierarchy. Each key in the dictionary is a class which defines the method, and each value in the dictionary is an Association, whose key is the class again, and whose value is the actual CompiledMethod
- methodDictionary
- Answer the receiver's method dictionary
- newGetMethods
- Answer the receiver's complete method dictionary - including inherited and not overridden methods. Each value in the dictionary is an Association, whose key is the class which defines the method, and whose value is the actual CompiledMethod
6.8.6 Behavior: built ins
- basicNew
- Create a new instance of a class with no indexed instance variables; this method must not be overridden.
- basicNew: numInstanceVariables
- Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables; this method must not be overridden.
- basicNewInFixedSpace
- Create a new instance of a class with no indexed instance variables. The instance is guaranteed not to move across garbage collections. Like #basicNew, this method should not be overridden.
- basicNewInFixedSpace: numInstanceVariables
- Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. The instance is guaranteed not to move across garbage collections. Like #basicNew:, this method should not be overridden.
- compileString: aString
- Compile the code in aString, with no category. Fail if the code does not obey Smalltalk syntax. Answer the generated CompiledMethod if it does
- compileString: aString ifError: aBlock
- Compile the code in aString, with no category. Evaluate aBlock (passing the file name, line number and description of the error) if the code does not obey Smalltalk syntax. Answer the generated CompiledMethod if it does
- flushCache
- Invalidate the method cache kept by the virtual machine. This message should not need to be called by user programs.
- makeDescriptorFor: funcNameString
- returning: returnTypeSymbol
withArgs: argsArray
Private - Answer a CFunctionDescriptor
- methodsFor: category ifTrue: condition
- Compile the following code inside the receiver, with the given category, if condition is true; else ignore it
- new
- Create a new instance of a class with no indexed instance variables
- new: numInstanceVariables
- Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables.
- someInstance
- Private - Answer the first instance of the receiver in the object table
6.8.7 Behavior: compilation (alternative)
- methods
- Don't use this, it's only present to file in from Smalltalk/V
- methodsFor
- Don't use this, it's only present to file in from Dolphin Smalltalk
- methodsFor: category ifFeatures: features
- Start compiling methods in the receiver if this implementation of Smalltalk has the given features, else skip the section
- methodsFor: category stamp: notUsed
- Don't use this, it's only present to file in from Squeak
- privateMethods
- Don't use this, it's only present to file in from IBM Smalltalk
- publicMethods
- Don't use this, it's only present to file in from IBM Smalltalk
6.8.8 Behavior: compiling methods
- methodsFor: aCategoryString
- Calling this method prepares the parser to receive methods to be compiled and installed in the receiver's method dictionary. The methods are put in the category identified by the parameter.
6.8.9 Behavior: creating a class hierarchy
- addSubclass: aClass
- Add aClass asone of the receiver's subclasses.
- removeSubclass: aClass
- Remove aClass from the list of the receiver's subclasses
- superclass: aClass
- Set the receiver's superclass.
6.8.10 Behavior: creating method dictionary
- addSelector: selector withMethod: compiledMethod
- Add the given compiledMethod to the method dictionary, giving it the passed selector. Answer compiledMethod
- compile: code
- Compile method source. If there are parsing errors, answer nil. Else, return a CompiledMethod result of compilation
- compile: code ifError: block
- Compile method source. If there are parsing errors, invoke exception block, 'block' passing file name, line number and error. description. Return a CompiledMethod result of compilation
- compile: code notifying: requestor
- Compile method source. If there are parsing errors, send #error: to the requestor object, else return a CompiledMethod result of compilation
- compileAll
- Recompile all selectors in the receiver. Ignore errors.
- compileAll: aNotifier
- Recompile all selectors in the receiver. Notify aNotifier by sen- ding #error: messages if something goes wrong.
- compileAllSubclasses
- Recompile all selector of all subclasses. Notify aNotifier by sen- ding #error: messages if something goes wrong.
- compileAllSubclasses: aNotifier
- Recompile all selector of all subclasses. Notify aNotifier by sen- ding #error: messages if something goes wrong.
- createGetMethod: what
- Create a method accessing the variable `what'.
- createGetMethod: what default: value
- Create a method accessing the variable `what', with a default value of `value', using lazy initialization
- createSetMethod: what
- Create a method which sets the variable `what'.
- decompile: selector
- Decompile the bytecodes for the given selector.
- defineCFunc: cFuncNameString
- withSelectorArgs: selectorAndArgs
returning: returnTypeSymbol
args: argsArray
Lookup the C interface in the manual. Too complex to describe it here ;-)
- edit: selector
- Open Emacs to edit the method with the passed selector, then compile it
- methodDictionary: aDictionary
- Set the receiver's method dictionary to aDictionary
- recompile: selector
- Recompile the given selector, answer nil if something goes wrong or the new CompiledMethod if everything's ok.
- recompile: selector notifying: aNotifier
- Recompile the given selector. If there are parsing errors, send #error: to the aNotifier object, else return a CompiledMethod result of compilation
- removeSelector: selector
- Remove the given selector from the method dictionary, answer the CompiledMethod attached to that selector
- removeSelector: selector ifAbsent: aBlock
- Remove the given selector from the method dictionary, answer the CompiledMethod attached to that selector. If the selector cannot be found, answer the result of evaluating aBlock.
6.8.11 Behavior: enumerating
- allInstancesDo: aBlock
- Invokes aBlock for all instances of the receiver
- allSubclassesDo: aBlock
- Invokes aBlock for all subclasses, both direct and indirect.
- allSubinstancesDo: aBlock
- Invokes aBlock for all instances of each of the receiver's subclasses.
- allSuperclassesDo: aBlock
- Invokes aBlock for all superclasses, both direct and indirect.
- selectSubclasses: aBlock
- Return a Set of subclasses of the receiver satisfying aBlock.
- selectSuperclasses: aBlock
- Return a Set of superclasses of the receiver satisfying aBlock.
- subclassesDo: aBlock
- Invokes aBlock for all direct subclasses.
- withAllSubclassesDo: aBlock
- Invokes aBlock for the receiver and all subclasses, both direct and indirect.
- withAllSuperclassesDo: aBlock
- Invokes aBlock for the receiver and all superclasses, both direct and indirect.
6.8.12 Behavior: evaluating
- evalString: aString to: anObject
- Answer the stack top at the end of the evaluation of the code in aString. The code is executed as part of anObject
- evalString: aString to: anObject ifError: aBlock
- Answer the stack top at the end of the evaluation of the code in aString. If aString cannot be parsed, evaluate aBlock (see compileString:ifError:). The code is executed as part of anObject
- evaluate: code
- Evaluate Smalltalk expression in 'code' and return result.
- evaluate: code ifError: block
- Evaluate 'code'. If a parsing error is detected, invoke 'block'
- evaluate: code notifying: requestor
- Evaluate Smalltalk expression in 'code'. If a parsing error is encountered, send #error: to requestor
- evaluate: code to: anObject
- Evaluate Smalltalk expression as part of anObject's method definition
- evaluate: code to: anObject ifError: block
- Evaluate Smalltalk expression as part of anObject's method definition. This method is used to support Inspector expression evaluation. If a parsing error is encountered, invoke error block, 'block'
6.8.13 Behavior: hierarchy browsing
- printHierarchy
- Print my entire subclass hierarchy on the terminal.
- printHierarchyEmacs
- Print my entire subclass hierarchy on the terminal, in a format suitable for Emacs parsing.
6.8.14 Behavior: instance creation
- newInFixedSpace
- Create a new instance of a class without indexed instance variables. The instance is guaranteed not to move across garbage collections. If a subclass overrides #new, the changes will apply to this method too.
- newInFixedSpace: numInstanceVariables
- Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. The instance is guaranteed not to move across garbage collections. If a subclass overrides #new:, the changes will apply to this method too.
6.8.15 Behavior: instance variables
- addInstVarName: aString
- Add the given instance variable to instance of the receiver
- removeInstVarName: aString
- Remove the given instance variable from the receiver and recompile all of the receiver's subclasses
6.8.16 Behavior: support for lightweight classes
- article
- Answer an article (`a' or `an') which is ok for the receiver's name
- asClass
- Answer the first superclass that is a full-fledged Class object
- environment
- Answer the namespace that this class belongs to - the same as the superclass, since Behavior does not support namespaces yet.
- name
- Answer the class name; this prints to the name of the superclass enclosed in braces. This class name is used, for example, to print the receiver.
- nameIn: aNamespace
- Answer the class name when the class is referenced from aNamespace - a dummy one, since Behavior does not support names.
6.8.17 Behavior: testing the class hierarchy
- inheritsFrom: aClass
- Returns true if aClass is a superclass of the receiver
- kindOfSubclass
- Return a string indicating the type of class the receiver is
6.8.18 Behavior: testing the form of the instances
- instSize
- Answer how many fixed instance variables are reserved to each of the receiver's instances
- isBits
- Answer whether the instance variables of the receiver's instances are bytes or words
- isBytes
- Answer whether the instance variables of the receiver's instances are bytes
- isFixed
- Answer whether the receiver's instances have no indexed instance variables
- isIdentity
- Answer whether x = y implies x == y for instances of the receiver
- isImmediate
- Answer whether, if x is an instance of the receiver, x copy == x
- isPointers
- Answer whether the instance variables of the receiver's instances are objects
- isVariable
- Answer whether the receiver's instances have indexed instance variables
- isWords
- Answer whether the instance variables of the receiver's instances are words
6.8.19 Behavior: testing the method dictionary
- canUnderstand: selector
- Returns true if the instances of the receiver understand the given selector
- hasMethods
- Return whether the receiver has any methods defined
- includesSelector: selector
- Returns true if the local method dictionary contains the given selector
- scopeHas: name ifTrue: aBlock
- If methods understood by the receiver's instances have access to a symbol named 'name', evaluate aBlock
- whichClassIncludesSelector: selector
- Answer which class in the receiver's hierarchy contains the implementation of selector used by instances of the class (nil if none does)
- whichSelectorsAccess: instVarName
- Answer a Set of selectors which access the given instance variable
- whichSelectorsReferTo: anObject
- Returns a Set of selectors that refer to anObject
- whichSelectorsReferToByteCode: aByteCode
- Return the collection of selectors in the class which reference the byte code, aByteCode
|