Class.st
author claus
Thu, 29 Sep 1994 21:38:11 +0100
changeset 153 22f4c4bcc93f
parent 139 19ccaf2031c8
child 155 edd7fc34e104
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	       All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

ClassDescription subclass:#Class
       instanceVariableNames:'classvars comment subclasses classFileName package'
       classVariableNames:'UpdatingChanges FileOutErrorSignal'
       poolDictionaries:''
       category:'Kernel-Classes'
!

Class comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Class.st,v 1.19 1994-09-29 20:38:11 claus Exp $
'!

!Class class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	       All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/Class.st,v 1.19 1994-09-29 20:38:11 claus Exp $
"
!

documentation
"
    Class adds more functionality to classes; minimum stuff has already
    been defined in Behavior and ClassDescription; this adds naming, categories etc.

    Also change management and recompilation is defined here (since the superclasses
    do not have enough symbolic information to support compilation).

    For a minimum system, the compiler is planned to generate classes as subclasses of
    Behavior - to excludes all name, source info etc., 
    however, normally all classes are subclasses of Class.

    Instance variables:

	classvars       <String>        the names of the class variables
	comment         <String>        the classes comment
	subclasses      <Collection>    cached collection of subclasses
					(currently unused - but will be soon)
	classFileName   <String>        the file (or nil) where the classes
					sources are found (currently not used)
	package         <Symbol>        the package, in which the class was defined

    Class variables:

	UpdatingChanges <Boolean>       true if the changes-file shall be updated
					(except during startup and when filing in, this flag
					 is usually true)

    WARNING: layout known by compiler and runtime system
"
! !

!Class class methodsFor:'initialization'!

initialize
    "the classvariable 'UpdatingChanges' controls if changes are put
     into the changes-file; normally this variable is set to true, but
     (for example) during fileIn or when changes are applied, it is set to false
     to avoid putting too much junk into the changes-file."
     
    UpdatingChanges := true.
    FileOutErrorSignal isNil ifTrue:[
	Object initialize.

	FileOutErrorSignal := Object errorSignal newSignalMayProceed:false.
	FileOutErrorSignal nameClass:self message:#fileOutErrorSignal.
	FileOutErrorSignal notifierString:'error during fileOut'.
    ]
! !

!Class class methodsFor:'signal access'!

fileOutErrorSignal
    ^ FileOutErrorSignal
! !

!Class class methodsFor:'creating new classes'!

new
    "creates and returs a new class"

    |newClass|

    newClass := super new.
    newClass setComment:(self comment)
	       category:(self category).
    ^ newClass
! !

!Class methodsFor:'subclass creation'!

subclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s category:cat
    "create a new class as a subclass of an existing class (the receiver).
     The subclass will have indexed variables if the receiving-class has."

    self isVariable ifFalse:[
	^ self class
	    name:t
	    inEnvironment:Smalltalk
	    subclassOf:self
	    instanceVariableNames:f
	    variable:false
	    words:true
	    pointers:true
	    classVariableNames:d
	    poolDictionaries:s
	    category:cat
	    comment:nil
	    changed:false
    ].
    self isBytes ifTrue:[
	^ self
	    variableByteSubclass:t
	    instanceVariableNames:f
	    classVariableNames:d
	    poolDictionaries:s
	    category:cat
    ].
    self isLongs ifTrue:[
	^ self
	    variableLongSubclass:t
	    instanceVariableNames:f
	    classVariableNames:d
	    poolDictionaries:s
	    category:cat
    ].
    self isFloats ifTrue:[
	^ self
	    variableFloatSubclass:t
	    instanceVariableNames:f
	    classVariableNames:d
	    poolDictionaries:s
	    category:cat
    ].
    self isDoubles ifTrue:[
	^ self
	    variableDoubleSubclass:t
	    instanceVariableNames:f
	    classVariableNames:d
	    poolDictionaries:s
	    category:cat
    ].
    self isWords ifTrue:[
	^ self
	    variableWordSubclass:t
	    instanceVariableNames:f
	    classVariableNames:d
	    poolDictionaries:s
	    category:cat
    ].
    ^ self
	variableSubclass:t
	instanceVariableNames:f
	classVariableNames:d
	poolDictionaries:s
	category:cat
!

variableSubclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s category:cat
    "create a new class as a subclass of an existing class (the receiver) 
     in which the subclass has indexable pointer variables"

    self isVariable ifTrue:[
	self isPointers ifFalse:[
	    ^ self error:
		'cannot make a variable pointer subclass of a variable non-pointer class'
	]
    ].

    ^ self class
	name:t
	inEnvironment:Smalltalk
	subclassOf:self
	instanceVariableNames:f
	variable:true
	words:false
	pointers:true
	classVariableNames:d
	poolDictionaries:s
	category:cat
	comment:nil
	changed:false
!

variableByteSubclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s category:cat
    "create a new class as a subclass of an existing class (the receiver) 
     in which the subclass has indexable byte-sized nonpointer variables"

    self isVariable ifTrue:[
	self isBytes ifFalse:[
	    ^ self error:
		'cannot make a variable byte subclass of a variable non-byte class'
	].
    ].

    ^ self class
	name:t
	inEnvironment:Smalltalk
	subclassOf:self
	instanceVariableNames:f
	variable:true
	words:false
	pointers:false
	classVariableNames:d
	poolDictionaries:s
	category:cat
	comment:nil
	changed:false
!

variableWordSubclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s category:cat
    "create a new class as a subclass of an existing class (the receiver) 
     in which the subclass has indexable word-sized nonpointer variables"

    self isVariable ifTrue:[
	self isWords ifFalse:[
	    ^ self error:
		'cannot make a variable word subclass of a variable non-word class'
	].
    ].

    ^ self class
	name:t
	inEnvironment:Smalltalk
	subclassOf:self
	instanceVariableNames:f
	variable:true
	words:true
	pointers:false
	classVariableNames:d
	poolDictionaries:s
	category:cat
	comment:nil
	changed:false
!

variableLongSubclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s category:cat
    "create a new class as a subclass of an existing class (the receiver) 
     in which the subclass has indexable long-sized nonpointer variables"

    self isVariable ifTrue:[
	self isLongs ifFalse:[
	    ^ self error:
		'cannot make a variable long subclass of a variable non-long class'
	].
    ].

    ^ self class
	name:t
	inEnvironment:Smalltalk
	subclassOf:self
	instanceVariableNames:f
	variable:#long 
	words:false
	pointers:false
	classVariableNames:d
	poolDictionaries:s
	category:cat
	comment:nil
	changed:false
!

variableFloatSubclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s category:cat

    "create a new class as a subclass of an existing class (the receiver) 
     in which the subclass has indexable float-sized nonpointer variables"

    self isVariable ifTrue:[
	self isFloats ifFalse:[
	    ^ self error:
		'cannot make a variable float subclass of a variable non-float class'
	].
    ].

    ^ self class
	name:t
	inEnvironment:Smalltalk
	subclassOf:self
	instanceVariableNames:f
	variable:#float 
	words:false
	pointers:false
	classVariableNames:d
	poolDictionaries:s
	category:cat
	comment:nil
	changed:false
!

variableDoubleSubclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s category:cat

    "create a new class as a subclass of an existing class (the receiver) 
     in which the subclass has indexable double-sized nonpointer variables"

    self isVariable ifTrue:[
	self isDoubles ifFalse:[
	    ^ self error:
		'cannot make a variable double subclass of a variable non-double class'
	].
    ].

    ^ self class
	name:t
	inEnvironment:Smalltalk
	subclassOf:self
	instanceVariableNames:f
	variable:#double 
	words:false
	pointers:false
	classVariableNames:d
	poolDictionaries:s
	category:cat
	comment:nil
	changed:false
! !

!Class methodsFor:'ST/V subclass creation'!

subclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s
    "this method allows fileIn of ST/V classes 
     (which seem to have no category)"

    ^ self subclass:t 
	   instanceVariableNames:f
	   classVariableNames:d
	   poolDictionaries:s
	   category:'ST/V classes'
!

variableByteSubclass:t classVariableNames:d poolDictionaries:s
    "this method allows fileIn of ST/V variable byte classes 
     (which seem to have no category and no instvars)"

    ^ self variableByteSubclass:t 
	   instanceVariableNames:''
	   classVariableNames:d
	   poolDictionaries:s
	   category:'ST/V classes'
!

variableSubclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s
    "this method allows fileIn of ST/V variable pointer classes 
     (which seem to have no category)"

    ^ self variableSubclass:t 
	   instanceVariableNames:f
	   classVariableNames:d
	   poolDictionaries:s
	   category:'ST/V classes'
! !

!Class methodsFor:'accessing'!

classVariableString
    "return a string of the class variables names.
     Only names of class variables defined in this class are in the
     returned string."

    classvars isNil ifTrue:[^ ''].
    ^ classvars

    "
     Object classVariableString 
     Float classVariableString  
    "
!

classVarNames
    "return a collection of the class variable name-strings.
     Only names of class variables defined in this class are included
     in the returned collection - use allClassVarNames, to get all known names."

    classvars isNil ifTrue:[
	^ OrderedCollection new
    ].
    ^ classvars asCollectionOfWords

    "
     Object classVarNames 
     Float classVarNames
    "
!

classVarAt:aSymbol
    "return the value of a class variable.
     Currently, this returns nil if there is no such classvar -
     this may change."

    "
     this hides the (current) implementation of classVariables
     from the outside world. Currently, classvars are stored in
     the Smalltalk dictionary with a funny name, since there are
     no classPools yet.
    "
    ^ Smalltalk at:(self name , ':' , aSymbol) asSymbol
!

classVarAt:aSymbol put:something
    "store something in a classvariable.
     Currently this creates a global with a funny name if no such
     classVar exists - this may change."

    "
     this hides the (current) implementation of classVariables
     from the outside world. Currently, classvars are stored in
     the Smalltalk dictionary with a funny name, since there are
     no classPools yet.
    "
    Smalltalk at:(self name , ':' , aSymbol) asSymbol put:something.
!

allClassVarNames
    "return a collection of all the class variable name-strings
     this includes all superclass-class variables"

    ^ self addAllClassVarNamesTo:(OrderedCollection new)

    "
     Float allClassVarNames
    "
!

comment
    "return the comment (aString) of the class"

    ^ comment

    "
     Object comment 
    "
!          

setComment:aString
    "set the comment of the class to be the argument, aString;
     do NOT create a change record"

    comment := aString
!

comment:aString
    "set the comment of the class to be the argument, aString;
     create a change record and notify dependents."

    |oldComment|

    comment ~= aString ifTrue:[
	oldComment := comment.
	comment := aString.
	self changed:#comment with:oldComment.
	self addChangeRecordForClassComment:self.
    ]
!

classFileName
    "return the name of the file from which the class was compiled.
     This is currently NOT used."

    ^ classFileName
!

definition
    "return an expression-string to define myself"

    |s|

    s := WriteStream on:(String new).
    self fileOutDefinitionOn:s.
    ^ s contents

    "
     Object definition 
     Point definition  
    "
!

sharedPools
    "ST/X does not (currently) support pools"

    ^ #()
!

setComment:com category:categoryStringOrSymbol
    "set the comment and category of the class;
     do NOT create a change record"

    comment := com.
    category := categoryStringOrSymbol asSymbol
!

setClassVariableString:aString
    "set the classes classvarnames string. 
     This is a dangerous (low level) operation, since the 
     classvariables are not really created or updated. Also,
     NO change record is written."

    classvars := aString
!

classVariableString:aString
    "set the classes classvarnames string; 
     Initialize new class variables with nil, clear and remove old ones. 
     No change record is written and no classes are recompiled."

    |prevVarNames varNames|

    "ignore for metaclasses except the one"
    (self isMeta) ifTrue:[
	(self == Metaclass) ifFalse:[
	    ^ self
	]
    ].
    (classvars = aString) ifFalse:[
	prevVarNames := self classVarNames.
	classvars := aString.
	varNames := self classVarNames.

	"new ones get initialized to nil;
	 - old ones are nilled and removed from Smalltalk"

	varNames do:[:aName |
	    (prevVarNames includes:aName) ifFalse:[
		"a new one"
		self classVarAt:aName put:nil.
	    ] ifTrue:[
		prevVarNames remove:aName
	    ]
	].
	"left overs are gone"
	prevVarNames do:[:aName |
	    self classVarAt:aName put:nil.
	    Smalltalk removeKey:(self name , ':' , aName) asSymbol.
	].
	Smalltalk changed
    ]
!

addClassVarName:aString
    "add a class variable if not already there and initialize it with nil.
     Also write a change record and notify dependents.
     BUG: Currently, no recompilation is done - this will change."

    (self classVarNames includes:aString) ifFalse:[
	self classVariableString:(self classVariableString , ' ' , aString).
	self addChangeRecordForClass:self.
	self changed:#definition.
    ]
!

removeClassVarName:aString
    "remove a class variable if not already there.
     Also write a change record and notify dependents.
     BUG: Currently, no recompilation is done - this will change."

    |names newNames|

    names := self classVarNames.
    (names includes:aString) ifTrue:[
	newNames := ''.
	names do:[:nm | nm ~= aString ifTrue:[newNames := newNames , nm , ' ']].
	self classVariableString:newNames withoutSpaces.
	self addChangeRecordForClass:self.
	self changed:#definition.
    ]
!

renameCategory:oldCategory to:newCategory
    "rename a category (changes category of those methods).
     Append a change record and notifies dependents."

    |any|

    any := false.
    methodArray do:[:aMethod |
	aMethod category = oldCategory ifTrue:[
	    aMethod category:newCategory.
	    any := true.
	]
    ].
    any ifTrue:[
	self addChangeRecordForRenameCategory:oldCategory to:newCategory.
	self changed:#methodCategory.
    ]
! !

!Class methodsFor:'adding/removing'!

addSelector:newSelector withMethod:newMethod
    "add the method given by 2nd argument under the selector given by
     1st argument to the methodDictionary. 
     Append a change record to the changes file and tell dependents."

    (super addSelector:newSelector withMethod:newMethod) ifTrue:[
	self addChangeRecordForMethod:newMethod
    ]
!

removeSelector:aSelector
    "remove the selector, aSelector and its associated method 
     from the methodDictionary.
     Append a change record to the changes file and tell dependents."

    (super removeSelector:aSelector) ifTrue:[
	self addChangeRecordForRemoveSelector:aSelector.
	self changed:#methodDictionary with:aSelector.
    ]
! !

!Class methodsFor:'changes management'!

updateChanges:aBoolean
    "turn on/off changes management"

    |prev|

    prev := UpdatingChanges.
    UpdatingChanges := aBoolean.
    ^ prev
!

changesStream
    "return a Stream for the changes file"

    |aStream|

    UpdatingChanges ifTrue:[
	aStream := FileStream oldFileNamed:'changes'.
	aStream isNil ifTrue:[
	    aStream := FileStream newFileNamed:'changes'.
	    aStream isNil ifTrue:[
		self error:'cannot update changes file'.
		^ nil
	    ]
	].
	aStream setToEnd
    ].
    ^ aStream
!

sourcesStream
    "return a Stream for the sources file"

    |aStream|

    UpdatingChanges ifTrue:[
	aStream := FileStream oldFileNamed:('st.sou').
	aStream isNil ifTrue:[
	    aStream := FileStream newFileNamed:'st.sou'.
	    aStream isNil ifTrue:[
		Transcript showCr:'cannot update sources file'.
		^ nil
	    ]
	].
	aStream setToEnd
    ].
    ^ aStream
!

addChangeRecordForMethod:aMethod
    "add a method-change-record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	self fileOutMethod:aMethod on:aStream.
	aStream cr.
	aStream close.

	"this test allows a smalltalk without Projects/ChangeSets"
	Project notNil ifTrue:[
	    Project addMethodChange:aMethod in:self
	]
    ]
!

addChangeRecordForRemoveSelector:aSelector
    "add a method-remove-record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	self printClassNameOn:aStream.
	aStream nextPutAll:(' removeSelector:#' , aSelector).
	aStream nextPut:(aStream class chunkSeparator).
	aStream cr.
	aStream close
    ]
!

addChangeRecordForClass:aClass
    "add a class-definition-record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	aClass fileOutDefinitionOn:aStream.
	aStream nextPut:(aStream class chunkSeparator).
	aStream cr.
	aStream close
    ]
!

addChangeRecordForClassInstvars:aClass
    "add a class-instvars-record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	aClass fileOutClassInstVarDefinitionOn:aStream.
	aStream nextPut:(aStream class chunkSeparator).
	aStream cr.
	aStream close
    ]
!

addChangeRecordForClassComment:aClass
    "add a class-comment-record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	aClass fileOutCommentOn:aStream.
	aStream nextPut:(aStream class chunkSeparator).
	aStream cr.
	aStream close
    ]
!

addChangeRecordForClassRename:oldName to:newName
    "add a class-rename-record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	aStream nextPutAll:('Smalltalk renameClass:' , oldName , ' to:''' , newName , '''').
	aStream nextPut:(aStream class chunkSeparator).
	aStream cr.
	aStream close
    ]
!

addChangeRecordForClassRemove:oldName
    "add a class-remove-record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	aStream nextPutAll:('Smalltalk removeClass:' , oldName).
	aStream nextPut:(aStream class chunkSeparator).
	aStream cr.
	aStream close
    ]
!

addChangeRecordForRenameCategory:oldCategory to:newCategory
    "add a category-rename record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	self printClassNameOn:aStream.
	aStream nextPutAll:(' renameCategory:' , oldCategory storeString).
	aStream nextPutAll:(' to:' , newCategory storeString).
	aStream nextPut:(aStream class chunkSeparator).
	aStream cr.
	aStream close
    ]
!

addChangeRecordForChangeCategory
    "add a category change record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	self printClassNameOn:aStream.
	aStream nextPutAll:(' category:' , category storeString).
	aStream nextPut:(aStream class chunkSeparator).
	aStream cr.
	aStream close
    ]
!

addChangeRecordForSnapshot:aFileName
    "add a snapshot-record to the changes file"

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	aStream nextPutAll:('''---- snapshot ' , aFileName , ' ',
			    Date today printString , ' ' ,
			    Time now printString ,
			    ' ----''!!').
	aStream cr.
	aStream close
    ]
! !

!Class methodsFor:'compiling'!

compile:code
    "compile code, aString for this class; if sucessful update method
     dictionary."

    self compiler compile:code forClass:self
!

compile:code notifying:requestor
    "compile code, aString for this class; on any error, notify
     requestor, anObject with the error reason"

    self compiler compile:code forClass:self notifying:requestor
!

recompileMethodsAccessingAny:setOfNames
    "recompile all methods accessing a variable from setOfNames"

    self recompileMethodsAccessingAny:setOfNames orSuper:false 
!

recompileMethodsAccessingAny:setOfNames orSuper:superBoolean
    "recompile all methods accessing a variable from setOfNames,
     or super (if superBoolean is true)"

    |p|

    selectorArray do:[:aSelector |
	|m|

	m := self compiledMethodAt:aSelector.
	p := Parser parseMethod:(m source) in:self.
	(p isNil 
	 or:[(p usedVars notNil and:[p usedVars includesAny:setOfNames])
	 or:[superBoolean and:[p usesSuper]]]) ifTrue:[
	    self recompile:aSelector
	]
    ]
!

recompile:aSelector
    "recompile the method associated with the argument, aSelector;
     used when a superclass changes instances and we have to recompile
     subclasses"

    |cat code upd|

    upd := Class updateChanges:false.
    [
	cat := (self compiledMethodAt:aSelector) category.
	code := self sourceCodeAt:aSelector.
	self compiler compile:code forClass:self inCategory:cat
    ] valueNowOrOnUnwindDo:[
	Class updateChanges:upd
    ]
!

recompile
    "recompile all methods
     used when a class changes instances and therefore all methods
     have to be recompiled"

    selectorArray do:[:aSelector |
	self recompile:aSelector
    ]
!

recompileAll
    "recompile this class and all subclasses"

    |classes|

    classes := self subclasses.
    self recompile.
    classes do:[:aClass |
	aClass recompileAll
    ]
!

recompileInvalidatedMethods:trap
    "recompile all invalidated methods"

    |trapCode trapByteCode|

    trapCode := trap code.
    trapByteCode := trap byteCode.

    selectorArray do:[:aSelector |
	|m|

	m := self compiledMethodAt:aSelector.
	((m code == trapCode) and:[m byteCode == trapByteCode]) ifTrue:[
	    self recompile:aSelector
	]
    ]
! !

!Class methodsFor:'queries'!

isClass
    "return true, if the receiver is some kind of class 
     (a real class, not just behavior);
     true is returned here - the method is redefined from Object"

    ^ true
!

categories
    "Return a Collection of all method-category strings known in class"

    |newList cat|

    newList := OrderedCollection new.
    methodArray do:[:aMethod |
	cat := aMethod category.
	newList indexOf:cat ifAbsent:[newList add:cat]
    ].
    ^ newList
!

allCategories
    "Return a Collection of all method-category strings known in class
     and all superclasses"

    ^ self addAllCategoriesTo:(OrderedCollection new)
! !

!Class methodsFor:'private'!

addAllClassVarNamesTo:aCollection
    "helper - add the name-strings of the class variables and of the class-vars
     of all superclasses to the argument, aCollection. Return aCollection"

    (superclass notNil) ifTrue:[
	superclass addAllClassVarNamesTo:aCollection
    ].
    classvars notNil ifTrue:[
	aCollection addAll:(classvars asCollectionOfWords).
    ].
    ^ aCollection
!

addCategoriesTo:aCollection
    "helper - add categories to the argument, aCollection"

    |cat|

    methodArray do:[:aMethod |
	cat := aMethod category.
	(aCollection detect:[:element | cat = element]
		     ifNone:[nil])
	    isNil ifTrue:[
		aCollection add:cat
	]
    ].
    ^ aCollection
!

addAllCategoriesTo:aCollection
    "helper - add categories and all superclasses categories
     to the argument, aCollection"

    (superclass notNil) ifTrue:[
	superclass addAllCategoriesTo:aCollection
    ].
    ^ self addCategoriesTo:aCollection
! !

!Class methodsFor:'fileIn interface'!

methodsFor:aCategory
    "return a ClassCategoryReader to read in and compile methods for me.
     This one actually creates the ClassReader when code is filed-in."

    ^ ClassCategoryReader class:self category:aCategory
!

publicMethodsFor:aCategory
    "this method allows fileIn of ENVY methods 
     (although ST/X currently does NOT support method visibility).
     Returns a ClassCategoryReader to read in and compile methods for me."

    ^ self methodsFor:aCategory
!

privateMethodsFor:aCategory
    "this method allows fileIn of ENVY methods 
     (although ST/X currently does NOT really enforce method visibility yet).
     Returns a ClassCategoryReader to read in and compile methods for me."

    ^ (self methodsFor:aCategory) privateProtocol
!

ignoredMethodsFor:aCategory
    "this is a speciality of ST/X - it allows quick commenting of methods
     from a source-file by replacing the 'methodsFor:' by 'ignoredMethodsFor'.
     Returns a ClassCategoryReader to read in and skip methods."

    ^ (self methodsFor:aCategory) ignoreMethods
!

methods
    "this method allows fileIn of ST/V methods -
     return a ClassCategoryReader to read in and compile methods for me."

    ^ ClassCategoryReader class:self category:'ST/V methods'
! !

!Class methodsFor:'c function interfacing'!

cInterfaceFunction:selector calling:cFunctionNameString args:argTypeArray returning:returnType
    "create an interface to an existing (i.e. already linked in) c function.
     The function can be called by sending selector to the receiver class.
     The c-function has the name cFunctionNameString, and expects parameters as specified in
     argTypeArray. The functions return value has a type as specified by returnType.
     Warning: this interface is EXPERIMENTAL - it may change or even be removed."

    StubGenerator createStubFor:selector calling:cFunctionNameString 
			   args:argTypeArray returning:returnType
			     in:self                          

    "
     Object subclass:#CInterface
	    instanceVariableNames:''
	    classVariableNames:''
	    poolDictionaries:''
	    category:'Examples'.

     CInterface cInterfaceFunction:#printfOn:format:withFloat: 
			   calling:'fprintf' 
			      args:#(ExternalStream String Float) 
			 returning:#SmallInteger.

     CInterface printfOn:Stdout format:'this is a float: %g' withFloat:(Float pi). Stdout cr  
    "
! !

!Class methodsFor:'fileOut'!

fileOutCommentOn:aStream
    "append an expression on aStream, which defines my comment"

    aStream nextPutAll:name.
    aStream nextPutAll:' comment:'.
    comment isNil ifTrue:[
	aStream nextPutAll:''''''
    ] ifFalse:[
	aStream nextPutAll:(comment storeString)
    ].
    aStream cr
!

fileOutDefinitionOn:aStream
    "append an expression on aStream, which defines myself."

    |isVar line|

    "take care of nil-superclass"
    superclass isNil ifTrue:[
"/      previous versions of stc were not able to compile nil-subclasses;
"/      after 2.10, it can ...
"/        line := 'Object "nil"'.
	line := 'nil'
    ] ifFalse:[
	line := (superclass name)
    ].
    superclass isNil ifTrue:[
	isVar := self isVariable
    ] ifFalse:[
	"I cant remember what this is for ?"
	isVar := (self isVariable and:[superclass isVariable not])
    ].
    isVar ifTrue:[
	self isBytes ifTrue:[
	    line := line , ' variableByteSubclass:#'
	] ifFalse:[
	    self isWords ifTrue:[
		line := line , ' variableWordSubclass:#'
	    ] ifFalse:[
		self isLongs ifTrue:[
		    line := line , ' variableLongSubclass:#'
		] ifFalse:[
		    self isFloats ifTrue:[
			line := line , ' variableFloatSubclass:#'
		    ] ifFalse:[
			self isDoubles ifTrue:[
			    line := line , ' variableDoubleSubclass:#'
			] ifFalse:[
			    line := line , ' variableSubclass:#'
			]
		    ]
		]
	    ]
	]
    ] ifFalse:[
	line := line , ' subclass:#'
    ].
    line := line , name.
    aStream nextPutAll:line.

    aStream crTab. 
    aStream nextPutAll:' instanceVariableNames:'''.
    self printInstVarNamesOn:aStream indent:16.
    aStream nextPutAll:''''.

    aStream crTab.
    aStream nextPutAll:' classVariableNames:'''.
    self printClassVarNamesOn:aStream indent:16.
    aStream nextPutAll:''''.

    aStream crTab.
    aStream nextPutAll:' poolDictionaries:'''''.

    aStream crTab.
    aStream nextPutAll:' category:'.
    category isNil ifTrue:[
	aStream nextPutAll:''''''
    ] ifFalse:[
	aStream nextPutAll:(category asString storeString)
    ].
    aStream cr
!

fileOutClassInstVarDefinitionOn:aStream
    "append an expression to define my classInstanceVariables on aStream"

    aStream nextPutAll:(name , ' class instanceVariableNames:''').
    self class printInstVarNamesOn:aStream indent:8.
    aStream nextPutAll:''''
!

fileOutCategory:aCategory on:aStream
    "file out all methods belonging to aCategory, aString onto aStream"

    |nMethods count sep source|

    methodArray notNil ifTrue:[
	nMethods := 0.
	methodArray do:[:aMethod |
	    (aCategory = aMethod category) ifTrue:[
		nMethods := nMethods + 1
	    ]
	].
	sep := aStream class chunkSeparator.
	(nMethods ~~ 0) ifTrue:[
	    aStream nextPut:sep.
	    self printClassNameOn:aStream.
	    aStream nextPutAll:' methodsFor:'''.
	    aCategory notNil ifTrue:[
		aStream nextPutAll:aCategory
	    ].
	    aStream nextPut:$'. aStream nextPut:sep. aStream cr.
	    aStream cr.
	    count := 1.
	    methodArray do:[:aMethod |
		(aCategory = aMethod category) ifTrue:[
		    source := aMethod source.
		    source isNil ifTrue:[
			FileOutErrorSignal raiseRequestWith:'no source for method'
		    ] ifFalse:[
			aStream nextChunkPut:(aMethod source).
		    ].
		    (count ~~ nMethods) ifTrue:[
			aStream cr.
			aStream cr
		    ].
		    count := count + 1
		]
	    ].
	    aStream space.
	    aStream nextPut:sep.
	    aStream cr
	]
    ]
!

fileOutMethod:aMethod on:aStream
    "file out the method, aMethod onto aStream"

    |cat sep source|

    methodArray notNil ifTrue:[
	sep := aStream class chunkSeparator.
	aStream nextPut:sep.
	self printClassNameOn:aStream.
	aStream nextPutAll:' methodsFor:'''.
	cat := aMethod category.
	cat notNil ifTrue:[
	    aStream nextPutAll:cat
	].
	aStream nextPut:$'.
	aStream nextPut:sep.
	aStream cr.
	aStream cr.
	source := aMethod source.
	source isNil ifTrue:[
	    FileOutErrorSignal 
		raiseRequestWith:self
		errorString:('no source for method: ' ,
			     self name , '>>' ,
			     (self selectorForMethod:aMethod))
	] ifFalse:[
	    aStream nextChunkPut:(aMethod source).
	].
	aStream space.
	aStream nextPut:sep.
	aStream cr
    ]
!

fileOutOn:aStream
    "file out my definition and all methods onto aStream"

    |collectionOfCategories copyrightText sep|

    "
     if there is a copyright method, add a copyright
     at the beginning
    "
    (self class selectorArray includes:#copyright) ifTrue:[
	"
	 get the copyright methods source,
	 and insert at beginning.
	"
	copyrightText := (self class compiledMethodAt:#copyright) source.
	copyrightText isNil ifTrue:[
	    "
	     no source available - trigger an error
	    "
	    self error:'no source for class ' , name , ' available. Cannot fileOut'.
	    ^ self
	].
	copyrightText := copyrightText asCollectionOfLines.
	copyrightText := copyrightText copyFrom:2 to:(copyrightText size).
	copyrightText do:[:line | aStream nextPutAll:line. aStream cr.].
    ].

    sep := aStream class chunkSeparator.
    "
     first, a timestamp
    "
    aStream nextPutAll:(Smalltalk timeStamp).
    aStream nextPut:sep. 
    aStream cr.
    aStream cr.

    "
     then the definition
    "
    self fileOutDefinitionOn:aStream.
    aStream nextPut:sep. 
    aStream cr.
    aStream cr.
    "
     optional classInstanceVariables
    "
    self class instanceVariableString isBlank ifFalse:[
	self fileOutClassInstVarDefinitionOn:aStream.
	aStream nextPut:sep. 
	aStream cr.
	aStream cr
    ].

    "
     a comment - if any
    "
    comment notNil ifTrue:[
	aStream nextPutAll:name.
	aStream nextPutAll:' comment:'.
	aStream nextPutAll:(comment storeString).
	aStream nextPut:sep.
	aStream cr.
	aStream cr
    ].

    "
     methods from all categories in metaclass
    "
    collectionOfCategories := self class categories.
    collectionOfCategories notNil ifTrue:[
	collectionOfCategories do:[:aCategory |
	    self class fileOutCategory:aCategory on:aStream.
	    aStream cr
	]
    ].
    "
     methods from all categories in myself
    "
    collectionOfCategories := self categories.
    collectionOfCategories notNil ifTrue:[
	collectionOfCategories do:[:aCategory |
	    self fileOutCategory:aCategory on:aStream.
	    aStream cr
	]
    ].
    "
     optionally an initialize message
    "
    (self class implements:#initialize) ifTrue:[
	aStream nextPutAll:(name , ' initialize').
	aStream nextPut:sep.
	aStream cr
    ]
!

fileOutCategory:aCategory
    "create a file 'class-category.st' consisting of all methods in aCategory.
     If the current project is not nil, create the file in the projects
     directory."

    |aStream fileName|

    fileName := name , '-' , aCategory , '.st'.
    fileName replaceAll:(Character space) by:$_.

    "
     this test allows a smalltalk to be built without Projects/ChangeSets
    "
    Project notNil ifTrue:[
	fileName := Project currentProjectDirectory , fileName.
    ].

    "
     if file exists, save original in a .sav file
    "
    fileName asFilename exists ifTrue:[
	fileName asFilename copyTo:(fileName , '.sav')
    ].
    aStream := FileStream newFileNamed:fileName.
    aStream isNil ifTrue:[
	^ FileOutErrorSignal raiseRequestWith:fileName
				  errorString:('cannot create file:', fileName)
    ].
    self fileOutCategory:aCategory on:aStream.
    aStream close
!

fileOutMethod:aMethod
    "create a file 'class-method.st' consisting of the method, aMethod.
     If the current project is not nil, create the file in the projects
     directory."

    |aStream fileName selector|

    selector := self selectorForMethod:aMethod.
    selector notNil ifTrue:[
	fileName := name , '-' , selector, '.st'.
	fileName replaceAll:$: by:$_.
	"
	 this test allows a smalltalk to be built without Projects/ChangeSets
	"
	Project notNil ifTrue:[
	    fileName := Project currentProjectDirectory , fileName.
	].

	"
	 if file exists, save original in a .sav file
	"
	fileName asFilename exists ifTrue:[
	    fileName asFilename copyTo:(fileName , '.sav')
	].
	aStream := FileStream newFileNamed:fileName.
	aStream isNil ifTrue:[
	    ^ FileOutErrorSignal raiseRequestWith:fileName
				      errorString:('cannot create file:', fileName)
	].
	self fileOutMethod:aMethod on:aStream.
	aStream close
    ]
!

fileOut
    "create a file 'class.st' consisting of all methods in myself.
     If the current project is not nil, create the file in the projects
     directory. Care is taken, to not clobber any existing file in
     case of errors (for example: disk full). Also, since the classes
     methods need a valid sourcefile, the current sourceFile cannot be rewritten,
     but must be kept around until the fileOut is finished."

    |aStream baseName dirName fileName newFileName needRename|

    baseName := (Smalltalk fileNameForClass:self name).
    fileName := baseName , '.st'.
    "
     this test allows a smalltalk to be built without Projects/ChangeSets
    "
    Project notNil ifTrue:[
	dirName := Project currentProjectDirectory
    ] ifFalse:[
	dirName := ''
    ].
    fileName := dirName , fileName.
    "
     if file exists, copy the existing to a .sav-file,
     create new file in a .new-file,
     and, if that worked rename afterwards ...
    "
    fileName asFilename exists ifTrue:[
	fileName asFilename copyTo:('/tmp/' , baseName , '.sav').
	newFileName := dirName , baseName , '.new'.
	needRename := true
    ] ifFalse:[
	newFileName := fileName.
	needRename := false
    ].

    aStream := FileStream newFileNamed:newFileName.
    aStream isNil ifTrue:[
	^ FileOutErrorSignal raiseRequestWith:newFileName
				  errorString:('cannot create file:', newFileName)
    ].
    self fileOutOn:aStream.
    aStream close.

    "
     finally, replace the old-file
     be careful, if the old one is a symbolic link; in this case,
     we have to do a copy ...
    "
    needRename ifTrue:[
	newFileName asFilename copyTo:fileName.
	newFileName asFilename delete
    ].
!

fileOutIn:aFileDirectory
    "create a file 'class.st' consisting of all methods in self in
     directory aFileDirectory (ignoring any directory setting in
     the current porject)."

    |aStream fileName|

    fileName := (Smalltalk fileNameForClass:self name) , '.st'.
    aStream := FileStream newFileNamed:fileName in:aFileDirectory.
    aStream isNil ifTrue:[
	^ self error:('cannot create source file:', fileName)
    ].
    self fileOutOn:aStream.
    aStream close
! !

!Class methodsFor:'printOut'!

printClassNameOn:aStream
    "helper for fileOut - print my name if I am not a Metaclass;
     otherwise my name without -class followed by space-class"

    self isMeta ifTrue:[
	aStream nextPutAll:(name copyTo:(name size - 5)).
	aStream nextPutAll:' class'
    ] ifFalse:[
	name printOn:aStream
    ]
!

printNameArray:anArray on:aStream indent:indent
    "print an array of strings separated by spaces; when the stream
     defines a lineLength, break when this limit is reached; indent
     every line; used to printOut instanve variable names"

    |thisName nextName arraySize lenMax pos mustBreak line spaces|

    arraySize := anArray size.
    arraySize ~~ 0 ifTrue:[
	pos := indent.
	lenMax := aStream lineLength.
	thisName := anArray at:1.
	line := ''.
	1 to:arraySize do:[:index |
	    line := line , thisName.
	    pos := pos + thisName size.
	    (index == arraySize) ifFalse:[
		nextName := anArray at:(index + 1).
		mustBreak := false.
		(lenMax > 0) ifTrue:[
		    ((pos + nextName size) > lenMax) ifTrue:[
			mustBreak := true
		    ]
		].
		mustBreak ifTrue:[
		    aStream nextPutAll:line.
		    aStream cr.
		    spaces isNil ifTrue:[
			spaces := String new:indent
		    ].
		    line := spaces.
		    pos := indent
		] ifFalse:[
		    line := line , ' '.
		    pos := pos + 1
		].
		thisName := nextName
	    ]
	].
	aStream nextPutAll:line
    ]
!

printClassVarNamesOn:aStream indent:indent
    "print the class variable names indented and breaking at line end"

    self printNameArray:(self classVarNames) on:aStream indent:indent
!

printInstVarNamesOn:aStream indent:indent
    "print the instance variable names indented and breaking at line end"

    self printNameArray:(self instVarNames) on:aStream indent:indent
!

printHierarchyOn:aStream
    "print my class hierarchy on aStream"

    self printHierarchyAnswerIndentOn:aStream
!

printHierarchyAnswerIndentOn:aStream
    "print my class hierarchy on aStream - return indent
     recursively calls itself to print superclass and use returned indent
     for my description - used in the browser"

    |indent|

    indent := 0.
    (superclass notNil) ifTrue:[
	indent := (superclass printHierarchyAnswerIndentOn:aStream) + 2
    ].
    aStream spaces:indent.
    aStream nextPutAll:name.
    aStream nextPutAll:' ('.
    self printInstVarNamesOn:aStream indent:(indent + name size + 2).
    aStream nextPutAll:')'.
    aStream cr.
    ^ indent
!

printFullHierarchyOn:aStream indent:indent
    "print myself and all subclasses on aStream.
     recursively calls itself to print subclasses. 
     Can be used to print hierarchy on the printer."

    aStream spaces:indent.
    aStream bold.
    aStream nextPutAll:name.
    aStream normal.
    aStream nextPutAll:' ('.
    self printInstVarNamesOn:aStream indent:(indent + name size + 2).
    aStream nextPutAll:')'.
    aStream cr.

    (self subclasses sort:[:a :b | a name < b name]) do:[:aSubclass |
	aSubclass printFullHierarchyOn:aStream indent:(indent + 2)
    ]

    "|printStream|
     printStream := Printer new.
     Object printFullHierarchyOn:printStream indent:0.
     printStream close"
!

printOutDefinitionOn:aPrintStream
    "print out my definition"

    aPrintStream nextPutAll:'class                '.
    aPrintStream bold.
    aPrintStream nextPutAll:name.
    aPrintStream normal.
    aPrintStream cr. 

    aPrintStream nextPutAll:'superclass           '.
    superclass isNil ifTrue:[
	aPrintStream nextPutAll:'Object'
    ] ifFalse:[
	aPrintStream nextPutAll:(superclass name)
    ].
    aPrintStream cr. 

    aPrintStream nextPutAll:'instance Variables   '.
    self printInstVarNamesOn:aPrintStream indent:21.
    aPrintStream cr. 

    aPrintStream nextPutAll:'class Variables      '.
    self printClassVarNamesOn:aPrintStream indent:21.
    aPrintStream cr.

    category notNil ifTrue:[
	aPrintStream nextPutAll:'category             '.
	aPrintStream nextPutAll:(category printString).
	aPrintStream cr
    ].

    comment notNil ifTrue:[
	aPrintStream cr.
	aPrintStream nextPutAll:'comment:'.
	aPrintStream cr.
	aPrintStream italic.
	aPrintStream nextPutAll:comment.
	aPrintStream normal.
	aPrintStream cr
    ]
!

printOutSourceProtocol:aString on:aPrintStream
    "given the source in aString, print the methods message specification
     and any method comments - without source; used to generate documentation
     pages"

    |text line nQuote index|

    text := aString asText.
    (text size < 1) ifTrue:[^self].
    aPrintStream bold.
    aPrintStream nextPutAll:(text at:1).
    aPrintStream cr.
    (text size >= 2) ifTrue:[
	aPrintStream italic.
	line := (text at:2).
	nQuote := line occurrencesOf:(Character doubleQuote).
	(nQuote == 2) ifTrue:[
	    aPrintStream nextPutAll:line.
	    aPrintStream cr
	] ifFalse:[
	    (nQuote == 1) ifTrue:[
		aPrintStream nextPutAll:line.
		aPrintStream cr.
		index := 3.
		line := text at:index.
		nQuote := line occurrencesOf:(Character doubleQuote).
		[nQuote ~~ 1] whileTrue:[
		    aPrintStream nextPutAll:line.
		    aPrintStream cr.
		    index := index + 1.
		    line := text at:index.
		    nQuote := line occurrencesOf:(Character doubleQuote)
		].
		aPrintStream nextPutAll:(text at:index).
		aPrintStream cr
	     ]
	 ]
    ].
    aPrintStream normal
!

printOutSource:aString on:aPrintStream
    "print out a source-string; the message-specification is printed bold,
     comments are printed italic"

    |text textIndex textSize line lineIndex lineSize inComment aCharacter|
    text := aString asText.
    aPrintStream bold.
    aPrintStream nextPutAll:(text at:1).
    aPrintStream normal.
    aPrintStream cr.
    inComment := false.
    textSize := text size.
    textIndex := 2.
    [textIndex <= textSize] whileTrue:[
	line := text at:textIndex.
	((line occurrencesOf:Character doubleQuote) == 0) ifTrue:[
	    aPrintStream nextPutAll:line
	] ifFalse:[
	    lineSize := line size.
	    lineIndex := 1.
	    [lineIndex <= lineSize] whileTrue:[
		aCharacter := line at:lineIndex.
		(aCharacter == Character doubleQuote) ifTrue:[
		    inComment ifTrue:[
			aPrintStream normal.
			aPrintStream nextPut:aCharacter.
			inComment := false
		    ] ifFalse:[
			aPrintStream nextPut:aCharacter.
			aPrintStream italic.
			inComment := true
		    ]
		] ifFalse:[
		    aPrintStream nextPut:aCharacter
		].
		lineIndex := lineIndex + 1
	    ]
	].
	aPrintStream cr.
	textIndex := textIndex + 1
    ]
!
    
printOutCategory:aCategory on:aPrintStream
    "print out all methods in aCategory on aPrintStream should be a PrintStream"

    |any|
    methodArray notNil ifTrue:[
	any := false.
	methodArray do:[:aMethod |
	    (aCategory = aMethod category) ifTrue:[
		any := true
	    ]
	].
	any ifTrue:[
	     aPrintStream italic.
	     aPrintStream nextPutAll:aCategory.
	     aPrintStream normal.
	     aPrintStream cr.
	     aPrintStream cr.
	     methodArray do:[:aMethod |
		 (aCategory = aMethod category) ifTrue:[
		     self printOutSource:(aMethod source) on:aPrintStream.
		     aPrintStream cr.
		     aPrintStream cr
		 ]
	     ].
	     aPrintStream cr
	 ]
    ]
!

printOutOn:aPrintStream
    "print out all methods on aPrintStream which should be a printStream"

    |collectionOfCategories|
    self printOutDefinitionOn:aPrintStream.
    aPrintStream cr.
    collectionOfCategories := self class categories.
    collectionOfCategories notNil ifTrue:[
	aPrintStream nextPutAll:'class protocol'.
	aPrintStream cr. aPrintStream cr.
	collectionOfCategories do:[:aCategory |
	    self class printOutCategory:aCategory on:aPrintStream
	]
    ].
    collectionOfCategories := self categories.
    collectionOfCategories notNil ifTrue:[
	aPrintStream nextPutAll:'instance protocol'.
	aPrintStream cr. aPrintStream cr.
	collectionOfCategories do:[:aCategory |
	    self printOutCategory:aCategory on:aPrintStream
	]
    ]
!

printOutCategoryProtocol:aCategory on:aPrintStream
    |any|

    methodArray notNil ifTrue:[
	any := false.
	methodArray do:[:aMethod |
	    (aCategory = aMethod category) ifTrue:[
		any := true
	    ]
	].
	any ifTrue:[
	    aPrintStream italic.
	    aPrintStream nextPutAll:aCategory.
	    aPrintStream normal.
	    aPrintStream cr.
	    aPrintStream cr.
	    methodArray do:[:aMethod |
		(aCategory = aMethod category) ifTrue:[
		    self printOutSourceProtocol:(aMethod source) 
					     on:aPrintStream.
		    aPrintStream cr.
		    aPrintStream cr
		]
	    ].
	    aPrintStream cr
	]
    ]
!

printOutProtocolOn:aPrintStream
    |collectionOfCategories|
    self printOutDefinitionOn:aPrintStream.
    aPrintStream cr.
    collectionOfCategories := self class categories.
    collectionOfCategories notNil ifTrue:[
	aPrintStream nextPutAll:'class protocol'.
	aPrintStream cr. aPrintStream cr.
	collectionOfCategories do:[:aCategory |
	    self class printOutCategoryProtocol:aCategory on:aPrintStream
	]
    ].
    collectionOfCategories := self categories.
    collectionOfCategories notNil ifTrue:[
	aPrintStream nextPutAll:'instance protocol'.
	aPrintStream cr. aPrintStream cr.
	collectionOfCategories do:[:aCategory |
	    self printOutCategoryProtocol:aCategory on:aPrintStream
	]
    ]
! !

!Class methodsFor: 'binary storage'!

addGlobalsTo: globalDictionary manager: manager
"
    classPool == nil ifFalse: [
	classPool associationsDo: [:assoc|
	    globalDictionary at: assoc put: self
	]
    ]
"
!

storeBinaryDefinitionOf: anAssociation on: stream manager: manager
    "not usable at the moment - there are no classpools currently"

    | string |

    string := self name, ' classPool at: ', anAssociation key storeString.
    stream nextNumber: 2 put: string size.
    string do: [:char| stream nextPut: char asciiValue]
! !