Class.st
author Claus Gittinger <cg@exept.de>
Sat, 09 Dec 1995 15:46:03 +0100
changeset 717 a9d03e3c21cf
parent 708 ba92b2a8477d
child 719 c557a530f971
permissions -rw-r--r--
handle (i.e. double) exclas in the extracted copyRightText

"
 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 revision
                history'
	 classVariableNames:'UpdatingChanges LockChangesFile FileOutErrorSignal
                CatchMethodRedefinitions MethodRedefinitionSignal
                UpdateChangeFileQuerySignal'
	 poolDictionaries:''
	 category:'Kernel-Classes'
!

!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.
"
!

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 production code, the stc compiler is planned to (optionally) 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; either a string,
					a number specifying the offset in classFilename, or nil

	subclasses      <Collection>    cached collection of subclasses
					(currently unused - but will be soon)

	classFilename   <String>        the file (or nil) where the classes
					sources are found 

	package         <Symbol>        the package, in which the class was defined
					(inserted by compilers)

	revision        <String>        revision string - inserted by stc

	history         <any>           a place for a history string (not currently used)

    Class variables:

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

	LockChangesFile <Boolean>       if true, the change file is locked for updates.
					Required when multiple users operate on a common
					change file.
					This is an experimental new feature, being evaluated.

	UpdateChangeFileQuerySignal     used as an upQuery from the change management.
					Whenever a changeRecord is to be written,
					this signal is raised and a handler (if present)
					is supposed to return true or false.
					If unhandled, the value of the global
					UpdatingChanges is returned for backward
					compatibility (which means that the old
					mechanism is used if no query-handler
					is present).

	FileOutErrorSignal              raised when an error occurs during fileOut

	CatchMethodRedefinitions        if true, classes protect themself 
	MethodRedefinitionSignal        (by raising MethodRedefinitionSignal)
					from redefining any existing methods,
					which are defined in another package.
					(i.e. a signal will be raised, if you
					 fileIn something which redefines an
					 existing method and the packages do not
					 match).
					The default is (currently) 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.
    LockChangesFile := false.
    CatchMethodRedefinitions := true.

    FileOutErrorSignal isNil ifTrue:[
	FileOutErrorSignal := ErrorSignal newSignalMayProceed:false.
	FileOutErrorSignal nameClass:self message:#fileOutErrorSignal.
	FileOutErrorSignal notifierString:'error during fileOut'.

	MethodRedefinitionSignal := ErrorSignal newSignalMayProceed:true.
	MethodRedefinitionSignal nameClass:self message:#methodRedefinitionSignal.
	MethodRedefinitionSignal notifierString:'attempt to redefine method from different package'.

	UpdateChangeFileQuerySignal := QuerySignal new mayProceed:true.
	UpdateChangeFileQuerySignal nameClass:self message:#updateChangeFileQuerySignal.
	UpdateChangeFileQuerySignal notifierString:'asking if changeFile update is wanted'.
	UpdateChangeFileQuerySignal handlerBlock:[:ex | ex proceedWith:UpdatingChanges].
    ]
! !

!Class class methodsFor:'Signal constants'!

fileOutErrorSignal
    "return the signal raised when an error occurs while fileing out.
     This is signalled to allow browsers some user feed back in case
     a fileout fails (for example due to disk-full errors)"

    ^ FileOutErrorSignal
!

methodRedefinitionSignal
    "return the signal raised when a method is about to be installed
     which redefines an existing method and the methods packages are not
     equal. This helps when filing in alien code, to prevent existing
     methods to be overwritten or redefined by incompatible methods"

    ^ MethodRedefinitionSignal
!

updateChangeFileQuerySignal
    "return the signal used as an upQuery if the changeFile should be updated.
     If unhandled, the value of UpdatingChanges is returned by the signals
     static handler."

    ^ UpdateChangeFileQuerySignal

! !

!Class class methodsFor:'accessing - flags'!

catchMethodRedefinitions
    "return the redefinition catching flag."

    ^ CatchMethodRedefinitions
!

catchMethodRedefinitions:aBoolean
    "turn on/off redefinition catching. Return the prior value of the flag."

    |prev|

    prev := CatchMethodRedefinitions.
    CatchMethodRedefinitions := aBoolean.
    ^ prev
!

lockChangesFile
    "return true, if the change file is locked during update"

    ^ LockChangesFile
!

lockChangesFile:aBoolean
    "turn on/off change-file-locking. Return the previous value of the flag."

    |prev|

    prev := LockChangesFile.
    LockChangesFile := aBoolean.
    ^ prev
!

updateChanges:aBoolean
    "turn on/off changes management. Return the prior value of the flag."

    |prev|

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

updatingChanges
    "return true if changes are recorded"

    ^ UpdatingChanges
! !

!Class class methodsFor:'enumeration '!

allClassesInCategory:aCategory do:aBlock
    "evaluate aBlock for all classes in aCategory;
     no specific order is defined."

    Smalltalk allBehaviorsDo:[:aClass |
	aClass isMeta ifFalse:[
	    (aClass category = aCategory) ifTrue:[
		aBlock value:aClass
	    ]
	].
    ]

    "
     Class allClassesInCategory:'Kernel-Classes' 
			     do:[:class |Transcript showCr:class name]
    "
!

allClassesInCategory:aCategory inOrderDo:aBlock
    "evaluate aBlock for all classes in aCategory;
     superclasses come first - then subclasses."

    |classes|

    classes := OrderedCollection new.
    Smalltalk allBehaviorsDo:[:aClass |
	aClass isMeta ifFalse:[
	    (aClass category = aCategory) ifTrue:[
		classes add:aClass
	    ]
	]
    ].
    classes topologicalSort:[:a :b | b isSubclassOf:a].
    classes do:aBlock
! !

!Class class methodsFor:'helpers'!

revisionInfoFromString:aString
    "return a dictionary filled with revision info.
     This extracts the relevant info from aString."

    |words info nm mgr|

    info := IdentityDictionary new.
    words := aString asCollectionOfWords.

    "/
    "/ supported formats:
    "/
    "/ $-Header: pathName rev date time user state $
    "/ $-Revision: rev $
    "/ $-Id: fileName rev date time user state $
    "/

    ((words at:1) = '$Header:') ifTrue:[
	nm := words at:2.
	info at:#repositoryPathName put:nm.
	(nm endsWith:',v') ifTrue:[
	    nm := nm copyWithoutLast:2
	].
	info at:#fileName put:nm asFilename baseName.
	info at:#revision put:(words at:3).
	info at:#date put:(words at:4).
	info at:#time put:(words at:5).
	info at:#user put:(words at:6).
	info at:#state put:(words at:7).
	^ info
    ].
    ((words at:1) = '$Revision:') ifTrue:[
	info at:#revision put:(words at:2).
	^ info
    ].
    ((words at:1) = '$Id:') ifTrue:[
	info at:#fileName put:(words at:2).
	info at:#revision put:(words at:3).
	info at:#date put:(words at:4).
	info at:#time put:(words at:5).
	info at:#user put:(words at:6).
	info at:#state put:(words at:7).
	^ info
    ].

    "/
    "/ mhmh - maybe its some other source code system
    "/
    (mgr := Smalltalk at:SourceCodeManager) notNil ifTrue:[
	^ mgr revisionInfoFromString:aString
    ].
    ^ nil

    "Created: 15.11.1995 / 14:58:35 / cg"
    "Modified: 7.12.1995 / 13:21:40 / cg"
! !

!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'!

addClassVarName:aString
    "add a class variable if not already there and initialize it with nil.
     Also writes a change record and notifies 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.
    ]

    "Created: 29.10.1995 / 19:40:51 / cg"
!

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

    ^ self addAllClassVarNamesTo:(OrderedCollection new)

    "
     Float allClassVarNames
    "
!

binaryRevision
    "return the revision-ID from which the class was stc-compiled;
     nil if its an autoloaded or filedIn class.
     If a classes binary is up-to-date w.r.t. the source repository,
     the returned string is the same as the one returned by #revision."

    ^ revision

    "
     Object binaryRevision
    "

    "
     to find all classes which are not up-to-date:

     |classes|

     classes := Smalltalk allClasses 
		    select:[:cls | cls binaryRevision notNil and:[cls binaryRevision ~= cls revision]].
     SystemBrowser browseClasses:classes title:'classes which are not up-to-date'
    "

    "Created: 7.12.1995 / 10:58:47 / cg"
!

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

    ^ classFilename
!

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.
!

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
    "
!

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  
    "
!

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 any|

    "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"
	any := false.

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

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

    |stream string|

    "the comment is either a string, or an integer specifying the
     position within the classes sourcefile ...
    "
    comment isNumber ifTrue:[
	classFilename notNil ifTrue:[
	    stream := self sourceStream. "/ Smalltalk sourceFileStreamFor:classFilename.
	    stream notNil ifTrue:[
		stream position:comment.
		string := String readFrom:stream onError:''.
		stream close.
		^ string
	    ]
	]
    ].
    ^ comment

    "
     Object comment 
    "
!

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 := self comment.
	comment := aString.
	self changed:#comment with:oldComment.
	self addChangeRecordForClassComment:self.
    ]

    "Created: 29.10.1995 / 19:41:24 / cg"
!

definition
    "return an expression-string to define myself"

    |s|

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

    "
     Object definition 
     Point definition  
    "
!

history 
    "return the history  of the class"

    ^ history 

    "
     Object history   
    "
!

history:aString
    "set the history of the class."

    history  := aString
!

package
    "return the package of the class"

    ^ package

    "
     Object package  
    "
!

package:aStringOrSymbol
    "set the package of the class."

    package := aStringOrSymbol
!

packageSourceCodeInfo
    "return the sourceCodeInfo, which defines the module and the subdirectory
     in which the receiver class was built. 
     This info is extracted from the package id (which is added to stc-compiled classes).
     This method is to be obsoleted soon, since the same info is now found
     in the versionString.

     The info returned consists of a dictionary
     filled with (at least) values at: #module, #directory and #library.
     If no such info is present in the class, nil is returned.
     (this happens with autoloaded and filed0in classes)

     By convention, this info is encoded in the classes package
     string (which is given as argument to stc) as the last word in parenthesis. 
     The info consists of 1 to 3 subcomponents, separated by colons.
     The first defines the classes module (i.e. some application identifier), 
     the second defines the subdirectory within that module, the third
     defines the name of the class library. 
     If left blank, the module info defaults to 'stx',
     the directory info defaults to library name.
     The library name may not be left blank.
     (this is done for backward compatibility,)

     For example: 
	'....(libbasic)'                         -> module: stx directory: libbasic library: libbasic
	'....(stx:libbasic)'                     -> module: stx directory: libbasic library: libbasic
	'....(aeg:libIECInterface)'              -> module: aeg directory: libIECInterface library:libIECInterface
	'....(stx:goodies/persistency:libdbase)' -> module: stx directory: goodies/persistency library:libdbase 

     The way how the sourceCodeManager uses this to find the source location
     depends on the scheme used. For CVS, the module is taken as the -d arg,
     while the directory is prepended to the file name.
     Other schemes may do things differently - these are not yet specified.

     Caveat:
	Encoding this info in the package string seems somewhat kludgy.
    "

    |sourceInfo packageString idx1 idx2 
     moduleString directoryString libraryString components|

    package isNil ifTrue:[^ nil].

    packageString := package asString.
    idx1 := packageString lastIndexOf:$(.
    idx1 ~~ 0 ifTrue:[
	idx2 := packageString indexOf:$) startingAt:idx1+1.
	idx2 ~~ 0 ifTrue:[
	    sourceInfo := packageString copyFrom:idx1 + 1 to:idx2 - 1
	]
    ].
    sourceInfo isNil ifTrue:[^ nil].
    components := sourceInfo asCollectionOfSubstringsSeparatedBy:$:.
    components size == 0 ifTrue:[
	moduleString := 'stx'.
	directoryString := libraryString := ''.
	^ nil
    ] ifFalse:[
	components size == 1 ifTrue:[
	    "/ a single name given - the module becomes 'stx',
	    "/ if the component includes slashes, its the directory
	    "/ otherwise the library
	    "/ 
	    moduleString := 'stx'.
	    directoryString := libraryString := components at:1.
	    (libraryString includes:$/) ifTrue:[
		libraryString := libraryString asFilename baseName
	    ]
	] ifFalse:[
	    components size == 2 ifTrue:[
		"/ two components - assume its the directory and the library
		moduleString := 'stx'.
		directoryString := components at:1.
		libraryString := components at:2.
	    ] ifFalse:[
		"/ all components given
		moduleString := components at:1.
		directoryString := components at:2.
		libraryString := components at:3.
	    ]
	]
    ].
    libraryString isEmpty ifTrue:[
	directoryString notEmpty ifTrue:[
	    libraryString := directoryString asFilename baseName
	].
	libraryString isEmpty ifTrue:[
	    "/ lets extract the library from the liblist file ...
	    libraryString := Smalltalk libraryFileNameOfClass:self.
	    libraryString isNil ifTrue:[^ nil].
	]
    ].

    moduleString isEmpty ifTrue:[
	moduleString := 'stx'.
    ].
    directoryString isEmpty ifTrue:[
	directoryString := libraryString.
    ].

    ^ IdentityDictionary
	with:(#module->moduleString)
	with:(#directory->directoryString)
	with:(#library->libraryString)

    "
     Object packageSourceCodeInfo     
     View packageSourceCodeInfo    
     Model packageSourceCodeInfo  
     BinaryObjectStorage packageSourceCodeInfo  
     MemoryMonitor packageSourceCodeInfo  
     ClockView packageSourceCodeInfo  
    "

    "Created: 4.11.1995 / 20:36:53 / cg"
    "Modified: 25.11.1995 / 18:29:31 / cg"
!

primitiveDefinitions:aString
    "set the primitiveDefinition string"

    self setPrimitiveSpecsAt:1 to:aString.
    self addChangeRecordForPrimitiveDefinitions:self.

    "Created: 29.10.1995 / 19:41:39 / cg"
!

primitiveDefinitionsString
    "return the primitiveDefinition string or nil"

    ^ self getPrimitiveSpecsAt:1

    "
     Object primitiveDefinitionsString 
     String primitiveDefinitionsString
    "
!

primitiveFunctions:aString
    "set the primitiveFunction string"

    self setPrimitiveSpecsAt:3 to:aString.
    self addChangeRecordForPrimitiveFunctions:self.

    "Created: 29.10.1995 / 19:41:48 / cg"
!

primitiveFunctionsString
    "return the primitiveFunctions string or nil"

    ^ self getPrimitiveSpecsAt:3 
!

primitiveSpec
    "return the primitiveSpec or nil"

    ^  primitiveSpec
!

primitiveSpec:anArrayOf3ElementsOrNil
    "set the primitiveSpec or nil"

    primitiveSpec := anArrayOf3ElementsOrNil
!

primitiveVariables:aString
    "set the primitiveVariable string"

    self setPrimitiveSpecsAt:2 to:aString.
    self addChangeRecordForPrimitiveVariables:self.

    "Created: 29.10.1995 / 19:41:58 / cg"
!

primitiveVariablesString
    "return the primitiveVariables string or nil"

    ^ self getPrimitiveSpecsAt:2 
!

removeClassVarName:aString
    "remove a class variable if not already there.
     Also writes a change record and notifies 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.
    ]

    "Created: 29.10.1995 / 19:42:08 / cg"
!

renameCategory:oldCategory to:newCategory
    "rename a category (changes category of those methods).
     Appends 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.
    ]

    "Created: 29.10.1995 / 19:42:15 / cg"
!

revision
    "return the revision-ID of the class which corresponds to the
     rcs-id of the source to which this class is equivalent.
     Initially, this is the same as #binaryRevision; however, once changes have
     been checked into a source repository, the binary continues to remain based upon
     the old revision, while logically, the class has the new (checked-in) revision.
     To check if a source corresponds to a compiled binary, compare this 
     ID with the one returned by #binaryRevision."

    |info|

    info := self revisionInfo.
    info notNil ifTrue:[
	^ info at:#revision
    ].
    ^ revision

    "
     Object revision 
    "

    "Created: 11.11.1995 / 14:27:20 / cg"
    "Modified: 7.12.1995 / 10:54:53 / cg"
!

revision:aString
    "set the revision-ID.
     This should normally not be done in the running system, as the source-manager
     will need this to validate sourcefiles being correct for a given binary
     (and optionally: extracting the required sourcefile from the rcs source)"

    revision := aString
!

setClassFilename:aFilename
    "set the classes filename. 
     This is a dangerous (low level) operation, since the 
     comment and primitiveSpecs may no longer be accessable, if a wrong filename
     is set here."

    classFilename := aFilename

    "Modified: 8.9.1995 / 14:16:48 / claus"
!

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
!

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

    comment := aString
!

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

    |cat|

    comment := com.
    categoryStringOrSymbol isNil ifTrue:[
	cat := ''
    ] ifFalse:[
	cat := categoryStringOrSymbol
    ].
    category := cat asSymbol
!

setHistory:aString
    "set the history of the class."

    history  := aString
!

setPackage:aStringOrSymbol
    "set the package of the class."

    package := aStringOrSymbol
!

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

    ^ #()
!

source
    "return the classes full source code"

    |code aStream|

" this is too slow for big classes ...
    code := String new:1000.
    aStream := WriteStream on:code.
    self fileOutOn:aStream
"
    aStream := FileStream newFileNamed:'__temp'.
    aStream isNil ifTrue:[
	self notify:'cannot create temporary file.'.
	^ nil
    ].
    FileOutErrorSignal handle:[:ex |
	aStream nextPutAll:'"no source available"'.
    ] do:[
	self fileOutOn:aStream.
    ].
    aStream close.
    aStream := FileStream oldFileNamed:'__temp'.
    aStream isNil ifTrue:[
	self notify:'oops - cannot reopen temp file'.
	^ nil
    ].
    code := aStream contents.
    aStream close.
    OperatingSystem removeFile:'__temp'.
    ^ code
!

sourceCodeManager
    "return my source code manager.
     For now, all classes return the same global manager.
     But future versions may support mixed reporitories"

    ^ Smalltalk at:#SourceCodeManager

    "Created: 7.12.1995 / 13:16:46 / cg"
!

sourceStream
    "return an open stream on my sourcefile, nil if that is not available"

    |source fileName aStream cls mgr|

    self isMeta ifTrue:[
	cls := self soleInstance
    ] ifFalse:[
	cls := self
    ].
    classFilename notNil ifTrue:[
	source := classFilename
    ] ifFalse:[
	source := (Smalltalk fileNameForClass:cls) , '.st'
    ].

    "/
    "/ if there is no SourceCodeManager, look in
    "/ standard places first
    "/
    (mgr := self sourceCodeManager) isNil ifTrue:[
	fileName := Smalltalk getSourceFileName:source.
	fileName notNil ifTrue:[
	    aStream := fileName asFilename readStream.
	]
    ].

    aStream isNil ifTrue:[
	"/      
	"/ hard case - there is no source file for this class
	"/ (in the source-dir-path).
	"/      

	"/      
	"/ look if my binary is from a dynamically loaded module,
	"/ and, if so, look in the modules directory for the
	"/ source file.
	"/      
	ObjectFileLoader notNil ifTrue:[
	    ObjectFileLoader loadedObjectHandlesDo:[:h |
		|f classes|

		aStream isNil ifTrue:[
		    (classes := h classes) notNil ifTrue:[
			(classes includes:self) ifTrue:[
			    f := h pathName.
			    f := f asFilename directory.
			    f := f construct:source.
			    f exists ifTrue:[
				aStream := f readStream.
			    ].
			].
		    ].
		]
	    ].
	].
    ].

    aStream isNil ifTrue:[

	"/ mhmh - still no source file.
	"/ If there is a SourceCodeManager, ask it to aquire the
	"/ the source for my class, and return an open stream on it. 
	"/ if that one does not know about the source, look in
	"/ standard places

	mgr notNil ifTrue:[
	    aStream := mgr sourceStreamFor:cls.
	    aStream isNil ifTrue:[
		fileName := Smalltalk getSourceFileName:cls name.
		fileName notNil ifTrue:[
		    aStream := fileName asFilename readStream.
		]
	    ].
	].

	"/
	"/ final chance: try current directory
	"/
	aStream isNil ifTrue:[
	    aStream := source asFilename readStream.
	].
    ].

    ^ aStream

    "
     Object sourceStream
     Clock sourceStream
     Autoload sourceStream
    "

    "Created: 10.11.1995 / 21:05:13 / cg"
    "Modified: 7.12.1995 / 13:21:16 / cg"
! !

!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."

    |oldMethod|

    CatchMethodRedefinitions ifTrue:[
	"check for attempts to redefine a method
	 in a different package. Signal a resumable error if so.
	 This allows tracing redefinitions of existing system methods
	 when filing in alien code ....
	 (which we may want to forbit sometimes)
	"
	oldMethod := self compiledMethodAt:newSelector.
	oldMethod notNil ifTrue:[
	    oldMethod package ~= newMethod package ifTrue:[
		"
		 attempt to redefine an existing method, which was
		 defined in another package.
		 If you continue in the debugger, the new method gets installed.
		 Otherwise, the existing (old) method remains valid.

		 You can turn of the catching of redefinitions by setting
		   CatchMethodRedefinitions to false
		 (also found in the NewLaunchers 'settings-misc' menu)
		"
		MethodRedefinitionSignal 
		    raiseErrorString:(' ' , name , '>>' , newSelector) 
	    ]
	]
    ].
    (super addSelector:newSelector withMethod:newMethod) ifTrue:[
	self addChangeRecordForMethod:newMethod.
    ]

    "Created: 29.10.1995 / 19:42:42 / cg"
!

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.
    ]

    "Created: 29.10.1995 / 19:42:47 / cg"
!

unload
    "if the receiver was autoloaded, unload and reinstall it as
     autoloaded. Can be used to get rid of no longer needed autoloaded
     classes. 
     (maybe, autoloaded classes should unload themselfes when no
      longer needed - for example, after some delay when the last instance 
      is gone ...)"

    |nm|

    self wasAutoloaded ifFalse:[

	"
	 can it be done ?
	"
	self methodArray do:[:aMethod |
	    aMethod source isNil ifTrue:[^false].
	    aMethod hasPrimitiveCode ifTrue:[^ false].
	].
    ].

    self allSubclassesDo:[:aClass |
	aClass unload
    ].
    Transcript showCr:'unloading ' , name.

    Autoload removeClass:self.    
    nm := name.
    Smalltalk at:nm put:nil.
    name := nm , ' (leftover)'.
    ObjectMemory flushInlineCaches.
    ObjectMemory flushMethodCache.
    Autoload addClass:nm inCategory:category.
    ^ true

    "
     Clock open.
     Clock unload.
     ClockView unload.
     Clock open
    "
! !

!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]
!

storeBinaryDefinitionOn: stream manager: manager
    "classes will store the name, signature and instvar names.
     They restore by looking for that name in the Smalltalk dictionary.
     However, using the signature, a check for being valid is made at
     restore time."

    |varnames n sz|

    "
     output the signature
    "
    stream nextNumber:4 put:self signature.

    "
     output the instance variable name string
    "
    varnames := self allInstVarNames.
    n := varnames size.
    n == 0 ifTrue:[
	sz := 0
    ] ifFalse:[
	sz := varnames inject:0 into:[:sum :nm | sum + nm size].
	sz := sz + n - 1.
    ].
    stream nextNumber:2 put:sz.
    varnames keysAndValuesDo:[:i :nm |
	nm do:[:c |
	    stream nextPut:c asciiValue
	].
	i ~~ n ifTrue:[stream nextPut:(Character space asciiValue)]
    ].

    "
     output my name
    "
    stream nextNumber:2 put:name size.
    name do:[:c| 
	stream nextPut:c asciiValue
    ]

    "
     |s|
     s := WriteStream on:ByteArray new.
     Rectangle storeBinaryOn:s.
     Object readBinaryFrom:(ReadStream on:s contents)  
    "
! !

!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 isNil ifTrue:[
	^ self error:'this system does not support dynamic C Interface functions'.
    ].

    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:'changes management'!

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

    self writingChangePerform:#addChangeRecordForChangeCategory:to: with:category.
!

addChangeRecordForChangeCategory:category to:aStream
    "append a category change record to aStream"

    self printClassNameOn:aStream.
    aStream nextPutAll:(' category:' , category storeString).
    aStream nextPutChunkSeparator.

    "this test allows a smalltalk without Projects/ChangeSets"
    Project notNil ifTrue:[
	Project addClassDefinitionChangeFor:self
    ]

    "Created: 3.12.1995 / 13:43:33 / cg"
    "Modified: 3.12.1995 / 14:10:34 / cg"
!

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

    self writingChangePerform:#addChangeRecordForClass:to: with:aClass.
!

addChangeRecordForClass:aClass to:aStream
    "append a class-definition-record to aStream"

    aClass isLoaded ifTrue:[
	aClass fileOutDefinitionOn:aStream.
	aStream nextPutChunkSeparator.
	Project notNil ifTrue:[
	    Project addClassDefinitionChangeFor:aClass 
	]
    ]

    "Created: 3.12.1995 / 13:57:44 / cg"
    "Modified: 3.12.1995 / 14:11:26 / cg"
!

addChangeRecordForClassCheckIn:aClass
    "append a class-was-checkedIn-record to the changes file"

    self addInfoRecord:('checkin ' , aClass name , ' (' , aClass revision , ')')

    "Created: 18.11.1995 / 17:04:58 / cg"
    "Modified: 7.12.1995 / 23:45:01 / cg"
!

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

    self writingChangePerform:#addChangeRecordForClassComment:to: with:aClass.
!

addChangeRecordForClassComment:aClass to:aStream
    "append a class-comment-record to aStream"

    aClass fileOutCommentOn:aStream.
    aStream nextPutChunkSeparator.
!

addChangeRecordForClassFileOut:aClass
    "append a class-was-filedOut-record to the changes file"

    self addInfoRecord:('fileOut ' , aClass name) 
!

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

    self writingChangePerform:#addChangeRecordForClassInstvars:to: with:aClass.
!

addChangeRecordForClassInstvars:aClass to:aStream
    "append a class-instvars-record to aStream"

    aClass fileOutClassInstVarDefinitionOn:aStream.
    aStream nextPutChunkSeparator.
!

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

    self writingChangePerform:#addChangeRecordForClassRemove:to: with:oldName.
!

addChangeRecordForClassRemove:oldName to:aStream
    "append a class-remove-record to aStream"

    aStream nextPutAll:('Smalltalk removeClass:' , oldName).
    aStream nextPutChunkSeparator.
!

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

    self writingChangeDo:[:aStream |
	self addChangeRecordForClassRename:oldName to:newName to:aStream
    ]
!

addChangeRecordForClassRename:oldName to:newName to:aStream
    "append a class-rename-record to aStream"

    aStream nextPutAll:('Smalltalk renameClass:' , oldName , ' to:''' , newName , '''').
    aStream nextPutChunkSeparator.
!

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

    (UpdateChangeFileQuerySignal raise) ifTrue:[
	self writingChangePerform:#addChangeRecordForMethod:to: with:aMethod.
	"this test allows a smalltalk without Projects/ChangeSets"
	Project notNil ifTrue:[
	    Project addMethodChange:aMethod in:self
	]
    ]
!

addChangeRecordForMethod:aMethod to:aStream
    "append a method-change-record to aStream"

    self fileOutMethod:aMethod on:aStream.
!

addChangeRecordForMethodCategory:aMethod category:aString
    "add a methodCategory-change-record to the changes file"

    (UpdateChangeFileQuerySignal raise) ifTrue:[
	self writingChangeDo:[:aStream |
	    self addChangeRecordForMethodCategory:aMethod category:aString to:aStream.
	].

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

addChangeRecordForMethodCategory:aMethod category:newCategory to:aStream
    "append a methodCategory-change-record to aStream"

    |selector|

    selector := aMethod selector.
    selector notNil ifTrue:[
	aStream nextPutAll:'('.
	self printClassNameOn:aStream.
	aStream nextPutAll:(' compiledMethodAt:' , selector storeString).
	aStream nextPutAll:(') category:' , newCategory storeString).
	aStream nextPutChunkSeparator.
    ]
!

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

    (UpdateChangeFileQuerySignal raise) ifTrue:[
	self writingChangePerform:#addChangeRecordForMethodPrivacy:to: with:aMethod.
	"this test allows a smalltalk without Projects/ChangeSets"
	Project notNil ifTrue:[
	    Project addMethodPrivacyChange:aMethod in:self
	]
    ]

    "Modified: 27.8.1995 / 22:47:32 / claus"
!

addChangeRecordForMethodPrivacy:aMethod to:aStream
    "append a method-privacy-change-record to aStream"

    |selector|

    selector := aMethod selector.
    selector notNil ifTrue:[
	aStream nextPutAll:'('.
	self printClassNameOn:aStream.
	aStream nextPutAll:(' compiledMethodAt:' , selector storeString).
	aStream nextPutAll:(') privacy:' , aMethod privacy storeString).
	aStream nextPutChunkSeparator.
    ]

    "Modified: 27.8.1995 / 22:59:56 / claus"
!

addChangeRecordForPrimitiveDefinitions:aClass
    "add a primitiveDefinitions-record to the changes file"

    (UpdateChangeFileQuerySignal raise) ifTrue:[
	self writingChangePerform:#addChangeRecordForPrimitiveDefinitions:to: with:aClass.
	Project notNil ifTrue:[
	    Project addPrimitiveDefinitionsChangeFor:aClass
	]
    ]
!

addChangeRecordForPrimitiveDefinitions:aClass to:aStream
    "append a primitiveDefinitions-record to aStream"

    aStream nextPutAll:aClass name; nextPutAll:' primitiveDefinitions:'''; cr; 
	    nextPutAll:(aClass primitiveDefinitionsString storeString copyFrom:2).
    aStream nextPutChunkSeparator.
!

addChangeRecordForPrimitiveFunctions:aClass
    "add a primitiveFunctions-record to the changes file"

    (UpdateChangeFileQuerySignal raise) ifTrue:[
	self writingChangePerform:#addChangeRecordForPrimitiveFunctions:to: with:aClass.
	Project notNil ifTrue:[
	    Project addPrimitiveFunctionsChangeFor:aClass
	]
    ]
!

addChangeRecordForPrimitiveFunctions:aClass to:aStream
    "append a primitiveFunctions-record to aStream"

    aStream nextPutAll:aClass name; nextPutAll:' primitiveFunctions:'''; cr; 
	    nextPutAll:(aClass primitiveFunctionsString storeString copyFrom:2).
    aStream nextPutChunkSeparator.
!

addChangeRecordForPrimitiveVariables:aClass
    "add a primitiveVariables-record to the changes file"

    (UpdateChangeFileQuerySignal raise) ifTrue:[
	self writingChangePerform:#addChangeRecordForPrimitiveVariables:to: with:aClass.
	Project notNil ifTrue:[
	    Project addPrimitiveVariablesChangeFor:aClass
	]
    ]
!

addChangeRecordForPrimitiveVariables:aClass to:aStream
    "append a primitiveVariables-record to aStream"

    aStream nextPutAll:aClass name; nextPutAll:' primitiveVariables:'''; cr; 
	    nextPutAll:(aClass primitiveVariablesString storeString copyFrom:2).
    aStream nextPutChunkSeparator.
!

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

    self writingChangePerform:#addChangeRecordForRemoveSelector:to: with:aSelector.
!

addChangeRecordForRemoveSelector:aSelector to:aStream
    "append a method-remove-record to aStream"

    self printClassNameOn:aStream.
    aStream nextPutAll:(' removeSelector:#' , aSelector).
    aStream nextPutChunkSeparator.
!

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

    self writingChangeDo:[:aStream |
	self addChangeRecordForRenameCategory:oldCategory to:newCategory to:aStream.
    ]
!

addChangeRecordForRenameCategory:oldCategory to:newCategory to:aStream
    "append a category-rename record to aStream"

    self printClassNameOn:aStream.
    aStream nextPutAll:(' renameCategory:' , oldCategory storeString).
    aStream nextPutAll:(' to:' , newCategory storeString).
    aStream nextPutChunkSeparator.
!

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

    self addInfoRecord:('snapshot ' , aFileName) 
!

addChangeRecordForSnapshot:aFileName to:aStream
    "add a snapshot-record to aStream"

    self addInfoRecord:('snapshot ' , aFileName) to:aStream
!

addChangeTimeStampTo:aStream
    "a timestamp - prepended to any change, except infoRecords"

    |info|

    info := 'timestamp ' , OperatingSystem getLoginName , '@' , OperatingSystem getHostName.
    self addInfoRecord:info to:aStream. aStream cr.

    "Created: 18.11.1995 / 15:41:01 / cg"
!

addInfoRecord:aMessage
    "add an info-record (snapshot, class fileOut etc.) to the changes file"

    self writingChangeWithTimeStamp:false perform:#addInfoRecord:to: with:aMessage.

    "Modified: 18.11.1995 / 15:45:10 / cg"
!

addInfoRecord:aMessage to:aStream
    "append an info-record (snapshot, class fileOut etc.) to aStream"

    aStream nextPutAll:('''---- ' , aMessage , ' ',
			Date today printString , ' ' ,
			Time now printString ,
			' ----''').
    aStream nextPutChunkSeparator.
!

changesStream
    "return a Stream for the writing changes file - or nil if no update is wanted"

    |streamType aStream fileName|

    (UpdateChangeFileQuerySignal raise) ifTrue:[
	fileName := ObjectMemory nameForChanges.
        
	LockChangesFile ifTrue:[
	    streamType := LockedFileStream. 
	] ifFalse:[
	    streamType := FileStream.
	].
	aStream := streamType oldFileNamed:fileName.
	aStream isNil ifTrue:[
	    aStream := streamType newFileNamed:fileName.
	    aStream isNil ifTrue:[
		self warn:'cannot create/update the changes file'.
		^ nil
	    ]
	].
	aStream setToEnd
    ].
    ^ aStream

    "Created: 28.10.1995 / 16:53:43 / cg"
    "Modified: 28.10.1995 / 16:55:03 / cg"
!

sourcesStream
    "return a stream for writing the sources file.
     Notice, in ST/X, it is noncommon to use a single
     source file; typically each classes source is kept
     in a separate file."

    |aStream fileName|

    fileName := ObjectMemory nameForSources.
    aStream := FileStream oldFileNamed:fileName.
    aStream isNil ifTrue:[
	aStream := FileStream newFileNamed:fileName.
	aStream isNil ifTrue:[
	    Transcript showCr:'cannot update sources file'.
	    ^ nil
	]
    ].
    aStream setToEnd.
    ^ aStream

    "Created: 28.10.1995 / 16:53:17 / cg"
!

withoutUpdatingChangesDo:aBlock
    "turn off change file update while evaluating aBlock.
     This method makes sure, that the update-flag is correctly restored
     in case of an abort or other error."

    UpdateChangeFileQuerySignal handle:[:ex | 
	ex proceedWith:false
    ] do:[
	aBlock value
    ].
!

writingChangeDo:aBlock
    "common helper to write a change record.
     Opens the changefile and executes aBlock passing the stream
     as argument. WriteErrors are cought and will lead to a warning.
     The changefile is not kept open, to force the change to go to disk
     as soon as possible - thus, in case of a crash, no changes should
     be lost due to buffering."

    self writingChangeWithTimeStamp:true do:aBlock

    "Modified: 18.11.1995 / 15:43:36 / cg"
!

writingChangePerform:aSelector with:anArgument
    self writingChangeWithTimeStamp:true perform:aSelector with:anArgument

    "Created: 28.10.1995 / 16:50:48 / cg"
    "Modified: 18.11.1995 / 15:44:53 / cg"
!

writingChangeWithTimeStamp:doStampIt do:aBlock
    "common helper to write a change record.
     Opens the changefile and executes aBlock passing the stream
     as argument. WriteErrors are cought and will lead to a warning.
     The changefile is not kept open, to force the change to go to disk
     as soon as possible - thus, in case of a crash, no changes should
     be lost due to buffering."

    |aStream|

    aStream := self changesStream.
    aStream notNil ifTrue:[
	FileStream writeErrorSignal handle:[:ex |
	    self warn:('could not update the changes-file\\' , ex errorString) withCRs.
	    ex return
	] do:[
	    doStampIt ifTrue:[self addChangeTimeStampTo:aStream].
	    aBlock value:aStream.
	    aStream cr.
	].
	aStream close
    ]

    "Created: 18.11.1995 / 15:36:02 / cg"
!

writingChangeWithTimeStamp:stampIt perform:aSelector with:anArgument
    self writingChangeWithTimeStamp:stampIt do:[:stream |
	self perform:aSelector with:anArgument with:stream.
    ]

    "Created: 18.11.1995 / 15:44:28 / cg"
! !

!Class methodsFor:'compiling'!

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

    self compilerClass 
	compile:code 
	forClass:self
!

compile:code classified:category
    "compile code, aString for this class; 
     if successful update the method dictionary. 
     The method is classified under category."

    self compilerClass 
	compile:code 
	forClass:self 
	inCategory:category
!

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

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

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

    selectorArray do:[:aSelector |
	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|

    Class withoutUpdatingChangesDo:[
	Class methodRedefinitionSignal handle:[:ex |
	    ex proceed
	] do:[
	    cat := (self compiledMethodAt:aSelector) category.
	    code := self sourceCodeAt:aSelector.
	    self compilerClass compile:code forClass:self inCategory:cat
	]
    ]
!

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
	]
    ]
!

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
	]
    ]
! !

!Class methodsFor:'fileIn interface'!

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."

    ^ ClassCategoryReader skippingChunks
!

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'
!

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
!

methodsForUndefined:categoryString
    "ST-80 compatibility.
     I dont yet know what this does - it was encountered by some tester.
     For now, simply forward it."

    ^ self methodsFor:categoryString
!

primitiveDefinitions
    "this method allows fileIn of classes with primitive code
     outside of methods - it returns a CCReader which skips the next chunks"

    ^ ClassCategoryReader class:self primitiveSpec:#primitiveDefinitions: 
!

primitiveFunctions
    "this method allows fileIn of classes with primitive code
     outside of methods - it returns a CCReader which skips the next chunks"

    ^ ClassCategoryReader class:self primitiveSpec:#primitiveFunctions: 
!

primitiveVariables
    "this method allows fileIn of classes with primitive code
     outside of methods - it returns a CCReader which skips the next chunks"

    ^ ClassCategoryReader class:self primitiveSpec:#primitiveVariables: 
!

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
!

protectedMethodsFor: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) protectedProtocol
!

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
! !

!Class methodsFor:'fileOut'!

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

    |isVar line s|

    "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:[
	    s := ' variableByteSubclass:#'
	] ifFalse:[
	    self isWords ifTrue:[
		s := ' variableWordSubclass:#'
	    ] ifFalse:[
		self isLongs ifTrue:[
		    s := ' variableLongSubclass:#'
		] ifFalse:[
		    self isFloats ifTrue:[
			s := ' variableFloatSubclass:#'
		    ] ifFalse:[
			self isDoubles ifTrue:[
			    s := ' variableDoubleSubclass:#'
			] ifFalse:[
			    s := ' variableSubclass:#'
			]
		    ]
		]
	    ]
	]
    ] ifFalse:[
	s := ' subclass:#'
    ].
    line := line , s , 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:[
	s := ''''''
    ] ifFalse:[
	s := category asString storeString
    ].
    aStream nextPutAll:s.
    aStream cr
!

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 may not be rewritten."

    |aStream baseName dirName fileName newFileName needRename
     mySourceFileName sameFile|

    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 the new file as XXX.new-file,
     and, if that worked rename afterwards ...
    "
    (fileName asFilename exists 
    and:[classFilename notNil]) ifTrue:[
	"
	 check for overwriting my current source file
	 this is not allowed, since it would clobber my methods source
	 file ... you have to save it to some other place.
	 This happens if you ask for a fileOut into the source-directory
	 (from which my methods get their source)
	"
	mySourceFileName := Smalltalk getSourceFileName:classFilename. 
	sameFile := (fileName = mySourceFileName).
	sameFile ifFalse:[
	    mySourceFileName notNil ifTrue:[
		sameFile := (fileName asFilename info at:#id) == (mySourceFileName asFilename info at:#id)
	    ]
	].
	sameFile ifTrue:[
	    ^ FileOutErrorSignal 
		raiseRequestWith:fileName
		errorString:('may not overwrite sourcefile:', fileName)
	].

	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
    ].

    "
     add a change record; that way, administration is much easier,
     since we can see in that changeBrowser, which changes have 
     already found their way into a sourceFile and which must be
     applied again
    "
    self addChangeRecordForClassFileOut:self
!

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
!

fileOutCategory:aCategory except:skippedMethods only:savedMethods on:aStream
    "file out all methods belonging to aCategory, aString onto aStream.
     If skippedMethods is nonNil, those are not saved.
     If savedMethods is nonNil, only those are saved.
     If both are nil, all are saved. See version-method handling in
     fileOut for what this is needed."

    |source sortedSelectors first privacy interrestingMethods|

    methodArray notNil ifTrue:[
	interrestingMethods := OrderedCollection new.
	methodArray do:[:aMethod |
	    |wanted|

	    (aCategory = aMethod category) ifTrue:[
		skippedMethods notNil ifTrue:[
		    wanted := (skippedMethods includesIdentical:aMethod) not
		] ifFalse:[
		    savedMethods notNil ifTrue:[
			wanted := (savedMethods includesIdentical:aMethod).
		    ] ifFalse:[
			wanted := true
		    ]
		].
		wanted ifTrue:[interrestingMethods add:aMethod].
	    ]
	].
	interrestingMethods notEmpty ifTrue:[
	    first := true.
	    privacy := nil.

	    "/
	    "/ sort by selector
	    "/
	    sortedSelectors := interrestingMethods collect:[:m | self selectorAtMethod:m].
	    sortedSelectors sortWith:interrestingMethods.

	    interrestingMethods do:[:aMethod |
		first ifFalse:[
		    privacy ~~ aMethod privacy ifTrue:[
			first := true.
			aStream space.
			aStream nextPutChunkSeparator.
		    ].
		    aStream cr; cr
		].

		privacy := aMethod privacy.

		first ifTrue:[
		    aStream nextPutChunkSeparator.
		    self printClassNameOn:aStream.
		    privacy ~~ #public ifTrue:[
			aStream space; nextPutAll:privacy; nextPutAll:'MethodsFor:'''.
		    ] ifFalse:[
			aStream nextPutAll:' methodsFor:'''.
		    ].
		    aCategory notNil ifTrue:[
			aStream nextPutAll:aCategory
		    ].
		    aStream nextPut:$'; nextPutChunkSeparator; cr; cr.
		    first := false.
		].
		source := aMethod source.
		source isNil ifTrue:[
		    FileOutErrorSignal raiseRequestWith:'no source for method'
		] ifFalse:[
		    aStream nextChunkPut:source.
		].
	    ].
	    aStream space.
	    aStream nextPutChunkSeparator.
	    aStream cr
	]
    ]

    "Modified: 28.8.1995 / 14:30:41 / claus"
    "Modified: 15.11.1995 / 12:45:54 / cg"
!

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

    self fileOutCategory:aCategory except:nil only:nil on:aStream
!

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

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

    "mhmh - good idea; saw this in SmallDraw sourcecode ..."

    aStream cr; cr; nextPut:(Character doubleQuote); cr.
    aStream space; 
	    nextPutAll:'The following class instance variables are inherited by this class:';
	    cr; cr.
    self allSuperclassesDo:[:aSuperClass |
	aStream tab; nextPutAll:aSuperClass name; nextPutAll:' - '.
	aStream nextPutAll:(aSuperClass class instanceVariableString); cr.
    ].
    aStream nextPut:(Character doubleQuote); cr.
!

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

    |comment s|

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

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

    ^ self basicFileOutDefinitionOn:aStream
!

fileOutIn:aFileDirectory
    "create a file 'class.st' consisting of all methods in self in
     directory aFileDirectory (ignoring any directory setting in
     the current porject). 
     This is not logged in that change file (should it be ?)."

    |aStream fileName|

    fileName := (Smalltalk fileNameForClass:self name) , '.st'.
    aStream := FileStream newFileNamed:fileName in:aFileDirectory.
    aStream isNil ifTrue:[
	^ FileOutErrorSignal 
		raiseRequestWith:fileName
		errorString:('cannot create file:', fileName)
    ].
    self fileOutOn: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 selectorAtMethod: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
    ]
!

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

    |cat source privacy|

    methodArray notNil ifTrue:[
	aStream nextPutChunkSeparator.
	self printClassNameOn:aStream.

	(privacy := aMethod privacy) ~~ #public ifTrue:[
	    aStream space; nextPutAll:privacy; nextPutAll:'MethodsFor:'''.
	] ifFalse:[
	    aStream nextPutAll:' methodsFor:'''.
	].
	cat := aMethod category.
	cat notNil ifTrue:[
	    aStream nextPutAll:cat
	].
	aStream nextPut:$'; nextPutChunkSeparator; cr; cr.
	source := aMethod source.
	source isNil ifTrue:[
	    FileOutErrorSignal 
		raiseRequestWith:self
		errorString:('no source for method: ' ,
			     self name , '>>' ,
			     (self selectorAtMethod:aMethod))
	] ifFalse:[
	    aStream nextChunkPut:source.
	].
	aStream space.
	aStream nextPutChunkSeparator.
	aStream cr
    ]

    "Modified: 27.8.1995 / 01:23:19 / claus"
!

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

    ^ self fileOutOn:aStream withTimeStamp:true

    "Created: 15.11.1995 / 12:53:32 / cg"
!

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

    |collectionOfCategories copyrightMethod copyrightText comment cls versionMethod skippedMethods|

    self isLoaded ifFalse:[
        ^ FileOutErrorSignal 
            raiseRequestWith:self
                 errorString:'will not fileOut unloaded classes'
    ].

    "
     if there is a copyright method, add a copyright comment
     at the beginning, taking the string from the copyright method.
     We cannot do this unconditionally - that would lead to my copyrights
     being put on your code ;-).
     On the other hand: I want every file created by myself to have the
     copyright string at the beginning be preserved .... even if the
     code was edited in the browser and filedOut.
    "
    (copyrightMethod := self class compiledMethodAt:#copyright) notNil ifTrue:[
        "
         get the copyright methods source,
         and insert at beginning.
        "
        copyrightText := copyrightMethod source.
        copyrightText isNil ifTrue:[
            "
             no source available - trigger an error
            "
            FileOutErrorSignal
                raiseRequestWith:'no source for class ' , name , ' available. Cannot fileOut'.
            ^ self
        ].
        "
         strip off the selector-line
        "
        copyrightText := copyrightText asCollectionOfLines asStringCollection.
        copyrightText := copyrightText copyFrom:2 to:(copyrightText size).
"/        copyrightText do:[:line | aStream nextPutAll:line. aStream cr.].
        copyrightText := copyrightText asString.
        aStream nextChunkPut:copyrightText.
    ].

    stampIt ifTrue:[
        "/
        "/ first, a timestamp
        "/
        aStream nextPutAll:(Smalltalk timeStamp).
        aStream nextPutChunkSeparator. 
        aStream cr; cr.
    ].

    "/
    "/ then the definition
    "/
    self fileOutDefinitionOn:aStream.
    aStream nextPutChunkSeparator. 
    aStream cr; cr.

    "/
    "/ optional classInstanceVariables
    "/
    self class instanceVariableString isBlank ifFalse:[
        self fileOutClassInstVarDefinitionOn:aStream.
        aStream nextPutChunkSeparator. 
        aStream cr; cr
    ].

    "/
    "/ a comment - if any
    "/
    (comment := self comment) notNil ifTrue:[
        aStream nextPutAll:name; nextPutAll:' comment:'.
        aStream nextPutAll:(comment storeString).
        aStream nextPutChunkSeparator.
        aStream cr; cr
    ].

    "/
    "/ primitive definitions - if any
    "/
    self fileOutPrimitiveSpecsOn:aStream.

    "/
    "/ methods from all categories in metaclass (i.e. class methods)
    "/ EXCEPT: the version method is placed at the very end, to
    "/         avoid sourcePosition-shifts when checked out later.
    "/
    collectionOfCategories := self class categories asSortedCollection.
    collectionOfCategories notNil ifTrue:[
        "/
        "/ documentation first (if any), but not the version method
        "/
        (collectionOfCategories includes:'documentation') ifTrue:[
            versionMethod := self class compiledMethodAt:#version.
            versionMethod notNil ifTrue:[
                skippedMethods := Array with:versionMethod
            ].
            self class fileOutCategory:'documentation' except:skippedMethods only:nil on:aStream.
            aStream cr.
        ].

        "/
        "/ initialization next (if any)
        "/
        (collectionOfCategories includes:'initialization') ifTrue:[
            self class fileOutCategory:'initialization' on:aStream.
            aStream cr.
        ].

        "/
        "/ instance creation next (if any)
        "/
        (collectionOfCategories includes:'instance creation') ifTrue:[
            self class fileOutCategory:'instance creation' on:aStream.
            aStream cr.
        ].
        collectionOfCategories do:[:aCategory |
            ((aCategory ~= 'documentation')
            and:[(aCategory ~= 'initialization')
            and:[aCategory ~= 'instance creation']]) ifTrue:[
                self class fileOutCategory:aCategory on:aStream.
                aStream cr
            ]
        ]
    ].

    "/
    "/ methods from all categories in myself
    "/
    collectionOfCategories := self categories asSortedCollection.
    collectionOfCategories notNil ifTrue:[
        collectionOfCategories do:[:aCategory |
            self fileOutCategory:aCategory on:aStream.
            aStream cr
        ]
    ].

    "/
    "/ finally, the previously skipped version method
    "/
    versionMethod notNil ifTrue:[
        self class fileOutCategory:'documentation' except:nil only:skippedMethods on:aStream.
    ].

    "/
    "/ optionally an initialize message
    "/
    (self class implements:#initialize) ifTrue:[
        aStream nextPutAll:(name , ' initialize').
        aStream nextPutChunkSeparator.
        aStream cr
    ]

    "Created: 15.11.1995 / 12:53:06 / cg"
    "Modified: 9.12.1995 / 15:38:31 / cg"
!

fileOutPrimitiveDefinitionsOn:aStream
    "append primitive defs (if any) to aStream."

    |s|

    "
     primitive definitions - if any
    "
    (s := self primitiveDefinitionsString) notNil ifTrue:[
	aStream nextPutChunkSeparator; 
		nextPutAll:name; nextPutAll:' primitiveDefinitions';
		nextPutChunkSeparator;
		cr.
	aStream nextPutAll:s.
	aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
    ].
    (s := self primitiveVariablesString) notNil ifTrue:[
	aStream nextPutChunkSeparator; 
		nextPutAll:name; nextPutAll:' primitiveVariables';
		nextPutChunkSeparator;
		cr.
	aStream nextPutAll:s.
	aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
    ].
!

fileOutPrimitiveSpecsOn:aStream
    "append primitive defs (if any) to aStream."

    |s|

    "
     primitive definitions - if any
    "
    self fileOutPrimitiveDefinitionsOn:aStream.
    "
     primitive functions - if any
    "
    (s := self primitiveFunctionsString) notNil ifTrue:[
	aStream nextPutChunkSeparator; 
		nextPutAll:name; nextPutAll:' primitiveFunctions';
		nextPutChunkSeparator;
		cr.
	aStream nextPutAll:s.
	aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
    ].
! !

!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)); nextPutAll:' class'
    ] ifFalse:[
	name printOn:aStream
    ]
!

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

    self printNameArray:(self classVarNames) on:aStream indent: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; bold; nextPutAll:name; normal; 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"
!

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; nextPutAll:' ('.
    self printInstVarNamesOn:aStream indent:(indent + name size + 2).
    aStream nextPutAll:')'.
    aStream cr.
    ^ indent
!

printHierarchyOn:aStream
    "print my class hierarchy on aStream"

    self printHierarchyAnswerIndentOn:aStream
!

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

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

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 instance 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
    ]
!

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; cr.
	     methodArray do:[:aMethod |
		 (aCategory = aMethod category) ifTrue:[
		     self printOutSource:(aMethod source) on:aPrintStream.
		     aPrintStream cr; cr
		 ]
	     ].
	     aPrintStream cr
	 ]
    ]
!

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; cr.
	    methodArray do:[:aMethod |
		(aCategory = aMethod category) ifTrue:[
		    self printOutSourceProtocol:aMethod
					     on:aPrintStream.
		    aPrintStream cr; cr
		]
	    ].
	    aPrintStream cr
	]
    ]
!

printOutDefinitionOn:aPrintStream
    "print out my definition"

    |comment s|

    aPrintStream nextPutAll:'class                '; bold; nextPutAll:name; normal; cr. 
    aPrintStream nextPutAll:'superclass           '.
    superclass isNil ifTrue:[
	s := 'Object'
    ] ifFalse:[
	s := superclass name
    ].
    aPrintStream nextPutAll:s.
    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             '; nextPutAll:(category printString).
	aPrintStream cr
    ].

    (comment := self comment) notNil ifTrue:[
	aPrintStream cr; nextPutAll:'comment:'; cr; italic; nextPutAll:comment; normal; 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; cr.
	collectionOfCategories do:[:aCategory |
	    self class printOutCategory:aCategory on:aPrintStream
	]
    ].
    collectionOfCategories := self categories.
    collectionOfCategories notNil ifTrue:[
	aPrintStream nextPutAll:'instance protocol'.
	aPrintStream cr; cr.
	collectionOfCategories do:[:aCategory |
	    self printOutCategory:aCategory on:aPrintStream
	]
    ]
!

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

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 asStringCollection.
    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
    ]
!

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

    |text|

    text := aMethod source asStringCollection.
    (text size < 1) ifTrue:[^self].
    aPrintStream bold.
    aPrintStream nextPutAll:(text at:1).
    aPrintStream cr.
    (text size >= 2) ifTrue:[
	aPrintStream italic.
	aPrintStream spaces:((text at:2) indexOfNonSeparatorStartingAt:1).
	aPrintStream nextPutAll:aMethod comment.
	aPrintStream cr.
    ].
    aPrintStream normal

    "
      Float printOutProtocolOn:Stdout 
    "
! !

!Class methodsFor:'private'!

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

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

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"

    methodArray do:[:aMethod |
	|cat|

	cat := aMethod category.
	(aCollection includes:cat) ifFalse:[
	    aCollection add:cat
	]
    ]
!

getPrimitiveSpecsAt:index
    "return a primitiveSpecification component as string or nil"

    |pos stream string|

    primitiveSpec isNil ifTrue:[^ nil].
    pos := primitiveSpec at:index.
    pos isNil ifTrue:[^ nil].

    "the primitiveSpec is either a string, or an integer specifying the
     position within the classes sourcefile ...
    "
    pos isNumber ifTrue:[
	classFilename notNil ifTrue:[
	    stream := self sourceStream. "/ Smalltalk sourceFileStreamFor:classFilename.
	    stream notNil ifTrue:[
		stream position:pos+1.
		string := stream nextChunk.
		stream close.
		^ string
	    ]
	].
	^ nil
    ].
    ^ pos
!

revisionInfo
    "return a dictionary filled with revision info.
     This extracts the relevant info from the revisionString.
     The revisionInfo contains all or a subset of:
	#binaryRevision - the revision upon which the binary of this class is based
	#revision       - the revision upon which the class is based logically
			  (different, if a changed class was checked in, but not yet recompiled)
	#user           - the user who checked in the logical revision
	#date           - the date when the logical revision was checked in
	#time           - the time when the logical revision was checked in
	#fileName       - the classes source file name
	#repositoryPath - the classes source container
    "

    |vsnString info|

    vsnString := self revisionString.
    vsnString notNil ifTrue:[
	info := Class revisionInfoFromString:vsnString.
	info at:#binaryRevision put:revision.
    ].
    ^ info

    "
     Object revisionString 
     Object revisionInfo 
     Image revisionInfo 
    "

    "Created: 11.11.1995 / 14:27:20 / cg"
    "Modified: 7.12.1995 / 12:45:06 / cg"
!

revisionString
    "return my revision string; that one is extracted from the
     classes #version method. Either this is a method returning that string,
     or its a comment-only method and the comment defines the version.
     If the source is not accessable or no such method exists,
     nil is returned."

    |cls meta m src val|

    self isMeta ifTrue:[
	meta := self. cls := self soleInstance
    ] ifFalse:[
	cls := self. meta := self class
    ].

    m := meta compiledMethodAt:#version.
    m isNil ifTrue:[
	m := cls compiledMethodAt:#version.
	m isNil ifTrue:[^ nil].
    ].

    "/ if its a method returning the string,
    val := cls version.
    val isString ifTrue:[^ val].

    src := m source.
    src isNil ifTrue:[^ nil].
    ^ self revisionStringFromSource:src 

    "
     Smalltalk allClassesDo:[:cls |
	Transcript showCr:cls revisionString
     ].

     Number revisionString  
     FileDirectory revisionString  
    "

    "Created: 29.10.1995 / 19:28:03 / cg"
    "Modified: 15.11.1995 / 15:01:54 / cg"
!

revisionStringFromSource:aMethodSourceString
    "extract a revision string from a methods source string"

    |lines idx val|

    lines := aMethodSourceString asCollectionOfLines.
    lines do:[:l |
	|i|

	i := l indexOfSubCollection:'$Header: '.
	i ~~ 0 ifTrue:[
	    ^ l copyFrom:i
	]
    ].
    ^ nil
!

setPrimitiveSpecsAt:index to:aString
    "set a primitiveSpecification component to aString"

    primitiveSpec isNil ifTrue:[
	primitiveSpec := Array new:3
    ].
    primitiveSpec at:index put:aString
!

updateVersionMethodFor:newRevisionString
    "helper for the checkin procedure.
     Update my #version method, to now return newRevisionString."

    |cls vs m mgr|

    cls := self.
    self isMeta ifFalse:[
        cls := self class
    ].
"/    m := cls compiledMethodAt:#version.
"/    m isNil ifTrue:[^ false].
"/    vs := self revisionString.
"/    vs isNil ifTrue:[^ false].
"/
"/    (mgr := self sourceCodeManager) isNil ifTrue:[^ false].
"/    newString := mgr updatedRevisionStringOf:cls forRevision:newRevision with:vs. 
"/    newString isNil ifTrue:[^ false].

    Class withoutUpdatingChangesDo:[
        Compiler compile:'version
    ^ ''' , newRevisionString , '''
'
                 forClass:cls inCategory:#documentation notifying:nil 
                     install:true skipIfSame:false silent:true. 
    ].
"/ ('updated to :' , newRevisionString) printNL.

    ^ true

    "Created: 7.12.1995 / 20:42:22 / cg"
    "Modified: 7.12.1995 / 23:34:43 / cg"
! !

!Class methodsFor:'queries'!

allCategories
    "Return a Collection of all method-category strings known in class
     and all superclasses. The returned collection is not sorted by any order."

    |coll|

    coll := OrderedCollection new.
    self addAllCategoriesTo:coll.
    ^ coll

    "
     Point categories  
     Point allCategories 
    "
!

categories
    "Return a Collection of all method-category strings known in class.
     The returned collection is not sorted by any order."

    |newList cat|

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

    "
     Point categories  
    "
!

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.
     See also Behavior>>isBehavior."

    ^ true

    "
     Point isClass  
     1 isClass      
     Behavior new isBehavior  
     Behavior new isClass       
     Class new isBehavior    
     Class new isClass
    "
!

wasAutoloaded
    "return true, if this class came into the system via an
     autoload; false otherwise.
     This is not an attribute of the class, but instead remembered in
     Autoload. The interface here is for covenience."

    ^ Autoload wasAutoloaded:self
!

whichClassDefinesClassVar:aVariableName
    "return the class which defines the class variable
     named aVariableName. This method should not be used for
     repeated searches (i.e. in the compiler/parser), since it creates
     many throw away intermediate objects."

    |cls|

    cls := self.
    [cls notNil] whileTrue:[
	(cls classVarNames includes:aVariableName) ifTrue:[ ^ cls].
	cls := cls superclass
    ].
    ^ nil

    "
     StandardSystemView whichClassDefinesClassVar:'ErrorSignal'
     StandardSystemView whichClassDefinesClassVar:'Foo'
    "
!

whichClassDefinesInstVar:aVariableName
    "return the class which defines the instance variable
     named aVariableName. This method should not be used for
     repeated searches (i.e. in the compiler/parser), since it creates
     many throw away intermediate objects."

    |cls|

    cls := self.
    [cls notNil] whileTrue:[
	(cls instVarNames includes:aVariableName) ifTrue:[ ^ cls].
	cls := cls superclass
    ].
    ^ nil

    "
     StandardSystemView whichClassDefinesInstVar:'label'  
     StandardSystemView whichClassDefinesInstVar:'paint'  
     StandardSystemView whichClassDefinesInstVar:'foo'  
    "
! !

!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
!

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
!

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
!

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
!

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
!

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
!

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
! !

!Class class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Class.st,v 1.101 1995-12-09 14:46:03 cg Exp $'
! !
Class initialize!