Back: CInt-accessing
Up: Class reference
Forward: Class-accessing instances and variables
 
Top: GNU Smalltalk User's Guide
Contents: Table of Contents
Index: Class index
About: About this document

6.28 Class

Defined in namespace Smalltalk
Category: Language-Implementation
I am THE class object. My instances are the classes of the system. I provide information commonly attributed to classes: namely, the class name, class comment (you wouldn't be reading this if it weren't for me), a list of the instance variables of the class, and the class category.

6.28.1 Class: accessing instances and variables  (instance)
6.28.2 Class: filing  (instance)
6.28.3 Class: instance creation  (instance)
6.28.4 Class: instance creation - alternative  (instance)
6.28.5 Class: printing  (instance)
6.28.6 Class: saving and loading  (instance)
6.28.7 Class: testing  (instance)
6.28.8 Class: testing functionality  (instance)


6.28.1 Class: accessing instances and variables

addClassVarName: aString
Add a class variable with the given name to the class pool dictionary

addSharedPool: aDictionary
Add the given shared pool to the list of the class' pool dictionaries

allClassVarNames
Answer the names of the variables in the receiver's class pool dictionary and in each of the superclasses' class pool dictionaries

category
Answer the class category

category: aString
Change the class category to aString

classPool
Answer the class pool dictionary

classVarNames
Answer the names of the variables in the class pool dictionary

comment
Answer the class comment

comment: aString
Change the class name

environment
Answer `environment'.

environment: aNamespace
Set the receiver's environment to aNamespace and recompile everything

initialize
redefined in children (?)

name
Answer the class name

removeClassVarName: aString
Removes the class variable from the class, error if not present, or still in use.

removeSharedPool: aDictionary
Remove the given dictionary to the list of the class' pool dictionaries

sharedPools
Return the names of the shared pools defined by the class


6.28.2 Class: filing

fileOutDeclarationOn: aFileStream
File out class definition to aFileStream

fileOutHeaderOn: aFileStream
Write date and time stamp to aFileStream

fileOutOn: aFileStream
File out complete class description: class definition, class and instance methods


6.28.3 Class: instance creation

extend
Redefine a version of the receiver in the current namespace. Note: this method can bite you in various ways when sent to system classes; read the section on namespaces in the manual for some examples of the problems you can encounter.

subclass: classNameString
instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a fixed subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed.

variableByteSubclass: classNameString
instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a byte variable subclass of the receiver with the given name, instance variables (must be "), class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed.

variableSubclass: classNameString
instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a variable pointer subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed.

variableWordSubclass: classNameString
instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a word variable subclass of the receiver with the given name, instance variables (must be "), class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed.


6.28.4 Class: instance creation - alternative

categoriesFor: method are: categories
Don't use this, it is only present to file in from IBM Smalltalk

subclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames
Don't use this, it is only present to file in from IBM Smalltalk

subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames
Don't use this, it is only present to file in from IBM Smalltalk

variableByteSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames
Don't use this, it is only present to file in from IBM Smalltalk

variableByteSubclass: classNameString classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames
Don't use this, it is only present to file in from IBM Smalltalk

variableLongSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames
Don't use this, it is only present to file in from IBM Smalltalk

variableLongSubclass: classNameString classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames
Don't use this, it is only present to file in from IBM Smalltalk

variableSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames
Don't use this, it is only present to file in from IBM Smalltalk

variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames
Don't use this, it is only present to file in from IBM Smalltalk


6.28.5 Class: printing

article
Answer an article (`a' or `an') which is ok for the receiver's name

printOn: aStream
Print a representation of the receiver on aStream

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


6.28.6 Class: saving and loading

binaryRepresentationVersion
Answer a number >= 0 which represents the current version of the object's representation. The default implementation answers zero.

convertFromVersion: version withFixedVariables: fixed
indexedVariables: indexed for: anObjectDumper This method is called if a VersionableObjectProxy is attached to a class. It receives the version number that was stored for the object (or nil if the object did not use a VersionableObjectProxy), the fixed instance variables, the indexed instance variables, and the ObjectDumper that has read the object. The default implementation ignores the version and simply fills in an instance of the receiver with the given fixed and indexed instance variables (nil if the class instances are of fixed size). If instance variables were removed from the class, extras are ignored; if the class is now fixed and used to be indexed, indexed is not used.

nonVersionedInstSize
Answer the number of instance variables that the class used to have when objects were stored without using a VersionableObjectProxy. The default implementation answers the current instSize.


6.28.7 Class: testing

= aClass
Returns true if the two class objects are to be considered equal.


6.28.8 Class: testing functionality

asClass
Answer the receiver.

isClass
Answer `true'.




This document was generated on May, 12 2002 using texi2html