*** empty log message ***
authorClaus Gittinger <cg@exept.de>
Fri, 17 Dec 1999 12:45:38 +0100
changeset 1010 46287addc332
parent 1009 e578b6db8219
child 1011 19d3649887aa
*** empty log message ***
ObjectFileLoader.st
bc.mak
nt.mak
--- a/ObjectFileLoader.st	Wed Dec 15 20:36:33 1999 +0100
+++ b/ObjectFileLoader.st	Fri Dec 17 12:45:38 1999 +0100
@@ -182,6 +182,9 @@
 #  undef Block
 #  undef Time
 #  undef Date
+#  undef Set
+#  undef Delay
+#  undef Signal
 
 #  ifdef i386
 #   ifndef _X86_
@@ -234,6 +237,15 @@
 #  ifdef __DEF_Date
 #   define Date __DEF_Date
 #  endif
+# ifdef __DEF_Set
+#  define Set __DEF_Set
+# endif
+# ifdef __DEF_Signal
+#  define Signal __DEF_Signal
+# endif
+# ifdef __DEF_Delay
+#  define Delay __DEF_Delay
+# endif
 # endif
 
 #endif /* WIN_DL */
@@ -840,13 +852,13 @@
 
     handle := self loadDynamicObject:aFileName.
     handle isNil ifTrue:[
-        Transcript showCR:('failed to load: ' , aFileName).
-        ('ObjectFileLoader [warning]: '
-         , aFileName
-         , ' failed. ('
-         , LinkErrorMessage
-         , ')') errorPrintCR.
-        ^ nil
+	Transcript showCR:('failed to load: ' , aFileName).
+	('ObjectFileLoader [warning]: '
+	 , aFileName
+	 , ' failed. ('
+	 , LinkErrorMessage
+	 , ')') errorPrintCR.
+	^ nil
     ].
 
     "
@@ -855,9 +867,9 @@
     symName := '_' , aClassName , '_Init'.
     initAddr := self getFunction:symName from:handle.
     initAddr isNil ifTrue:[
-        "try with added underscore"
-        symName := '__' , aClassName , '_Init'.
-        initAddr := self getFunction:symName from:handle.
+	"try with added underscore"
+	symName := '__' , aClassName , '_Init'.
+	initAddr := self getFunction:symName from:handle.
     ].
 
     knownToBeOk := true.
@@ -891,92 +903,92 @@
 "/    ].
 
     initAddr notNil ifTrue:[
-        Verbose ifTrue:[
-            ('calling init at: ' , (initAddr printStringRadix:16)) infoPrintCR.
-        ].
-        info := self performModuleInitAt:initAddr for:aClassName identifyAs:handle.
-        status := info at:1.
-        "
-         if any classes are missing ...
-        "
-        (status == #missingClass) ifTrue:[
-            "
-             ... and we are loading a module ...
-            "
-            Transcript showCR:'try for missing class in same object ...'.
-            Verbose ifTrue:[
-                'try for missing class:' infoPrint. (info at:2) infoPrintCR.
-            ].
-            otherClass := self loadClass:(info at:2) fromObjectFile:aFileName.
-            otherClass notNil ifTrue:[
-                "
-                 try again ...
-                "
-                Transcript showCR:'missing class is here; try again ...'.
-                info := self performModuleInitAt:initAddr for:aClassName identifyAs:handle.
-                status := info at:1.
-            ]
-        ].
-
-        Verbose ifTrue:[
-            'done init status=' infoPrint. info infoPrintCR.
-        ].
-        (status == #unregisteredSuperclass) ifTrue:[
-            Transcript showCR:'superclass is not registered'.
-        ].
-
-        (Symbol hasInterned:aClassName) ifTrue:[
-            newClass := Smalltalk at:aClassName asSymbol ifAbsent:[nil].
-            Verbose ifTrue:[
-                'newClass is: ' infoPrint. newClass infoPrintCR
-            ].
-            newClass notNil ifTrue:[
-                Smalltalk at:aClassName asSymbol put:newClass.
-
-                (newClass implements:#initialize) ifTrue:[
-                    Verbose ifTrue:[
-                        'initialize newClass ...' infoPrintCR
-                    ].
-                    newClass initialize.
-                ].
-                "force cache flush"
-                Smalltalk isInitialized ifTrue:[
-                    Smalltalk changed.
-                ]
-            ].
-        ] ifFalse:[
-            'ObjectFileLoader [warning]: class ' errorPrint. aClassName errorPrint.
-            ' did not define itself' errorPrintCR
-            "
-             do not unload - could have installed other classes/methods ...
-            "
-        ].
-        Smalltalk flushCachedClasses.
-        ^ newClass
+	Verbose ifTrue:[
+	    ('calling init at: ' , (initAddr printStringRadix:16)) infoPrintCR.
+	].
+	info := self performModuleInitAt:initAddr for:aClassName identifyAs:handle.
+	status := info at:1.
+	"
+	 if any classes are missing ...
+	"
+	(status == #missingClass) ifTrue:[
+	    "
+	     ... and we are loading a module ...
+	    "
+	    Transcript showCR:'try for missing class in same object ...'.
+	    Verbose ifTrue:[
+		'try for missing class:' infoPrint. (info at:2) infoPrintCR.
+	    ].
+	    otherClass := self loadClass:(info at:2) fromObjectFile:aFileName.
+	    otherClass notNil ifTrue:[
+		"
+		 try again ...
+		"
+		Transcript showCR:'missing class is here; try again ...'.
+		info := self performModuleInitAt:initAddr for:aClassName identifyAs:handle.
+		status := info at:1.
+	    ]
+	].
+
+	Verbose ifTrue:[
+	    'done init status=' infoPrint. info infoPrintCR.
+	].
+	(status == #unregisteredSuperclass) ifTrue:[
+	    Transcript showCR:'superclass is not registered'.
+	].
+
+	(Symbol hasInterned:aClassName) ifTrue:[
+	    newClass := Smalltalk at:aClassName asSymbol ifAbsent:[nil].
+	    Verbose ifTrue:[
+		'newClass is: ' infoPrint. newClass infoPrintCR
+	    ].
+	    newClass notNil ifTrue:[
+		Smalltalk at:aClassName asSymbol put:newClass.
+
+		(newClass implements:#initialize) ifTrue:[
+		    Verbose ifTrue:[
+			'initialize newClass ...' infoPrintCR
+		    ].
+		    newClass initialize.
+		].
+		"force cache flush"
+		Smalltalk isInitialized ifTrue:[
+		    Smalltalk changed.
+		]
+	    ].
+	] ifFalse:[
+	    'ObjectFileLoader [warning]: class ' errorPrint. aClassName errorPrint.
+	    ' did not define itself' errorPrintCR
+	    "
+	     do not unload - could have installed other classes/methods ...
+	    "
+	].
+	Smalltalk flushCachedClasses.
+	^ newClass
     ].
 
     Verbose ifTrue:[
-        ('no symbol: ', symName,' in ',aFileName) infoPrintCR.
+	('no symbol: ', symName,' in ',aFileName) infoPrintCR.
     ].
 
     "
      unload
     "
     Verbose ifTrue:[
-        'unloading due to init failure:' infoPrint. handle pathName infoPrintCR.
+	'unloading due to init failure:' infoPrint. handle pathName infoPrintCR.
     ].
 
     moreHandles notNil ifTrue:[
-        moreHandles do:[:aHandle |
-            Verbose ifTrue:[
-                ('unloading: ', aHandle printString) infoPrintCR.
-            ].
-            self unloadDynamicObject:handle.
-        ]
+	moreHandles do:[:aHandle |
+	    Verbose ifTrue:[
+		('unloading: ', aHandle printString) infoPrintCR.
+	    ].
+	    self unloadDynamicObject:handle.
+	]
     ].
 
     Verbose ifTrue:[
-        ('unloading: ', handle printString) infoPrintCR.
+	('unloading: ', handle printString) infoPrintCR.
     ].
     self unloadDynamicObject:handle.
     ^ nil
@@ -1123,8 +1135,8 @@
      Return nil on error, an objectFile handle if ok."
 
     ^ self
-        loadObjectFile:aFileName 
-        invokeInitializeMethods:true
+	loadObjectFile:aFileName 
+	invokeInitializeMethods:true
 !
 
 loadObjectFile:aFileName invokeInitializeMethods:invokeInitializeMethods
@@ -1141,13 +1153,13 @@
 
     handle := self loadDynamicObject:aFileName.
     handle isNil ifTrue:[
-        Transcript showCR:('failed to load: ' , aFileName).
-        ('ObjectFileLoader [warning]: '
-         , aFileName
-         , ' failed. ('
-         , LinkErrorMessage
-         , ')') errorPrintCR.
-        ^ nil
+	Transcript showCR:('failed to load: ' , aFileName).
+	('ObjectFileLoader [warning]: '
+	 , aFileName
+	 , ' failed. ('
+	 , LinkErrorMessage
+	 , ')') errorPrintCR.
+	^ nil
     ].
 
     didInit := false.
@@ -1157,23 +1169,23 @@
     "/ are to be resolved. If thats the case, load all libraries ...
 
     SearchedLibraries notNil ifTrue:[
-        (self hasUndefinedSymbolsIn:handle) ifTrue:[
-            self initializeLoader.
-
-            SearchedLibraries do:[:libName |
-                (self hasUndefinedSymbolsIn:handle) ifTrue:[
-                    Transcript showCR:'   ... trying ' , libName , ' to resolve undefined symbols ...'.
-                    dummyHandle := Array new:4.
-                    dummyHandle := self primLoadDynamicObject:libName into:dummyHandle.
+	(self hasUndefinedSymbolsIn:handle) ifTrue:[
+	    self initializeLoader.
+
+	    SearchedLibraries do:[:libName |
+		(self hasUndefinedSymbolsIn:handle) ifTrue:[
+		    Transcript showCR:'   ... trying ' , libName , ' to resolve undefined symbols ...'.
+		    dummyHandle := Array new:4.
+		    dummyHandle := self primLoadDynamicObject:libName into:dummyHandle.
 "/                    dummyHandle isNil ifTrue:[
 "/                        Transcript showCR:'   ... load of library ' , libName , ' failed.'.
 "/                    ]
-                ]
-            ].
-            (self hasUndefinedSymbolsIn:handle) isNil ifTrue:[
-                Transcript showCR:('LOADER: still undefined symbols in ',aFileName,'.').
-            ].
-        ]
+		]
+	    ].
+	    (self hasUndefinedSymbolsIn:handle) isNil ifTrue:[
+		Transcript showCR:('LOADER: still undefined symbols in ',aFileName,'.').
+	    ].
+	]
     ].
 
     "
@@ -1191,138 +1203,138 @@
     initAddr := self findInitFunction:className in:handle.
 
     initAddr notNil ifTrue:[
-        Verbose ifTrue:[
-            ('calling init at:' , (initAddr printStringRadix:16)) infoPrintCR.
-        ].
-        info := self 
-                    performModuleInitAt:initAddr 
-                    invokeInitializeMethods:invokeInitializeMethods
-                    for:nil
-                    identifyAs:handle.
-        status := info at:1.
-        status == #ok ifTrue:[
-            didInit := true.
-        ]
+	Verbose ifTrue:[
+	    ('calling init at:' , (initAddr printStringRadix:16)) infoPrintCR.
+	].
+	info := self 
+		    performModuleInitAt:initAddr 
+		    invokeInitializeMethods:invokeInitializeMethods
+		    for:nil
+		    identifyAs:handle.
+	status := info at:1.
+	status == #ok ifTrue:[
+	    didInit := true.
+	]
     ] ifFalse:[
-        "/
-        "/ look for explicit C-init (xxx__Init) function
-        "/ This is used in C object files
-        "/
-        initAddr := self findFunction:className suffix:'__Init' in:handle.
-        initAddr notNil ifTrue:[
-            isCModule := true.
-
-            Object osSignalInterruptSignal handle:[:ex |
-                ('ObjectFileLoader [warning]: hard error in initFunction of class-module: ' , aFileName) errorPrintCR.
-                status := #initFailed.
-            ] do:[
-                (self callInitFunctionAt:initAddr 
-                     specialInit:false 
-                     forceOld:true 
-                     interruptable:false
-                     argument:0
-                     identifyAs:handle
-                     returnsObject:false) < 0 ifTrue:[
-
-                    Verbose ifTrue:[
-                        'init function return failure ... unload' infoPrintCR.
-                    ].
-                    status := #initFailed.
-                ] ifFalse:[
-                    didInit := true.
-                ]
-            ]
-        ] ifFalse:[
-            status := #noInitFunction.
-
-            "
-             look for any init-function(s); call them all
-            "
-            Verbose ifTrue:[
-                'no good init functions found; looking for candidates ...' infoPrintCR.
-            ].
-            initNames := self namesMatching:'*_Init' segment:'[tT?]' in:aFileName.
-            initNames notNil ifTrue:[
-                initNames do:[:aName |
-                    initAddr := self getFunction:aName from:handle.
-                    initAddr isNil ifTrue:[
-                        (aName startsWith:'_') ifTrue:[
-                            initAddr := self getFunction:(aName copyFrom:2) from:handle.
-                        ].
-                    ].
-                    initAddr isNil ifTrue:[
-                        Transcript showCR:('no symbol: ',aName,' in ',aFileName).
-                    ] ifFalse:[
-                        Verbose ifTrue:[
-                            ('calling init at:' , (initAddr printStringRadix:16)) infoPrintCR
-                        ].
-                        self 
-                            performModuleInitAt:initAddr 
-                            invokeInitializeMethods:invokeInitializeMethods
-                            for:nil 
-                            identifyAs:handle.
-                        didInit := true.
-                    ]
-                ].
-            ].
-        ]
+	"/
+	"/ look for explicit C-init (xxx__Init) function
+	"/ This is used in C object files
+	"/
+	initAddr := self findFunction:className suffix:'__Init' in:handle.
+	initAddr notNil ifTrue:[
+	    isCModule := true.
+
+	    Object osSignalInterruptSignal handle:[:ex |
+		('ObjectFileLoader [warning]: hard error in initFunction of class-module: ' , aFileName) errorPrintCR.
+		status := #initFailed.
+	    ] do:[
+		(self callInitFunctionAt:initAddr 
+		     specialInit:false 
+		     forceOld:true 
+		     interruptable:false
+		     argument:0
+		     identifyAs:handle
+		     returnsObject:false) < 0 ifTrue:[
+
+		    Verbose ifTrue:[
+			'init function return failure ... unload' infoPrintCR.
+		    ].
+		    status := #initFailed.
+		] ifFalse:[
+		    didInit := true.
+		]
+	    ]
+	] ifFalse:[
+	    status := #noInitFunction.
+
+	    "
+	     look for any init-function(s); call them all
+	    "
+	    Verbose ifTrue:[
+		'no good init functions found; looking for candidates ...' infoPrintCR.
+	    ].
+	    initNames := self namesMatching:'*_Init' segment:'[tT?]' in:aFileName.
+	    initNames notNil ifTrue:[
+		initNames do:[:aName |
+		    initAddr := self getFunction:aName from:handle.
+		    initAddr isNil ifTrue:[
+			(aName startsWith:'_') ifTrue:[
+			    initAddr := self getFunction:(aName copyFrom:2) from:handle.
+			].
+		    ].
+		    initAddr isNil ifTrue:[
+			Transcript showCR:('no symbol: ',aName,' in ',aFileName).
+		    ] ifFalse:[
+			Verbose ifTrue:[
+			    ('calling init at:' , (initAddr printStringRadix:16)) infoPrintCR
+			].
+			self 
+			    performModuleInitAt:initAddr 
+			    invokeInitializeMethods:invokeInitializeMethods
+			    for:nil 
+			    identifyAs:handle.
+			didInit := true.
+		    ]
+		].
+	    ].
+	]
     ].
 
     didInit ifFalse:[
-        status == #noInitFunction ifTrue:[
-            msg := 'LOADER: no init function; assume load ok'
-        ] ifFalse:[
-
-            (status ~~ #registrationFailed 
+	status == #noInitFunction ifTrue:[
+	    msg := 'LOADER: no init function; assume load ok'
+	] ifFalse:[
+
+	    (status ~~ #registrationFailed 
 	    and:[status ~~ #initFailed 
 	    and:[status ~~ #missingClass 
 	    and:[status ~~ #versionMismatch]]])
 	    ifTrue:[
-                self listUndefinedSymbolsIn:handle.
-            ].
-
-            Verbose ifTrue:[
-                'unloading, since init failed ...' infoPrintCR.
-            ].
-            self unloadDynamicObject:handle.
-            Verbose ifTrue:[
-                'unloaded.' infoPrintCR.
-            ].
-            handle := nil.
-
-            status == #initFailed ifTrue:[
-                msg := 'LOADER: module not loaded (init function signalled failure).'
-            ] ifFalse:[
-                status == #missingClass ifTrue:[
-                    msg := 'LOADER: module not loaded (superclass missing: ' , (info at:2) , ').'
-                ] ifFalse:[
+		self listUndefinedSymbolsIn:handle.
+	    ].
+
+	    Verbose ifTrue:[
+		'unloading, since init failed ...' infoPrintCR.
+	    ].
+	    self unloadDynamicObject:handle.
+	    Verbose ifTrue:[
+		'unloaded.' infoPrintCR.
+	    ].
+	    handle := nil.
+
+	    status == #initFailed ifTrue:[
+		msg := 'LOADER: module not loaded (init function signalled failure).'
+	    ] ifFalse:[
+		status == #missingClass ifTrue:[
+		    msg := 'LOADER: module not loaded (superclass missing: ' , (info at:2) , ').'
+		] ifFalse:[
 		    status == #registrationFailed ifTrue:[
-                        msg :=  'LOADER: module registration failed (incompatible object or missing superclass)'
+			msg :=  'LOADER: module registration failed (incompatible object or missing superclass)'
 		    ] ifFalse:[
-		        status == #versionMismatch ifTrue:[
-                            msg :=  'LOADER: module registration failed (class version mismatch ' , (info at:2) printString , ')'
-		        ] ifFalse:[
-                            (self namesMatching:'*__sepInitCode__*' segment:'[tT?]' in:aFileName) notNil ifTrue:[
-                                msg := 'LOADER: module not loaded (unknown error reason).'
-                            ] ifFalse:[
-                                msg := 'LOADER: module not loaded (no _Init entry in object file ?).'
+			status == #versionMismatch ifTrue:[
+			    msg :=  'LOADER: module registration failed (class version mismatch ' , (info at:2) printString , ')'
+			] ifFalse:[
+			    (self namesMatching:'*__sepInitCode__*' segment:'[tT?]' in:aFileName) notNil ifTrue:[
+				msg := 'LOADER: module not loaded (unknown error reason).'
+			    ] ifFalse:[
+				msg := 'LOADER: module not loaded (no _Init entry in object file ?).'
 			    ]
 			]
-                    ].
-                ].
-            ].
-        ].
-        Transcript showCR:msg
+		    ].
+		].
+	    ].
+	].
+	Transcript showCR:msg
     ].
 
     isCModule ifFalse:[
-        Smalltalk isInitialized ifTrue:[
-            "
-             really dont know, if it has changed ...
-             ... but assume, that new classes have been installed.
-            "
-            Smalltalk changed.
-        ]
+	Smalltalk isInitialized ifTrue:[
+	    "
+	     really dont know, if it has changed ...
+	     ... but assume, that new classes have been installed.
+	    "
+	    Smalltalk changed.
+	]
     ].
     ^ handle
 
@@ -1386,27 +1398,27 @@
     |handle|
 
     LoadedObjects notNil ifTrue:[
-        handle := LoadedObjects at:aFileName ifAbsent:nil
+	handle := LoadedObjects at:aFileName ifAbsent:nil
     ].
     handle isNil ifTrue:[
-        ('OBJFLOADER: oops file to be unloaded was not loaded dynamically (', (aFileName ? 'unknown-file') , ')') infoPrintCR.
-        ^ self
+	('OBJFLOADER: oops file to be unloaded was not loaded dynamically (', (aFileName ? 'unknown-file') , ')') infoPrintCR.
+	^ self
     ].
     handle isClassLibHandle ifFalse:[
-        self warn:'module is not a classLib module'.
-        ^ self
+	self warn:'module is not a classLib module'.
+	^ self
     ].
 
     "/ remove the classes ...
 
     Class withoutUpdatingChangesDo:[
-        handle classes do:[:aClass |
-            aClass notNil ifTrue:[
-                aClass isMeta ifFalse:[
-                    aClass removeFromSystem
-                ]
-            ]
-        ]
+	handle classes do:[:aClass |
+	    aClass notNil ifTrue:[
+		aClass isMeta ifFalse:[
+		    aClass removeFromSystem
+		]
+	    ]
+	]
     ].
 
     "/ call the modules deInit-function ...
@@ -2030,52 +2042,52 @@
     |p l s addr segment name entry|
 
     OperatingSystem isVMSlike ifTrue:[
-        "/ no nm command
-        ^ nil
+	"/ no nm command
+	^ nil
     ].
     OperatingSystem isMSDOSlike ifTrue:[
-        "/ no nm command
-        ^ nil
+	"/ no nm command
+	^ nil
     ].
     OperatingSystem getOSType = 'aix' ifTrue:[
-        "/ no useful nm info
-        ^ nil
+	"/ no useful nm info
+	^ nil
     ].
 
     l := OrderedCollection new.
     p := PipeStream readingFrom:(self nm:aFileName).
     p isNil ifTrue:[
-        ('ObjectFileLoader [info]: cannot read names from ' , aFileName) infoPrintCR.
-        ^ nil
+	('ObjectFileLoader [info]: cannot read names from ' , aFileName) infoPrintCR.
+	^ nil
     ].
     [p atEnd] whileFalse:[
-        entry := p nextLine.
-        Verbose ifTrue:[
-            entry infoPrintCR.
-        ].
-        entry notNil ifTrue:[
-            s := ReadStream on:entry.
-            addr := s nextAlphaNumericWord.
-            s skipSeparators.
-            segment := s upToSeparator.
-            s skipSeparators.
-            name := s upToEnd withoutSeparators.
-            (addr notNil and:[segment notNil and:[name notNil]]) ifTrue:[
-                (aPattern match:name) ifTrue:[
-                    (segmentPattern isNil or:[segmentPattern match:segment]) ifTrue:[
-                        l add:name.
-                        Verbose ifTrue:[
-                            ('found name: ' , name) infoPrintCR.
-                        ]
-                    ] ifFalse:[
-                        Verbose ifTrue:[
-                            name infoPrint. ' segment mismatch ' infoPrint.
-                            segmentPattern infoPrint. ' ' infoPrint. segment infoPrintCR.
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	entry := p nextLine.
+	Verbose ifTrue:[
+	    entry infoPrintCR.
+	].
+	entry notNil ifTrue:[
+	    s := ReadStream on:entry.
+	    addr := s nextAlphaNumericWord.
+	    s skipSeparators.
+	    segment := s upToSeparator.
+	    s skipSeparators.
+	    name := s upToEnd withoutSeparators.
+	    (addr notNil and:[segment notNil and:[name notNil]]) ifTrue:[
+		(aPattern match:name) ifTrue:[
+		    (segmentPattern isNil or:[segmentPattern match:segment]) ifTrue:[
+			l add:name.
+			Verbose ifTrue:[
+			    ('found name: ' , name) infoPrintCR.
+			]
+		    ] ifFalse:[
+			Verbose ifTrue:[
+			    name infoPrint. ' segment mismatch ' infoPrint.
+			    segmentPattern infoPrint. ' ' infoPrint. segment infoPrintCR.
+			]
+		    ]
+		]
+	    ]
+	]
     ].
     p close.
     ^ l
@@ -2139,227 +2151,227 @@
      saveOldMethodsPerClass anyModulesToInitialize|
 
     PreviouslyLoadedObjects notNil ifTrue:[
-        anyModulesToInitialize := false.
-
-        PreviouslyLoadedObjects do:[:entry |
-            |fileName handle cls sel|
-
-            fileName := entry key.
-            handle := entry value.
-            handle moduleID:nil.
-
-            handle isClassLibHandle ifTrue:[
-                ('ObjectFileLoader [info]: reloading classes in ' , fileName , ' ...') infoPrintCR.
-
-                "/
-                "/ remember all byteCode methods (as added in the session)
-                "/                
-                savedByteCodeMethods := Dictionary new.
-                savedOldClasses := IdentitySet new.
-                saveOldMethodsPerClass := Dictionary new.
-
-                handle classes do:[:aClass |
-                    |clsName mthdDict|
-
-                    (aClass notNil and:[aClass ~~ 0]) ifTrue:[
-                        clsName := aClass name.
-                        mthdDict := aClass methodDictionary.
-                        saveOldMethodsPerClass at:clsName put:mthdDict copy.
-                        savedMethods := IdentityDictionary new.
-                        savedOldClasses add:aClass.
-                        mthdDict keysAndValuesDo:[:sel :m |
-                            m byteCode notNil ifTrue:[
-                                "/ an interpreted method - must be preserved
-                                savedMethods at:sel put:m
-                            ]
-                        ].
-                        savedMethods notEmpty ifTrue:[
-                            savedByteCodeMethods at:clsName put:savedMethods
-                        ].
-                    ]
-                ].
-                "/
-                "/ load the class binary
-                "/                
-                handle := self loadObjectFile:fileName invokeInitializeMethods:false.
-                handle notNil ifTrue:[
-                    anyModulesToInitialize := true
-                ].
-
-                "/ after reloading of the objectFile,
-                "/ some of the changes made in the previous life have to be
-                "/ redone here - otherwise, we will be left with the
-                "/ state contained in the loaded objectModule - instead of
-                "/ what we had when saving the image ...
-
-                "/
-                "/ reinstall the byteCode methods
-                "/                
-                savedByteCodeMethods keysAndValuesDo:[:nm :savedMethods |
-                    |cls|
-
-                    cls := Smalltalk classNamed:nm.
-                    savedMethods keysAndValuesDo:[:sel :m |
-                        cls primAddSelector:sel withMethod:m. 
+	anyModulesToInitialize := false.
+
+	PreviouslyLoadedObjects do:[:entry |
+	    |fileName handle cls sel|
+
+	    fileName := entry key.
+	    handle := entry value.
+	    handle moduleID:nil.
+
+	    handle isClassLibHandle ifTrue:[
+		('ObjectFileLoader [info]: reloading classes in ' , fileName , ' ...') infoPrintCR.
+
+		"/
+		"/ remember all byteCode methods (as added in the session)
+		"/                
+		savedByteCodeMethods := Dictionary new.
+		savedOldClasses := IdentitySet new.
+		saveOldMethodsPerClass := Dictionary new.
+
+		handle classes do:[:aClass |
+		    |clsName mthdDict|
+
+		    (aClass notNil and:[aClass ~~ 0]) ifTrue:[
+			clsName := aClass name.
+			mthdDict := aClass methodDictionary.
+			saveOldMethodsPerClass at:clsName put:mthdDict copy.
+			savedMethods := IdentityDictionary new.
+			savedOldClasses add:aClass.
+			mthdDict keysAndValuesDo:[:sel :m |
+			    m byteCode notNil ifTrue:[
+				"/ an interpreted method - must be preserved
+				savedMethods at:sel put:m
+			    ]
+			].
+			savedMethods notEmpty ifTrue:[
+			    savedByteCodeMethods at:clsName put:savedMethods
+			].
+		    ]
+		].
+		"/
+		"/ load the class binary
+		"/                
+		handle := self loadObjectFile:fileName invokeInitializeMethods:false.
+		handle notNil ifTrue:[
+		    anyModulesToInitialize := true
+		].
+
+		"/ after reloading of the objectFile,
+		"/ some of the changes made in the previous life have to be
+		"/ redone here - otherwise, we will be left with the
+		"/ state contained in the loaded objectModule - instead of
+		"/ what we had when saving the image ...
+
+		"/
+		"/ reinstall the byteCode methods
+		"/                
+		savedByteCodeMethods keysAndValuesDo:[:nm :savedMethods |
+		    |cls|
+
+		    cls := Smalltalk classNamed:nm.
+		    savedMethods keysAndValuesDo:[:sel :m |
+			cls primAddSelector:sel withMethod:m. 
 "/ ('preserved ' , cls name , '>>' , sel) printCR.
-                    ]
-                ].
-
-                "/
-                "/ re-remove removed methods
-                "/ and re-change method categories
-                "/
-                savedOldClasses do:[:oldClass |
-                    |newClass oldMethods newMethodDict oldMthd newMthd 
-                     oldCat oldClassVarString oldClassCategory|
-
-                    newClass := Smalltalk classNamed:(oldClass name).
-                    newClass notNil ifTrue:[
-                        oldClassVarString := oldClass classVariableString.
-                        newClass classVariableString ~= oldClassVarString ifTrue:[
-                            "/ there is no need to recreate the variable
-                            "/ (its in the smalltalk dictionary)
-                            newClass setClassVariableString:oldClassVarString
-                        ].
-                        newClass isMeta ifFalse:[
-                            oldClassCategory := oldClass category.
-                            newClass category ~= oldClassCategory ifTrue:[
-                                newClass category:oldClassCategory
-                            ]
-                        ].
-                        oldMethods := saveOldMethodsPerClass at:oldClass name.
-                        newMethodDict := newClass methodDictionary.
-                        newMethodDict keys copy do:[:newSelector |
-                            (oldMethods includesKey:newSelector) ifFalse:[
+		    ]
+		].
+
+		"/
+		"/ re-remove removed methods
+		"/ and re-change method categories
+		"/
+		savedOldClasses do:[:oldClass |
+		    |newClass oldMethods newMethodDict oldMthd newMthd 
+		     oldCat oldClassVarString oldClassCategory|
+
+		    newClass := Smalltalk classNamed:(oldClass name).
+		    newClass notNil ifTrue:[
+			oldClassVarString := oldClass classVariableString.
+			newClass classVariableString ~= oldClassVarString ifTrue:[
+			    "/ there is no need to recreate the variable
+			    "/ (its in the smalltalk dictionary)
+			    newClass setClassVariableString:oldClassVarString
+			].
+			newClass isMeta ifFalse:[
+			    oldClassCategory := oldClass category.
+			    newClass category ~= oldClassCategory ifTrue:[
+				newClass category:oldClassCategory
+			    ]
+			].
+			oldMethods := saveOldMethodsPerClass at:oldClass name.
+			newMethodDict := newClass methodDictionary.
+			newMethodDict keys copy do:[:newSelector |
+			    (oldMethods includesKey:newSelector) ifFalse:[
 "/                                ('ObjectFileLoader [info]: remove method #' , newSelector , ' from reloaded ' , oldClass name , '.') infoPrintCR.
-                                newMethodDict removeKey:newSelector
-                            ] ifTrue:[
-                                oldMthd := oldMethods at:newSelector.
-                                newMthd := newMethodDict at:newSelector.
-                                (oldCat := oldMthd category) ~= newMthd category ifTrue:[
+				newMethodDict removeKey:newSelector
+			    ] ifTrue:[
+				oldMthd := oldMethods at:newSelector.
+				newMthd := newMethodDict at:newSelector.
+				(oldCat := oldMthd category) ~= newMthd category ifTrue:[
 "/                                    ('ObjectFileLoader [info]: change category of method #' , newSelector , ' in ' , oldClass name , '.') infoPrintCR.
-                                    newMthd category:oldCat
-                                ]
-                            ]
-                        ]
-                    ]
-                ].
-
-                "/
-                "/ validate old-classes vs. new classes.
-                "/ and if things look ok, get rid of old stuff
-                "/ and make instances become instances of the new class
-                "/
+				    newMthd category:oldCat
+				]
+			    ]
+			]
+		    ]
+		].
+
+		"/
+		"/ validate old-classes vs. new classes.
+		"/ and if things look ok, get rid of old stuff
+		"/ and make instances become instances of the new class
+		"/
 "/                ('ObjectFileLoader [info]: migrating classes ...') infoPrintCR.
 
-                savedOldClasses do:[:oldClass |
-                    |newClass oldCat oldCVars|
-
-                    newClass := Smalltalk classNamed:(oldClass name).
-                    newClass == oldClass ifTrue:[
+		savedOldClasses do:[:oldClass |
+		    |newClass oldCat oldCVars|
+
+		    newClass := Smalltalk classNamed:(oldClass name).
+		    newClass == oldClass ifTrue:[
 "/                        ('ObjectFileLoader [info]: class ' , oldClass name , ' reloaded.') infoPrintCR.
-                    ] ifFalse:[
-                        (newClass isNil or:[newClass == oldClass]) ifTrue:[
-                            ('ObjectFileLoader [warning]: reload of ' , oldClass name , ' seemed to fail.') errorPrintCR.
-                        ] ifFalse:[
+		    ] ifFalse:[
+			(newClass isNil or:[newClass == oldClass]) ifTrue:[
+			    ('ObjectFileLoader [warning]: reload of ' , oldClass name , ' seemed to fail.') errorPrintCR.
+			] ifFalse:[
 "/'oldSize: ' print. oldClass instSize print. ' (' print. oldClass instSize class name print. ') ' print.
 "/'newSize: ' print. newClass instSize print. ' (' print. oldClass instSize class name print. ') ' printCR.
 
-                            oldClass instSize ~~ newClass instSize ifTrue:[
-                                ('ObjectFileLoader [warning]: ' , oldClass name , ' has changed its size.') errorPrintCR.
-                            ] ifFalse:[
-                                oldClass class instSize ~~ newClass class instSize ifTrue:[
-                                    ('ObjectFileLoader [warning]: ' , oldClass name , ' class has changed its size.') errorPrintCR.
-                                ] ifFalse:[
+			    oldClass instSize ~~ newClass instSize ifTrue:[
+				('ObjectFileLoader [warning]: ' , oldClass name , ' has changed its size.') errorPrintCR.
+			    ] ifFalse:[
+				oldClass class instSize ~~ newClass class instSize ifTrue:[
+				    ('ObjectFileLoader [warning]: ' , oldClass name , ' class has changed its size.') errorPrintCR.
+				] ifFalse:[
 "/                                    ('ObjectFileLoader [info]: migrating ' , oldClass name) infoPrintCR.
-                                    (oldCat := oldClass category) ~= newClass category ifTrue:[
-                                        newClass category:oldCat.
-                                    ].
-                                    (oldCVars := oldClass classVariableString) ~= newClass classVariableString ifTrue:[
-                                        newClass setClassVariableString:oldCVars
-                                    ].
-                                    oldClass becomeSameAs:newClass
+				    (oldCat := oldClass category) ~= newClass category ifTrue:[
+					newClass category:oldCat.
+				    ].
+				    (oldCVars := oldClass classVariableString) ~= newClass classVariableString ifTrue:[
+					newClass setClassVariableString:oldCVars
+				    ].
+				    oldClass becomeSameAs:newClass
 "/                                    oldClass become:newClass
-                                ]
-                            ]
-                        ]
-                    ]
-                ]
-
-            ] ifFalse:[
-                handle isMethodHandle ifTrue:[
-                    oldDummyMethod := handle method.
-                    (oldDummyMethod isKindOf:Method) ifFalse:[
-                        ('ObjectFileLoader [info]: ignore obsolete (already collected) method in ' , fileName) infoPrintCR
-                    ] ifTrue:[
-                        ('ObjectFileLoader [info]: reloading method in ' , fileName , ' ...') infoPrintCR.
-                        who := oldDummyMethod who.
-                        newHandle := self loadMethodObjectFile:fileName.
-                        newHandle isNil ifTrue:[
-                            ('ObjectFileLoader [warning]: failed to reload method in ' , fileName , ' ...') errorPrintCR.
-                            handle moduleID:nil.
-                        ] ifFalse:[
-                            m := newHandle method.
-                            oldDummyMethod sourceFilename notNil ifTrue:[
-                                m sourceFilename:(oldDummyMethod sourceFilename)
-                                  position:(oldDummyMethod sourcePosition).
-                            ] ifFalse:[
-                                m source:(oldDummyMethod source).
-                            ].
-                            m package:(oldDummyMethod package).
-                            who notNil ifTrue:[
-                                cls := who methodClass.
-                                sel := who methodSelector.
-                                m == (cls compiledMethodAt:sel) ifFalse:[
-                                    'ObjectFileLoader [warning]: oops - loaded method installed wrong' errorPrintCR.
-                                ] ifTrue:[
+				]
+			    ]
+			]
+		    ]
+		]
+
+	    ] ifFalse:[
+		handle isMethodHandle ifTrue:[
+		    oldDummyMethod := handle method.
+		    (oldDummyMethod isKindOf:Method) ifFalse:[
+			('ObjectFileLoader [info]: ignore obsolete (already collected) method in ' , fileName) infoPrintCR
+		    ] ifTrue:[
+			('ObjectFileLoader [info]: reloading method in ' , fileName , ' ...') infoPrintCR.
+			who := oldDummyMethod who.
+			newHandle := self loadMethodObjectFile:fileName.
+			newHandle isNil ifTrue:[
+			    ('ObjectFileLoader [warning]: failed to reload method in ' , fileName , ' ...') errorPrintCR.
+			    handle moduleID:nil.
+			] ifFalse:[
+			    m := newHandle method.
+			    oldDummyMethod sourceFilename notNil ifTrue:[
+				m sourceFilename:(oldDummyMethod sourceFilename)
+				  position:(oldDummyMethod sourcePosition).
+			    ] ifFalse:[
+				m source:(oldDummyMethod source).
+			    ].
+			    m package:(oldDummyMethod package).
+			    who notNil ifTrue:[
+				cls := who methodClass.
+				sel := who methodSelector.
+				m == (cls compiledMethodAt:sel) ifFalse:[
+				    'ObjectFileLoader [warning]: oops - loaded method installed wrong' errorPrintCR.
+				] ifTrue:[
 "/                                  cls changed:#methodDictionary with:(Array with:sel with:oldDummyMethod).
-                                ]
-                            ].
-                        ]
-                    ]
-                ] ifFalse:[
-                    handle isFunctionObjectHandle ifTrue:[
-                        functions := handle functions.
-                        functions isEmpty ifTrue:[
-                            ('ObjectFileLoader [info]: ignore obsolete (unreferenced) functions in ' , fileName) infoPrintCR
-                        ] ifFalse:[
-                            newHandle := self loadDynamicObject:fileName.
-                            newHandle isNil ifTrue:[
-                                ('ObjectFileLoader [warning]: failed to reload ' , fileName , ' ...') errorPrintCR.
-                                handle moduleID:nil.
-                            ] ifFalse:[
-                                ('ObjectFileLoader [info]: reloading ' , fileName , ' ...') infoPrintCR.
-                                functions do:[:oldFunction |
-                                    newFunction := newHandle getFunction:(oldFunction name).
-                                    newFunction isNil ifTrue:[
-                                        ('ObjectFileLoader [info]: function: ''' , oldFunction name , ''' no longer present.') errorPrintCR.
-                                        oldFunction code:nil.
-                                        oldFunction setName:oldFunction name moduleHandle:nil.
-                                    ] ifFalse:[
-                                        oldFunction code:(newFunction code).
-                                        oldFunction setName:oldFunction name moduleHandle:newHandle.
-                                        ('ObjectFileLoader [info]: rebound function: ''' , oldFunction name , '''.') infoPrintCR.
-                                    ]
-                                ].
-                                handle becomeSameAs:newHandle.      "/ the old handle is now void
-                            ]
-                        ]
-                    ] ifFalse:[
-                        ('ObjectFileLoader [info]: ignored invalid (obsolete) objectFile handle: ' , handle printString) infoPrintCR.
-                    ]
-                ]
-            ]
-        ].
-        PreviouslyLoadedObjects := nil.
-
-        "/ now, as we hopefully have all loaded,
-        "/ send #reinitializeAfterLoad to each of them
-        anyModulesToInitialize ifTrue:[
-            AbortSignal catch:[
-                self moduleInit:4 forceOld:false interruptable:true.
-            ]
-        ]
+				]
+			    ].
+			]
+		    ]
+		] ifFalse:[
+		    handle isFunctionObjectHandle ifTrue:[
+			functions := handle functions.
+			functions isEmpty ifTrue:[
+			    ('ObjectFileLoader [info]: ignore obsolete (unreferenced) functions in ' , fileName) infoPrintCR
+			] ifFalse:[
+			    newHandle := self loadDynamicObject:fileName.
+			    newHandle isNil ifTrue:[
+				('ObjectFileLoader [warning]: failed to reload ' , fileName , ' ...') errorPrintCR.
+				handle moduleID:nil.
+			    ] ifFalse:[
+				('ObjectFileLoader [info]: reloading ' , fileName , ' ...') infoPrintCR.
+				functions do:[:oldFunction |
+				    newFunction := newHandle getFunction:(oldFunction name).
+				    newFunction isNil ifTrue:[
+					('ObjectFileLoader [info]: function: ''' , oldFunction name , ''' no longer present.') errorPrintCR.
+					oldFunction code:nil.
+					oldFunction setName:oldFunction name moduleHandle:nil.
+				    ] ifFalse:[
+					oldFunction code:(newFunction code).
+					oldFunction setName:oldFunction name moduleHandle:newHandle.
+					('ObjectFileLoader [info]: rebound function: ''' , oldFunction name , '''.') infoPrintCR.
+				    ]
+				].
+				handle becomeSameAs:newHandle.      "/ the old handle is now void
+			    ]
+			]
+		    ] ifFalse:[
+			('ObjectFileLoader [info]: ignored invalid (obsolete) objectFile handle: ' , handle printString) infoPrintCR.
+		    ]
+		]
+	    ]
+	].
+	PreviouslyLoadedObjects := nil.
+
+	"/ now, as we hopefully have all loaded,
+	"/ send #reinitializeAfterLoad to each of them
+	anyModulesToInitialize ifTrue:[
+	    AbortSignal catch:[
+		self moduleInit:4 forceOld:false interruptable:true.
+	    ]
+	]
     ]
 
     "Modified: / 16.5.1998 / 14:23:12 / cg"
@@ -3399,92 +3411,92 @@
     |key fileName functionName deInitAddr m|
 
     Verbose ifTrue:[
-        'unload module name=' infoPrint. handle pathName infoPrintCR.
+	'unload module name=' infoPrint. handle pathName infoPrintCR.
     ].
 
     handle isUnknownHandle ifTrue:[
 	Verbose ifTrue:[
 	    'module type is not known - assume uninitialized classLib'
 	].
-        self unregisterModule:handle.
+	self unregisterModule:handle.
 	handle makeClassLibHandle.
     ] ifFalse:[
-        handle isClassLibHandle ifTrue:[
-            Verbose ifTrue:[
-                'a classLib - deinit classes' infoPrintCR.
-            ].
-            self deinitializeClassesFromModule:handle.
-            Verbose ifTrue:[
-                'unregister' infoPrintCR.
-            ].
-            self unregisterModule:handle.
-        ] ifFalse:[    
-            handle isMethodHandle ifTrue:[
-                Verbose ifTrue:[
-                    'a methodHandle - unregister' infoPrintCR.
-                ].
-                self unregisterModule:handle.
-            ] ifFalse:[
-                handle isFunctionObjectHandle ifTrue:[
-                    Verbose ifTrue:[
-                        'a functionObject - fixup functionRefs' infoPrintCR.
-                    ].
-                    handle functions do:[:f |
-                                    f notNil ifTrue:[
-                                        f code:0
-                                    ]
-                                ].
-                ].
-
-                "/
-                "/ call its deInit function (if present)
-                "/
-                Verbose ifTrue:[
-                    'search for deInit function...' infoPrintCR.
-                ].
-                fileName := handle pathName asFilename baseName.
-                functionName := self initFunctionBasenameForFile:fileName.
+	handle isClassLibHandle ifTrue:[
+	    Verbose ifTrue:[
+		'a classLib - deinit classes' infoPrintCR.
+	    ].
+	    self deinitializeClassesFromModule:handle.
+	    Verbose ifTrue:[
+		'unregister' infoPrintCR.
+	    ].
+	    self unregisterModule:handle.
+	] ifFalse:[    
+	    handle isMethodHandle ifTrue:[
+		Verbose ifTrue:[
+		    'a methodHandle - unregister' infoPrintCR.
+		].
+		self unregisterModule:handle.
+	    ] ifFalse:[
+		handle isFunctionObjectHandle ifTrue:[
+		    Verbose ifTrue:[
+			'a functionObject - fixup functionRefs' infoPrintCR.
+		    ].
+		    handle functions do:[:f |
+				    f notNil ifTrue:[
+					f code:0
+				    ]
+				].
+		].
+
+		"/
+		"/ call its deInit function (if present)
+		"/
+		Verbose ifTrue:[
+		    'search for deInit function...' infoPrintCR.
+		].
+		fileName := handle pathName asFilename baseName.
+		functionName := self initFunctionBasenameForFile:fileName.
     
-                deInitAddr := self findFunction:functionName suffix:'__deInit' in:handle.
-                deInitAddr notNil ifTrue:[
-                    Verbose ifTrue:[
-                        'invoke deInit function...' infoPrintCR.
-                    ].
-                    self callInitFunctionAt:deInitAddr 
-                         specialInit:false 
-                         forceOld:true 
-                         interruptable:false
-                         argument:0
-                         identifyAs:handle
-                         returnsObject:false.
-                ]
-            ]
-        ].
+		deInitAddr := self findFunction:functionName suffix:'__deInit' in:handle.
+		deInitAddr notNil ifTrue:[
+		    Verbose ifTrue:[
+			'invoke deInit function...' infoPrintCR.
+		    ].
+		    self callInitFunctionAt:deInitAddr 
+			 specialInit:false 
+			 forceOld:true 
+			 interruptable:false
+			 argument:0
+			 identifyAs:handle
+			 returnsObject:false.
+		]
+	    ]
+	].
     ].
 
     Verbose ifTrue:[
-        'cleanup done - now unload...' infoPrintCR.
+	'cleanup done - now unload...' infoPrintCR.
     ].
 
     "/
     "/ now, really unload
     "/
     (self primUnloadDynamicObject:handle) ifFalse:[
-        ^ self error:'unloadDynamic failed' mayProceed:true
+	^ self error:'unloadDynamic failed' mayProceed:true
     ].
 
     Verbose ifTrue:[
-        'unload done ...' infoPrintCR.
+	'unload done ...' infoPrintCR.
     ].
 
     "/
     "/ remove from loaded objects
     "/
     LoadedObjects notNil ifTrue:[
-        key := LoadedObjects keyAtEqualValue:handle.
-        key notNil ifTrue:[
-            LoadedObjects removeKey:key
-        ]
+	key := LoadedObjects keyAtEqualValue:handle.
+	key notNil ifTrue:[
+	    LoadedObjects removeKey:key
+	]
     ].
 
     "
@@ -3492,17 +3504,17 @@
      but make it unexecutable. Its still visible in the browser.
     "
     handle isMethodHandle ifTrue:[
-        ((m := handle method) notNil 
-        and:[m ~~ 0]) ifTrue:[
-            m makeUnloaded.
-        ]
+	((m := handle method) notNil 
+	and:[m ~~ 0]) ifTrue:[
+	    m makeUnloaded.
+	]
     ].
 
     handle isClassLibHandle ifTrue:[
-        Smalltalk flushCachedClasses.
+	Smalltalk flushCachedClasses.
     ].
     handle isMethodHandle ifTrue:[
-        ObjectMemory flushCaches.
+	ObjectMemory flushCaches.
     ].
 
     handle moduleID:nil.
@@ -3824,7 +3836,7 @@
     "Initialize a loaded smalltalk module."
 
     ^ self
-        performModuleInitAt:initAddr invokeInitializeMethods:true for:className identifyAs:handle.
+	performModuleInitAt:initAddr invokeInitializeMethods:true for:className identifyAs:handle.
 
 !
 
@@ -3836,10 +3848,10 @@
 
     "
      need 4 passes to init: 0: let module register itself & create its pools/globals
-                            0b check if modules superclasses are all loaded
-                            1: let it get var-refs to other pools/globals
-                            2: let it install install class, methods and literals
-                            3: let it send #initialize to its class object
+			    0b check if modules superclasses are all loaded
+			    1: let it get var-refs to other pools/globals
+			    2: let it install install class, methods and literals
+			    3: let it send #initialize to its class object
     "
 
     stillTrying := true.
@@ -3847,78 +3859,78 @@
     [stillTrying] whileTrue:[
 	stillTrying := false.
 
-        "/
-        "/ let it register itself
-        "/ and define its globals
-        "/
-        Verbose ifTrue:[
-            'phase 0 (module registration) ...' infoPrintCR
-        ].
-        self callInitFunctionAt:initAddr 
-             specialInit:true 
-             forceOld:true 
-             interruptable:false
-             argument:0
-             identifyAs:handle
-             returnsObject:false.
-
-        "/
-        "/ check if superclasses are present
-        "/
-        info := self loadStatusFor:className.
-        status := info at:1.
-        badClassName := info at:2.
-
-        Verbose ifTrue:[
-            '... status is ' infoPrint. info infoPrintCR
-        ].
-
-        (status ~~ #ok) ifTrue:[
-            (status == #missingClass) ifTrue:[
-                ('ObjectFileLoader [error]: load failed - missing class: ' , badClassName) infoPrintCR.
-                ^ info
-            ].
-            (status == #versionMismatch) ifTrue:[
-                ('ObjectFileLoader [error]: load failed - version mismatch: ' , badClassName) infoPrintCR.
-                ^ info
-            ].
-            (status == #unregisteredSuperclass) ifTrue:[
-                ('ObjectFileLoader [error]: load failed - unregistered: ' , badClassName) infoPrintCR.
-                ^ info
-            ].
+	"/
+	"/ let it register itself
+	"/ and define its globals
+	"/
+	Verbose ifTrue:[
+	    'phase 0 (module registration) ...' infoPrintCR
+	].
+	self callInitFunctionAt:initAddr 
+	     specialInit:true 
+	     forceOld:true 
+	     interruptable:false
+	     argument:0
+	     identifyAs:handle
+	     returnsObject:false.
+
+	"/
+	"/ check if superclasses are present
+	"/
+	info := self loadStatusFor:className.
+	status := info at:1.
+	badClassName := info at:2.
+
+	Verbose ifTrue:[
+	    '... status is ' infoPrint. info infoPrintCR
+	].
+
+	(status ~~ #ok) ifTrue:[
+	    (status == #missingClass) ifTrue:[
+		('ObjectFileLoader [error]: load failed - missing class: ' , badClassName) infoPrintCR.
+		^ info
+	    ].
+	    (status == #versionMismatch) ifTrue:[
+		('ObjectFileLoader [error]: load failed - version mismatch: ' , badClassName) infoPrintCR.
+		^ info
+	    ].
+	    (status == #unregisteredSuperclass) ifTrue:[
+		('ObjectFileLoader [error]: load failed - unregistered: ' , badClassName) infoPrintCR.
+		^ info
+	    ].
 	    (status ~~ #tryAgain) ifTrue:[
-                'ObjectFileLoader [error]: load failed' infoPrintCR.
-                ^ Array with:#loadFailed with:nil
+		'ObjectFileLoader [error]: load failed' infoPrintCR.
+		^ Array with:#loadFailed with:nil
 	    ].
 	    (status == #tryAgain) ifTrue:[
-	        "/ tryAgain:
-	        "/   must retry after initialization, to initialize
-	        "/   sub-subclasses of autoloaded classes
-	        "/   (sigh - class objects are created in phase 3,
-	        "/    so we must first complete the initialization cycle,
-	        "/    then do all again, for remaining modules)
+		"/ tryAgain:
+		"/   must retry after initialization, to initialize
+		"/   sub-subclasses of autoloaded classes
+		"/   (sigh - class objects are created in phase 3,
+		"/    so we must first complete the initialization cycle,
+		"/    then do all again, for remaining modules)
 		stillTrying := true.
-                'ObjectFileLoader [info]: retry registration after init' infoPrintCR.
+		'ObjectFileLoader [info]: retry registration after init' infoPrintCR.
 	    ]
-        ].
-
-        "/
-        "/ remaining initialization
-        "/
-
-        "/ module exports: declare module-globals & symbols ...
-        Verbose ifTrue:[
-            'phase 1 (resolve globals) ...' infoPrintCR
-        ].
-        self moduleInit:1 forceOld:true interruptable:false.
-
-
-        "/ module-imports: resolve globals ...
-        "/ create methods & install ...
-        Verbose ifTrue:[
-            'phase 2 (create objects) ...' infoPrintCR
-        ].
-        self moduleInit:2 forceOld:true interruptable:false.
+	].
+
+	"/
+	"/ remaining initialization
+	"/
+
+	"/ module exports: declare module-globals & symbols ...
+	Verbose ifTrue:[
+	    'phase 1 (resolve globals) ...' infoPrintCR
+	].
+	self moduleInit:1 forceOld:true interruptable:false.
+
+
+	"/ module-imports: resolve globals ...
+	"/ create methods & install ...
+	Verbose ifTrue:[
+	    'phase 2 (create objects) ...' infoPrintCR
+	].
+	self moduleInit:2 forceOld:true interruptable:false.
     ].
 
     ObjectMemory flushCaches.
@@ -3929,27 +3941,27 @@
     infoCollection := ObjectMemory binaryModuleInfo.
     info := infoCollection at:handle moduleID ifAbsent:nil.
     info isNil ifTrue:[
-        "/ mhmh registration failed -
-        'ObjectFileLoader [error]: registration failed' infoPrintCR.
-        ^ Array with:#registrationFailed with:nil
+	"/ mhmh registration failed -
+	'ObjectFileLoader [error]: registration failed' infoPrintCR.
+	^ Array with:#registrationFailed with:nil
     ].
 
     classNames := info classNames.
     classNames size > 0 ifTrue:[
-        classes := classNames collect:[:nm | Smalltalk classNamed:nm].
+	classes := classNames collect:[:nm | Smalltalk classNamed:nm].
     ].
     classes size > 0 ifTrue:[
-        classes := classes asArray.
-        classes := classes , (classes collect:[:aClass | aClass class]).
+	classes := classes asArray.
+	classes := classes , (classes collect:[:aClass | aClass class]).
     ].
     handle classes:classes.
 
     invokeInitializeMethods ifTrue:[
-        Verbose ifTrue:[
-            'phase 3 (send #initialize) ...' infoPrintCR
-        ].
-        "/ initialize ...
-        self moduleInit:3 forceOld:false interruptable:true.
+	Verbose ifTrue:[
+	    'phase 3 (send #initialize) ...' infoPrintCR
+	].
+	"/ initialize ...
+	self moduleInit:3 forceOld:false interruptable:true.
     ].
 
     ^ Array with:#ok with:nil
@@ -3979,26 +3991,26 @@
      (req'd if a subclass of an autoloaded class has been loaded)"
 
     Verbose ifTrue:[
-        'checkCall for:' infoPrint. aClass name infoPrint. ' -> ' infoPrint.
+	'checkCall for:' infoPrint. aClass name infoPrint. ' -> ' infoPrint.
     ].
     aClass isBehavior ifFalse:[
-        Verbose ifTrue:[
-            'false' infoPrintCR. 
-        ].
-        'ObjectFileLoader [warning]: check failed - no behavior' errorPrintCR.
-        ^ false
+	Verbose ifTrue:[
+	    'false' infoPrintCR. 
+	].
+	'ObjectFileLoader [warning]: check failed - no behavior' errorPrintCR.
+	^ false
     ].
     Verbose ifTrue:[
-        'true' infoPrintCR. 
-        ('ObjectFileLoader [info]: check for ' , aClass name , ' being loaded') infoPrintCR.
+	'true' infoPrintCR. 
+	('ObjectFileLoader [info]: check for ' , aClass name , ' being loaded') infoPrintCR.
     ].
     aClass autoload.
     (aClass isBehavior and:[aClass isLoaded]) ifTrue:[
-        Verbose ifTrue:[
-            ('ObjectFileLoader [info]: ok, loaded. continue registration of actual class') infoPrintCR.
-        ].
-        aClass signature.       "/ req'd in VM for validation
-        ^ true
+	Verbose ifTrue:[
+	    ('ObjectFileLoader [info]: ok, loaded. continue registration of actual class') infoPrintCR.
+	].
+	aClass signature.       "/ req'd in VM for validation
+	^ true
     ].
     ('ObjectFileLoader [warning]: superclass not loaded; registration of ' , aClass name , ' fails') errorPrintCR.
     ^ false
@@ -4026,6 +4038,6 @@
 !ObjectFileLoader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/ObjectFileLoader.st,v 1.210 1999-12-15 14:18:23 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/ObjectFileLoader.st,v 1.211 1999-12-17 11:45:37 cg Exp $'
 ! !
 ObjectFileLoader initialize!
--- a/bc.mak	Wed Dec 15 20:36:33 1999 +0100
+++ b/bc.mak	Fri Dec 17 12:45:38 1999 +0100
@@ -2,7 +2,7 @@
 # DO NOT EDIT 
 # automatically generated from Make.proto (by make nt.mak)
 #
-# $Header: /cvs/stx/stx/libcomp/bc.mak,v 1.22 1999-12-15 19:36:33 cg Exp $
+# $Header: /cvs/stx/stx/libcomp/bc.mak,v 1.23 1999-12-17 11:45:38 cg Exp $
 #
 TOP=..
 #
@@ -12,7 +12,7 @@
 MODULE_DIR=libcomp
 PACKAGE=$(MODULE):$(MODULE_DIR)
 LIBNAME=libcomp
-LIB_BASE=$(LIBCOMP_BASE)
+#LIB_BASE_LD_ARG=-B:$(LIBCOMP_BASE)
 STCOPT="+optinline -warnNonStandard"
 STCLOCALOPT=-package=$(PACKAGE) $(COMMONSYMBOLS) $(SEPINITCODE) $(RELOCINSTVARS) -varPrefix=$(LIBNAME)
 #STCLOCALOPT="-package=stx:libcomp +commonSymbols +sepInitCode -varPrefix=libcomp"
--- a/nt.mak	Wed Dec 15 20:36:33 1999 +0100
+++ b/nt.mak	Fri Dec 17 12:45:38 1999 +0100
@@ -2,7 +2,7 @@
 # DO NOT EDIT 
 # automatically generated from Make.proto (by make nt.mak)
 #
-# $Header: /cvs/stx/stx/libcomp/Attic/nt.mak,v 1.22 1999-12-15 19:36:33 cg Exp $
+# $Header: /cvs/stx/stx/libcomp/Attic/nt.mak,v 1.23 1999-12-17 11:45:38 cg Exp $
 #
 TOP=..
 #
@@ -12,7 +12,7 @@
 MODULE_DIR=libcomp
 PACKAGE=$(MODULE):$(MODULE_DIR)
 LIBNAME=libcomp
-LIB_BASE=$(LIBCOMP_BASE)
+#LIB_BASE_LD_ARG=-B:$(LIBCOMP_BASE)
 STCOPT="+optinline -warnNonStandard"
 STCLOCALOPT=-package=$(PACKAGE) $(COMMONSYMBOLS) $(SEPINITCODE) $(RELOCINSTVARS) -varPrefix=$(LIBNAME)
 #STCLOCALOPT="-package=stx:libcomp +commonSymbols +sepInitCode -varPrefix=libcomp"