Smalltalk.st
changeset 3044 a0bbac91639b
parent 3033 1631c1db9850
child 3062 5b8a2aa07108
--- a/Smalltalk.st	Thu Oct 16 13:17:03 1997 +0200
+++ b/Smalltalk.st	Tue Oct 21 19:44:59 1997 +0200
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:3.2.1 on 18-oct-1997 at 12:05:27 am'                 !
+
 Object subclass:#Smalltalk
 	instanceVariableNames:''
 	classVariableNames:'StartBlocks ImageStartBlocks ExitBlocks CachedClasses SystemPath
@@ -2244,44 +2246,6 @@
 
 !Smalltalk class methodsFor:'system management'!
 
-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"
-!
-
 compressSources
     "{ Pragma: +optSpace }"
 
@@ -2355,17 +2319,363 @@
     "Modified: 16.1.1997 / 01:25:58 / 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]
+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."
+
+    |newStream table source pos fileName|
+
+    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"
+! !
+
+!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
@@ -2385,18 +2695,236 @@
     "
 !
 
-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
+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 initialize:true lazy:false silent:nil
+!
+
+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 initialize:doInit lazy:false silent:nil
+!
+
+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 initialize:doInit lazy:loadLazy silent:nil
+!
+
+fileInClass:aClassName 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.
     ].
-    ^ nil
+
+    [
+        Class withoutUpdatingChangesDo:
+        [
+            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, 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
+                                    ]
+                                ]
+                            ]
+                        ].
+                        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
+
+    "Modified: 11.11.1996 / 09:56:39 / 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
@@ -2447,6 +2975,133 @@
     "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"
@@ -2681,99 +3336,6 @@
     ^ nil
 !
 
-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"
-!
-
 libraryFileNameOfClass:aClassOrClassName
     "for a given class, return the name of a classLibrary which contains
      binary code for it.
@@ -2833,85 +3395,6 @@
     "Modified: 6.11.1995 / 15:41:39 / 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"
-!
-
-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"
-!
-
-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
-
-!
-
 readAbbreviations
     "read classname to filename mappings from include/abbrev.stc.
      sigh - all for those poor sys5.3 or MSDOS people with short filenames ..."
@@ -3049,37 +3532,6 @@
     "Modified: 18.7.1996 / 15:53:35 / 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
-    ]
-!
-
 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)
@@ -3194,367 +3646,6 @@
     "
 ! !
 
-!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
-    "
-!
-
-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 initialize:true lazy:false silent:nil
-!
-
-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 initialize:doInit lazy:false silent:nil
-!
-
-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 initialize:doInit lazy:loadLazy silent:nil
-!
-
-fileInClass:aClassName 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:
-        [
-            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, 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
-                                    ]
-                                ]
-                            ]
-                        ].
-                        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
-
-    "Modified: 11.11.1996 / 09:56:39 / 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"
-! !
-
 !Smalltalk class methodsFor:'time-versions'!
 
 configuration
@@ -3843,5 +3934,5 @@
 !Smalltalk class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.262 1997-10-15 13:42:16 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.263 1997-10-21 17:44:26 cg Exp $'
 ! !