Smalltalk.st
author Claus Gittinger <cg@exept.de>
Fri, 31 Jul 1998 16:41:35 +0200
changeset 3698 8bce45214d24
parent 3678 606bf9fca8f2
child 3840 6f9a04b9f005
permissions -rw-r--r--
fixed renaming of a private class (must recompile owner) moved some system debugging methods to ObjectMemory.

"
 COPYRIGHT (c) 1988 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.
"

Object subclass:#Smalltalk
	instanceVariableNames:''
	classVariableNames:'StartBlocks ImageStartBlocks ExitBlocks CachedClasses SystemPath
		StartupClass StartupSelector StartupArguments CommandLine
		CommandLineArguments CachedAbbreviations SilentLoading
		Initializing StandAlone LogDoits LoadBinaries RealSystemPath
		ResourcePath SourcePath BitmapPath BinaryPath FileInPath
		BinaryDirName ResourceDirName SourceDirName BitmapDirName
		FileInDirName ChangeFileName ImageStartTime ImageRestartTime
		DemoMode SyntaxHilighting SaveEmergencyImage'
	poolDictionaries:''
	category:'System-Support'
!

!Smalltalk class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1988 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
"
    This is one of the central classes in the system;
    it provides all system-startup, shutdown and maintenance support.
    Also global variables are (conceptionally) kept here.

    As you will notice, this is NOT a Dictionary
    - my implementation of globals is totally different
      due to the need to be able to access globals from c-code as well,
      I do not use associations for globals, but instead keep the
      name<->value relations in the VM and access globals via utility
      functions found there.

    However, it provides the known enumeration protocol.
    It may change to become a subclass of collection at some time,
    to inherit more collection stuff ...


    [Instance variables:]
					none - all handling is done in the VM

    [Class variables:]

	StartBlocks     <Collection>    blocks to be executed in a separate process after
					everything has been initialized. These blocks will
					be deleted after execution and therefore not be
					executed after an image restart. Initial processes
					are usually started here.

	ImageStartBlocks 
			<Collection>    blocks to be executed in a separate process after
					everything has been initialized. These blocks will be
					executed after an image restart.

	ExitBlocks      <Collection>    blocks to evaluate before system is
					left. Not currently used (GNU-ST compatibility).

	SystemPath      <Collection>    path to search for system files (sources, bitmaps etc)
					Set to a default here, but typically changed from some
					startup.rc file

	StartupClass    <Class>         class and selector, where the system starts up
	StartupSelector <Symbol>        (right after VM initialization)
	StartupArguments <Array>        If an image is saved while those being nonNil, 
					the image will come up there.
					Allows for customized images to be
					generated from a standard ST/X.

	CommandLine          <String>   Unix (OS-) command line

	CommandLineArguments <Array>    Unix (OS-) command line arguments broken into words

	SilentLoading   <Boolean>       suppresses messages during fileIn and in compiler
					(can be set to true from a customized main.c)

	Initializing    <Boolean>       true while (re-)initializing
					Controls the behavior of certain error
					reporters (for example: suppress dialogBoxes)
					while the system is not yet fit for full operation.

	StandAlone      <Boolean>       true, if this is a standalone app;
					if true the process scheduler watches for
					which processes are still running, and 
					exits ST/X, when the last non-background
					and non-system process exits.
                                        
	LogDoits        <Boolean>       if true, doits are also logged in the changes
					file. Default is false, since the changes file
					may become huge if every tiny doIt is saved there ...

	LoadBinaries    <Boolean>       if true, we attempt to load classes rom a binary
					file, if present. If false, this is always suppressed.

	SaveEmergencyImage <Boolean>    if true (the default), an emergency image
					is saved, if the main Display looses its
					connection. This is useful if you have a
					flaky display connection (serial line)
					and want to have your stuff saved automatically
					in case of a broken connection.

    strictly private classVariables (helpers):

	CachedClasses   <Collection>    known classes (cached for faster class enumeration)

	CachedAbbreviations
			<Dictionary>    className to filename mappings

	RealSystemPath  <Collection>    cached collection of directories along the path
					which really exist. Caching avoids long checks
					for existing directories on broken NFS volumes.

	SourcePath      <Collection>    cached names of really existing directories
	BitmapPath                      These are remembered, since in NFS systems,
	ResourcePath                    the time to lookup files may become long
	BinaryPath                      (especially, if some directories are on machines
	FileInPath                      which are not up ...). 
					Therefore, the set of really
					existing directories is cached when the SystemPath
					is walked the first time.
					A consequence is that you have to invoke
					flushSystemPath, when you create any of those
					directories while running
					(and want the running ST/X to look there)


    [author:]
	Claus Gittinger

    [see also:]
	ObjectMemory
"
! !

!Smalltalk class methodsFor:'initialization'!

initGlobalsFromEnvironment
    "setup globals from the shell-environment"

    |envString i langString terrString|

    "
     extract Language and LanguageTerritory from LANG variable.
     valid are for example: english_us / us_us / us
			    english / en_en / en
			    german / de_de / de
			    german_austria
    "

    Language := #english.
    LanguageTerritory := #us.

    envString := OperatingSystem getEnvironment:'LANG'.
    envString notNil ifTrue:[
	envString isEmpty ifFalse:[
	    i := envString indexOf:$_.
	    (i == 0) ifTrue:[
		langString := envString.
		terrString := envString
	    ] ifFalse:[
		langString := envString copyTo:(i - 1).
		terrString := envString copyFrom:(i + 1)
	    ].
	    Language := langString asLowercase asSymbol.
	    LanguageTerritory := terrString asLowercase asSymbol
	]
    ].

    "
     Smalltalk initGlobalsFromEnvironment
    "

    "Modified: 22.2.1996 / 16:59:12 / cg"
!

initInterrupts
    "initialize interrupts"

    OperatingSystem enableUserInterrupts.
    OperatingSystem enableHardSignalInterrupts.

    ObjectMemory userInterruptHandler:self.
    ObjectMemory signalInterruptHandler:self.
    ObjectMemory recursionInterruptHandler:self.

    "
     Smalltalk initInterrupts
    "

    "Modified: 20.8.1997 / 09:35:49 / stefan"
!

initStandardStreams
    "initialize some well-known streams"

    Stdout := NonPositionableExternalStream forStdout.
    Stderr := NonPositionableExternalStream forStderr.
    Stdin := NonPositionableExternalStream forStdin.
    Printer := PrinterStream.
    Transcript := Stderr

    "
     Smalltalk initStandardStreams
    "
!

initStandardTools
    "predefine some tools which we will need later
     - if the view-classes exist,
       they will redefine Inspector and Debugger for graphical interfaces"

    "redefine debug-tools, if view-classes exist"

    Display notNil ifTrue:[
	InspectorView notNil ifTrue:[
	    Inspector := InspectorView
	].
	DebugView notNil ifTrue:[
	    Debugger := DebugView
	].
	Display initialize
    ]

    "
     Smalltalk initStandardTools
    "
!

initSystemPath
    "setup path where system files are searched for.
     the default path is set to:
	    .
	    ..
	    $HOME                    (if defined)
	    $HOME/.smalltalk         (if defined & existing)
	    $SMALLTALK_LIBDIR        (if defined & existing)
	    $STX_LIBDIR              (if defined & existing)
	    /usr/local/lib/smalltalk (if existing)
	    /usr/lib/smalltalk       (if existing)

     of course, it is possible to add entries from the 'smalltalk.rc'
     startup file; add expressions such as:
	    Smalltalk systemPath addFirst:'/foo/bar/baz'.
	or: 
	    Smalltalk systemPath addLast:'/fee/foe/foo'.
    "

    |p homePath userPrivateSTXDir|

    ChangeFileName := 'changes'.
    OperatingSystem isVMSlike ifTrue:[
	BitmapDirName := 'bitmaps.dir'.
	BinaryDirName := 'binary.dir'.
	SourceDirName := 'source.dir'.
	ResourceDirName := 'resources.dir'.
	FileInDirName := 'filein.dir'.
    ] ifFalse:[
	BitmapDirName := 'bitmaps'.
	BinaryDirName := 'binary'.
	SourceDirName := 'source'.
	ResourceDirName := 'resources'.
	FileInDirName := 'fileIn'.
    ].

    SystemPath isNil ifTrue:[
	homePath := OperatingSystem getHomeDirectory.
	homePath isNil ifTrue:[
	    homePath := Filename currentDirectory name
	].

	"
	 the path is set to search files first locally
	 - this allows private stuff to override global stuff
	"
	SystemPath := OrderedCollection new.
	"/
	"/ the current (default) directory
	"/
	SystemPath add:(Filename currentDirectory name).
	OperatingSystem isVMSlike ifFalse:[
	    SystemPath add:'..'.
	].
	"/
	"/ the users home (login) directory
	"/
	SystemPath add:homePath.
	"/
	"/ a users private smalltalk directory in its home (login) directory
	"/
	OperatingSystem isUNIXlike ifTrue:[
	    userPrivateSTXDir := homePath asFilename constructString:'.smalltalk'.
	] ifFalse:[
	    userPrivateSTXDir := homePath asFilename constructString:'smalltalk'.
	].
	(userPrivateSTXDir asFilename isDirectory) ifTrue:[
	    SystemPath add:userPrivateSTXDir
	].
	"/
	"/ SMALLTALK_LIBDIR and/or STX_LIBDIR from the environment
	"/
	p := OperatingSystem getEnvironment:'SMALLTALK_LIBDIR'.
	p notNil ifTrue:[
	    SystemPath add:p
	].
	p := OperatingSystem getEnvironment:'STX_LIBDIR'.
	p notNil ifTrue:[
	    SystemPath add:p
	].
	"/
	"/ standard locations:
	"/ UNIX: 
	"/     /usr/local/lib/smalltalk
	"/     /usr/lib/smalltalk
	"/ VMS:
	"/     stx$root:[lib]
	"/     stx$lib:
	"/ MSDOS:
	"/     \smalltalk (this will change to ...Programs\Smalltalk)
	"/
	OperatingSystem isVMSlike ifTrue:[
	    SystemPath add:'stx$lib:'.
	    SystemPath add:'stx$root:[lib]'.
	    SystemPath add:'stx$root:'.
	] ifFalse:[
	    OperatingSystem isUNIXlike ifTrue:[
		('/usr/local/lib/smalltalk' asFilename isDirectory) ifTrue:[
		    SystemPath add:'/usr/local/lib/smalltalk'
		].
		('/usr/lib/smalltalk' asFilename isDirectory) ifTrue:[
		    SystemPath add:'/usr/lib/smalltalk'
		].
	    ] ifFalse:[
		('\smalltalk' asFilename isDirectory) ifTrue:[
		    SystemPath add:'\smalltalk'
		]
	    ]
	].
	self flushPathCaches
    ]

    "
     Smalltalk initSystemPath
     Smalltalk systemPath
    "
!

initUserPreferences
    "setup other stuff"

    LogDoits := false.
    LoadBinaries := false.
    SyntaxHilighting := false.
    SaveEmergencyImage := true.

    "Modified: / 24.10.1997 / 18:22:47 / cg"
!

initializeModules
    "perform module specific initialization and
     send #initialize to all classes.
     Notice: this is not called when an image is restarted"
%{
    __init_registered_modules__(3);
    @global(DemoMode) = __getDemoMode() ? true : false;
%}
!

initializeSystem
    "initialize all other classes; setup dispatcher processes etc.
     This one is the very first entry into the smalltalk world,
     right after startup, ususally immediately followed by Smalltalk>>start.
     Notice: 
	this is not called when an image is restarted; in this
	case the show starts in Smalltalk>>restart."

    Initializing := true.
    AbstractOperatingSystem initializeConcreteClass.

    SilentLoading := false.

    "/
    "/ define low-level debugging tools - graphical classes are not prepared yet
    "/ to handle things. 
    "/ This will bring us into the MiniDebugger when an error occurs
    "/ during startup
    "/
    Inspector := MiniInspector.
    Debugger := MiniDebugger.

    "/
    "/ start catching SIGSEGV and SIGBUS
    "/
    OperatingSystem enableHardSignalInterrupts.

    self initGlobalsFromEnvironment.

    "/
    "/ sorry - there are some, which MUST be initialized before ..
    "/ reason: if any error happens during init, we need Signals, Stdout etc. to be there
    "/
    Object initialize.
    Signal initialize.
    Filename initialize.
    ObjectMemory initialize.
    OperatingSystem initialize.
    Stream initialize.
    ExternalStream initialize.

    self initStandardStreams.    "/ setup Stdin, Stdout etc.

    "/
    "/ sorry, path must be set before ...
    "/ reason: some classes need it during initialize (they might need resources, bitmaps etc)
    "/
    self initSystemPath.

    "/
    "/ must init display here - some classes (Color, Form) need it during initialize
    "/"
    Workstation notNil ifTrue:[
	Workstation initialize
    ].

    Compiler := ByteCodeCompiler.
    Compiler isNil ifTrue:[
	"
	 ByteCodeCompiler is not in the system (i.e. has not been linked in)
	 this allows at least immediate evaluations for runtime systems without compiler
	 NOTICE: a parser is always needed, otherwise we cannot read resource files etc.
	"
	Compiler := Parser
    ].

    "/
    "/ another one, to be initialized before others
    "/
    ProcessorScheduler initialize.

    "/
    "/ now, finally, initialize all other classes
    "/
    self initializeModules.

    ImageStartTime := AbsoluteTime now.

    Display notNil ifTrue:[
	Display initialize.
	Display initializeDeviceResources.
    ].
    self initInterrupts.
    self initUserPreferences.

    "/
    "/ give classes a chance to perform 2nd-level initialization
    "/ now, we are certain, that all other classes have been initialized
    "/ (especially: streams and signals can now be used)
    "/
    ObjectMemory changed:#initialized.

    "Modified: 8.1.1997 / 19:58:12 / stefan"
    "Modified: 7.9.1997 / 23:34:44 / cg"
!

isInitialized
    "this returns true, if the system is properly initialized;
     i.e. false during startup. Especially, the whole viewing stuff is
     not working correctly until initialized."

    ^ Initializing not
!

reinitStandardStreams
    "reinitialize some well-known streams.
     Tis must be done very early during startup, to allow for
     debug and trace messages to be output
     (otherwise, the file-descriptors are invalid)"

    Stdout reOpen. Stderr reOpen. Stdin reOpen.
! !

!Smalltalk class methodsFor:'accessing'!

associationAt:aKey
    "return a key-value association for aKey.
     Since ST/X's Smalltalk as no real dictionary, this is
     simulated here."

    |val|

    val := self at:aKey ifAbsent:nil.
    val isNil ifTrue:[^ nil].
    ^ Association key:aKey value:val

    "Created: / 1.11.1997 / 13:27:20 / cg"
!

associationAt:aKey ifAbsent:exceptionBlock
    "return a key-value association for aKey, or the value
     from exceptionBlock, if no such key is present.
     Since ST/X's Smalltalk as no real dictionary, this is
     simulated here."

    |val|

    val := self at:aKey ifAbsent:nil.
    val isNil ifTrue:[^ exceptionBlock value].
    ^ Association key:aKey value:val

    "Created: / 18.6.1998 / 17:05:24 / cg"
!

at:aKey
    "retrieve the value stored under aKey, a symbol. 
     Return nil if not present 
     (this will be changed to trigger an error - better use #at:ifAbsent:)"

%{  /* NOCONTEXT */
    RETURN ( __GLOBAL_GET(aKey) );
%}
!

at:aKey ifAbsent:aBlock
    "retrieve the value stored at aKey.
     If there is nothing stored under this key, return the value of
     the evaluation of aBlock."

    (self includesKey:aKey) ifTrue:[
	^ self at:aKey
    ].
    ^ aBlock value

    "
     Smalltalk at:#fooBar                       <- returns nil
     Smalltalk at:#fooBar ifAbsent:['sorry']    <- no error
    "
!

at:aKey put:aValue
    "store the argument aValue under aKey, a symbol.
     Return aValue (sigh)."

    |oldValue|

%{
    oldValue = __GLOBAL_SET(aKey, aValue, (OBJ *)0);
%}.
    CachedClasses notNil ifTrue:[
	oldValue isBehavior ifTrue:[
	    oldValue name == aKey ifTrue:[
		CachedClasses remove:oldValue ifAbsent:[]
	    ]
	].
	aValue isBehavior ifTrue:[
"/            aValue isMeta ifTrue:[
"/                "/ this should not happen
"/                ('SMALLTALK: store a Metaclass: ' , aValue name , ' as ' , aKey) infoPrintCR.
"/            ].

	    aValue name == aKey ifTrue:[
		CachedClasses add:aValue
	    ] ifFalse:[
		CachedClasses := nil
	    ]
	].
    ].
    ^ aValue.
"/
"/%{  /* NOCONTEXT */
"/    (void) __GLOBAL_SET(aKey, aValue, (OBJ *)0);
"/%}.
"/    CachedClasses := nil.
"/    ^ aValue

    "Modified: 19.4.1996 / 11:31:49 / cg"
!

includesKey:aKey
    "return true, if the key is known"

%{  /* NOCONTEXT */
    RETURN ( __GLOBAL_KEYKNOWN(aKey) );
%}
!

keyAtValue:anObject
    "return the symbol under which anObject is stored - or nil"

    self keysDo:[:aKey |
	(self at:aKey) == anObject ifTrue:[^ aKey]
    ].
    ^ nil

    "Smalltalk keyAtValue:Object"
!

keys
    "return a collection with all keys in the Smalltalk dictionary"

    |keys|

    keys := IdentitySet new.
    self keysDo:[:k | keys add:k].
    ^ keys
!

removeKey:aKey
    "remove the association stored under the key-argument from the globals dictionary.
     WARNING: 
	this is somewhat dangerous: conceptionally, the association is removed,
	to which machine & byte compiled code refers if it accesses a global.
	If there are still global accesses in some literalArray or from machine-compiled code,
	it continues to reference the globals value via that obsolete association and gets a nil
	value.  (which is correct)
	However, if that global is later reintroduced, a new association will be created and
	the new global now referenced via the new association.
	The old accesses will still see nil, although the globals value is actually non-nil
	(this is questionable).
	To avoid this problem, the #removeClass: method never removed the key."

    CachedClasses := nil.

%{  /* NOCONTEXT */
    RETURN ( __GLOBAL_REMOVE(aKey) );
%}
!

values
    "return a collection with all values in the Smalltalk dictionary"

    |values|

    values := OrderedCollection new.
    self do:[:v | values add:v].
    ^ values

    "Created: 20.6.1997 / 16:58:28 / cg"
! !

!Smalltalk class methodsFor:'binary storage'!

addGlobalsForBinaryStorageTo:globalDictionary
    |pools|

    pools := Set new.

    self keysAndValuesDo:[:key :value |
	(key includes:$:) ifFalse:[       "/ skip classVars
	    (value ~~ self 
	    and:[value notNil]) ifTrue:[
		value isClass ifTrue:[
		    value addGlobalsForBinaryStorageTo:globalDictionary.
		    pools addAll:value sharedPools
		] ifFalse:[
		    globalDictionary at:(key->value) put:self
		].
		value notNil ifTrue:[
		    globalDictionary at:value put:self
		]
	    ]
	]
    ].

    pools do:[:poolDictionary|
	poolDictionary addGlobalsForBinaryStorageTo:globalDictionary
    ]

    "Modified: 19.3.1997 / 18:15:25 / cg"
    "Created: 21.3.1997 / 15:40:31 / cg"
!

storeBinaryDefinitionOf:anObject on:stream manager:manager
    |string|

    anObject class == Association ifTrue:[
	string := 'Smalltalk associationAt: ', anObject key storeString
    ] ifFalse: [
	string := 'Smalltalk at: ', (self keyAtValue: anObject) storeString
    ].
    stream nextNumber:2 put:string size.
    stream nextPutBytes:(string size) from:string startingAt:1.
"/    string do:[:char | stream nextPut:char asciiValue]

    "Modified: 19.3.1997 / 18:49:14 / cg"
! !

!Smalltalk class methodsFor:'browsing'!

browseAllCallsOn:aSelectorSymbol
    "{ Pragma: +optSpace }"

    "startup a browser for all methods sending a particular message"

    SystemBrowser browseAllCallsOn:aSelectorSymbol

    "
     Smalltalk browseAllCallsOn:#at:put: 
    "
!

browseAllSelect:aBlock
    "{ Pragma: +optSpace }"

    "startup a browser for all methods for which aBlock returns true"

    SystemBrowser browseAllSelect:aBlock

    "
     Smalltalk browseAllSelect:[:m | m literals isNil]
    "
!

browseChanges
    "{ Pragma: +optSpace }"

    "startup a changes browser"

    ChangesBrowser notNil ifTrue:[
	ChangesBrowser open
    ] ifFalse:[
	self warn:'no ChangesBrowser built in'
    ]

    "
     Smalltalk browseChanges
    "
!

browseImplementorsOf:aSelectorSymbol
    "{ Pragma: +optSpace }"

    "startup a browser for all methods implementing a particular message"

    SystemBrowser browseImplementorsOf:aSelectorSymbol

    "
     Smalltalk browseImplementorsOf:#at:put: 
    "
!

syntaxHilighting
    ^ SyntaxHilighting

    "Created: 8.8.1997 / 10:55:22 / cg"
! !

!Smalltalk class methodsFor:'class management'!

flushCachedClasses
    CachedClasses := nil
!

removeClass:aClass
    "remove the argument, aClass from the smalltalk dictionary;
     we have to flush the caches since these methods are now void.
     Also, class variables of aClass are removed."

    |sym cSym names oldName actualName wrongName|

    oldName := aClass name.
    sym := oldName asSymbol.
    ((self at:sym) == aClass) ifFalse:[
        "check other name ..."
        (self includes:aClass) ifFalse:[
            'Smalltalk [warning]: no such class: ' errorPrint. oldName errorPrintCR.
            ^ self
        ].
        "
         the class has changed its name - without telling me ...
         what should be done in this case ?
        "
        'Smalltalk [warning]: class ' errorPrint. oldName errorPrint.
        ' has changed its name' errorPrintCR.

        "/
        "/ might be an alias (i.e. removing a compatibility name)
        "/
        actualName := self keyAtValue:aClass.
        ('Smalltalk [info]: ' , oldName , ' is actually stored as ' , actualName , '.') infoPrintCR.
        sym := actualName asSymbol.
        oldName := actualName asString.
        wrongName := true.
    ].

    self at:sym put:nil.    "nil it out for compiled accesses"

    "/
    "/ see comment in removeKey: on why we dont remove it here
    "/
    "/ self removeKey:sym.     "/ remove key - this actually fails, if there are
                               "/ still compiled code references."

    "remove private classes"

    aClass privateClassesSorted do:[:somePrivateClass |
        aClass privateClassesAt:(somePrivateClass nameWithoutPrefix) asSymbol put:nil.
    ].

    "remove class variables"

    names := aClass classVariableString asCollectionOfWords.
    names do:[:name |
        cSym := (sym , ':' , name) asSymbol.
        self at:cSym asSymbol put:nil.

        "/
        "/ see comment in removeKey: on why we dont remove it here
        "/
        "/ self removeKey:cSym
    ].


"/    actually could get along with less flushing
"/    (entries for aClass and subclasses only)
"/    but we have to delay this, until we have the set of subclasses
"/    at hand - for now, searching for all subclasses is way more
"/    expensive then cache flushing.
"/
"/    aClass allSubclassesDo:[:aSubclass |
"/        ObjectMemory flushInlineCachesForClass:aSubclass.
"/        ObjectMemory flushMethodCacheFor:aSubclass
"/    ].
"/    ObjectMemory flushInlineCachesForClass:aClass.
"/    ObjectMemory flushMethodCacheFor:aClass

    ObjectMemory flushInlineCaches.
    ObjectMemory flushMethodCache.

    aClass addChangeRecordForClassRemove:oldName.
    self changed:#classRemove with:aClass.

    aClass category:#'* removed *'.

    wrongName == true ifTrue:[
        "/
        "/ an alias (i.e. removing a compatibility name
        "/
        self flushCachedClasses.
        "/ check if there are more refs to it ...
        [self includes:aClass] whileTrue:[
            actualName := self keyAtValue:aClass.
            ('Smalltalk [info]: ' , aClass name , ' is also registered under the name ' , actualName
                          , ' - remove that binding too.') infoPrintCR.
            self at:actualName put:nil.
        ].
    ].

    "Modified: / 20.6.1998 / 13:26:10 / cg"
!

renameClass:aClass to:newName
    "rename aClass to newName. Most of the work is in
     renaming the classVariables (create & copy over values)
     and patching the classes methods to access the new variables."

    |oldName oldSym newSym names oldCVSym newCVSym value oldNameToNewName
     oldNameSpace newNameSpace oldBaseName newBaseName privateClasses
     oldBaseNameWithoutPrefix newBaseNameWithoutPrefix|

    oldName := aClass name.
    aClass isPrivate ifTrue:[
        oldNameSpace := aClass topOwningClass nameSpace.
    ] ifFalse:[
        oldNameSpace := aClass nameSpace.
    ].
    oldBaseName := aClass nameWithoutNameSpacePrefix.
    oldBaseNameWithoutPrefix := aClass nameWithoutPrefix.
    oldSym := oldName asSymbol.
    privateClasses := aClass privateClassesSorted.

    ((self at:oldSym) ~~ aClass) ifTrue:[
        'Smalltalk [warning]: rename failed - name is different from key' errorPrintCR.
        ^ self
    ].

    "/ rename the class

    newSym := newName asSymbol.
    aClass setName:newSym.

    "/ store it in Smalltalk

    self at:oldSym put:nil.

    "/
    "/ see comment in #removeKey: on why we dont remove it it here
    "/
    "/ self removeKey:oldSym.
    self at:newSym put:aClass.

    "/ create new class variables and copy over values

    oldNameToNewName := IdentityDictionary new.

    names := aClass classVariableString asCollectionOfWords.
    names do:[:name |
        oldCVSym := (oldSym , ':' , name) asSymbol.
        value := self at:oldCVSym.
        self at:oldCVSym put:nil.

        "/
        "/ see comment in #removeKey: on why we dont remove it it here
        "/
        "/ self removeKey:cSym.

        newCVSym := (newSym , ':' , name) asSymbol.
        self at:newCVSym put:value.

        oldNameToNewName at:oldCVSym put:newCVSym.
    ].

    "/ patch methods literal arrays from oldCVname to newCVname

    oldNameToNewName keysAndValuesDo:[:oldNameSym :newNameSym |
        aClass withAllSubclasses do:[:aSubClass |
            Transcript showCR:'changing global accesses from ''' , oldNameSym , ''' into ''' , newNameSym , ''' in class: ''' , aSubClass name , ''' ...'.        
            aSubClass class methodDictionary do:[:aMethod |
                aMethod changeLiteral:oldNameSym to:newNameSym
            ].
            aSubClass methodDictionary do:[:aMethod |
                aMethod changeLiteral:oldNameSym to:newNameSym
            ]
        ].

        "/ and also in privateClasses ? ...

"/        privateClasses size > 0 ifTrue:[
"/            privateClasses do:[:aPrivateClass |
"/                aPrivateClass withAllSubclasses do:[:aSubClass |
"/                    aSubClass class methodDictionary do:[:aMethod |
"/                        aMethod changeLiteral:oldNameSym to:newNameSym
"/                    ].
"/                    aSubClass methodDictionary do:[:aMethod |
"/                        aMethod changeLiteral:oldNameSym to:newNameSym
"/                    ]
"/                ].
"/            ]
"/        ]
    ].

    aClass addChangeRecordForClassRename:oldSym to:newSym.

    aClass isPrivate ifTrue:[
        newNameSpace := aClass topOwningClass nameSpace.
    ] ifFalse:[    
        newNameSpace := aClass nameSpace.
    ].

    privateClasses size > 0 ifTrue:[
        "/ must rename privateClasses as well
        privateClasses do:[:aPrivateClass |
            self renameClass:aPrivateClass
                 to:(newSym , '::' , aPrivateClass nameWithoutPrefix).
        
            Transcript showCR:'recompiling methods in ''' , newNameSpace name , ''' accessing ''' , oldName , '::' , aPrivateClass nameWithoutPrefix , ''' ...'.
            Class class
                recompileGlobalAccessorsTo:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol 
                in:newNameSpace 
                except:nil.
        ]
    ].

    oldNameSpace ~~ newNameSpace ifTrue:[
        "/ all those referencing the class from the old nameSpace
        "/ must be recompiled ...
        "/ (to now access the global from smalltalk)

        oldNameSpace ~~ Smalltalk ifTrue:[
            Transcript showCR:'recompiling methods in ''' , oldNameSpace name , ''' accessing ''' , oldName , ''' ...'.

            Class class
                recompileGlobalAccessorsTo:oldName asSymbol 
                in:oldNameSpace 
                except:nil.
        ].

        "/ all referencing the class in the new namespace
        "/ as well; to now access the new class.

        (newNameSpace notNil and:[newNameSpace ~~ Smalltalk]) ifTrue:[
            Transcript showCR:'recompiling methods in ''' , newNameSpace name , ''' accessing ''' , oldBaseName , ''' ...'.

            Class class
                recompileGlobalAccessorsTo:oldBaseName asSymbol 
                in:newNameSpace 
                except:nil.
        ].
    ] ifFalse:[
        "/ all references to a global with my new name in my owning class
        "/ must now be redirected to myself.

        aClass isPrivate ifTrue:[
            newBaseName := aClass nameWithoutNameSpacePrefix.
            newBaseNameWithoutPrefix := aClass nameWithoutPrefix.

            Transcript showCR:'recompiling methods accessing ''' , oldBaseNameWithoutPrefix , ''' in: ''' , aClass owningClass name , ''' ...'.        
            aClass owningClass recompileMethodsAccessingGlobal:oldBaseNameWithoutPrefix.
            aClass owningClass class recompileMethodsAccessingGlobal:oldBaseNameWithoutPrefix.

            Transcript showCR:'recompiling methods accessing ''' , oldBaseName , ''' in: ''' , aClass owningClass name , ''' ...'.        
            aClass owningClass recompileMethodsAccessingGlobal:oldBaseName.
            aClass owningClass class recompileMethodsAccessingGlobal:oldBaseName.

            Transcript showCR:'recompiling methods accessing ''' , newBaseNameWithoutPrefix , ''' in: ''' , aClass owningClass name , ''' ...'.        
            aClass owningClass recompileMethodsAccessingGlobal:newBaseNameWithoutPrefix.
            aClass owningClass class recompileMethodsAccessingGlobal:newBaseNameWithoutPrefix.

            Transcript showCR:'recompiling methods accessing ''' , newBaseName , ''' in: ''' , aClass owningClass name , ''' ...'.        
            aClass owningClass recompileMethodsAccessingGlobal:newBaseName.
            aClass owningClass class recompileMethodsAccessingGlobal:newBaseName.
        ]
    ]

    "Created: / 29.10.1995 / 19:58:32 / cg"
    "Modified: / 18.6.1996 / 14:20:50 / stefan"
    "Modified: / 31.7.1998 / 15:46:34 / cg"
! !

!Smalltalk class methodsFor:'copying'!

deepCopy
    "redefined to return self - there is only one Smalltalk dictionary"

    ^ self

    "Modified: 18.5.1996 / 12:13:33 / cg"
!

deepCopyUsing:aDictionary
    "redefined to return self - there is only one Smalltalk dictionary"

    ^ self

    "Modified: 18.5.1996 / 12:13:36 / cg"
!

shallowCopy
    "redefined to return self - there is only one Smalltalk dictionary"

    ^ self

    "Modified: 18.5.1996 / 12:13:39 / cg"
!

simpleDeepCopy
    "redefined to return self - there is only one Smalltalk dictionary"

    ^ self

    "Modified: 18.5.1996 / 12:13:42 / cg"
! !

!Smalltalk class methodsFor:'debugging ST/X'!

debugBreakPoint
    "{ Pragma: +optSpace }"

    "call the dummy debug function, on which a breakpoint
     can be put in adb, sdb, dbx or gdb.
     WARNING: this method is for debugging only
	      it will be removed without notice."
%{
    __PATCHUPCONTEXTS(__context);
    __debugBreakPoint__();
%}
!

exitWithCoreDump
    "{ Pragma: +optSpace }"

    "abort program and dump core"

%{  /* NOCONTEXT */
    abort();
    /* NEVER RETURNS */
%}
!

fatalAbort
    "{ Pragma: +optSpace }"

    "report a fatal-error, print a stack backtrace and exit with core dump.
     (You may turn off the stack print with debugPrinting:false)"
%{
    __fatal0(__context, "fatalAbort");
    /* NEVER RETURNS */
%}
!

fatalAbort:aMessage
    "{ Pragma: +optSpace }"

    "report a fatal-error; print a stack backtrace and exit with core dump
     (You may turn off the stack print with debugPrinting:false)"

%{
    char *msg;

    if (__isString(aMessage))
	msg = (char *) __stringVal(aMessage);
    else
	msg = "fatalAbort";

    __fatal0(__context, msg);
    /* NEVER RETURNS */
%}
! !

!Smalltalk class methodsFor:'enumerating'!

allBehaviorsDo:aBlock
    "evaluate the argument, aBlock for all classes in the system"

    CachedClasses isNil ifTrue:[
	self allClasses
    ].
    CachedClasses do:aBlock

    "
     Smalltalk allBehaviorsDo:[:aClass | aClass name printCR]
    "
!

allClassesDo:aBlock
    "evaluate the argument, aBlock for all classes in the system.
     Backward compatibility - use #allBehaviorsDo: for ST-80 compatibility."

    ^ self allBehaviorsDo:aBlock

    "
     Smalltalk allClassesDo:[:aClass | aClass name printCR]
    "
!

allClassesInCategory:aCategory
    "return a collection of for all classes in aCategory;
     The order of the classes is not defined."

    |coll|

    coll := OrderedCollection new.
    self allClassesInCategory:aCategory do:[:aClass |
	coll add:aClass
    ].
    ^ coll

    "
     Smalltalk allClassesInCategory:'Views-Basic'
    "

    "Modified: 25.4.1996 / 18:06:13 / cg"
!

allClassesInCategory:aCategory do:aBlock
    "evaluate the argument, aBlock for all classes in the aCategory;
     The order of the classes is not defined."

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

    "
     Smalltalk allClassesInCategory:'Views-Basic' do:[:aClass | aClass name printCR]
    "
!

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

    |classes|

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

    "
     Smalltalk allClassesInCategory:'Views-Basic' inOrderDo:[:aClass | aClass name printCR]
    "
!

allKeysDo:aBlock
    "evaluate the argument, aBlock for all keys in the Smalltalk dictionary"

    ^ self keysDo:aBlock
!

associationsDo:aBlock
    "evaluate the argument, aBlock for all key/value pairs 
     in the Smalltalk dictionary"

    self keysDo:[:aKey |
	aBlock value:(aKey -> (self at:aKey))
    ]

    "Smalltalk associationsDo:[:assoc | assoc printCR]"
!

do:aBlock
    "evaluate the argument, aBlock for all values in the Smalltalk dictionary"

    |work|

%{  /* NOREGISTER - work may not be placed into a register here */
    __GLOBALS_DO(&aBlock, &work);
%}
!

keysAndValuesDo:aBlock
    "evaluate the two-arg block, aBlock for all keys and values"

    self keysDo:[:aKey |
	aBlock value:aKey value:(self at:aKey)
    ]
!

keysDo:aBlock
    "evaluate the argument, aBlock for all keys in the Smalltalk dictionary"
    |work|

%{  /* NOREGISTER - work may not be placed into a register here */
    __GLOBALKEYS_DO(&aBlock, &work);
%}
! !

!Smalltalk class methodsFor:'inspecting'!

inspectorClass
    "{ Pragma: +optSpace }"

    "redefined to launch a DictionaryInspector
     (instead of the default Inspector)."

    ^ DictionaryInspectorView
! !

!Smalltalk class methodsFor:'message control'!

silentLoading
    "returns the Silentloading class variable."

     ^ SilentLoading
!

silentLoading:aBoolean
    "{ Pragma: +optSpace }"

    "allows access to the Silentloading class variable, which controls
     messages from all kinds of system onto the transcript.
     You can save a snapshot with this flag set to true, which makes
     the image come up silent. Can also be set, to read in files unlogged."

    |prev|

    prev := SilentLoading.
    SilentLoading := aBoolean.
    ^ prev
! !

!Smalltalk class methodsFor:'misc stuff'!

addExitBlock:aBlock
    "{ Pragma: +optSpace }"

    "add a block to be executed when Smalltalk finishes.
     This feature is currently not used anywhere - but could be useful for
     cleanup in stand alone applications."

    ExitBlocks isNil ifTrue:[
	ExitBlocks := OrderedCollection with:aBlock
    ] ifFalse:[
	ExitBlocks add:aBlock
    ]
!

addImageStartBlock:aBlock
    "{ Pragma: +optSpace }"

    "add a blocks to be executed in a separate process after
     everything has been initialized. 
     These blocks will be executed after an image restart."

    ImageStartBlocks isNil ifTrue:[
	ImageStartBlocks := OrderedCollection with:aBlock
    ] ifFalse:[
	ImageStartBlocks add:aBlock
    ]

    "Created: 9.9.1996 / 16:48:20 / stefan"
!

addStartBlock:aBlock
    "{ Pragma: +optSpace }"

    "add a blocks to be executed in a separate process after
     everything has been initialized. These blocks will
     be deleted after execution and therefore not be
     executed after an image restart. 
     Initial processes are usually started here (see smalltalk.rc / private.rc)."

    StartBlocks isNil ifTrue:[
	StartBlocks := OrderedCollection with:aBlock
    ] ifFalse:[
	StartBlocks add:aBlock
    ]

    "Created: 9.9.1996 / 16:46:53 / stefan"
!

exit
    "{ Pragma: +optSpace }"

    "finish Smalltalk system"

    ObjectMemory changed:#aboutToQuit.  "/ for ST-80 compatibility
    ExitBlocks notNil ifTrue:[
	ExitBlocks do:[:aBlock |
	    aBlock value
	]
    ].
    OperatingSystem exit

    "
     Smalltalk exit
    "
!

sleep:aDelay
    "{ Pragma: +optSpace }"

    "wait for aDelay seconds.
     OBSOLETE: this is historical leftover and will be removed"

    OperatingSystem sleep:aDelay
! !

!Smalltalk class methodsFor:'queries'!

allClasses
    "return an unordered collection of all classes in the system.
     Only globally anchored classes are returned 
     (i.e. anonymous ones have to be aquired by Behavior allSubInstances)"

    |classes|

    "/ you may wonder, what this while is for, here ...
    "/ the reason is that if we modify the class hierarchy in
    "/ anothe view (background fileIn), while building up the
    "/ cachedClasses set, this may be flushed (invalidated) by the
    "/ other process in the meanwhile.
    "/ If that happens, we restart the set-building here
    "/
    [(classes := CachedClasses) isNil] whileTrue:[
	CachedClasses := classes := IdentitySet new:800. 
	self do:[:anObject |
	    anObject notNil ifTrue:[
		anObject isBehavior ifTrue:[
		    classes add:anObject
		]
	    ]
	]
    ].
    ^ classes

    "
     Smalltalk allClasses

    to get the list sorted by name:

     Smalltalk allClasses asSortedCollection:[:a :b | a name < b name]
    "

    "Modified: 13.12.1995 / 14:52:50 / cg"
!

cellAt:aName
    "{ Pragma: +optSpace }"

    "return the address of a global cell
     - used internally for compiler only"

%{  /* NOCONTEXT */
    RETURN ( __GLOBAL_GETCELL(aName) );
%}
!

classNamed:aString
    "return the class with name aString, or nil if absent.
     To get to the metaClass, append ' class' to the string."

    |cls sym meta|

    "be careful, to not invent new symbols ..."
    sym := aString asSymbolIfInterned.
    sym notNil ifTrue:[
	cls := self at:sym ifAbsent:[].
	cls isBehavior ifTrue:[^ cls]
    ].
    (aString endsWith:' class') ifTrue:[

	meta := self classNamed:(aString copyWithoutLast:6).
	meta notNil ifTrue:[
	    ^ meta class
	].
    ].
    ^ nil

    "
     Smalltalk classNamed:'Object'    
     Smalltalk classNamed:'fooBar' 
     Smalltalk classNamed:'true'    
     Smalltalk classNamed:'Object class'    
     Smalltalk classNamed:'Metaclass'    
     Smalltalk classNamed:'Array'    
     Smalltalk classNamed:'Array class'    
    "

    "Created: 24.11.1995 / 17:30:22 / cg"
    "Modified: 24.11.1995 / 17:31:29 / cg"
    "Modified: 19.6.1996 / 14:22:21 / stefan"
!

classNames
    "return a collection of all classNames in the system"

    ^ self allClasses collect:[:aClass | aClass name]

    "
     Smalltalk classNames
    "
!

classnameCompletion:aPartialClassName
    "given a partial classname, return an array consisting of
     2 entries: 1st: collection consisting of matching names
		2nd: the best (longest) match"

    |searchName matches ignCaseMatches best isMatchString|

    searchName := aPartialClassName.
    searchName isEmpty ifTrue:[
	^ Array with:searchName with:#()
    ].

    (searchName at:1) isLowercase ifTrue:[
	searchName := searchName copy asUppercaseFirst
    ].

    isMatchString := searchName includesMatchCharacters.
    matches := OrderedCollection new.
    ignCaseMatches := OrderedCollection new.
    self allClassesDo:[:aClass |
	|className addIt|

	className := aClass name.
	aClass isMeta ifFalse:[
        
	    isMatchString ifTrue:[
		addIt := searchName match:className
	    ] ifFalse:[
		addIt := className startsWith:searchName
	    ].
	    addIt ifTrue:[
		matches add:aClass name
	    ] ifFalse:[
		"/ try ignoring case
		isMatchString ifTrue:[
		    addIt := searchName match:className ignoreCase:true
		] ifFalse:[
		    addIt := className asLowercase startsWith:searchName asLowercase
		].
		addIt ifTrue:[
		    ignCaseMatches add:aClass name
		]
	    ]
	]
    ].

    matches isEmpty ifTrue:[
	matches := ignCaseMatches
    ].

    matches isEmpty ifTrue:[
	^ Array with:searchName with:(Array with:searchName)
    ].
    matches size == 1 ifTrue:[
	^ Array with:matches first with:(matches asArray)
    ].
    matches := matches asSortedCollection.
    isMatchString ifTrue:[
	best := searchName.
    ] ifFalse:[
	best := matches longestCommonPrefix.
    ].
    ^ Array with:best with:matches asArray

    "
     Smalltalk classnameCompletion:'Arr' 
     Smalltalk classnameCompletion:'Arra' 
     Smalltalk classnameCompletion:'arra' 
     Smalltalk classnameCompletion:'*rray' 
    "

    "Created: 24.11.1995 / 17:24:45 / cg"
    "Modified: 3.4.1997 / 18:25:01 / cg"
!

defaultNameSpace
    "return the default namespace, where new classes are installed,
     if NO special nameSpace handler is present"

    |p|

    (Project notNil and:[(p := Project current) notNil]) ifTrue:[
	^ p defaultNameSpace
    ].

    ^ self

    "Created: 19.12.1996 / 23:49:25 / cg"
    "Modified: 2.1.1997 / 20:01:31 / cg"
!

includes:something
    "this should come from Collection.
     will change the inheritance - Smalltalk is actually a collection"

    self do:[:element | element = something ifTrue:[^ true]].
    ^ false
!

isNamespace
    ^ true

    "Created: 11.10.1996 / 18:10:43 / cg"
!

numberOfGlobals
    "return the number of global variables in the system"

    |tally "{ Class: SmallInteger }" |

    tally := 0.
    self do:[:obj | tally := tally + 1].
    ^ tally

    "Smalltalk numberOfGlobals"
!

references:anObject
    "redefined, since the references are only kept in the VM's symbol table"

    self keysAndValuesDo:[:key :val |
        (key == anObject) ifTrue:[^ true].
        (val == anObject ) ifTrue:[^ true].
    ].
    ^ super references:anObject

    "Modified: / 3.2.1998 / 14:22:46 / cg"
!

referencesAny:aCollection
    "redefined, since the references are only kept in the VM's symbol table"

    self keysAndValuesDo:[:key :val |
        aCollection do:[:anObject |
            (key == anObject) ifTrue:[^ true].
            (val == anObject ) ifTrue:[^ true].
        ]
    ].
    ^ super referencesAny:aCollection

    "Created: / 2.2.1998 / 16:01:20 / cg"
!

referencesDerivedInstanceOf:aClass
    "redefined, since the references are only kept in the VM's symbol table"

    self keysAndValuesDo:[:key :val |
	(key isKindOf:aClass) ifTrue:[^ true].
	(val isKindOf:aClass) ifTrue:[^ true].
    ].
    ^ super referencesDerivedInstanceOf:aClass
!

referencesInstanceOf:aClass
    "redefined, since the references are only kept in the VM's symbol table"

    self keysAndValuesDo:[:key :val |
	(key isMemberOf:aClass) ifTrue:[^ true].
	(val isMemberOf:aClass) ifTrue:[^ true].
    ].
    ^ super referencesInstanceOf:aClass
!

resolveName:aName inClass:aClass
    "resolve aName as if compiled within aClass;
     i.e. if it has a private class with this name, return it;
     if aName is known within the classes namespace, return that.
     Otherwise, return a global with that name.
     This should be used whereever Smalltalk>>at: used to be used,
     to resolve a global by name."

    |sym cls ns|

    aName isNil ifTrue:[^ nil].
    aName isBehavior ifTrue:[^ aName].       "/ already resolved

    sym := aName asSymbol.

    cls := aClass privateClassesAt:sym.
    cls notNil ifTrue:[^ cls].

    ns := aClass nameSpace.
    (ns notNil and:[ns ~~ Smalltalk]) ifTrue:[
	ns isNamespace ifTrue:[
	    cls := ns at:sym ifAbsent:nil.
	] ifFalse:[
	    cls := ns privateClassesAt:sym
	].
	cls notNil ifTrue:[^ cls].
    ].
    ^ self at:sym ifAbsent:nil.
!

selectorCompletion:aPartialSymbolName
    "given a partial selector, return an array consisting of
     2 entries: 1st: collection consisting of matching implemented selectors
                2nd: the longest match"

    |matches best lcSym|

    matches := IdentitySet new.

    "/ search for exact match
    self allClassesDo:[:aClass |
        aClass methodDictionary keysAndValuesDo:[:aSelector :aMethod |
            (aSelector startsWith:aPartialSymbolName) ifTrue:[
                matches add:aSelector
            ]
        ].
        aClass class methodDictionary keysAndValuesDo:[:aSelector :aMethod |
            (aSelector startsWith:aPartialSymbolName) ifTrue:[
                matches add:aSelector
            ]
        ]
    ].
    matches isEmpty ifTrue:[
        "/ search for case-ignoring match
        lcSym := aPartialSymbolName asLowercase.
        self allClassesDo:[:aClass |
            aClass methodDictionary keysAndValuesDo:[:aSelector :aMethod |
                (aSelector asLowercase startsWith:lcSym) ifTrue:[
                    matches add:aSelector
                ]
            ].
            aClass class methodDictionary keysAndValuesDo:[:aSelector :aMethod |
                (aSelector asLowercase startsWith:lcSym) ifTrue:[
                    matches add:aSelector
                ]
            ]
        ].
    ].

    matches isEmpty ifTrue:[
        ^ Array with:aPartialSymbolName with:(Array with:aPartialSymbolName)
    ].
    matches size == 1 ifTrue:[
        ^ Array with:matches first with:(matches asArray)
    ].
    matches := matches asSortedCollection.
    best := matches longestCommonPrefix.
    ^ Array with:best with:matches asArray

    "
     Smalltalk selectorCompletion:'at:p'  
     Smalltalk selectorCompletion:'nextP' 
     Smalltalk selectorCompletion:'nextp' 
    "

    "Modified: / 7.6.1996 / 08:44:33 / stefan"
    "Modified: / 14.6.1998 / 15:54:03 / cg"
! !

!Smalltalk class methodsFor:'startup'!

mainStartup:graphicalMode
    "common start/restart action, if there is a Display, initialize it
     and start dispatching; otherwise go into a read-eval-print loop."

    |mainProcess standAloneProcess imageName thisIsARestart|

    imageName := ObjectMemory imageName.
    thisIsARestart := imageName notNil.

    "
     if there is a display, start its event dispatcher 
    "
    Display notNil ifTrue:[
        Display deviceIOTimeoutErrorSignal handlerBlock:[:ex |
            SaveEmergencyImage == true ifTrue:[
                'Display [warning]: broken display connection - emergency save in ''crash.img''.' infoPrintCR.
                ObjectMemory primSnapShotOn:'crash.img'.
            ].
            'Display [warning]: broken display connection - exit.' infoPrintCR.
            Smalltalk exit.
        ].
"/        Display deviceIOErrorSignal handlerBlock:[:ex |
"/            'Display [warning]: I/O error on display connection - exit.' infoPrintCR.
"/        ].
        Display startDispatch.
    ].

    Initializing := false.

    "/ start a process, which evaluates all StartBlocks
    "/ this used to be done right here (in this system-process),
    "/ but lead to trouble, when it suspended.
    "/ Therefore, it is now done by an extra user-process.

    mainProcess := [
        StartBlocks notNil ifTrue:[
            StartBlocks do:[:aBlock|
                aBlock value
            ].
            StartBlocks := nil.
        ].
        ImageStartBlocks notNil ifTrue:[
            ImageStartBlocks do:[:aBlock|
                aBlock value
            ].
        ].
        StandAlone ifFalse:[
            (SilentLoading == true) ifFalse:[   "i.e. undefined counts as false" 
                thisIsARestart ifTrue:[
                    Transcript cr.
                    Transcript showCR:('Smalltalk restarted from:'
                                        , imageName
                                        , ' (saved '
                                        , ObjectMemory imageSaveTime printString
                                        , ')' ).
                ] ifFalse:[
                    Transcript showCR:(self hello).
                    Transcript showCR:(self copyrightString).
                    Transcript cr.
                ].
                Transcript cr.
            ].

            DemoMode ifTrue:[
                Transcript showCR:'*** Restricted use:                              ***'.
                Transcript showCR:'*** This program may be used for education only. ***'.
                Transcript showCR:'*** Please read the files COPYRIGHT and LICENSE  ***'.
                Transcript showCR:'*** for more details.                            ***'.
                Transcript cr.
            ].
        ].

        thisIsARestart ifTrue:[
            "/
            "/ the final late notification - users can now assume that
            "/ views, forms etc. have been recreated.

            ObjectMemory changed:#returnFromSnapshot.
        ]

    ] newProcess.
    mainProcess priority:8.
    mainProcess name:'start block handler'.
    mainProcess beGroupLeader.
    mainProcess resume.


    "/ start a process, which evaluates the startupClass>>startupSelector
    "/ message.

    (StartupClass notNil and:[StartupSelector notNil]) ifTrue:[
        "
         allow more customization by reading an image specific rc-file
        "
        thisIsARestart ifTrue:[
            (imageName asFilename hasSuffix:'img') ifTrue:[
                imageName := imageName copyWithoutLast:4
            ].
            self fileIn:(imageName , '.rc')
        ].

"/        Display notNil ifTrue:[
"/            Display class exitOnLastClose:true.
"/        ].
"/        Processor exitWhenNoMoreUserProcesses:true.

        standAloneProcess := [
            StartupClass perform:StartupSelector withArguments:StartupArguments.
            "/
            "/ non-GUI apps exit after the startup;
            "/ assume that GUI apps have created & opened some view ...
            "/
            Display isNil ifTrue:[
                Smalltalk exit.
            ].
            "/
            "/ GUI apps exit after the last user process has finished
            "/
            Display class exitOnLastClose:true.
            Processor exitWhenNoMoreUserProcesses:true.
        ] newProcess.
        standAloneProcess priority:8.
        standAloneProcess name:'main'.
        standAloneProcess beGroupLeader.
        standAloneProcess resume.
    ].

    "
     if view-classes exist, start dispatching;
     otherwise go into a read-eval-print loop
    "
    ((Display notNil and:[graphicalMode]) or:[standAloneProcess notNil]) ifTrue:[
        Processor dispatchLoop.
    ] ifFalse:[
        StandAlone ifFalse:[
            self readEvalPrint
        ]
    ].

    "done - the last process finished"

    self exit

    "Created: / 18.7.1996 / 21:07:39 / cg"
    "Modified: / 9.9.1996 / 17:42:50 / stefan"
    "Modified: / 25.5.1998 / 15:02:57 / cg"
!

readEvalPrint
    "{ Pragma: +optSpace }"

    "simple read-eval-print loop for non-graphical Minitalk"

    |text|

    'ST- ' print.
    Stdin skipSeparators.
    Stdin atEnd ifFalse:[
	text := Stdin nextChunk.
	[text notNil] whileTrue:[
	    AbortSignal handle:[:ex |
		'evaluation aborted' printCR
	    ] do:[
		(Compiler evaluate:text) printCR.
	    ].
	    'ST- ' print.
	    text := Stdin nextChunk
	].
    ].
    '' printCR
!

restart
    "startup after an image has been loaded;
     there are three change-notifications made to dependents of ObjectMemory,
     which allow a stepwise re-init: #earlyRestart, #restarted and #returnFromSnapshot.

     #earlySystemInstallation is sent for ST80 compatibility

     #earlyRestart is send first, nothing has been setup yet.
                   (should be used to flush all device dependent entries)

     #restarted is send right after.
                   (should be used to recreate external resources (fds, bitmaps etc)

     #returnFromSnapshot is sent last
                   (should be used to restart processes, reOpen Streams which cannot
                    be automatically be reopened (i.e. Sockets, Pipes) and so on.
                   (Notice that positionable fileStreams are already reopened and repositioned)
     "

    |deb insp idx|

    "/
    "/ when we arrive here, all objects from our previous life
    "/ have been reloaded - however, these contain invalid device
    "/ handles, display information etc.
    "/ also, dynamically loaded modules have not yet been reloaded.

    Initializing := true.
    AbstractOperatingSystem initializeConcreteClass.

    ImageRestartTime := AbsoluteTime now.

    CommandLine := CommandLineArguments copy.
    CommandLineArguments := CommandLineArguments asOrderedCollection.
    CommandLineArguments removeAtIndex:1. "/ the command

    idx := CommandLineArguments indexOf:'-q'.
    idx ~~ 0 ifTrue:[
        Object infoPrinting:false.
        ObjectMemory infoPrinting:false.
        CommandLineArguments removeAtIndex:idx.
    ].

    "/
    "/ invalidate the display connection.
    "/ This is required to avoid trouble if someone accesses
    "/ the Display during early startup.

    Display notNil ifTrue:[
        Display class allScreens do:[:aDisplay |
            aDisplay invalidateConnection
        ].
    ].

    "/
    "/ start catching SIGSEGV and SIGBUS

    OperatingSystem enableHardSignalInterrupts.

    "/ reinit Filename
    Filename reinitialize.

    "/
    "/ flush cached path directories (may have changed in the meanwhile)

    self flushPathCaches.

    "/
    "/ reinit the default streams: Stdin, Stdout and Stderr
    "/ after that, we can write to stderr.

    self reinitStandardStreams.

    "/
    "/ temporary switch back to dumb interface - 
    "/ to handle errors while view-stuff is not yet reinitialized"

    insp := Inspector.
    deb := Debugger.
    deb notNil ifTrue:[
        deb reinitialize
    ].
    Inspector := MiniInspector.
    Debugger := MiniDebugger.

    "/ reload any dynamically loaded objects.
    "/ this must be done before doing anything else below,
    "/ because the Processor may restart processes which use
    "/ this code.
    "/ Also, a dynamic object might be registered as dependent of
    "/ ObjectFileLoader; therefore, must reload before doing any notifications.

    ObjectFileLoader notNil ifTrue:[
        ObjectFileLoader reloadAllRememberedObjectFiles.
    ].

    ObjectMemory changed:#earlySystemInstallation.

    "/
    "/ reinitialize the Processor - restartable processes
    "/ are now restarted here.
    "/
    Processor reinitialize.

    "/
    "/ flush device handles & recreate OS resources (if possible)
    "/ (mostly view/GC/color & font stuff)

    ObjectMemory
        changed:#earlyRestart; changed:#restarted.

    "/
    "/ start catching SIGINT and SIGQUIT

    OperatingSystem enableUserInterrupts.

    "/
    "/ some class must be reinitialized before all others ...
    "/ - sorry, but order is important
    "/
    Workstation notNil ifTrue:[
        Workstation reinitialize.
    ].

    "/
    "/ done later now - when display connection is working
    "/
"/    "/
"/    "/ the final late notification - users can now assume that
"/    "/ views, forms etc. have been recreated.
"/
"/    ObjectMemory changed:#returnFromSnapshot.

    "/ now, display and view-stuff works;
    "/ back to the previous debugging interface

    Inspector := insp.
    Debugger := deb.

    Initializing := false.

    "/
    "/ if there is no Transcript, go to stderr

    Transcript isNil ifTrue:[
        Transcript := Stderr
    ].

    "/ give user a chance to re-customize things
    "/ reading if smalltalk_r.rc may be suppressed by the
    "/ -fastStart argument.

    idx := CommandLineArguments indexOf:'-faststart'.
    idx ~~ 0 ifTrue:[
        CommandLineArguments removeAtIndex:idx.
    ] ifFalse:[
        Class withoutUpdatingChangesDo:[
            (self fileIn:(self commandName , '_r.rc')) ifFalse:[
                "no _r.rc file where executable is; try default smalltalk_r.rc"
                self fileIn:'smalltalk_r.rc'
            ].
        ]
    ].

    self mainStartup:true

    "Modified: / 7.6.1998 / 02:48:00 / cg"
!

start
    "main startup, if there is a Display, initialize it
     and start dispatching; otherwise go into a read-eval-print loop."

    |idx graphicalMode arg debuggingStandAlone|

    graphicalMode := true.
    debuggingStandAlone := false.
    Initializing := true.

    CommandLine := CommandLineArguments copy.
    CommandLineArguments := CommandLineArguments asOrderedCollection.
    CommandLineArguments removeAtIndex:1. "/ the command

    "/
    "/ turn off info messages in standAlone app
    "/
    StandAlone ifTrue:[
	InfoPrinting := false.
	ObjectMemory infoPrinting:false.
	idx := CommandLineArguments indexOf:'-debug'.
	idx ~~ 0 ifTrue:[
	    CommandLineArguments removeAtIndex:idx.
	    debuggingStandAlone := true
	]
    ].

    "
     while reading patches- and rc-file, do not add things into change-file
    "
    Class withoutUpdatingChangesDo:[
	|myName defaultRC prevCatchSetting|

	"/
	"/ look for any '-q', '-e' or '-f' command line arguments
	"/ and handle them;
	"/ read startup and patches file
	"/
	idx := CommandLineArguments indexOf:'-q'.
	idx ~~ 0 ifTrue:[
	    Object infoPrinting:false.
	    ObjectMemory infoPrinting:false.
	    CommandLineArguments removeAtIndex:idx.
	].

	StandAlone ifFalse:[
	    "/ look for a '-e filename' argument - this will force evaluation of
	    "/ filename only, no standard startup

	    idx := CommandLineArguments indexOf:'-e'.
	    idx ~~ 0 ifTrue:[
		arg := CommandLineArguments at:idx + 1.

		CommandLineArguments
		    removeAtIndex:idx+1; removeAtIndex:idx.

		arg = '-' ifTrue:[
		    self fileInStream:Stdin
			   lazy:nil
			   silent:nil
			   logged:false
			   addPath:nil
		] ifFalse:[
		    self fileIn:arg.
		].
		self exit
	    ].
	].

	"/ if there is a <command>.pch, that patches file is read.
	"/ otherwise, look for a patches file.
	"/ BUT: the patches file is not read in StandAlone operation

	myName := self commandName.

	"/ look for a '-f filename' argument - this will force evaluation of
	"/ filename instead of smalltalk.rc

	idx := CommandLineArguments indexOf:'-f'.
	idx ~~ 0 ifTrue:[
	    myName := (CommandLineArguments at:idx + 1).
	    CommandLineArguments
		removeAtIndex:idx+1; removeAtIndex:idx.
	].

	"/ patches are installed, even if system methods are
	"/ overwritten.

	prevCatchSetting := Class catchMethodRedefinitions.
	Class catchMethodRedefinitions:false.

	(self secureFileIn:(myName asFilename withSuffix:'pch')) ifFalse:[
	    StandAlone ifFalse:[
		self secureFileIn:'patches'.
	    ].
	].

	Class catchMethodRedefinitions:prevCatchSetting.

	"/ then look for <command>.rc
	"/ if not found, read smalltalk.rc (or stxapp.rc for standAlone operation)
        
	(self secureFileIn:(myName asFilename withSuffix:'rc')) ifFalse:[
	    StandAlone ifFalse:[
		defaultRC := 'smalltalk.rc'
	    ] ifTrue:[
		defaultRC := 'stxapp.rc'
	    ].

	    "/ no .rc file where executable is; try default smalltalk.rc (or stxapp.rc)

	    (self secureFileIn:defaultRC) ifFalse:[
		StandAlone ifFalse:[
		    'Smalltalk [warning]: no startup rc-file found. Going into line-by-line interpreter.' infoPrintCR.
		    graphicalMode := false.
		]
	    ]
	].
    ].

    StandAlone ifTrue:[
	Debugger := Inspector := nil.
	debuggingStandAlone ifTrue:[
	    Debugger := MiniDebugger.
	].
    ] ifFalse:[
	"
	 enable the graphical debugger/inspector 
	 (they could have been (re)defined as autoloaded in the patches file)
	"
	self initStandardTools.
    ].

    Display isNil ifTrue:[
	graphicalMode := false.
    ].

    self mainStartup:graphicalMode

    "Modified: 10.1.1997 / 17:24:37 / cg"
! !

!Smalltalk class methodsFor:'startup queries'!

commandLine
    "return the full command line arguments (with which ST/X was started)"

    ^ CommandLine

    "Created: 19.7.1996 / 11:09:06 / cg"
!

commandLineArguments
    "return the user command line arguments;
     This is a collection of strings (separated command line words),
     from which the internal startup arguments have already been removed.
     I.e. if started with: 'smalltalk -I -f xxx foo bar baz',
     the commandLineArguments will be #('foo' 'bar' 'baz').
     In contrast, the value returned by #commandLine will be the full set of words."

    ^ CommandLineArguments

    "Modified: 19.7.1996 / 11:11:03 / cg"
!

commandName
    "return the excutables name - this is normally 'smalltalk', but
     can be something else for standAlone apps."

    ^ CommandLine at:1.

    "Modified: 19.7.1996 / 11:11:16 / cg"
!

isStandAloneApp
    "return true, if this is a standAlone application
     (in contrast to a full smalltalk system)."

    ^ StandAlone
!

startupArguments
    "return the arguments passed to StartupClass"

    ^ StartupArguments
!

startupClass
    "return the class, that will get the start message when smalltalk
     starts and its non-nil. Usually this is nil, but saving an image 
     with a non-nil StartupClass allows stand-alone applications"

    ^ StartupClass
!

startupClass:aClass selector:aSymbol arguments:anArrayOrNil
    "{ Pragma: +optSpace }"

    "set the class, selector and arguments to be performed when smalltalk
     starts. Setting those before saving a snapshot, will make the saved
     image come up executing your application (instead of the normal mainloop)"

    StartupClass := aClass.
    StartupSelector := aSymbol.
    StartupArguments := anArrayOrNil
!

startupSelector
    "return the selector, that will be sent to StartupClass"

    ^ StartupSelector
! !

!Smalltalk class methodsFor:'system environment'!

language
    "return the language setting"

    ^ Language

    "
     Smalltalk language
    "

    "Modified: 26.4.1996 / 17:10:05 / cg"
!

language:aLanguageSymbol
    "set the language"

    Language := aLanguageSymbol.
    self changed:#Language

    "
     Smalltalk language:#de
    "

    "Modified: 26.4.1996 / 17:13:34 / cg"
!

languageTerritory
    "return the language territory setting"

    ^ LanguageTerritory
!

languageTerritory:aTerritorySymbol
    "set the language territory"

    LanguageTerritory := aTerritorySymbol.
    self changed:#LanguageTerritory

    "
     Time now

     Smalltalk languageTerritory:#us.
     Time now

     Smalltalk languageTerritory:#de.
     Time now    
    "

    "Modified: 26.4.1996 / 17:12:39 / cg"
! !

!Smalltalk class methodsFor:'system management'!

compressSources
    "{ Pragma: +optSpace }"

    "compress the sources file, and remove all method source strings
     from the system and replace them by refs to a string in the source file.
     This is a bit different in ST/X than in other smalltalks,
     since we use per-class sourcefiles for the compiled classes,
     and a mix of in-memory strings and one-for-all sourceFile for
     incremental compiled methods.
     Therefore, only those sources which are not coming from compiled
     methods are put into the 'st.src' file - all others are untouched.
     This is being automated - so dont care for now."

    "
     first, find all methods which contain either a string-ref
     or an external string in the 'st.src' file
    "
    |newStream table source pos fileName|

    newStream := 'src.tmp' asFilename writeStream.
    newStream isNil ifTrue:[
	self error:'cannot create new temporary source file'.
	^ self
    ].

    table := IdentityDictionary new:100.

    Method allSubInstancesDo:[:aMethod |
	source := nil.
	aMethod sourcePosition notNil ifTrue:[
	    aMethod sourceFilename = 'st.src' ifTrue:[
		source := aMethod source.
	    ]
	] ifFalse:[
	    source := aMethod source
	].

	source notNil ifTrue:[
	    pos := newStream position.
	    newStream nextChunkPut:source.

	    "
	     dont change the methods info - maybe some write error
	     occurs later, in that case we abort and leave everything
	     untouched.
	    "
	    table at:aMethod put:pos
	]
    ].

    newStream close.

    "
     now, rename the new source file,
    "
    fileName := (ObjectMemory nameForSources).
    'src.tmp' asFilename renameTo:fileName.

    "good - now go over all changed methods, and change their
     source reference"

    table keysAndValuesDo:[:aMethod :pos |
	aMethod localSourceFilename:fileName position:pos.
"/        aMethod printCR.
    ].

    "
     Smalltalk compressSources
    "

    "Modified: 16.1.1997 / 01:25:58 / cg"
!

generateSingleSourceFile
    "{ Pragma: +optSpace }"

    "generate the sources file, and remove all method source strings
     from the system and replace them by refs to a string in the source file.
     This makes the image independent from the per-class source files
     and makes transportation of endUser applications easier, since
     only 3 files (executable, image and sourceFile) need to be 
     transported."

    |newStream table source pos fileName|

    newStream := 'src.tmp' asFilename writeStream.
    newStream isNil ifTrue:[
	self error:'cannot create new temporary source file'.
	^ self
    ].

    table := IdentityDictionary new:100.

    Method allSubInstancesDo:[:aMethod |
	source := aMethod source.
	source notNil ifTrue:[
	    pos := newStream position.
	    newStream nextChunkPut:source.

	    "
	     dont change the methods info - maybe some write error
	     occurs later, in that case we abort and leave everything
	     untouched.
	    "
	    table at:aMethod put:pos
	]
    ].

    newStream close.

    "
     now, rename the new source file,
    "
    fileName := (ObjectMemory nameForSources).
    'src.tmp' asFilename renameTo:fileName.

    "good - now go over all changed methods, and change their
     source reference"

    table keysAndValuesDo:[:aMethod :pos |
	aMethod localSourceFilename:fileName position:pos.
"/        aMethod printCR.
    ].

    "
     Smalltalk generateSingleSourceFile
    "

    "Modified: 16.1.1997 / 01:25:58 / cg"
    "Created: 17.10.1997 / 13:00:56 / cg"
!

installAutoloadedClasses
    "read the standard abbreviation file; install all classes found there as
     autoloaded. This takes some time ..."

    self installAutoloadedClassesFrom:'include/abbrev.stc'

    "
     Smalltalk installAutoloadedClasses
    "

    "Modified: 10.1.1997 / 15:10:48 / cg"
    "Created: 14.2.1997 / 17:32:57 / cg"
!

installAutoloadedClassesFrom:anAbbrevFilePath
    "read the given abbreviation file; install all classes found there as
     autoloaded. This takes some time ..."

    |f s s2 l clsName abbrev package cat rev cls|

    f := self getSystemFileName:anAbbrevFilePath.

    f notNil ifTrue:[
	s := f asFilename readStream.
	s notNil ifTrue:[

	    "/ yes, create any required nameSpace, without asking user.
	    Class createNameSpaceQuerySignal answer:true do:[

		[s atEnd] whileFalse:[
		    l := s nextLine withoutSeparators.
		    l notEmpty ifTrue:[
			s2 := l readStream.
			clsName := (s2 upTo:Character space) withoutSeparators asSymbol.
			(self at:clsName) isNil ifTrue:[
			    s2 skipSeparators.
			    abbrev := (s2 upTo:Character space) withoutSeparators asSymbol.
			    s2 skipSeparators.
			    package := (s2 upTo:Character space) withoutSeparators asSymbol.
			    s2 skipSeparators.

			    rev := nil.    
			    s2 skipSeparators.
			    s2 atEnd ifFalse:[
				s2 peek isDigit ifTrue:[
				    rev := (s2 upTo:Character space) withoutSeparators.
				    s2 skipSeparators.
				]
			    ].
			    cat := s2 upToEnd withoutSeparators.

			    (cat startsWith:$') ifTrue:[
				cat := (cat copyFrom:2 to:(cat size - 1)) withoutSeparators.
			    ].

			    (cat isNil or:[cat isEmpty]) ifTrue:[
				cat := 'autoloaded'
			    ].

			    "/ '  autoloaded: ' print. clsName print. ' in ' print. cat printCR.

			    "/ install if not already compiled-in
			    Autoload subclass:clsName
				instanceVariableNames:''
				classVariableNames:''
				poolDictionaries:''
				category:cat
				inEnvironment:Smalltalk.

			    cls := self at:clsName.
			    cls isNil ifTrue:[
				('Smalltalk [warning]: failed to add ' , clsName , ' as autoloaded.') infoPrintCR.
			    ] ifFalse:[
				cls package:package asSymbol.
				rev notNil ifTrue:[
				    cls setBinaryRevision:rev
				]
			    ]    
			]
		    ]
		]
	    ].
	    s close.
	].
    ]

    "
     Smalltalk installAutoloadedClassesFrom:'include/abbrev.stc'
    "

    "Modified: 10.2.1997 / 12:22:44 / cg"
!

loadBinaries
    "return true, if binaries should be loaded into the system,
     false if this should be suppressed. The default is false (for now)."

    ^ LoadBinaries
!

loadBinaries:aBoolean
    "{ Pragma: +optSpace }"

    "turn on/off loading of binary objects"

    aBoolean ifTrue:[
	(ObjectFileLoader notNil and:[ObjectFileLoader canLoadObjectFiles]) ifTrue:[
	    LoadBinaries := true.
	    ^ self
	].
	'Smalltalk [info]: this system does not support binary loading' infoPrintCR.
    ].
    LoadBinaries := false

    "Modified: 10.1.1997 / 15:11:00 / cg"
!

logDoits
    "return true if doits should go into the changes file
     as well as changes - by default, this is off, since
     it can blow up the changes file enormously ...
    "

    ^ LogDoits

    "
     LogDoits := false
     LogDoits := true
    "
!

logDoits:aBoolean
    "{ Pragma: +optSpace }"

    "turn on/off logging of doits in the changes file.
     By default, this is off, since it can blow up the 
     changes file enormously ...
    "

    LogDoits := aBoolean

!

makeBytecodeMethods
    "{ Pragma: +optSpace }"

    "walk over all methods and make each a bytecode method
     iff it does not contain primitive C code.
     Experimental and not yet used."

    Method allSubInstancesDo:[:aMethod |
	|newMethod|

	aMethod hasPrimitiveCode ifFalse:[
	    newMethod := aMethod asByteCodeMethod.
	    newMethod ~~ aMethod ifTrue:[
		aMethod becomeSameAs:newMethod
	    ]
	].
    ].

    "
     Smalltalk makeBytecodeMethods
    "

    "Modified: 16.1.1997 / 01:25:58 / cg"
    "Created: 17.10.1997 / 13:52:19 / cg"
!

saveEmergencyImage:aBoolean
    "set/clear the flag which controls if ST/X should save an
     emergency image in case of a broken display connection.
     The default is true.
     This may be useful, if you work with an unsecure display
     (serial line), and want to have a chance of proceeding after
     a crash. In multiheaded applications, this only affects 
     crashes of the master Display connection (the initial connection);
     errors on other displays are reported to the views and treated
     like window destroy from the windowManager."

    SaveEmergencyImage := aBoolean

    "Modified: / 24.10.1997 / 18:22:26 / cg"
!

systemOrganization
    "for partial ST80 compatibility;
     In ST80, Smalltalk organization returns a systemOrganizer, which
     keeps track of class-categories, while all classes return a classOrganizer
     from #organization, which keeps track of method categories of that class.
     Since in ST/X, Smallalk is a class, there is now a conflict.
     To make a workaround possible, use #systemOrganization when porting
     VW apps to ST/X to get the class-categories.
     Read the documentation in SystemOrganizer for more info."

    ^ SystemOrganizer for:nil

    "Created: / 20.6.1998 / 12:24:02 / cg"
    "Modified: / 20.6.1998 / 12:41:34 / cg"
!

underclaredPrefix
    "the prefix used for undeclared variables"

    ^ 'Undeclared:::'

    "Created: / 31.10.1997 / 01:13:10 / cg"
! !

!Smalltalk class methodsFor:'system management-fileIn'!

fileIn:aFileName
    "read in the named file - look for it in some standard places;
     return true if ok, false if failed"

    ^ self fileIn:aFileName lazy:nil silent:nil logged:false 

    "
     Smalltalk fileIn:'source/TicTacToe.st'
    "

    "Created: 28.10.1995 / 17:06:28 / cg"
!

fileIn:aFileName lazy:lazy
    "read in the named file - look for it in some standard places;
     return true if ok, false if failed.
     If lazy is true, no code is generated for methods, instead stubs
     are created which compile themself when first executed. This allows
     for much faster fileIn (but slows down the first execution later).
     Since no syntax checks are done when doing lazy fileIn, use this only for
     code which is known to be syntactically correct."

    ^ self fileIn:aFileName lazy:lazy silent:nil logged:false 

    "
     Smalltalk fileIn:'source/TicTacToe.st' lazy:true
    "

    "Created: 28.10.1995 / 17:06:36 / cg"
!

fileIn:aFileName lazy:lazy silent:silent
    "read in the named file - look for it in some standard places;
     return true if ok, false if failed.
     If lazy is true, no code is generated for methods, instead stubs
     are created which compile themself when first executed. This allows
     for much faster fileIn (but slows down the first execution later).
     Since no syntax checks are done when doing lazy fileIn, use this only for
     code which is known to be syntactically correct.
     If silent is true, no compiler messages are output to the transcript.
     Giving nil for silent/lazy will use the current settings."

    ^ self fileIn:aFileName lazy:lazy silent:silent logged:false

    "Created: 28.10.1995 / 17:06:41 / cg"
!

fileIn:aFileNameOrString lazy:lazy silent:silent logged:logged
    "read in the named file - look for it in some standard places;
     return true if ok, false if failed.
     If lazy is true, no code is generated for methods, instead stubs
     are created which compile themself when first executed. This allows
     for much faster fileIn (but slows down the first execution later).
     Since no syntax checks are done when doing lazy fileIn, use this only for
     code which is known to be syntactically correct.
     If silent is true, no compiler messages are output to the transcript.
     Giving nil for silent/lazy will use the current settings."

    |fileNameString aStream path morePath bos|

    fileNameString := aFileNameOrString asString.

    "
     an object or shared object ?
    "
    (ObjectFileLoader notNil
    and:[ObjectFileLoader hasValidBinaryExtension:fileNameString]) ifTrue:[
	LoadBinaries ifFalse:[^ false].
	path := self getBinaryFileName:fileNameString.
	path isNil ifTrue:[^ false].
	^ (ObjectFileLoader loadObjectFile:fileNameString) notNil
    ].

    (fileNameString asFilename hasSuffix:'cls') ifTrue:[
	BinaryObjectStorage notNil ifTrue:[
	    path := self getBinaryFileName:fileNameString.
	    path isNil ifTrue:[^ false].
	    aStream := path asFilename readStream.
	    aStream notNil ifTrue:[
		bos := BinaryObjectStorage onOld:aStream.
		bos next.
		bos close.
		^ true
	    ].
	    ^ false
	]
    ].

    (fileNameString startsWith:'source/') ifTrue:[
	aStream := self sourceFileStreamFor:(fileNameString copyFrom:8)
    ] ifFalse:[
	(fileNameString startsWith:'fileIn/') ifTrue:[
	    aStream := self fileInFileStreamFor:(fileNameString copyFrom:8)
	] ifFalse:[
	    aStream := self systemFileStreamFor:fileNameString.
	    (aStream notNil and:[fileNameString includes:$/]) ifTrue:[
		"/ temporarily prepend the files directory
		"/ to the searchPath.
		"/ This allows fileIn-driver files to refer to local
		"/ files via a relative path, and drivers to fileIn other
		"/ drivers ...
		morePath := aStream pathName asFilename directoryName.
	    ]
	]
    ].
    aStream isNil ifTrue:[^ false].
    ^ self fileInStream:aStream lazy:lazy silent:silent logged:logged addPath:morePath

    "
     Smalltalk fileIn:'source/TicTacToe.st' lazy:true silent:true
    "

    "Modified: 8.1.1997 / 17:58:31 / cg"
!

fileIn:aFileName logged:logged
    "read in the named file - look for it in some standard places;
     return true if ok, false if failed.
     The argument logged controls, if the changefile is to be updated."

    ^ self fileIn:aFileName lazy:nil silent:nil logged:logged 

    "
     Smalltalk fileIn:'source/TicTacToe.st' logged:false
    "
!

fileInChanges
    "read in the last changes file - bringing the system to the state it
     had when left the last time.
     WARNING: this method is rubbish: it should only read things after the
	      last '**snapshot**' - entry 
	      (instead of the complete changes file)."

    "
     do NOT update the changes file now ...
    "
    self fileIn:ChangeFileName logged:false

    "
     Smalltalk fileInChanges 
    "
!

fileInClass:aClassName
    "find a source/object file for aClassName and -if found - load it.
     search is in some standard places trying driver-file (.ld), object-file (.o) and 
     finally source file (.st) in that order.
     The file is first searched for using the class name, then the abbreviated name."

    ^ self 
	fileInClass:aClassName 
	package:nil
	initialize:true 
	lazy:false 
	silent:nil

    "Modified: / 9.1.1998 / 14:41:46 / cg"
!

fileInClass:aClassName fromObject:aFileName
    "read in the named object file and dynamic-link it into the system
     - look for it in some standard places.
     Only install the named class from this object file.
     Return true if ok, false if failed."

    |path ok|

    "
     check if the dynamic loader class is in
    "
    (LoadBinaries not or:[ObjectFileLoader isNil]) ifTrue:[^ false].

    (path := self getBinaryFileName:aFileName) isNil ifTrue:[^ false].
    ok := (ObjectFileLoader loadClass:aClassName fromObjectFile:path) notNil.
    ok ifTrue:[
	SilentLoading ifFalse:[
	    Transcript show:'  loaded ' , aClassName , ' from ' ; showCR:aFileName.
	]
    ].
    ^ ok

    "
     Smalltalk fileInClass:'AbstractPath' fromObject:'../../goodies/Paths/AbstrPath.so' 
     Smalltalk fileInClass:'ClockView' fromObject:'../../libwidg3/libwidg3.so' 
    "

    "Modified: 10.9.1996 / 20:43:52 / cg"
!

fileInClass:aClassName initialize:doInit
    "find a source/object file for aClassName and -if found - load it.
     search is in some standard places trying driver-file (.ld), object-file (.o) and 
     finally source file (.st) in that order.
     The file is first searched for using the class name, then the abbreviated name."

    ^ self 
	fileInClass:aClassName 
	package:nil
	initialize:doInit 
	lazy:false 
	silent:nil

    "Modified: / 9.1.1998 / 14:42:02 / cg"
!

fileInClass:aClassName initialize:doInit lazy:loadLazy
    "find a source/object file for aClassName and -if found - load it.
     search is in some standard places trying driver-file (.ld), object-file (.o) and 
     finally source file (.st) in that order.
     The file is first searched for using the class name, then the abbreviated name."

     ^ self 
	fileInClass:aClassName 
	package:nil
	initialize:doInit 
	lazy:loadLazy 
	silent:nil

    "Modified: / 9.1.1998 / 14:42:19 / cg"
!

fileInClass:aClassName initialize:doInit lazy:loadLazy silent:beSilent 
    "find a source/object file for aClassName and -if found - load it.
     Search is in some standard places, trying driver-file (.ld), object-file (.so / .o) and 
     finally source file (.st), in that order.
     The file is first searched for using the class name, then the abbreviated name.
     The argument doInit controlls if the class should be sent a #initialize after the
     load; loadLazy tells if it should be loaded lazyly. beSilent tells if the compiler
     should not send notes to the transcript; it can be true, false or nil, where
     nil uses the value from SilentLoading."

    ^ self
	fileInClass:aClassName 
	package:nil
	initialize:doInit 
	lazy:loadLazy 
	silent:beSilent

    "Modified: / 9.1.1998 / 14:42:28 / cg"
!

fileInClass:aClassName package:package initialize:doInit lazy:loadLazy silent:beSilent 
    "find a source/object file for aClassName and -if found - load it.
     This is the workhorse for autoloading.
     Search is in some standard places, trying driver-file (.ld), object-file (.so / .o) and 
     finally source file (.st), in that order.
     The file is first searched for using the class name, then the abbreviated name.
     The argument doInit controlls if the class should be sent a #initialize after the
     load; loadLazy tells if it should be loaded lazyly. beSilent tells if the compiler
     should not send notes to the transcript; it can be true, false or nil, where
     nil uses the value from SilentLoading."

    |shortName libName newClass ok wasLazy wasSilent sharedLibExtension inStream mgr fn|

    wasLazy := Compiler compileLazy:loadLazy.
    beSilent notNil ifTrue:[
        wasSilent := self silentLoading:beSilent.
    ].

    [
        Class withoutUpdatingChangesDo:
        [
            |zarFn zar entry|

            ok := false.

            shortName := self fileNameForClass:aClassName.
            "
             first, look for a loader-driver file (in fileIn/xxx.ld)
            "
            (ok := self fileIn:('fileIn/' , shortName , '.ld') lazy:loadLazy silent:beSilent)
            ifFalse:[
                "
                 try abbreviated driver-file (in fileIn/xxx.ld)
                "
                shortName ~= aClassName ifTrue:[
                    ok := self fileIn:('fileIn/' , aClassName , '.ld') lazy:loadLazy silent:beSilent
                ].
                ok ifFalse:[
                    "
                     then, if dynamic linking is available, 
                    "
                    (LoadBinaries and:[ObjectFileLoader notNil]) ifTrue:[
                        sharedLibExtension := ObjectFileLoader sharedLibraryExtension.

                        "
                         first look for a class packages shared binary in binary/xxx.o
                        "
                        libName := self libraryFileNameOfClass:aClassName.
                        libName notNil ifTrue:[
                            (ok := self fileInClass:aClassName fromObject:(libName, sharedLibExtension))
                            ifFalse:[
                                sharedLibExtension ~= '.o' ifTrue:[
                                    ok := self fileInClass:aClassName fromObject:(libName, '.o')
                                ]
                            ].
                        ].

                        "
                         then, look for a shared binary in binary/xxx.o
                        "
                        ok ifFalse:[
                            (ok := self fileInClass:aClassName fromObject:(shortName, sharedLibExtension))
                            ifFalse:[
                                sharedLibExtension ~= '.o' ifTrue:[
                                    ok := self fileInClass:aClassName fromObject:(shortName, '.o')
                                ].
                                ok ifFalse:[
                                    shortName ~= aClassName ifTrue:[
                                        (ok := self fileInClass:aClassName fromObject:(aClassName, sharedLibExtension))
                                        ifFalse:[
                                            sharedLibExtension ~= '.o' ifTrue:[
                                                ok := self fileInClass:aClassName fromObject:(aClassName, '.o')
                                            ]
                                        ]
                                    ].
                                ].
                            ].
                        ].
                    ].

                    "
                     if that did not work, look for a compiled-bytecode file ...
                    "
                    ok ifFalse:[
                        (ok := self fileIn:(shortName , '.cls') lazy:loadLazy silent:beSilent)
                        ifFalse:[
                            shortName ~= aClassName ifTrue:[
                                ok := self fileIn:(aClassName , '.cls') lazy:loadLazy silent:beSilent
                            ]
                        ]
                    ].
                    "
                     if that did not work, and the classes package is known,
                     look for an st-cls file 
                     in a package subdir of the source-directory ...
                    "
                    ok ifFalse:[
                        package notNil ifTrue:[
                            (ok := self fileIn:(package , '/' , shortName , '.cls') lazy:loadLazy silent:beSilent)
                            ifFalse:[
                                shortName ~= aClassName ifTrue:[
                                    ok := self fileIn:(package , '/' , aClassName , '.cls') lazy:loadLazy silent:beSilent
                                ]
                            ]
                        ]
                    ].

                    "
                     if that did not work, look for an st-source file ...
                    "
                    ok ifFalse:[
                        fn := shortName , '.st'.
                        (ok := self fileIn:fn lazy:loadLazy silent:beSilent)
                        ifFalse:[
                            shortName ~= aClassName ifTrue:[
                                fn := aClassName , '.st'.
                                ok := self fileIn:fn lazy:loadLazy silent:beSilent
                            ].
                            ok ifFalse:[
                                "
                                 ... and in the standard source-directory
                                "
                                fn := 'source/' , shortName , '.st'.
                                (ok := self fileIn:fn lazy:loadLazy silent:beSilent)
                                ifFalse:[
                                    shortName ~= aClassName ifTrue:[
                                        fn := 'source/' , aClassName , '.st'.
                                        ok := self fileIn:fn lazy:loadLazy silent:beSilent
                                    ]
                                ]
                            ]
                        ].
                        "
                         if that did not work, and the classes package is known,
                         look for an st-source file 
                         in a package subdir of the source-directory ...
                        "
                        ok ifFalse:[
                            package notNil ifTrue:[
                                fn := package , '/' , shortName , '.st'.
                                (ok := self fileIn:fn lazy:loadLazy silent:beSilent)
                                ifFalse:[
                                    shortName ~= aClassName ifTrue:[
                                        fn := package , '/' , aClassName , '.st'.
                                        ok := self fileIn:fn lazy:loadLazy silent:beSilent
                                    ].
                                    ok ifFalse:[
                                        "
                                         ... and in the standard source-directory
                                        "
                                        fn := 'source/' , package , '/' , shortName , '.st'.
                                        (ok := self fileIn:fn lazy:loadLazy silent:beSilent)
                                        ifFalse:[
                                            shortName ~= aClassName ifTrue:[
                                                fn := 'source/' , package , '/' , aClassName , '.st'.
                                                ok := self fileIn:fn lazy:loadLazy silent:beSilent
                                            ]
                                        ]
                                    ]
                                ].
                            ]
                        ].
                        "
                         if that did not work, and the classes package is known,
                         look for a zipArchive containing a class entry.
                        "
                        ok ifFalse:[
                            package notNil ifTrue:[
                                zarFn := package asFilename withSuffix:'zip'.
                                zarFn := self getSourceFileName:zarFn.
                                zarFn notNil ifTrue:[
                                    zar := ZipArchive oldFileNamed:zarFn.
                                    zar notNil ifTrue:[
                                        entry := zar extract:(shortName , '.st').
                                        entry isNil ifTrue:[
                                            entry := zar extract:(aClassName , '.st').
                                        ].
                                        entry notNil ifTrue:[
                                            ok := self 
                                                    fileInStream:(entry asString readStream)
                                                    lazy:loadLazy 
                                                    silent:beSilent 
                                                    logged:false
                                                    addPath:nil
                                        ].
                                    ]
                                ]
                            ]
                        ].

                        "
                         if that did not work, 
                         look for a zipArchive containing a class entry.
                        "
                        ok ifFalse:[
                            zarFn := self getSourceFileName:'source.zip'.
                            zarFn notNil ifTrue:[
                                zar := ZipArchive oldFileNamed:zarFn.
                                zar notNil ifTrue:[
                                    entry := zar extract:(shortName , '.st').
                                    entry isNil ifTrue:[
                                        entry := zar extract:(aClassName , '.st').
                                    ].
                                    entry notNil ifTrue:[
                                        ok := self 
                                                fileInStream:(entry asString readStream)
                                                lazy:loadLazy 
                                                silent:beSilent 
                                                logged:false
                                                addPath:nil
                                    ].
                                ]
                            ]
                        ].
                        ok ifFalse:[
                            "
                             new: if there is a sourceCodeManager, ask it for the classes sourceCode
                            "
                            (mgr := Smalltalk at:#SourceCodeManager) notNil ifTrue:[
                                inStream := mgr getMostRecentSourceStreamForClassNamed:aClassName.
                                inStream notNil ifTrue:[
                                    fn := nil.
                                    ok := self fileInStream:inStream lazy:loadLazy silent:beSilent logged:false addPath:nil. 
                                ]
                            ].
                        ].
                    ].
                ].
            ]
        ].
        ok ifTrue:[
            newClass := self at:(aClassName asSymbol).
            newClass notNil ifTrue:[
                fn notNil ifTrue:[
                    newClass classFilename isNil ifTrue:[
                        newClass setClassFilename:fn
                    ].
                ].

                doInit ifTrue:[
                    newClass initialize
                ]
            ]
        ].
    ] valueNowOrOnUnwindDo:[
        Compiler compileLazy:wasLazy. 
        wasSilent notNil ifTrue:[
            self silentLoading:wasSilent
        ]
    ].

    ^ newClass

    "Created: / 9.1.1998 / 14:40:32 / cg"
    "Modified: / 22.4.1998 / 18:01:37 / cg"
!

fileInClassLibrary:aClassLibraryName
    "find an object file containing a binary class library in some standard places
     and load it. This install all of its contained classes.
     Return true if ok, false if not."

    ObjectFileLoader isNil ifTrue:[^ false].
    ^ (ObjectFileLoader 
	    loadObjectFile:(aClassLibraryName , (ObjectFileLoader sharedLibraryExtension))
      ) notNil

    "
     Smalltalk fileInClassLibrary:'libtable'
     Smalltalk fileInClassLibrary:'binary/libwidg3'
    "

    "Modified: 8.1.1997 / 17:58:56 / cg"
!

fileInStream:aStream lazy:lazy silent:silent logged:logged addPath:morePath
    "read sourceCode from aStream;
     return true if ok, false if failed.
     If lazy is true, no code is generated for methods, instead stubs
     are created which compile themself when first executed. This allows
     for much faster fileIn (but slows down the first execution later).
     Since no syntax checks are done when doing lazy fileIn, use this only for
     code which is known to be syntactically correct.
     If silent is true, no compiler messages are output to the transcript.
     Giving nil for silent/lazy will use the current settings.
     If morePath is nonNil, it is prepended to the systemPath temporarily during the
     fileIn. This allows for st-expressions to refer to more files (i.e. fileIn more)
     using a relative path."

    |wasLazy wasSilent oldSystemPath oldRealPath|

    aStream isNil ifTrue:[^ false].

    lazy notNil ifTrue:[wasLazy := Compiler compileLazy:lazy].
    silent notNil ifTrue:[wasSilent := self silentLoading:silent].
    [
	Class updateChangeFileQuerySignal answer:logged do:[
	    oldSystemPath := SystemPath copy.
	    morePath notNil ifTrue:[
		SystemPath addFirst:morePath.
		oldRealPath := RealSystemPath.
		RealSystemPath := nil.
	    ].
	    aStream fileIn
	]
    ] valueNowOrOnUnwindDo:[
	morePath notNil ifTrue:[
	    SystemPath := oldSystemPath.
	    RealSystemPath := oldRealPath.
	].
	lazy notNil ifTrue:[Compiler compileLazy:wasLazy]. 
	silent notNil ifTrue:[self silentLoading:wasSilent].
	aStream close
    ].
    ^ true

    "
     Smalltalk fileInStream:('source/TicTacToe.st' asFilename readStream) lazy:true silent:true
    "

    "Modified: 5.11.1996 / 20:03:35 / cg"
!

loadClassLibraryIfAbsent:name
    "dynamically load a classLibrary, if not already loaded
     and the system supports dynamic loading.
     Return true, if the library is loaded, false if not.
     This entry is called without system specific filename
     extensions - it is portable among different architectures
     as long as corresponding files (x.so / x.dll / x.sl / x.o) 
     are be present ..."

    ObjectMemory 
	binaryModuleInfo 
	    do:[:entry | 
		   entry type == #classLibrary ifTrue:[
		       entry libraryName = name ifTrue:[
			  ^ true        "/ already loaded
		       ]
		   ].
	       ].

    ^ self fileInClassLibrary:name

    "
     Smalltalk loadClassLibraryIfAbsent:'libbasic'
     Smalltalk loadClassLibraryIfAbsent:'libwidg3'
    "

    "Modified: 31.10.1996 / 16:57:24 / cg"
!

secureFileIn:aFileName
    "read in the named file, looking for it at standard places.
     Catch any error during fileIn. Return true if ok, false if failed"

    |retVal|

    retVal := false.

    (SignalSet with:AbortSignal with:Process terminateSignal)
	handle:[:ex |
	    ex return
	] do:[
	    retVal := self fileIn:aFileName
	].
    ^ retVal
!

silentFileIn:aFilename
    "same as fileIn:, but do not output 'compiled...'-messages on Transcript.
     Main use is during startup."

    |wasSilent|

    wasSilent := self silentLoading:true.
    [
	self fileIn:aFilename
    ] valueNowOrOnUnwindDo:[
	self silentLoading:wasSilent
    ]
! !

!Smalltalk class methodsFor:'system management-files'!

bitmapFileStreamFor:aFileName
    "search aFileName in some standard places;
     return a readonly fileStream or nil if not found.
     Searches in subdirectories named 'bitmaps' in SystemPath"

    |aString|

    aString := self getBitmapFileName:aFileName.
    aString notNil ifTrue:[
	^ aString asFilename readStream
    ].
    ^ nil
!

classNameForFile:aFileName
    "return the className which corresponds to an abbreviated fileName,
     or nil if no special translation applies. The given filename arg may
     include a '.st' suffix (but no other)."

    |fn|

    (aFileName asFilename hasSuffix:'st') ifTrue:[
	fn := aFileName copyWithoutLast:3
    ] ifFalse:[
	fn := aFileName
    ].
    ^ self filenameAbbreviations keyAtEqualValue:fn ifAbsent:[fn].

    "
     Smalltalk classNameForFile:'DrawObj'  
     Smalltalk classNameForFile:'DrawObj.st' 
     Smalltalk classNameForFile:'ArrColl.st' 
     Smalltalk classNameForFile:'ArrColl.chg' 
    "

    "Modified: 11.12.1995 / 14:51:10 / cg"
!

constructPathFor:aDirectoryName
    "search for aDirectory in SystemPath; 
     return a collection of pathes which include that directory."

    ^ self realSystemPath select:[:dirName |
	|fullPath|

	fullPath := dirName asFilename construct:aDirectoryName.
	"/ fullPath exists and:[fullPath isDirectory and:[fullPath isReadable]]
	fullPath isDirectory and:[fullPath isReadable]
    ].
!

fileInFileStreamFor:aFileName
    "search aFileName in some standard places;
     return a readonly fileStream or nil if not found.
     Searches in subdirectories named 'fileIn' in SystemPath"

    |aString|

    aString := self getFileInFileName:aFileName.
    aString notNil ifTrue:[
	^ aString asFilename readStream
    ].
    ^ nil
!

fileNameForClass:aClassOrClassName
    "return a good filename for aClassOrClassName -
     using the abbreviation file if there is one"

    |fileName abbrev aClassName|


    aClassOrClassName isBehavior ifTrue:[
	aClassOrClassName isMeta ifTrue:[
	    aClassName := aClassOrClassName soleInstance name
	] ifFalse:[
	    aClassName := aClassOrClassName name
	]
    ] ifFalse:[
	aClassName := aClassOrClassName
    ].

    fileName := aClassName asSymbol.

    "first look, if the class exists and has a fileName"

" later ... - compiler should put the source file name into the class
    (Symbol hasInterned:aClassName) ifTrue:[:sym |
	|class|

	(Smalltalk includesKey:sym) ifTrue:[
	    class := Smalltalk at:sym.
	    class isClass ifTrue:[
		abbrev := class classFileName.
	    ]
	]
    ].
"

    "look for abbreviation"

    abbrev := self filenameAbbreviations at:fileName ifAbsent:[nil].
    abbrev notNil ifTrue:[^ abbrev].

    "no abbreviation found - if its a short name, take it"

    OperatingSystem maxFileNameLength < (fileName size + 3) ifTrue:[
	"this will only be triggered on sys5.3/DOS type systems"
	('Smalltalk [info]: cant find short for ' , fileName , ' in abbreviation file') infoPrintCR.
    ].
    ^ fileName asString

    "
     Smalltalk fileNameForClass:SmallInteger    
     Smalltalk fileNameForClass:'SmallInteger'    
     Smalltalk fileNameForClass:'UnixOperatingSystem' 
     Smalltalk fileNameForClass:'Launcher' 
     Smalltalk fileNameForClass:'SomeUnknownClass' 
    "

    "Modified: / 27.7.1998 / 19:59:47 / cg"
!

filenameAbbreviations
    "return a dictionary containing the classname-to-filename
     mappings. (needed for sys5.3 users, where filenames are limited
     to 14 chars)"

    CachedAbbreviations isNil ifTrue:[
	self readAbbreviations
    ].
    ^ CachedAbbreviations

    "flush with:

     CachedAbbreviations := nil
    "
    "
     Smalltalk filenameAbbreviations
    "
!

flushPathCaches
    "{ Pragma: +optSpace }"

    "forget pathCaches - these are collections containing valid directory names,
     where system files (resource, bitmaps etc.) are found.
     A flush is only required, if a new system directory has been created while
     the system is active, and those files should override the others
     (for example, if you created a private resource directory)"

    RealSystemPath := ResourcePath := SourcePath := BitmapPath := BinaryPath := FileInPath := nil

    "
     Smalltalk flushPathCaches
    "
!

getBinaryFileName:aFileName
    "search aFileName in some standard places 
     (subdirectories named 'binary' in SystemPath);
     return the absolute filename or nil if none is found."

    BinaryPath isNil ifTrue:[
	BinaryPath := self constructPathFor:BinaryDirName
    ].

    ^ self searchPath:BinaryPath for:aFileName in:BinaryDirName

    "Modified: 18.7.1996 / 15:53:49 / cg"
!

getBitmapFileName:aFileName
    "search aFileName in some standard places 
     (subdirectories named 'bitmaps' in SystemPath);
     return the absolute filename or nil if none is found."

    |f|

    BitmapPath isNil ifTrue:[
	BitmapPath := self constructPathFor:BitmapDirName
    ].

    "/ first, try a bitmaps subdir along the path.
    f := self searchPath:BitmapPath for:aFileName in:BitmapDirName.
    f isNil ifTrue:[
	"/ then, try it itself along the path.
	f := self searchPath:RealSystemPath for:aFileName in:nil
    ].
    ^ f

    "
     Smalltalk getBitmapFileName:'SBrowser.xbm'
    "

    "Modified: 18.7.1996 / 15:53:55 / cg"
!

getFileInFileName:aFileName
    "search aFileName in some standard places 
     (subdirectories named 'fileIn' in SystemPath);
     return the absolute filename or nil if none is found."

    FileInPath isNil ifTrue:[
	FileInPath := self constructPathFor:FileInDirName
    ].

    ^ self searchPath:FileInPath for:aFileName in:FileInDirName

    "Modified: 18.7.1996 / 15:53:59 / cg"
!

getResourceFileName:aFileName
    "search aFileName in some standard places 
     (subdirectories named 'resource' in SystemPath);
     return the absolute filename or nil if none is found."

    |f|

    ResourcePath isNil ifTrue:[
	ResourcePath := self constructPathFor:ResourceDirName
    ].

    "/ first, try a resource subdir along the path.
    f := self searchPath:ResourcePath for:aFileName in:ResourceDirName.
    f isNil ifTrue:[
	"/ then, try it itself along the path.
	f := self searchPath:RealSystemPath for:aFileName in:nil
    ].
    ^ f

    "
     Smalltalk getResourceFileName:'SBrowser.rs'
    "

    "Modified: 18.7.1996 / 15:54:03 / cg"
!

getSourceFileName:aFileName
    "search aFileName in some standard places 
     (subdirectories named 'source' in SystemPath);
     return the absolute filename or nil if none is found.
     This is used to find a sourceFile for a methods source,
     if no sourceCodeManager is available."

    |f|

    SourcePath isNil ifTrue:[
	SourcePath := self constructPathFor:SourceDirName
    ].

    "/ first, try a source subdir along the path.
    f := self searchPath:SourcePath for:aFileName in:SourceDirName.
    f isNil ifTrue:[
	"/ then, try it itself along the path.
	f := self searchPath:RealSystemPath for:aFileName in:nil
    ].
    ^ f

    "
     Smalltalk getSourceFileName:'Smalltalk.st'  
     Smalltalk getSourceFileName:'ArrColl.st' 
    "

    "Modified: 18.7.1996 / 15:54:07 / cg"
!

getSystemFileName:aFileNameOrString
    "search aFileNameOrString in some standard places;
     return the absolute filename or nil if none is found.
     see comment in Smalltalk>>initSystemPath."

    "credits for this method go to Markus ...."

    |fn nameString|

    fn := aFileNameOrString asFilename.
    nameString := fn name.
    fn isAbsolute ifTrue:[
	"dont use path for absolute file names"

	^ nameString
    ].

    self realSystemPath do:[:dirName |
	|realName|

	realName := dirName asFilename construct:nameString.
	"/
	"/ here, we also return true if its a directory
	"/ (Even if unreadable). 
	"/ It could be that the file itself is still readable.
	"/
	(realName isDirectory or:[realName isReadable]) ifTrue: [
	    ^ realName name
	]
    ].
    ^ nil
!

libraryFileNameOfClass:aClassOrClassName
    "for a given class, return the name of a classLibrary which contains
     binary code for it.
     Read the libinfo file 'liblist.stc' (which is created during the compilation process)
     for an entry for aClassOrClassName.
     Search for the className in the first col, and return the value found in
     the 2nd col.
     Return nil if no entry is found.

     A nil returns means that this class is either built-in or not present
     in a package-class library (i.e. either as separate .o or separate .st file).
     Otherwise, the returned name is the classLibrary object of that class.
     The classes code can be loaded from that file if binary loading is supported."

    |aStream line words n aClassName|

    aClassOrClassName isBehavior ifTrue:[
	aClassName := aClassOrClassName name
    ] ifFalse:[
	aClassName := aClassOrClassName
    ].
    aClassName := aClassName asString.

    #('include/liblist.stc')    "/ filenames
    with:#(2)                   "/ column
    do:[:fileName :col |

	aStream := self systemFileStreamFor:fileName.
	aStream notNil ifTrue:[
	    [aStream atEnd] whileFalse:[
		line := aStream nextLine.
		line notNil ifTrue:[
		    (line startsWith:'#') ifFalse:[
			words := line asCollectionOfWords.
			(n := words size) > 1 ifTrue:[
			    (words at:1) = aClassName ifTrue:[
				n >= col ifTrue:[
				    aStream close.
				    ^ (words at:col) withoutSeparators
				]
			    ]
			]
		    ]
		]
	    ].
	    aStream close
	].
    ].

    ^ nil

    "
     Smalltalk libraryFileNameOfClass:'ClockView' 
     Smalltalk libraryFileNameOfClass:'Bag' 
    "

    "Modified: 6.11.1995 / 15:41:39 / cg"
!

readAbbreviations
    "read classname to filename mappings from include/abbrev.stc.
     sigh - all for those poor sys5.3 or MSDOS people with short filenames ..."

    |abbrevs aStream line words nm abbrev key oldAbbrev cls|

    CachedAbbreviations := abbrevs := IdentityDictionary new.
    aStream := self systemFileStreamFor:'include/abbrev.stc'.
    aStream notNil ifTrue:[
        ('Smalltalk [info]: reading class abbreviations from ''' , aStream pathName ,'''') infoPrintCR.
        [aStream atEnd] whileFalse:[
            line := aStream nextLine.
            line notNil ifTrue:[
                (line startsWith:'#') ifFalse:[
                    words := line asCollectionOfWords.
                    words size >= 2 ifTrue:[
                        nm := (words at:1) withoutSeparators.
                        abbrev := (words at:2) withoutSeparators.
                        nm ~= abbrev ifTrue:[
                            key := nm asSymbol.    
                            oldAbbrev := abbrevs at:key ifAbsent:nil.
                            oldAbbrev notNil ifTrue:[
                                oldAbbrev ~= abbrev ifTrue:[
                                    StandAlone ifFalse:[
                                        ('Smalltalk [warning]: conflict for: ' , nm , ' in abbrev.stc (' , oldAbbrev , ' <-> ' , abbrev , ')') infoPrintCR
                                    ]
                                ].
                            ] ifFalse:[
                                cls := self classNamed:abbrev.

                                cls notNil ifTrue:[
                                    cls name ~= nm ifTrue:[
                                        "/ ok, there is a class named after this abbrev ...
                                        "/ this is only a conflict, if the other class has no
                                        "/ abbreviation (or the same).
                                        (abbrevs at:(cls name asSymbol) ifAbsent:cls name) = abbrev ifTrue:[
                                            cls isNamespace ifFalse:[
                                                StandAlone ifFalse:[
                                                    ('Smalltalk [warning]: conflict for: ' , cls name , ' in abbrev.stc (' , nm , ' -> ' , abbrev , ')') infoPrintCR
                                                ]
                                            ]
                                        ]
                                    ]
                                ].
                                abbrevs at:nm asSymbol put:abbrev.
                            ]
                        ]
                    ]
                ]
            ]
        ].
        aStream close
    ] ifFalse:[
        ('Smalltalk [warning]: no ''abbrev.stc'' file found') infoPrintCR

    ].
    ^ abbrevs

    "
     Smalltalk readAbbreviations
    "

    "Modified: / 27.7.1998 / 19:59:07 / cg"
!

realSystemPath
    "return the realSystemPath - thats the directorynames from
     SystemPath which exist and are readable"

    RealSystemPath isNil ifTrue:[
	OperatingSystem isVMSlike ifTrue:[
	    "/ temporary kludge: since we cannot currently
	    "/ check for existance of a name like 'volume:',
	    "/ leave those in the Path without a check.
	    RealSystemPath := SystemPath select:[:dirName |
		|f|

		f := dirName asFilename.
		f isVolumeOnly ifTrue:[
		    true
		] ifFalse:[
		    (f isDirectory) and:[f isReadable]
		]
	    ]
	] ifFalse:[
	    RealSystemPath := SystemPath select:[:dirName |
		|f|

		f := dirName asFilename.
		(f isDirectory) and:[f isReadable]
	    ]
	].
    ].
    ^ RealSystemPath
!

resourceFileStreamFor:aFileName
    "search aFileName in some standard places;
     return a readonly fileStream or nil if not found.
     Searches in subdirectories named 'resource' in SystemPath"

    |aString|

    aString := self getResourceFileName:aFileName.
    aString notNil ifTrue:[
	^ aString asFilename readStream
    ].
    ^ nil
!

searchPath:aPath for:aFileName in:aDirName
    "search aPath for a subdirectory named aDirectory with a file
     named aFileName"

    |f|

    ((f := aFileName asFilename) isAbsolute 
    or:[f isExplicitRelative]) ifTrue:[
	"/
	"/ dont use path for absolute or explicit .-relative file names
	"/
	^ aFileName
    ].

    aPath do:[:dirName |
	|realName|

	aDirName notNil ifTrue:[
	    realName := (dirName asFilename construct:aDirName) constructString:aFileName.
	] ifFalse:[
	    realName := dirName asFilename constructString:aFileName.
	].
	realName asFilename isReadable ifTrue:[
	    ^ realName
	]
    ].
    ^ nil

    "Modified: 18.7.1996 / 15:53:35 / cg"
!

sourceDirectoryNameOfClass:aClassOrClassName
    "for a given class, return the pathname relative to TOP of the classes source code.
     Read the files 'abbrev.stc' and 'liblist.stc' (which are created during the compilation process)
     for an entry for aClassOrClassName.
     Search for the className in the first col, and return the value found in
     the 3rd col.
     Return nil if no entry is found."

    |aStream line words n aClassName|

    aClassOrClassName isBehavior ifTrue:[
	aClassName := aClassOrClassName name
    ] ifFalse:[
	aClassName := aClassOrClassName
    ].
    aClassName := aClassName asString.

    #('include/abbrev.stc' 'include/liblist.stc')    "/ filenames
    with:#(3 2)                   "/ column
    do:[:fileName :col |

	aStream := self systemFileStreamFor:fileName.
	aStream notNil ifTrue:[
	    [aStream atEnd] whileFalse:[
		line := aStream nextLine.
		line notNil ifTrue:[
		    (line startsWith:'#') ifFalse:[
			words := line asCollectionOfWords.
			(n := words size) > 1 ifTrue:[
			    (words at:1) = aClassName ifTrue:[
				n >= col ifTrue:[
				    aStream close.
				    ^ (words at:col) withoutSeparators
				]
			    ]
			]
		    ]
		]
	    ].
	    aStream close
	].
    ].

    ^ nil

    "
     Smalltalk sourceDirectoryNameOfClass:'ClockView' 
     Smalltalk sourceDirectoryNameOfClass:'Bag' 
     Smalltalk sourceDirectoryNameOfClass:'GLWireCubeDemoView' 
     Smalltalk sourceDirectoryNameOfClass:'SomeNonExistingClass' 
    "

    "Created: 6.11.1995 / 15:43:30 / cg"
    "Modified: 9.12.1995 / 23:54:14 / cg"
    "Modified: 3.1.1997 / 11:26:44 / stefan"
!

sourceFileStreamFor:aFileName
    "search aFileName in some standard places;
     return a readonly fileStream or nil if not found.
     Searches in subdirectories named 'source' in SystemPath"

    |aString|

    aString := self getSourceFileName:aFileName.
    aString notNil ifTrue:[
	^ aString asFilename readStream
    ].
    ^ nil
!

systemFileStreamFor:aFileName
    "search aFileName in some standard places;
     return a readonly fileStream or nil if not found.
     see comment in Smalltalk>>initSystemPath"

    |aString|

    aString := self getSystemFileName:aFileName.
    aString notNil ifTrue:[
	^ aString asFilename readStream
    ].
    ^ nil
!

systemPath
    "return a collection of directorynames, where smalltalk
     looks for system files 
     (usually in subdirs such as resources, bitmaps, source etc.)
     see comment in Smalltalk>>initSystemPath."

    ^ SystemPath

    "
     Smalltalk systemPath
     Smalltalk systemPath addLast:'someOtherDirectoryPath'
    "
!

systemPath:aPath
    "set the collection of directorynames, where smalltalk
     looks for system files 
     (usually in subdirs such as resources, bitmaps, source etc.)
     see comment in Smalltalk>>initSystemPath."

    SystemPath := aPath.
    self flushPathCaches

    "
     Smalltalk systemPath
     Smalltalk systemPath:(Smalltalk systemPath copy addLast:'someOtherDirectoryPath')
    "
! !

!Smalltalk class methodsFor:'time-versions'!

configuration
    "{ Pragma: +optSpace }"

    "for developers only: return the configuration, with which
     this smalltalk was compiled."

%{  /* NOCONTEXT */
    extern char *__getConfigurationString();

    RETURN (__MKSTRING(__getConfigurationString() COMMA_SND));
%}

    "
     Smalltalk configuration
    "
!

copyrightString
    "{ Pragma: +optSpace }"

    "return a copyright string"

%{  /* NOCONTEXT */
#ifndef __getCopyrightString
    extern OBJ __getCopyrightString();
#endif

    RETURN (__getCopyrightString());
%}

    "
     Smalltalk copyrightString
    "
!

distributorString
    "{ Pragma: +optSpace }"

    "return a string describing the distributor of this software"

%{  /* NOCONTEXT */
#ifndef __getDistributorString
    extern OBJ __getDistributorString();
#endif

    RETURN (__getDistributorString());
%}
    "
     Smalltalk distributorString
    "
!

expirationTime
    "{ Pragma: +optSpace }"

    "for developers only: return the time when the system will expire.
     after this time it will not run any longer.
     It returns nil, if no expiration time has been set (system runs forever :-))"

    |exp|

%{  
    extern unsigned int __getExpirationTime();

    exp = __MKUINT(__getExpirationTime());
%}.
    exp == 0 ifTrue:[
	^ nil
    ].
    ^ AbsoluteTime new fromOSTime:(exp * 1000). "OSTime is ms since 1970"

    "
     Smalltalk expirationTime
    "
!

fullVersionString
    "{ Pragma: +optSpace }"

    "return a full version string"

    ^ 'Smalltalk/X release ' , self versionString , ' of ' , self versionDate 

    "
     Smalltalk fullVersionString
    "

    "Created: / 27.10.1997 / 17:03:09 / cg"
    "Modified: / 27.10.1997 / 17:04:02 / cg"
!

hello
    "{ Pragma: +optSpace }"

    "return a greeting string"

    "stupid: this should come from a resource file ...
     but I dont use it here, to allow mini-systems without
     Resource-stuff."

    |proto lang|

    lang := Language.
    (lang == #german or:[lang == #de]) ifTrue:[
	proto := 'Willkommen bei %1 - Version %2 vom %3'
    ].
    (lang == #french or:[lang == #fr]) ifTrue:[
	proto := 'Bienvenue à %1 - version %2 de %3'
    ].

    "/ ... more needed here ...

    proto isNil ifTrue:[
	proto := 'Hello World - here is %1 version %2 of %3'.
    ].

    ^ proto bindWith:(Text string:'SmallTalk/X' emphasis:#bold)
		with:(self versionString) 
		with:(self versionDate)

    "
     Smalltalk language:#us.   
     Smalltalk hello     

     Smalltalk language:#de.   
     Smalltalk hello  

     Transcript showCR:(Smalltalk hello)
     Stdout showCR:(Smalltalk hello)
    "

    "Modified: 18.5.1996 / 14:25:13 / cg"
!

imageRestartTime
    "return a timestamp for the moment when this image was restarted.
     If we do not execute from an image (i.e. fresh start), return nil."

    ^ ImageRestartTime

    "
     Smalltalk imageStartTime
     Smalltalk imageRestartTime
    "

    "Created: 13.12.1995 / 17:44:20 / cg"
    "Modified: 6.3.1996 / 11:56:35 / cg"
!

imageSaveTime
    "return a timestamp for the moment when this image was saved"

    ^ ObjectMemory imageSaveTime
!

imageStartTime
    "return a timestamp for the moment when this system started the first time
     (i.e. the first initial start without an image)"

    ^ ImageStartTime

    "
     Smalltalk imageStartTime
     Smalltalk imageRestartTime
    "

    "Created: 13.12.1995 / 17:44:14 / cg"
    "Modified: 13.12.1995 / 17:45:47 / cg"
!

majorVersionNr
    "{ Pragma: +optSpace }"

    "return the major version number.
     This is only incremented for very fundamental changes,
     which make old object files totally incompatible
     (for example, if the layout/representation of fundamental
      classes changes).

     Naming is:
	<major><minor><revision><release>"

    ^ 3

    "
     Smalltalk majorVersionNr
    "

    "Modified: 8.11.1996 / 19:59:21 / cg"
!

minorVersionNr
    "{ Pragma: +optSpace }"

    "return the minor version number.
     This is incremented for changes which make some old object
     files incompatible, or the protocol changes such that some
     classes need rework."

    ^ 4

    "
     Smalltalk minorVersionNr
    "

    "Modified: / 3.11.1997 / 14:49:48 / cg"
!

releaseIdentification
    "{ Pragma: +optSpace }"

    "for developers only: return the release 
     (to further identify the version in case of errors)"

%{  /* NOCONTEXT */
    extern OBJ __getRel();

    RETURN (__getRel());
%}

    "
     Smalltalk releaseIdentification
    "
!

releaseNr
    "{ Pragma: +optSpace }"

    "return the revision number.
     Incremented for releases which fix bugs/add features but did not find
     their way to the outside world."

    ^ 1

    " 
     Smalltalk releaseNr 
    "

    "Created: 10.12.1995 / 01:42:19 / cg"
!

revisionNr
    "{ Pragma: +optSpace }"

    "return the revision number.
     Incremented for releases which fix bugs/add features
     and represent a stable workable version which got published
     to the outside world."

    ^ 8

    " 
     Smalltalk revisionNr
    "

    "Modified: / 19.6.1998 / 04:29:10 / cg"
!

timeStamp
    "return a string useful for timestamping a file.
     The returned string is padded with spaces for a constant
     length (to avoid changing a files size in fileOut with unchanged
     class)."

    ^ ('''From Smalltalk/X, Version:' , (Smalltalk versionString) , ' on '
       , Date today printString , ' at ' , Time now printString
       , '''') paddedTo:80 with:(Character space)
!

timeStamp:aStream
    "write a string useful for timestamping a file onto aStream.
     ST80 compatibility"

    aStream nextPutAll:(self timeStamp).

    "Created: / 18.6.1998 / 17:22:58 / cg"
!

versionDate
    "{ Pragma: +optSpace }"

    "return the executables build date - thats the date when the smalltalk
     executable was built"

%{  /* NOCONTEXT */
    extern char *__getBuildDateString();

    RETURN (__MKSTRING(__getBuildDateString() COMMA_SND) );
%}
    "
     Smalltalk versionDate
    "
!

versionString
    "{ Pragma: +optSpace }"

    "return the version string"

    ^ (self majorVersionNr printString ,
       '.',
       self minorVersionNr printString ,
       '.',
       self revisionNr printString)

    "
     Smalltalk versionString
    "
! !

!Smalltalk class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.295 1998-07-31 14:41:35 cg Exp $'
! !