Smalltalk.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 13 Mar 2013 00:42:41 +0000
branchjv
changeset 18028 e39da2aa21bc
parent 18027 3621469cc5e8
parent 14833 c718848b1051
child 18037 4cf874da38c9
permissions -rw-r--r--
Merged 3621469cc5e8 and a34396484b3c (branch default - CVS HEAD)

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

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

Object subclass:#Smalltalk
	instanceVariableNames:''
	classVariableNames:'StartBlocks ImageStartBlocks ExitBlocks CachedClasses
		NumberOfClassesHint SystemPath StartupClass StartupSelector
		StartupArguments CommandLine CommandName CommandLineArguments
		CachedAbbreviations VerboseLoading SilentLoading Initializing
		StandAlone HeadlessOperation IsPlugin IsSharedLibraryComponent
		IsSTScript DebuggingStandAlone LogDoits LoadBinaries
		RealSystemPath ResourcePath SourcePath BinaryPath FileInPath
		PackagePath BinaryDirName ResourceDirName SourceDirName
		BitmapDirName PackageDirName FileInDirName ChangeFileName
		ImageStartTime ImageRestartTime DemoMode SaveEmergencyImage
		SpecialObjectArray CallbackSignal KnownPackages
		ClassesFailedToInitialize HasNoConsole IgnoreHalt
		PackageToPathMapping'
	poolDictionaries:''
	category:'System-Support'
!

Smalltalk comment:''
!

!Smalltalk class methodsFor:'documentation'!

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

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

documentation
"
    This is one of the central classes in the system;
    it provides all system-startup, shutdown and maintenance support.
    Also global variables are (conceptionally) kept here.

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

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


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

    [Class variables:]

	StartBlocks     <Collection>    blocks to be executed in a separate process after
					everything has been initialized. These blocks will
					be deleted after execution and therefore not be
					executed after an image restart. Initial processes
					(such as the Launcher) are usually started here.
					These blocks are added by smalltalk.rc/private.rc etc.
					via #addStartBlock during early initialization.

	ImageStartBlocks
			<Collection>    blocks to be executed in a separate process after
					everything has been initialized. These blocks will be
					executed after an image restart.
					These blocks are usually added by smalltalk_r.rc etc.

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

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

	PackagePath     <Collection>    path to search for package.
					This is going to replace the above systemPath, and a classes
					resources will eventually searched in its package directory.
					This list defines the path, where packages are searched for,
					initially this is something like /opt/smalltalk/packages.
					Set to a default here, but typically changed from some
					startup.rc file

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

	CommandLine          <String>   Unix (OS-) command line

	CommandName          <String>   the command (i.e. argv[0])

	CommandLineArguments <Array>    Unix (OS-) command line arguments broken into words
					CommandName has been stripped off.
					(initially set by the VM)

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

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

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

	StandAlone      <Boolean>       true, if this is a standalone app;
					if true the process scheduler watches for
					which processes are still running, and
					exits ST/X, when the last non-background
					and non-system process exits.
					Can be set in an application-specific startup script,
					or, for standAlone programs, by C-code during initialization.

	HeadlessOperation               if true, a non-existing Display connection
			<Boolean>       will NOT lead to an error-exit during startup.
					Default is false.
					Can be set in an application-specific startup script,
					or, for standAlone programs, by C-code during initialization.

	LogDoits        <Boolean>       if true, doits are also logged in the changes
					file. Default is false, since the changes file
					may become huge if every tiny doIt is saved there ...

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

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

    strictly private classVariables (helpers):

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

	CachedAbbreviations
			<Dictionary>    className to filename mappings

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

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


    [author:]
	Claus Gittinger

    [see also:]
	ObjectMemory
	StandaloneStartup
	GetOpt
	ReadEvalPrintLoop
"
!

readme_resources
"
    What is a resource file:
	resource files contain language transformation and sometimes
	UI-look specifics such as icons etc.

    Where are resources stored in the image:
	Resource files are only read on demand (i.e. when needed) and only read once
	i.e. they are cached in the image).
	The cached data is held in a per-class class-instVar named 'ClassResources'.
	With only a few exceptions, the only classes which need resources are the GUI
	classes under the SimpleView hierarchy.

    How does the system find resources:
	The idea is that the system-provided resource files can be overwritten
	by the user or an application configuration.
	This works via a hierarchy of directories where resources are searched for,
	with the systems standard resource-files being at the end of that chain.

	When searching for a resource file for class X, the following files are searched
	in order:
		{ResourcePath} / resources / X.rs
		{SystemPath} / (CLASSES-PACKAGE-PATH) / X.rs
		{ResourcePath} / (CLASSES-PACKAGE-PATH) / X.rs
"
! !


!Smalltalk class methodsFor:'initialization'!

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

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

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

    self initGlobalsFromEnvironment.

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

    self initStandardStreams.    "/ setup Stdin, Stdout etc.

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

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

    "/
    "/ in case, someone needs the objectFileLoader early
    "/
    ObjectFileLoader initialize.

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

    ImageStartTime := Timestamp now.

    self initInterrupts.
    self initUserPreferences.

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

    "Modified: / 08-01-1997 / 19:58:12 / stefan"
    "Modified: / 05-12-2006 / 21:48:58 / cg"
    "Modified: / 24-10-2012 / 18:45:15 / sr"
!

initGlobalsFromEnvironment
    "setup globals from the shell-environment"

    |envString i langString terrString|

    StandAlone isNil ifTrue:[
	StandAlone := false.
    ].
    HeadlessOperation isNil ifTrue:[
	HeadlessOperation := false.
    ].

    "
     extract Language and LanguageTerritory from LANG variable.
     valid are for example:
			    en_en / en
			    en_us
			    en_gb
			    de_de / de
			    de_at       (for Austria)
    "

    Language := #en.
    LanguageTerritory := #us.


    "Format of LANG is: language[_territory][.codeset][@modifier]
	language        ISO-639  Language code
	territory       ISO-3166 Contry code"

    envString := OperatingSystem getLanguage.
    envString size > 0 ifTrue:[
	i := envString indexOf:$@.
	(i ~~ 0) ifTrue:[
	    LanguageModifier := (envString copyFrom:(i + 1)) asLowercase asSymbol.
	    envString := envString copyTo:(i - 1).
	] ifFalse:[
	    LanguageModifier := nil.
	].
	i := envString indexOf:$..
	(i ~~ 0) ifTrue:[
	    LanguageCodeset := (envString copyFrom:(i + 1)) asLowercase asSymbol.
	    envString := envString copyTo:(i - 1).
	] ifFalse:[
	    LanguageCodeset := #'iso8859-1'.
	].
	i := envString indexOf:$_.
	(i == 0) ifTrue:[
	    langString := envString.
	    terrString := envString
	] ifFalse:[
	    langString := envString copyTo:(i - 1).
	    terrString := envString copyFrom:(i + 1)
	].
	langString := langString asLowercase.
	terrString := terrString asLowercase.
	(langString = 'c' or:[terrString = 'c']) ifTrue:[
	    ('Smalltalk [info]: ignoring wrong LANG setting (',langString,'_',terrString,') - using english') infoPrintCR.
	] ifFalse:[
	    Language := langString asSymbol.
	    LanguageTerritory := terrString asSymbol
	]
    ].

    "
     Smalltalk initGlobalsFromEnvironment
    "

    "Modified: / 14-02-2012 / 15:25:08 / cg"
!

initInterrupts
    "initialize interrupts"

    OperatingSystem enableUserInterrupts.
    OperatingSystem enableHardSignalInterrupts.
    OperatingSystem enableCrashSignalInterrupts.

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

    OperatingSystem isOSXlike ifTrue:[
        "/ OSX sends SIGABRT for NSExceptions
        OperatingSystem operatingSystemSignal:(OperatingSystem sigABRT) install:NSException.
        OperatingSystem enableAbortInterrupts.
    ].

    "
     Smalltalk initInterrupts
    "

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

initStandardStreams
    "initialize some well-known streams"

    Stdout := NonPositionableExternalStream forStdout.
    Stderr := NonPositionableExternalStream forStderr.
    Stdin := NonPositionableExternalStream forStdin.
    PrinterStream notNil ifTrue:[
	Printer := PrinterStream defaultPrinter.
    ].
    Transcript := Stderr

    "
     Smalltalk initStandardStreams
    "

    "Modified: / 25-10-2006 / 17:36:46 / cg"
!

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

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

    "/ make the changeFilePath an absolute one,
    "/ in case some stupid windows fileDialog changes the current directory...
    ObjectMemory
	nameForChanges:(Filename currentDirectory construct:ObjectMemory nameForChangesLocal)
			    asAbsoluteFilename pathName

    "
     Smalltalk initStandardTools
    "

    "Modified: / 09-02-2011 / 20:44:47 / cg"
!

initSystemPath
    "setup path where system files are searched for.
     the default path is set to:
	    .
	    <directory of exe>       (WIN32 only)
	    $HOME                    (if defined)
	    $HOME/.smalltalk         (if defined & existing)
	    $SMALLTALK_LIBDIR        (if defined & existing)
	    $STX_LIBDIR              (if defined & existing)
	    $STX_TOPDIR              (if defined & existing)
	    REGISTRY('HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X\<CurrentVersion>\LibDir') (WIN32 only)
	    REGISTRY('HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X\LibDir')                  (WIN32 only)
	    <standard places>

     standard places (unix):
	    /opt/smalltalk/<release> (if existing)
	    /opt/smalltalk           (if existing)
	    /usr/local/lib/smalltalk (if existing)
	    /usr/lib/smalltalk       (if existing)
	    /lib/smalltalk           (if existing)

     win32:
	    \programs\exept\smalltalk (if existing)
	    \programs\smalltalk       (if existing)
	    \smalltalk                (if existing)

     vms:
	    $stx:lib                 (if existing)
	    $stx:root                (if existing)

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

     However, smalltalk.rc itself must be found along the above path.
    "

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

    SystemPath isNil ifTrue:[
	SystemPath := OperatingSystem defaultSystemPath.
	self flushPathCaches
    ].

    PackagePath isNil ifTrue:[
	PackagePath := OperatingSystem defaultPackagePath.
    ].

    "
     Smalltalk initSystemPath
     Smalltalk systemPath

     OperatingSystem defaultSystemPath
     OperatingSystem defaultPackagePath
    "

    "Modified: / 24.12.1999 / 00:23:35 / cg"
!

initUserPreferences
    "setup other stuff"

    LogDoits := false.
    LoadBinaries := false.
    SaveEmergencyImage := (StandAlone ~~ true).

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

initializeClass:aClass
    "sent from VM via #initializeModules"

    Error handle:[:ex |
	ObjectMemory printStackBacktrace.
	ClassesFailedToInitialize isNil ifTrue:[
	    ClassesFailedToInitialize := IdentitySet new.
	].
	ClassesFailedToInitialize add:aClass.
	('Smalltalk [warning]: error during initialize of ' , aClass name,': ', ex description printString) errorPrintCR.
	ex suspendedContext fullPrintAll.
	'------------------------------------------------' errorPrintCR.
	(Smalltalk commandLineArguments includes:'--debug') ifTrue:[
	    ex reject
	].
    ] do:[
	aClass initialize
    ].

    "Modified: / 11-09-2011 / 17:01:32 / cg"
!

initializeModules
    "perform module specific initialization and
     send #initialize to all classes.
     Notice: this is not called when an image is restarted"

    self initializeModulesOnce.
    ClassesFailedToInitialize size > 0 ifTrue:[
	('Smalltalk [info]: retry initialization of failed class(es)...') infoPrintCR.
	ClassesFailedToInitialize := nil.
	self initializeModulesOnce.
	ClassesFailedToInitialize size > 0 ifTrue:[
	    ('Smalltalk [error]: class(es) persist to fail during initialize') errorPrintCR.
	]
    ].

    ProjectDefinition initializeAllProjectDefinitions.

    "Modified: / 23-10-2006 / 16:40:39 / cg"
!

initializeModulesOnce
    "perform module specific initialization and
     send #initialize to all classes.
     Notice: this is not called when an image is restarted"

%{
    __init_registered_modules__(3);

    @global(DemoMode) = __getDemoMode() ? true : false;
    RETURN (self);
%}.
    ^ self primitiveFailed
!

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

    |idx|

    NumberOfClassesHint := 10000.

    Initializing := true.
    AbstractOperatingSystem initializeConcreteClass.

    CommandLineArguments isNil ifTrue:[
	CommandLineArguments := #('stx').
    ].
    CommandLine := CommandLineArguments copy.
    CommandLineArguments := CommandLineArguments asOrderedCollection.
    CommandName := CommandLineArguments removeFirst. "/ the command

    SilentLoading := (CommandLineArguments includes:'--silentStartup').
    VerboseLoading := (CommandLineArguments includes:'--verboseLoading').

    DebuggingStandAlone := false.

    StandAlone ifTrue:[
	InfoPrinting := false.
	ObjectMemory infoPrinting:false.

	idx := CommandLineArguments indexOf:'--debug'.
	idx ~~ 0 ifTrue:[
	    DebuggingStandAlone := true.
	].
	DebuggingStandAlone ifTrue:[
	    Inspector := MiniInspector.
	    Debugger := MiniDebugger.
	].
    ] ifFalse:[
	"/
	"/ define low-level debugging tools - graphical classes are not prepared yet
	"/ to handle things.
	"/ This will bring us into the MiniDebugger when an error occurs during startup.
	"/
	Inspector := MiniInspector.
	Debugger := MiniDebugger.
    ].

    Error handle:[:ex |
	StandAlone ifTrue:[
	    DebuggingStandAlone ifFalse:[
		'Startup Error - use --debug command line argument for more info' errorPrintCR.
		Smalltalk exit:1.
	    ].
	    'Startup Error' errorPrintCR.
	    thisContext fullPrintAll.
	].
	ex reject.
    ] do:[
	self basicInitializeSystem
    ].

    "Modified: / 12-10-2010 / 11:27:47 / cg"
!

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

    ^ Initializing not
!

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

    Stdout reOpen. Stderr reOpen. Stdin reOpen.
! !


!Smalltalk class methodsFor:'Compatibility-Squeak'!

at:aKey ifAbsentPut:aBlock
    "return the element indexed by aKey if present,
     if not present, store the result of evaluating valueBlock
     under aKey and return it."

    ^ self at:aKey ifAbsent:[ self at:aKey put:aBlock value ].

    "Created: / 29-05-2007 / 12:41:12 / cg"
!

beep
    Screen current beep
!

garbageCollect
   ObjectMemory garbageCollect
!

garbageCollectMost
    "collect recently created garbage; return the amount of freeSpace.
     In ST/X, only the newSpace is collected here, and the sum of
     newSpace + freeListSpace is returned."

    ObjectMemory scavenge.
    ^ ObjectMemory freeSpace
      + (ObjectMemory newSpaceSize - ObjectMemory newSpaceUsed)

!

isMorphic
    ^ false
!

platformName
    "not yet fully implemented (I have to figure out, what squeak returns in each case...)"

    ^ OperatingSystem platformName asUppercaseFirst

    "
     Smalltalk platformName -> 'Win32'
    "
!

registerExternalObject: anObject
    "Register the given object in the external objects array and return its index.
     If it is already there, just return its index.
     ExternalObjects are protected from GC and can be accessed easily from
     primitive code (via the global Smalltalk:SpecialObjectArray)"

    | objects firstEmptyIndex obj sz newObjects |

    objects := SpecialObjectArray.
    objects isNil ifTrue:[
	objects := Array new:5.
    ].

    "find the first empty slot and look if already registered"
    firstEmptyIndex := 0.
    1 to: objects size do: [:i |
	obj := objects at: i.
	obj == anObject ifTrue: [^ i].  "object already there, just return its index"
	(obj == nil and: [firstEmptyIndex = 0]) ifTrue: [
	    firstEmptyIndex := i
	]
    ].

    "if no empty slots, expand the array"
    firstEmptyIndex = 0 ifTrue: [
	sz := objects size.
	newObjects := objects species new: sz + 20.  "grow linearly"
	newObjects replaceFrom: 1 to: sz with: objects startingAt: 1.
	firstEmptyIndex := sz + 1.
	SpecialObjectArray := newObjects.
	objects := newObjects
    ].

    objects at: firstEmptyIndex put: anObject.
    ^ firstEmptyIndex

!

removeClassNamed: aName
    "Invoked from fileouts:  if there is currently a class in the system named aName, then remove it.
     If anything untoward happens, report it in the Transcript.  "

    | oldClass |

    (oldClass := self at: aName asSymbol ifAbsent: [nil]) isNil ifTrue:[
	Transcript showCR: 'Removal of class named ', aName, ' ignored because it does not exist.'.
	^ self
    ].
    oldClass removeFromSystem
!

renameClassNamed:oldName as:newName
    self renameClass:(self at:oldName) to:newName
!

unregisterExternalObject: anObject
    "Unregister the given object in the external objects array.
     Do nothing if it isn't registered."

    |objects|

    anObject isNil ifTrue:[^ self].
    objects := SpecialObjectArray.
    1 to: objects size do: [:i |
	(objects at: i) == anObject ifTrue: [
	    objects at: i put: nil
	]
    ].
!

windowSystemName
    "not yet fully implemented (I have to figure out, what squeak returns in each case...)"

    |platformName|

    platformName := Screen current platformName.
    platformName = #WIN32 ifTrue:[
	^ #Win32.
    ].
    ^ platformName.

    "
     Smalltalk windowSystemName
				-> 'Win32'
    "
! !


!Smalltalk class methodsFor:'Compatibility-V''Age'!

allClassesImplementing:aSelector
    ^ self allClassesForWhich:[:cls | cls includesSelector:aSelector].

    "Modified: / 10-08-2006 / 12:12:17 / cg"
!

declareConstant:constantName poolName:poolName value:value
    |pool|

    pool := self classNamed:poolName.
    pool declareConstant:constantName value:value
!

declarePoolDictionary:poolDictionaryName
    ^ SharedPool subclass:(poolDictionaryName asSymbol)
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:nil

    "Modified: / 07-02-2012 / 15:56:16 / cg"
!

declareVariable:varName poolName:poolName
    |pool|

    pool := self classNamed:poolName.
    pool declareVariable:varName

    "Created: / 07-02-2012 / 15:57:05 / cg"
! !


!Smalltalk class methodsFor:'Compatibility-VW5.4'!

defineClass:nameSymbol superclass:superclass indexedType:indexed private:private instanceVariableNames:instVars classInstanceVariableNames:classInstVars imports:imports category:category
    ^ self
	defineClass:nameSymbol
	superclass:superclass
	indexedType:indexed
	private:private
	instanceVariableNames:instVars
	classInstanceVariableNames:classInstVars
	imports:imports
	category:category
	attributes:nil
!

defineClass:nameSymbol superclass:superclass indexedType:indexed private:private instanceVariableNames:instVars classInstanceVariableNames:classInstVars imports:imports category:category attributes:annotations
    |newClass|

    indexed == #none ifTrue:[
	newClass := superclass
	    subclass:nameSymbol
	    instanceVariableNames:instVars
	    classVariableNames:''
	    poolDictionaries:''
	    category:category
	    inEnvironment:self.
	classInstVars size > 0 ifTrue:[
	    newClass class instanceVariableNames:classInstVars.
	].
	^ newClass
    ].
    self shouldImplement.
!

defineNameSpace:nameSymbol private:private imports:imports category:category
    |newNameSpace|

    private ifTrue:[self halt].     "/ what to do ?
    imports withoutSeparators notEmpty ifTrue:[self halt].     "/ what to do ?
    newNameSpace := NameSpace name:nameSymbol.
    newNameSpace setCategory:category.
    ^ newNameSpace
! !


!Smalltalk class methodsFor:'accessing'!

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

    |val|

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

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

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

    |val|

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

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

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

    aKey class == String ifTrue:[self error:'expected symbol'].

%{  /* NOCONTEXT */
    RETURN ( __GLOBAL_GET(aKey) );
%}.
    ^ self primitiveFailed
!

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

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

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

at:aKey ifPresent:aBlock
    "try to retrieve the value stored at aKey.
     If there is nothing stored under this key, do nothing.
     Otherwise, evaluate aBlock, passing the retrieved value as argument."

    |val|

    (self includesKey:aKey) ifTrue:[
	(val := self at:aKey) notNil ifTrue:[
	    ^ aBlock value:val
	]
    ].
    ^ nil

    "
     Smalltalk at:#fooBar ifPresent:[:what | Transcript showCR:what].
     Smalltalk at:#Object ifPresent:[:what | Transcript showCR:what].
    "

    "Modified: / 27-12-2011 / 10:14:30 / cg"
!

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

    |oldValue|

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

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

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

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

    "/ for debugging - this is a common mistake,
    "/ to try to access a class by nameString, instead
    "/ of by symbol.

    "/ aKey class == String ifTrue:[self halt].

%{  /* NOCONTEXT */
    RETURN ( __GLOBAL_KEYKNOWN(aKey) );
%}.
    ^ self primitiveFailed
!

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

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

    "Smalltalk keyAtValue:Object"
!

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

    |keys|

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

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

    CachedClasses := nil.

%{  /* NOCONTEXT */
    RETURN ( __GLOBAL_REMOVE(aKey) );
%}.
    ^ self primitiveFailed

!

startBlocks
    ^ StartBlocks
!

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

    |values|

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

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


!Smalltalk class methodsFor:'browsing'!

browseAllCallsOn:aSelectorSymbol
    "{ Pragma: +optSpace }"

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

    UserPreferences systemBrowserClass browseAllCallsOn:aSelectorSymbol

    "
     Smalltalk browseAllCallsOn:#at:put:
    "
!

browseAllSelect:aBlock
    "{ Pragma: +optSpace }"

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

    UserPreferences systemBrowserClass browseAllSelect:aBlock

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

browseChanges
    "{ Pragma: +optSpace }"

    "startup a changes browser"

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

    "
     Smalltalk browseChanges
    "
!

browseClass:aClass
    "{ Pragma: +optSpace }"

    "startup a browser on aClass.
     The broser will only show that class (i.e. be a singleClass-browser).
     See browseInClass: for a full browser, which has aClass selected initially."

    UserPreferences systemBrowserClass browseClass:aClass

    "
     Smalltalk browseClass:Array
    "
!

browseImplementorsMatching:aSelectorSymbolOrMatchPattern
    "{ Pragma: +optSpace }"

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

    UserPreferences systemBrowserClass browseImplementorsMatching:aSelectorSymbolOrMatchPattern

    "
     Smalltalk browseImplementorsOf:#'at:put:'
     Smalltalk browseImplementorsMatching:#'at:*'
    "
!

browseImplementorsOf:aSelectorSymbol
    "{ Pragma: +optSpace }"

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

    UserPreferences systemBrowserClass browseImplementorsOf:aSelectorSymbol

    "
     Smalltalk browseImplementorsOf:#at:put:
    "
!

browseInClass:aClass
    "{ Pragma: +optSpace }"

    "startup a full browser showing aClass.
     The browser will be a full browser with aClass initially selekted.
     See browseClass: for a singleClass browser, which shows only a single class."

    UserPreferences systemBrowserClass openInClass:aClass

    "
     Smalltalk browseInClass:Array
    "
!

browseInClass:aClass selector:selector
    "{ Pragma: +optSpace }"

    "startup a full browser showing aClass>>selector.
     The browser will be a full browser with aClass initially selekted.
     See browseClass: for a singleClass browser, which shows only a single class."

    UserPreferences systemBrowserClass openInClass:aClass selector:selector

    "
     Smalltalk browseInClass:Array selector:#at:
    "
! !


!Smalltalk class methodsFor:'class management'!

changeCategoryOf:aClass to:newCategory
    "change a classes category, add a change record,
     send change notifications"

    |ns oldCategory|

    oldCategory := aClass category.
    oldCategory ~= newCategory ifTrue:[
	aClass category:(newCategory withoutSeparators asSymbol).

	"notify change of category"
	ns := aClass environment ? self.
	ns changed:#organization with:(aClass -> oldCategory).
	ns ~~ self ifTrue:[
	    self changed:#organization with:(aClass -> oldCategory).
	]
    ].

    "
     Smalltalk changeCategoryOf:NewApplication to:#myApplications
    "

    "Modified: / 11.2.2000 / 11:36:27 / cg"
!

defineNameSpace: name private: private imports: imports category: category attributes: annotations
    NameSpace name:name

!

flushCachedClass:aClass
    CachedClasses notNil ifTrue:[
	CachedClasses remove:aClass ifAbsent:[].
    ].
!

flushCachedClasses
    CachedClasses := nil.

    "
     Smalltalk flushCachedClasses
    "
!

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

    |sym cSym names oldName oldNameSym actualName wrongName ns ons|

    aClass isNil ifTrue:[^ self].

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

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

    ns := aClass nameSpace.
    aClass topOwningClass notNil ifTrue:[
	ons := aClass topOwningClass nameSpace
    ].

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

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

    "remove private classes"

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

    "remove class variables"

    names := aClass classVariableString asCollectionOfWords.
    names do:[:name |
	cSym := aClass globalKeyForClassVar:name.
	self at:cSym asSymbol put:nil.

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


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

    ObjectMemory flushInlineCaches.
    ObjectMemory flushMethodCache.

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

    aClass setCategory:#'* removed *'.

"/    self flushCachedClasses.
"/    Class flushSubclassInfo.
    self flushCachedClass:aClass.
    Class flushSubclassInfoFor:aClass superclass.
    Class flushSubclassInfoFor:aClass.

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

    ns ~~ Smalltalk ifTrue:[
	ons notNil ifTrue:[
	    ClassBuilder
		recompileGlobalAccessorsTo:oldNameSym
		in:ons
		except:nil
	].
	(ns notNil and:[ns ~~ ons]) ifTrue:[
	    ClassBuilder
		recompileGlobalAccessorsTo:oldNameSym
		in:ns
		except:nil
	].
    ].

    "Modified: / 18-11-2006 / 17:16:31 / cg"
!

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

    |oldName oldSym newSym names oldCVSym newCVSym value oldNameToNewName
     oldNameSpace newNameSpace oldBaseName newBaseName privateClasses
     oldBaseNameWithoutPrefix newBaseNameWithoutPrefix i1 i2 nm ns subns
     oldMetaclass newMetaclass newCategory|

    "/ check for all intermediate namespaces / owning classes
    i1 := 1.
    i2 := 1.
    ns := self.
    [i2 ~~ 0] whileTrue:[
        i2 := newName indexOfSubCollection:'::' startingAt:i1.
        i2 ~~ 0 ifTrue:[
            nm := newName copyFrom:i1 to:i2-1.
            ns isNameSpace ifTrue:[
                subns := ns at:nm asSymbol ifAbsent:nil.
                subns isNil ifTrue:[
                    self error:'Nonexisting namespace: ',nm.
                    ^ nil.
                ].
            ] ifFalse:[
                subns := ns privateClassesAt:nm asSymbol.
                subns isNil ifTrue:[
                    self error:'Cannot create a namespace below a class'
                ]
            ].
            ns := subns.
            i1 := i2 + 2.
        ].
    ].

    oldName := aClass name.
    oldNameSpace := aClass topNameSpace.
    oldBaseName := aClass nameWithoutNameSpacePrefix.
    oldBaseNameWithoutPrefix := aClass nameWithoutPrefix.
    oldSym := oldName asSymbol.
    privateClasses := aClass privateClassesSorted.

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

    "/ rename the class

    newSym := newName asSymbol.

    "/ change the owning class
    ns isNameSpace ifFalse:[
        aClass isPrivate ifTrue:[
            aClass class setOwningClass:ns.
        ] ifFalse:[
            "/ sigh - must make a PrivateMetaclass from Metaclass
            oldMetaclass := aClass class.
            newMetaclass := PrivateMetaclass new.
            newMetaclass flags:(oldMetaclass flags).
            newMetaclass setSuperclass:(oldMetaclass superclass).
            newMetaclass instSize:(oldMetaclass instSize).
            newMetaclass setInstanceVariableString:(oldMetaclass instanceVariableString).
            newMetaclass setMethodDictionary:(oldMetaclass methodDictionary).
            newMetaclass setSoleInstance:aClass.
            newMetaclass setOwningClass:ns.

            aClass changeClassTo:newMetaclass.
            ObjectMemory flushCaches.
        ]
    ] ifTrue:[
        aClass isPrivate ifTrue:[
            newCategory := aClass topOwningClass category.

            "/ sigh - must make a Metaclass from PrivateMetaclass
            oldMetaclass := aClass class.

            newMetaclass := Metaclass new.
            newMetaclass flags:(oldMetaclass flags).
            newMetaclass setSuperclass:(oldMetaclass superclass).
            newMetaclass instSize:(oldMetaclass instSize).
            newMetaclass setInstanceVariableString:(oldMetaclass instanceVariableString).
            newMetaclass setMethodDictionary:(oldMetaclass methodDictionary).
            newMetaclass setSoleInstance:aClass.

            aClass category:newCategory.
            aClass changeClassTo:newMetaclass.
            ObjectMemory flushCaches.
        ]
    ].

    aClass setName:newSym.

    "/ store it in Smalltalk
    self at:oldSym put:nil.

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

    "/ create new class variables and copy over values

    oldNameToNewName := IdentityDictionary new.

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

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

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

        oldNameToNewName at:oldCVSym put:newCVSym.
    ].

    "/ patch methods literal arrays from oldCVname to newCVname

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

        "/ and also in privateClasses ? ...

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

    aClass addChangeRecordForClassRename:oldSym to:newSym.

    "/ clear the namespace (for namespace query to work)
    aClass setEnvironment:nil.
    newNameSpace := aClass topNameSpace.

    privateClasses size > 0 ifTrue:[
        "/ must rename privateClasses as well
        Class withoutUpdatingChangesDo:[
            privateClasses do:[:aPrivateClass |
                self renameClass:aPrivateClass
                     to:(newSym , '::' , aPrivateClass nameWithoutPrefix).

                Transcript showCR:'recompiling methods in ''' , newNameSpace name , ''' accessing ''' , oldName , '::' , aPrivateClass nameWithoutPrefix , ''' ...'.
                aClass theNonMetaclass recompileMethodsAccessingGlobal:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol.
                aClass theMetaclass recompileMethodsAccessingGlobal:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol.
                aClass theNonMetaclass recompileMethodsAccessingGlobal:(aPrivateClass nameWithoutPrefix) asSymbol.
                aClass theMetaclass recompileMethodsAccessingGlobal:(aPrivateClass nameWithoutPrefix) asSymbol.
"/                ClassBuilder
"/                    recompileGlobalAccessorsTo:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol
"/                    in:newNameSpace
"/                    except:nil.
            ]
        ]
    ].

    oldNameSpace ~~ newNameSpace ifTrue:[

        "/ all those referencing the class from the old nameSpace
        "/ must be recompiled ...
        "/ (to now access the global from smalltalk)

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

            ClassBuilder
                recompileGlobalAccessorsTo:oldName asSymbol
                in:oldNameSpace
                except:nil.
        ].

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

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

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

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

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

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

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

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

    aClass changed:#definition.
    "/ because of the change of my superclasses name ...
    aClass allSubclassesDo:[:subClass |
        subClass changed:#definition.
    ].
    "/ because of the change of my superclasses name ...
    aClass subclassesDo:[:subClass |
        subClass addChangeRecordForClass:subClass.
    ].
    self changed:#definition.
    self changed:#classRename with:(Array with:aClass with:oldName).

    "Created: / 29-10-1995 / 19:58:32 / cg"
    "Modified: / 18-06-1996 / 14:20:50 / stefan"
    "Modified: / 05-09-2006 / 12:52:25 / cg"
! !


!Smalltalk class methodsFor:'copying'!

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

    ^ self

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

deepCopyUsing:aDictionary postCopySelector:postCopySelector
    "return a deep copy of the receiver.
     Redefined to return the receiver - there is only one Smalltalk dictionary"

    ^ self

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

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

    ^ self

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

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

    ^ self

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


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

compileTrace:aBoolean
    "dump generated inline code (NOOP if VM was compiled without the trace-debug option)"
%{
    extern char __compileTrace__;

    __compileTrace__ = (aBoolean == true) ? 1 : 0;
%}
    "
     Smalltalk compileTrace:true
     Smalltalk compileTrace:false
    "
!

debugBreakPoint
    "{ Pragma: +optSpace }"

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

exitWithCoreDump
    "{ Pragma: +optSpace }"

    "abort program and dump core"

    OperatingSystem exitWithCoreDump
    "/ never returns

    "Be careful evaluating this
     Smalltalk exitWithCoreDump
    "

!

fatalAbort
    "{ Pragma: +optSpace }"

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

!

fatalAbort:aMessage
    "{ Pragma: +optSpace }"

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

%{
    char *msg;

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

    __fatal0(__context, msg);
    /* NEVER RETURNS */
%}.
    ^ self primitiveFailed
!

ignoreHalt
    "return true, if halts are ignored.
     Usually, this is done in standAlone applications"

    IgnoreHalt isNil ifTrue:[
	^  self isStandAloneApp
    ].
    ^ IgnoreHalt

    "Created: / 18-11-2010 / 11:20:16 / cg"
!

ignoreHalt:aBoolean
    "control if halts are to be ignored;
     usually, this is done in standAlone applications"

    IgnoreHalt := aBoolean

    "
     Smalltalk ignoreHalt:true.
     self halt.
     Smalltalk ignoreHalt:false.
     self halt.
    "

    "Created: / 18-11-2010 / 11:20:27 / cg"
!

vmInstructionTrace:aBoolean
    self halt:'not yet implemented'

    "Modified: / 19-01-2012 / 10:15:35 / cg"
! !


!Smalltalk class methodsFor:'enumerating'!

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

    self allClassesAndMetaclassesDo:aBlock

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

allClassCategories
    "return a set of all class categories in the system"

    |allCategories|

    allCategories := Set new.
    Smalltalk allClassesDo:[:cls |
	|category|

	category := cls category.
	category notNil ifTrue:[
	    allCategories add:category.
	].
    ].

    ^ allCategories.

    "
     Smalltalk allClassCategories
    "

    "Created: / 17.11.2001 / 12:13:09 / cg"
!

allClassesAndMetaclassesDo:aBlock
    "evaluate the argument, aBlock for all classes and metaclasses in the system."

    |already|

    already := IdentitySet new:NumberOfClassesHint*2.
    self allClassesDo:[:eachClass |
	|cls|

	cls := eachClass theNonMetaclass.
	(already includes:cls) ifFalse:[
	    aBlock value:cls.
	    already add:cls.
	].
	cls := cls class.
	(already includes:cls) ifFalse:[
	    aBlock value:cls.
	    already add:cls.
	].
    ].
!

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

    self allClasses do:aBlock

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

allClassesForWhich:filter
    "return a collection with all classes in the system,
     for which filter evaluates to true."

    |collectedClasses|

    collectedClasses := OrderedCollection new.
    self allClassesForWhich:filter do:[:cls |
	collectedClasses add:cls
    ].
    ^ collectedClasses

    "
     Smalltalk
	allClassesForWhich:[:cls | cls name startsWith:'Po']
    "

    "Created: / 10-08-2006 / 12:11:31 / cg"
!

allClassesForWhich:filter do:aBlock
    "evaluate the argument, aBlock for all classes in the system, for which filter evaluates to true."

    self allClassesDo:[:cls |
	(filter value:cls) ifTrue:[ aBlock value:cls ].
    ].

    "
     Smalltalk
	allClassesForWhich:[:cls | cls name startsWith:'Po']
	do:[:aClass | Transcript showCR:aClass name]
    "
!

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

    ^ self allClassesForWhich:[:cls | cls category = aCategory]

    "
     Smalltalk allClassesInCategory:'Views-Basic'
    "

    "Modified: / 10-08-2006 / 12:13:32 / cg"
!

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

    aCategory notNil ifTrue:[
	self allClassesForWhich:[:cls | cls category = aCategory] do:aBlock
    ]

    "
     Smalltalk allClassesInCategory:'Views-Basic' do:[:aClass | Transcript showCR:aClass]
    "

    "Modified: / 09-08-2006 / 17:18:50 / fm"
!

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

    |classes|

    aCategory notNil ifTrue:[
	classes := OrderedCollection new.
	self allClassesInCategory:aCategory do:[:aClass |
	    classes add:aClass
	].
	classes topologicalSort:[:a :b | b isSubclassOf:a].
	classes do:aBlock
    ]

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

    "Modified: / 17.11.2001 / 12:18:15 / cg"
!

allClassesInOrderDo:aBlock
    "evaluate the argument, aBlock for all classes in the system;
     Evaluation order is by inheritance: superclasses come first."

    |already|

    already := IdentitySet new:NumberOfClassesHint.
    self allClassesDo:[:eachClass |
	(already includes:eachClass) ifFalse:[
	    eachClass allSuperclasses reverseDo:[:eachSuperClass |
		(already includes:eachSuperClass) ifFalse:[
		    already add:eachSuperClass.
		    aBlock value:eachSuperClass.
		].
	    ].
	    already add:eachClass.
	    aBlock value:eachClass.
	]
    ].

    "
     Smalltalk allClassesInOrderDo:[:aClass | Transcript showCR:aClass name]
    "
!

allClassesInPackage:aPackageID
    "evaluate the argument, aBlock for all classes a package;
     The order of the classes is not defined.
     The returned collection may include private classes"

    ^ self allClassesForWhich:[:cls | cls package = aPackageID]

    "
     Smalltalk allClassesInPackage:'bosch:dapasx'
    "

    "Created: / 10-08-2006 / 12:14:10 / cg"
    "Modified: / 12-10-2006 / 23:48:43 / cg"
!

allClassesInPackage:aPackageID do:aBlock
    "evaluate the argument, aBlock for all classes a package;
     The order of the classes is not defined."

    ^ self allClassesForWhich:[:cls | cls package = aPackageID] do:aBlock

    "
     Smalltalk allClassesInPackage:'bosch:dapasx' do:[:aClass | Transcript showCR:aClass]
    "

    "Created: / 09-08-2006 / 17:14:17 / fm"
!

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

    ^ self keysDo:aBlock
!

allMethodCategories
    "return a set of all method-categories (protocols) in the system"

    |allCategories|

    allCategories := Set new.
    Smalltalk allClassesDo:[:cls |
	allCategories addAll:cls categories.
    ].

    ^ allCategories.

    "
     Smalltalk allMethodCategories
    "
!

allMethodsDo:aBlock
    "enumerate all methods in all classes"

    Smalltalk allClassesDo:[:eachClass |
	eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
	    aBlock value:mthd
	]
    ].
!

allMethodsWithSelectorDo:aTwoArgBlock
    "enumerate all methods in all classes and evaluate aBlock
     with method and selector as arguments."

    Smalltalk allClassesDo:[:eachClass |
	eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
	    aTwoArgBlock value:mthd value:sel
	]
    ].
!

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

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

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

basicKeys
    "for rel > 5 only"

    self primitiveFailed






!

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

    |work|

%{  /* NOREGISTER - work may not be placed into a register here */
    __GLOBALS_DO(&aBlock, &work);
    RETURN (self);
%}.
    self keysDo:[:aKey |
	aBlock value:(self at:aKey)
    ]
!

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

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

keysAndValuesSelect:selectBlockWith2Args thenCollect:collectBlockWith2Args
    |collected|

    collected := OrderedCollection new.
    self keysAndValuesDo:[:eachKey :eachValue |
	(selectBlockWith2Args value:eachKey value:eachValue) ifTrue:[
	    collected add:(collectBlockWith2Args value:eachKey value:eachValue)
	].
    ].
    ^ collected

    "
     Smalltalk
	keysAndValuesSelect:[:nm :val | (nm startsWith:'Ab') and:[val notNil]]
	thenCollect:[:nm :val | nm]
    "
!

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

%{  /* NOREGISTER - work may not be placed into a register here */
    __GLOBALKEYS_DO(&aBlock, &work);
    RETURN (self);
%}.
    self basicKeys do:[:aKey |
	aBlock value:aKey
    ]
! !


!Smalltalk class methodsFor:'message control'!

silentLoading
    "returns the Silentloading class variable, which globally controls if compilation
     messages are shown on the transcript during a fileIn."

     ^ SilentLoading ? false
!

silentLoading:aBoolean
    "{ Pragma: +optSpace }"

    "allows access to the Silentloading class variable, which controls
     messages (especially during fileIn) onto the transcript.
     You can save a snapshot with this flag set to true, which makes
     the image come up silent. Can also be set, to read in files unlogged."

    |prev|

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

silentlyLoadingDo:aBlock
    "evaluates aBlock with silent loading on - no compilation messages (except errors)
     are shown on the transcript"

    |sav|

    sav := SilentLoading.
    SilentLoading := true.
    aBlock ensure:[ SilentLoading := sav ].
! !


!Smalltalk class methodsFor:'misc accessing'!

beHeadless:aBoolean
    "set/clear the headlessOperation flag."

    HeadlessOperation := aBoolean
!

beSTScript:aBoolean
    "set/clear the isSTScript flag."

    IsSTScript := aBoolean

    "Created: / 06-12-2006 / 16:43:36 / cg"
!

standAloneApp:aBoolean
    "set/clear the StandAlone flag."

    StandAlone := aBoolean
! !


!Smalltalk class methodsFor:'private-system management-packages'!

knownPackages
    <resource: #obsolete>
    self obsoleteMethodWarning.
    ^ KnownPackages ? #()
!

loadExtensionsForPackage:aPackageId
    | extensionsLoaded |

    extensionsLoaded := false.
    ProgrammingLanguage allDo:[:lang|
	extensionsLoaded := extensionsLoaded | (self loadExtensionsForPackage:aPackageId language: lang)
    ].
    ^ extensionsLoaded

    "Modified: / 18-02-2007 / 11:03:26 / cg"
    "Modified: / 02-01-2010 / 10:43:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 04-09-2011 / 09:19:24 / cg"
!

loadExtensionsForPackage:aPackageId language: language
    |mgr packageDirName inStream projectDefinition extensionsFilename mod dir
     extensionsRevisionString extensionsRevisionInfo|

    language supportsExtensionMethods ifFalse:[^false].

    packageDirName := aPackageId copyReplaceAll:$: with:$/.
    packageDirName := self getPackageFileName:packageDirName.

    (packageDirName notNil and:[Class tryLocalSourceFirst]) ifTrue:[
	(self loadExtensionsFromDirectory:packageDirName language: language) ifTrue:[
	    ^ true.
	].
	packageDirName := nil.  "do not try again"
    ].

    "
     if there is a sourceCodeManager, ask it first for the extensions
    "
    (Smalltalk at:#AbstractSourceCodeManager) notNil ifTrue:[
	mgr := AbstractSourceCodeManager managerForPackage: aPackageId
    ].
    mgr notNil ifTrue:[
	extensionsFilename := 'extensions.' , language sourceFileSuffix.

	projectDefinition := ProjectDefinition definitionClassForPackage:aPackageId.
	projectDefinition notNil ifTrue:[
	    mod := aPackageId asPackageId module.
	    dir := aPackageId asPackageId directory.
	    extensionsRevisionString := projectDefinition perform:(mgr nameOfVersionMethodForExtensions) ifNotUnderstood:nil.
	    extensionsRevisionString notNil ifTrue:[
		extensionsRevisionInfo := mgr revisionInfoFromString:extensionsRevisionString inClass:nil.
		extensionsRevisionInfo notNil ifTrue:[
		    extensionsRevisionInfo fileName = extensionsFilename ifFalse:[
			"JV@2011-10-23: following condition is never satisfied for
			 filed-in packages. The whole scheme of extensionVersion_XXX
			 works ONLY for compiled packages as it depends on fact, that
			 extension Init() routine is called AFTER all classes are inited,
			 therefore the extensionVersion_XXX methods from extensions.st
			 overwrites methods coming from package definition class. All this
			 is so tricky and error prone, that we have to come up with better
			 solution!!"
			packageDirName notNil ifTrue:[
			    ^ self loadExtensionsFromDirectory:packageDirName language: language
			] ifFalse:[
			    ^ false
			]
		    ]
		]
	    ].
	    SourceCodeManagerError handle:[:ex |
	    ] do:[
		inStream := mgr streamForExtensionFile:extensionsFilename package:aPackageId directory:dir module:mod cache:true.
	    ].
	].
	inStream isNil ifTrue:[
	    SourceCodeManagerError handle:[:ex |
	    ] do:[
		inStream := mgr getMostRecentSourceStreamForFile:extensionsFilename inPackage:aPackageId.
	    ].
	].
	inStream notNil ifTrue:[
	    Class withoutUpdatingChangeSetDo:[
		inStream fileIn.
	    ].
	    inStream close.
	    VerboseLoading ifTrue:[
		Transcript showCR:('loaded extensions for ',aPackageId,' from repository').
	    ].
	    ^ true
	]
    ].

    packageDirName notNil ifTrue:[
	^ self loadExtensionsFromDirectory:packageDirName language: language
    ].
    ^ false

    "Created: / 02-01-2010 / 10:41:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-03-2011 / 10:03:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-11-2011 / 13:41:29 / cg"
    "Modified: / 23-10-2011 / 19:35:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

loadExtensionsFromDirectory:packageDirOrString

    | extensionsLoaded |
    extensionsLoaded := false.
    ProgrammingLanguage allDo:
	[:lang|
	extensionsLoaded := extensionsLoaded | (self loadExtensionsFromDirectory: packageDirOrString language: lang)].
    ^extensionsLoaded

    "Modified: / 02-01-2010 / 10:40:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

loadExtensionsFromDirectory:packageDirOrString language: language
    |packageDir f|

    packageDir := packageDirOrString asFilename.

    f := packageDir / ('extensions.' , language sourceFileSuffix).
    f exists ifTrue:[
        Class withoutUpdatingChangeSetDo:[
            f fileIn.
        ].
        VerboseLoading ifTrue:[
            Transcript showCR:('loaded extensions: ' , f pathName).
        ].
        ^ true
    ].
    ^ true"/false

    "Created: / 02-01-2010 / 10:38:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-11-2011 / 13:41:19 / cg"
    "Modified: / 31-01-2013 / 11:33:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

loadPackage:aPackageStringArg asAutoloaded:doLoadAsAutoloaded
    "make certain, that some particular package is loaded into the system.
     Return true on success, false otherwise."

    |packageId packageString packageDir def sourceCodeManager|

    packageId := aPackageStringArg asPackageId.
    packageString := packageId string.

    "if I am here, so must my package"
    packageString = 'stx:libbasic' ifTrue:[^ true].

    "/ if there is a projectDefinition, let it load itself...
    def := packageId projectDefinitionClass.
    (def notNil and:[def isLoaded]) ifTrue:[
        def loadAsAutoloaded:doLoadAsAutoloaded.
        ^ true.
    ].

    packageDir := self packageDirectoryForPackageId:packageId.
    packageDir isNil ifTrue:[
        (packageString includes:$:) ifFalse:[
            "/ assume stx
            packageDir := self packageDirectoryForPackageId:('stx:',packageString).
        ].
    ].

    (self
        loadPackage:packageString
        fromDirectory:packageDir
        asAutoloaded:doLoadAsAutoloaded) ifTrue: [^ true].

    AbstractSourceCodeManager notNil ifTrue:[
        sourceCodeManager := AbstractSourceCodeManager sourceCodeManagerForPackage: packageString.
        sourceCodeManager notNil ifTrue:[
            ^ sourceCodeManager loadPackageWithId: packageString fromRepositoryAsAutoloaded: doLoadAsAutoloaded
        ].
    ].

    ^ false

    "
     Smalltalk loadPackageWithId:'stx:libbasic'
     Smalltalk loadPackageWithId:'stx:goodies/persistency'
     Smalltalk loadPackageWithId:'exept:ctypes'
    "

    "Modified: / 16-11-2010 / 17:42:49 / cg"
!

loadPackage:packageId fromAllSourceFilesInDirectory:aDirectory
    "load all source files found in aDirectory and treat them like
     a package. Allows for initial import of alien ST-code as a new package.
     Experimental."

    |p t new anyFail repeatCount|

    "/ problem: dependencies.
    "/ solution: repeat twice, so that superclasses are present the second time

    Class packageQuerySignal answer:packageId asSymbol do:[
	|any|

	repeatCount := 0.
	[
	    repeatCount := repeatCount + 1.
	    anyFail := false.
	    aDirectory directoryContents do:[:file |
		|fn|

		fn := aDirectory / file.
		(fn hasSuffix:'st') ifTrue:[
		    Metaclass confirmationQuerySignal answer:false
		    do:[
			Error
			    handle:[:ex |
				anyFail := true
			    ]
			    do:[
				(self fileIn:fn) ifFalse:[
				    anyFail := true
				] ifTrue:[
				    any := true.
				]
			    ]
		    ]
		]
	    ].
	    any ifFalse:[
		^ false "/ no file found
	    ]
	] doWhile:[anyFail and:[repeatCount<2]].
    ].

    new := (p := Project projectWithId:packageId) isNil.
    new ifTrue:[ p := Project new].

    p name:packageId.
    p directory:aDirectory.
    p package:packageId.
    t := packageId asCollectionOfSubstringsSeparatedByAny:'/\:'.
    p repositoryModule:(t first).
    p repositoryDirectory:(packageId copyFrom:t first size + 2).
    p isLoaded:true.

    new ifTrue:[Project addLoadedProject:p].
    ^ anyFail not
!

loadPackage:packageId fromClassLibrary:aFilename
    "load a package from a compiled classLib.
     Experimental."

    |p t new|

    (self fileIn:aFilename) ifFalse:[
	(self fileInClassLibrary:aFilename) ifFalse:[
	    self warn:'Failed to load the package ', packageId printString.
	    ^ false.
	]
    ].

    new := (p := Project projectWithId:packageId) isNil.
    new ifTrue:[ p := Project new].

    p name:packageId.
    p directory:aFilename directory.
    p package:packageId.
    t := packageId asCollectionOfSubstringsSeparatedByAny:'/\:'.
    p repositoryModule:(t first).
    p repositoryDirectory:(packageId copyFrom:t first size + 2).
    p isLoaded:true.

    new ifTrue:[Project addLoadedProject:p].

    ^ true
!

loadPackage:aPackageString fromDirectory:packageDirOrStringOrNil asAutoloaded:doLoadAsAutoloaded
    "load a package referenced by aPackageString - a string like 'stx:libbasic'.
     The package is either located in packageDirOrStringOrNil, or in the current directory (if nil).
     Answer true, if the load succeeded, false if it failed"

    |packageDir shLibName
     binaryClassLibraryFilename projectDefinitionFilename projectDefinitionClass projectDefinitionClassName silent somethingHasBeenLoaded
     loadOK loadErrorOccurred exePath|

    packageDirOrStringOrNil notNil ifTrue:[
        packageDir := packageDirOrStringOrNil asFilename.
    ].
    VerboseLoading ifTrue:[
        silent := false
    ] ifFalse:[
        silent := (SilentLoading or:[ StandAlone ]) or:[ InfoPrinting not ].
    ].

    "For now: have to read the project definition first!!
     The class library may contain subclasses of classes in prerequisite packages -
     so the prerequisite packages have to be loaded first"
    "normally there is a project definiton, use that one to pull in the rest"

    "maybe, it is already in the image - autoloaded"
    projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.

false ifTrue:[
    "if not, file it in ..."
    (projectDefinitionClass isNil and:[packageDir notNil]) ifTrue:[
        projectDefinitionClassName := ProjectDefinition initialClassNameForDefinitionOf:aPackageString.
        "/ try to load the project definition class
        projectDefinitionFilename := (packageDir / projectDefinitionClassName) withSuffix:'st'.
        projectDefinitionFilename exists ifFalse:[
            projectDefinitionFilename := (packageDir / 'source' / projectDefinitionClassName) withSuffix:'st'.
        ].
        projectDefinitionFilename exists ifTrue:[
            Class withoutUpdatingChangesDo:[
                Smalltalk silentlyLoadingDo:[
                    projectDefinitionFilename fileIn.
                ].
            ].
            projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
            projectDefinitionClass notNil ifTrue:[
                projectDefinitionClass loadDirectory:(projectDefinitionFilename asFilename directory)
            ]
        ].
    ].
    projectDefinitionClass notNil ifTrue:[
        projectDefinitionClass autoload.
        somethingHasBeenLoaded := projectDefinitionClass loadAsAutoloaded:doLoadAsAutoloaded.
        (silent not and:[somethingHasBeenLoaded]) ifTrue:[
            Transcript showCR:('Smalltalk [info]: loaded package: ' , aPackageString , ' from project definition').
        ].
        ^ true.
    ].
].

    "/ no project-definition class.

    "Is there a shared library (.dll or .so) ?"
    shLibName := aPackageString asPackageId libraryName asFilename
                        withSuffix:ObjectFileLoader sharedLibrarySuffix.

"/    silent ifFalse:[
"/        Transcript showCR:('looking for binary classLib file: ' , shLibName pathName).
"/    ].
    exePath := OperatingSystem pathOfSTXExecutable asFilename directory.
    binaryClassLibraryFilename := exePath / shLibName.
    binaryClassLibraryFilename exists ifFalse:[
        exePath baseName = 'bin' ifTrue:[
            binaryClassLibraryFilename := exePath directory / 'lib' / shLibName.
        ].
        binaryClassLibraryFilename exists ifFalse:[
            binaryClassLibraryFilename := exePath directory / 'plugin' / shLibName.
            binaryClassLibraryFilename exists ifFalse:[
"/                binaryClassLibraryFilename := Filename currentDirectory / shLibName.
"/                binaryClassLibraryFilename exists ifFalse:[
                    packageDir notNil ifTrue:[
                        binaryClassLibraryFilename := packageDir / shLibName.
                        binaryClassLibraryFilename exists ifFalse:[
                            "/ mhmh - is this a good idea ? (temporary kludge)
                            ExternalAddress pointerSize == 4 ifTrue:[    
                                binaryClassLibraryFilename := packageDir / 'objbc' / shLibName.
                                binaryClassLibraryFilename exists ifFalse:[
                                    binaryClassLibraryFilename := packageDir / 'objvc' / shLibName.
                                ]
                            ] ifFalse:[
                                binaryClassLibraryFilename := packageDir / 'objmingw' / shLibName.
                            ].
                        ]
                    ]
"/                ].
            ].
        ].
        packageDir notNil ifTrue:[
            binaryClassLibraryFilename exists ifFalse:[
                "/ look in package directory
                binaryClassLibraryFilename := packageDir / shLibName.
                binaryClassLibraryFilename exists ifFalse:[
                    ExternalAddress pointerSize == 4 ifTrue:[    
                        binaryClassLibraryFilename := packageDir / 'objbc' / shLibName.
                        binaryClassLibraryFilename exists ifFalse:[
                            binaryClassLibraryFilename := packageDir / 'objvc' / shLibName.
                        ]
                    ] ifFalse:[
                        binaryClassLibraryFilename := packageDir / 'objmingw' / shLibName.
                    ].
                ].
            ].
        ].
    ].

    binaryClassLibraryFilename exists ifTrue:[
        ObjectFileLoader::ObjectFileLoadErrorNotification handle:[:ex |
            loadErrorOccurred := true.
            ex proceedWith:true.
        ] do:[
            loadOK := (ObjectFileLoader loadObjectFile:binaryClassLibraryFilename) notNil.
            "/ loadOK := self loadPackage:aPackageString fromClassLibrary:binaryClassLibraryFilename.
        ].
        loadOK ifTrue:[
            silent ifFalse:[
                Transcript showCR:('loaded package: ' , aPackageString , ' from binary classLib file: ' , binaryClassLibraryFilename pathName).
            ].
            "now, all compiled classes have been loaded.
             keep classes in the package which are autoloaded as autoloaded.
             (so the code below is disabled)"
"/            doLoadAsAutoloaded ifFalse:[
"/                "/ force autoloading...
"/                Smalltalk allClassesDo:[:eachClass |
"/                    eachClass package == aPackageString ifTrue:[eachClass autoload].
"/                ].
"/            ].
            ^ true
        ].
        loadErrorOccurred ifTrue:[
            self breakPoint:#cg.
            projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
            projectDefinitionClass notNil ifTrue:[
                "/ load prerequisites...
                projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
                self breakPoint:#cg.
            ].
        ].
    ].

    packageDir isNil ifTrue:[
        ^ false.
    ].

    "fallback - go through the project definition"
    projectDefinitionClass isNil ifTrue:[
        projectDefinitionClassName := ProjectDefinition initialClassNameForDefinitionOf:aPackageString.
        "/ try to load the project definition class
        projectDefinitionFilename := (packageDir / projectDefinitionClassName) withSuffix:'st'.
        projectDefinitionFilename exists ifFalse:[
            projectDefinitionFilename := (packageDir / 'source' / projectDefinitionClassName) withSuffix:'st'.
        ].
        projectDefinitionFilename exists ifTrue:[
            Class withoutUpdatingChangesDo:[
                Smalltalk silentlyLoadingDo:[
                    projectDefinitionFilename fileIn.
                ].
            ].
            projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
            projectDefinitionClass notNil ifTrue:[
                projectDefinitionClass loadDirectory:(projectDefinitionFilename asFilename directory)
            ]
        ].
    ].
    projectDefinitionClass notNil ifTrue:[
        projectDefinitionClass autoload.
        somethingHasBeenLoaded := projectDefinitionClass loadAsAutoloaded:doLoadAsAutoloaded.
        (silent not and:[somethingHasBeenLoaded]) ifTrue:[
            Transcript showCR:('Smalltalk [info]: loaded package: ' , aPackageString , ' from project definition').
        ].
        ^ true.
    ].

"/ loadAll no longer supported
"/    loadAllFilename := packageDir / 'loadAll'.
"/    loadAllFilename exists ifFalse:[
"/        loadAllFilename := packageDir / 'loadall'.
"/    ].
"/    loadAllFilename exists ifTrue:[
"/        (self loadPackage:aPackageString fromLoadAllFile:loadAllFilename) ifTrue:[
"/            silent ifFalse:[
"/                Transcript showCR:('loaded package: ' , aPackageString , ' from loadAll file: ' , loadAllFilename pathName).
"/            ].
"/            ^ true
"/        ]
"/    ].
"/
"/    packageName := packageDir baseName.

"/ zip-file loading no longer supported
"/  "/ .zip ?
"/    f := (packageDir / packageName) withSuffix:'zip'.
"/    f exists ifTrue:[
"/        (self loadPackage:aPackageString fromZIPArchive:f asAutoloaded:doLoadAsAutoloaded) ifTrue:[
"/            silent ifFalse:[
"/                Transcript showCR:('loaded package: ' , aPackageString , ' from zip file: ' , f pathName).
"/            ].
"/            ^ true
"/        ]
"/    ].

"/ abbrev-file loading no longer supported
"/    "/ abbrev.stc ?
"/    (self loadPackageFromAbbrevFile:aPackageString asAutoloaded:doLoadAsAutoloaded) ifTrue:[
"/        ^ true
"/    ].

"/ any .so-file loading no longer supported
"/    "/ any .so ?  -> load the first one found (maybe not a good idea)
"/    packageDir directoryContentsAsFilenamesDo:[:aFilename |
"/        (aFilename hasSuffix:ObjectFileLoader sharedLibrarySuffix) ifTrue:[
"/            (self loadPackage:aPackageString fromClassLibrary:aFilename) ifTrue:[
"/                silent ifFalse:[
"/                    Transcript showCR:('loaded package: ' , aPackageString , ' from binary classLib file: ' , aFilename pathName).
"/                ].
"/                doLoadAsAutoloaded ifFalse:[
"/                    "/ force autoloading...
"/                    Smalltalk allClassesDo:[:eachClass |
"/                        eachClass package == aPackageString ifTrue:[ eachClass autoload].
"/                    ].
"/                ].
"/                ^ true
"/            ]
"/        ]
"/    ].

"/    "/ source files-file loading no longer supported
"/    "/ however, allow for autoload-stub loaded
"/    doLoadAsAutoloaded ifTrue:[
"/        self
"/            recursiveInstallAutoloadedClassesFrom:packageDir
"/            rememberIn:(Set new)
"/            maxLevels:2
"/            noAutoload:false
"/            packageTop:packageDir
"/            showSplashInLevels:0.
"/    ].

"/    doLoadAsAutoloaded ifFalse:[
"/        "/ source files
"/        (self loadPackage:aPackageString fromAllSourceFilesInDirectory:packageDir) ifTrue:[
"/            silent ifFalse:[
"/                Transcript showCR:('loaded package: ' , aPackageString , ' from source files in:' , packageDir pathName).
"/            ].
"/            ^ true
"/        ].
"/    ].
"/    ^ true

    Transcript showCR:('Smalltalk [info]: no projectDef, dll or loadAll found in: ' , aPackageString).
    ^ false

    "
     Smalltalk loadPackageWithId:'stx:libbasic'
     Smalltalk loadPackageWithId:'stx:goodies/persistency'
     Smalltalk loadPackageWithId:'exept:ctypes'
    "

    "Modified: / 29-07-2011 / 19:55:35 / cg"
!

loadPackage:packageId fromLoadAllFile:aFilename
    <resource: #obsolete>
    "load a package from a loadAll - loader script.
     Experimental."

    |p t new|

    Metaclass confirmationQuerySignal answer:false
    do:[
	(self fileIn:aFilename) ifFalse:[
	    self warn:'Failed to load the package ', packageId printString.
	    ^ false.
	]
    ].

    new := (p := Project projectWithId:packageId) isNil.
    new ifTrue:[ p := Project new].

    p name:packageId.
    p directory:aFilename directory.
    p package:packageId.
    t := packageId asCollectionOfSubstringsSeparatedByAny:'/\:'.
    p repositoryModule:(t first).
    p repositoryDirectory:(packageId copyFrom:t first size + 2).
    p isLoaded:true.

    new ifTrue:[Project addLoadedProject:p].
    ^ true
!

loadPackage:aPackageId fromZIPArchive:f asAutoloaded:doLoadAsAutoloaded
    "load a package from a .zip delivery file.
     Experimental."

    "/ not yet implemented ...
    ^ false
!

loadPackageFromAbbrevFile:aPackageId asAutoloaded:doLoadAsAutoloaded
    <resource: #obsolete>
    |abbrevFile packageDir|

    packageDir := self packageDirectoryForPackageId:aPackageId.
    packageDir isNil ifTrue:[^ false].

    "/ abbrev.stc ?
    abbrevFile := packageDir / 'abbrev.stc'.
    abbrevFile exists ifFalse:[^ false].

    Smalltalk installAutoloadedClassesFrom:abbrevFile pathName.

    doLoadAsAutoloaded ifFalse:[
	"/ force autoloading...
	Smalltalk allClassesInPackage:aPackageId do:[:eachClass | eachClass autoload].
    ].

    self loadExtensionsFromDirectory:packageDir.
    VerboseLoading ifTrue:[
	Transcript showCR:('loaded package: ' , aPackageId , ' from abbrev file: ' , abbrevFile pathName).
    ].
    ^ true

    "Modified: / 04-11-2011 / 13:43:29 / cg"
! !


!Smalltalk class methodsFor:'queries'!

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

    |classes|

    "/ you may wonder, what this while is for, here ...
    "/ the reason is that if we modify the class hierarchy in
    "/ another view (background fileIn), while building up the
    "/ cachedClasses set, this may be flushed (invalidated) by the
    "/ other process in the meanwhile.
    "/ If that happens, we restart the set-building here
    "/
    [(classes := CachedClasses) isNil] whileTrue:[
	CachedClasses := classes := IdentitySet new:NumberOfClassesHint.
	self keysAndValuesDo:[:eachName :eachGlobal |
	    (eachGlobal notNil and:[eachGlobal isBehavior]) ifTrue:[
		"/ sigh - would like to skip over aliases
		"/ but this cannot be done simply by comparing
		"/ the classes name against the store-key
		"/ i.e. cannot do:
		"/      anObject name == sym ifTrue:[
		"/          classes add:anObject
		"/      ]
		"/ because that would lead to ignore all java
		"/ classes, which are stored under a different
		"/ key.

		(eachGlobal name == eachName
		 or:[eachGlobal isJavaClass]) ifTrue:[
		    classes add:eachGlobal
		].
	    ]
	].
	NumberOfClassesHint := classes size.
    ].
    ^ classes

    "
     CachedClasses := nil.
     Smalltalk allClasses

    to get the list sorted by name:

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

    "Modified: / 06-12-2011 / 12:41:42 / cg"
!

allClassesAndMetaclasses
    "return an unordered collection of all classes with their metaclasses in the system."

    |classes|

    classes := IdentitySet new:NumberOfClassesHint*2.
    self allClassesDo:[:eachClass |
	classes add:(eachClass theNonMetaclass).
	classes add:(eachClass theMetaclass).
    ].
    ^ classes
!

allClassesWithAllPrivateClasses
    "return an unordered collection of all classes in the Smalltalk namespace.
     Only globally anchored classes are returned; Namespaces are not included.
     (i.e. anonymous ones have to be aquired by Behavior allSubInstances)"

    ^ self allClasses select:[:aClass |
	    |owner|

	    (aClass isRealNameSpace not)
	    and:[
		owner := aClass topOwningClass.
		(owner ? aClass) nameSpace == Smalltalk
	    ]
      ]

    "
     Smalltalk allClassesWithAllPrivateClasses
    "

    "Modified: / 10-11-2006 / 17:24:00 / cg"
!

allExtensionsForPackage:aProjectID
    |methods|

    methods := OrderedCollection new.
    self allClassesDo:[:eachClass |
	methods addAll:(eachClass extensionsFrom:aProjectID).
    ].
    ^ methods
!

allImplementorsOf:aSelector
    "return a collection of classes which implement the given selector"

    |implementors|

    implementors := OrderedCollection new.
    self allClassesDo:[:cls |
	(cls includesSelector:aSelector) ifTrue:[
	    implementors add:cls.
	].
	(cls class includesSelector:aSelector) ifTrue:[
	    implementors add:cls class.
	].
    ].
    ^ implementors

    "
     Smalltalk allImplementorsOf:#isNil
     (Smalltalk allImplementorsOf:#add:) size
    "

    "Modified: / 07-05-2010 / 10:56:09 / cg"
!

allLoadedProjectIDs

    ^ self allProjectsIdsIncludingUnloadedClasses: false


    "
     Smalltalk allLoadedProjectIDs
    "
!

allProjectIDs

    ^ self allProjectsIdsIncludingUnloadedClasses: true


    "
     Smalltalk allProjectIDs
    "
!

allProjectsIdsIncludingUnloadedClasses: includeUnloadedClasses
    "Returns all projects ids.
     Excludes projects coming from unloaded classes if includeUnloadedClasses is false.
    "

    |allProjects|

    allProjects := Set new.
    self allClassesDo:[:eachClass |
	|cls pkg|

	eachClass isRealNameSpace ifFalse:[
	    (includeUnloadedClasses or:[eachClass isLoaded]) ifTrue:[
		cls := eachClass theNonMetaclass.
		cls isPrivate ifTrue:[
		    cls := cls topOwningClass
		].
		pkg := cls package.
		pkg size > 0 ifTrue:[
		    allProjects add:pkg.
		] ifFalse:[
		    "/ for now, nameSpaces are not in any package;
		    "/ this might change. Then, 0-sized packages are
		    "/ illegal, and the following should be enabled.
		    "/ self halt
		].
		cls isJavaClass ifFalse:[
		    cls instAndClassSelectorsAndMethodsDo:[:sel :mthd |
			allProjects add:mthd package asSymbol.
		    ].
		].
	    ].
	].
    ].
    allProjects := allProjects asOrderedCollection sort.
    ^ allProjects

    "
     Smalltalk allProjectsIdsIncludingUnloadedClasses: true
     Smalltalk allProjectsIdsIncludingUnloadedClasses: false
    "
!

cellAt:aName
    "{ Pragma: +optSpace }"

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

%{  /* NOCONTEXT */
    RETURN ( __GLOBAL_GETCELL(aName) );
%}.
    ^ self primitiveFailed

!

classCategoryCompletion:aPartialCategory
    "given a partial class category name, return an array consisting of
     2 entries: 1st: the best (longest) match
		2nd: collection consisting of matching categories"

    ^ DoWhatIMeanSupport classCategoryCompletion:aPartialCategory inEnvironment:self

    "
     Smalltalk classCategoryCompletion:'Sys'
     Smalltalk classCategoryCompletion:'System'
     Smalltalk classCategoryCompletion:'System-BinaryStorage'
    "

    "Modified: / 10-08-2006 / 13:06:34 / cg"
!

classNamed:aString
    "return the class with name aString, or nil if absent.
     To get to the metaClass, append ' class' to the string.
     To get a nameSpace or private class, prefix the name as required.
     If a private class of an autoloaded class is referenced, the owning class
     will be loaded."

    |cls sym nonMeta idx prefix rest namespace nsNameSymbol|

    "Quick try - if everything is loaded, this will succeed.
     But be careful, to not invent new symbols ..."
    sym := aString asSymbolIfInterned.
    sym notNil ifTrue:[
	cls := self at:sym ifAbsent:nil.
	cls isBehavior ifTrue:[^ cls].
    ].

    (aString endsWith:' class') ifTrue:[
	nonMeta := self classNamed:(aString copyWithoutLast:6).
	nonMeta notNil ifTrue:[
	    ^ nonMeta theMetaclass
	].
    ].

    "no success yet. Try if this is a private class of an autoloaded class"
    cls isNil ifTrue:[
	idx := aString indexOfSubCollection:'::'.
	idx ~~ 0 ifTrue:[
	    prefix := aString copyTo:idx-1.
	    nsNameSymbol := prefix asSymbolIfInterned.
	    nsNameSymbol notNil ifTrue:[
		rest := aString copyFrom:idx+2.
		namespace := self at:prefix asSymbolIfInterned ifAbsent:nil.
		"namespace may be the owner of a private class.
		 NameSpaces and Behaviors have the same protocol"
		[namespace isBehavior] whileTrue:[
		    idx := rest indexOfSubCollection:'::'.
		    idx ~~ 0 ifTrue:[
			prefix := rest copyTo:idx-1.
			rest := rest copyFrom:idx+2.
			"this does an implicit autoload if required"
			namespace := namespace privateClassesAt:prefix.
		    ] ifFalse:[
			namespace isLoaded ifTrue:[
			    cls := namespace privateClassesAt:rest.
			    cls isBehavior ifTrue:[^ cls].
			].
			namespace := nil.   "force exit of loop"
		    ].
		].
	    ].
	].
    ].

    ^ nil

    "
     Smalltalk classNamed:'Object'
     Smalltalk classNamed:'Authentication::BasicAuthenticator::BasicAuthenticationData'
     Smalltalk classNamed:'Authentication::BasicAuthenticator::BasicAuthenticationData class'
     Smalltalk classNamed:'Authentication::BasicAuthenticator'
     Smalltalk classNamed:'fooBar'
     Smalltalk classNamed:'true'
     Smalltalk classNamed:'Object class'
     Smalltalk classNamed:'Metaclass'
     Smalltalk classNamed:'Array'
     Smalltalk classNamed:'Array class'
    "

    "Created: / 24-11-1995 / 17:30:22 / cg"
    "Modified: / 19-06-1996 / 14:22:21 / stefan"
    "Modified: / 23-10-2006 / 18:06:53 / cg"
    "Modified (comment): / 20-08-2011 / 16:43:07 / cg"
!

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

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

    "
     Smalltalk classNames
    "
!

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

    ^ DoWhatIMeanSupport classnameCompletion:aPartialClassName inEnvironment:self
!

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

    ^ DoWhatIMeanSupport classnameCompletion:aPartialClassName inEnvironment:anEnvironment

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

     Smalltalk classnameCompletion:'Arr cl'
     Smalltalk classnameCompletion:'*rray cl'
    "

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

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

    ^ Project defaultNameSpace.

    "Created: / 19-12-1996 / 23:49:25 / cg"
    "Modified: / 17-08-2006 / 14:01:22 / cg"
!

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

    ^ DoWhatIMeanSupport globalNameCompletion:aPartialGlobalName inEnvironment:self match:true

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

    "Created: / 24-11-1995 / 17:24:45 / cg"
    "Modified: / 10-08-2006 / 13:05:39 / cg"
!

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

    <resource:#obsolete>
    self obsoleteMethodWarning:'use #globalNameCompletion:'.
    ^ DoWhatIMeanSupport globalNameCompletion:aPartialGlobalName inEnvironment:self

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

    "Created: / 24-11-1995 / 17:24:45 / cg"
    "Modified: / 10-08-2006 / 13:05:48 / cg"
!

hasClassNamed:aString
    Symbol
	hasInterned:aString
	ifTrue:[:aSymbol | ^ (self at:aSymbol ifAbsent:[ nil ]) isClass ].
    ^ false

    "Created: / 26-08-2009 / 11:43:03 / Jaroslav Havlin <havlij6@fel.cvut.cz>"
    "Modified: / 20-08-2011 / 16:41:31 / cg"
!

hasNameSpaces
    "can be redefined by dummy namespaces/environments, to suppress
     the namespace display in a browser (PocketSmalltalk)"

    ^ true
!

hasNamespaces
    "can be redefined by dummy namespaces/environments, to suppress
     the namespace display in a browser (PocketSmalltalk)"

    <resource:#obsolete>
    ^ true
!

hasSelectorNameSpaces
    "for now return false
     Selector namespaces are being implemented and supported by the VM,
     but not yet fully supported by all tools...
     Therefore, for now, do not generate code which uses this feature."

    ^ false

    "Created: / 05-03-2007 / 13:26:28 / cg"
!

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

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

isBrowserStartable
    ^ false.

    "Created: / 06-10-2006 / 11:46:52 / cg"
!

isNameSpace
    "return true, if the receiver is a nameSpace."

    ^ true

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

isRealNameSpace
    "return true, if the receiver is a nameSpace, but not Smalltalk (which is also a class)."

    ^ false

    "Created: / 10-11-2006 / 17:02:19 / cg"
!

isTopLevelNameSpace
    ^ true
!

isTopLevelNamespace
    "obsolete - use isTopLevelNameSpace"

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #isTopLevelNameSpace'.
    ^ true

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

keyIsClassVariableNameKey:aKey
    |i|

    i := aKey lastIndexOf:$:.
    i ~~ 0 ifTrue:[
	i > 1 ifTrue:[
	    (aKey at:(i-1)) == $: ifFalse:[
		^ true.
	    ].
	].
    ].
    ^ false.

    "
     self keyIsClassVariableNameKey:'foo::bar'
     self keyIsClassVariableNameKey:'foo:bar'
     self keyIsClassVariableNameKey:':bar'
     self keyIsClassVariableNameKey:'::bar'
    "
!

loadedClassNamed:aString
    "Same as #classNamed,
     but a private class of an autoloaded class will not be found."

    |cls sym nonMeta|

    "Quick try - if everything is loaded, this will succeed.
     But be careful, to not invent new symbols ..."
    sym := aString asSymbolIfInterned.
    sym notNil ifTrue:[
	cls := self at:sym ifAbsent:nil.
	cls isBehavior ifTrue:[^ cls].
    ].

    (aString endsWith:' class') ifTrue:[
	nonMeta := self loadedClassNamed:(aString copyWithoutLast:6).
	nonMeta notNil ifTrue:[
	    ^ nonMeta theMetaclass
	].
    ].
    ^ nil

    "
     Smalltalk loadedClassNamed:'Object'
     Smalltalk loadedClassNamed:'Authentication::BasicAuthenticator::BasicAuthenticationData'
     Smalltalk loadedClassNamed:'Authentication::BasicAuthenticator::BasicAuthenticationData class'
     Smalltalk loadedClassNamed:'Authentication::BasicAuthenticator'
     Smalltalk loadedClassNamed:'fooBar'
     Smalltalk loadedClassNamed:'true'
     Smalltalk loadedClassNamed:'Object class'
     Smalltalk loadedClassNamed:'Metaclass'
     Smalltalk loadedClassNamed:'Array'
     Smalltalk loadedClassNamed:'Array class'
    "
!

methodProtocolCompletion:aPartialProtocolName
    "given a partial method protocol name, return an array consisting of
     2 entries: 1st: the best (longest) match
		2nd: collection consisting of matching protocols"

    ^ DoWhatIMeanSupport methodProtocolCompletion:aPartialProtocolName inEnvironment:self

    "
     Smalltalk methodProtocolCompletion:'doc'
     Smalltalk methodProtocolCompletion:'docu'
     Smalltalk methodProtocolCompletion:'documenta'
    "

    "Modified: / 10-08-2006 / 13:05:20 / cg"
!

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

    |tally "{ Class: SmallInteger }" |

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

    "Smalltalk numberOfGlobals"
!

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

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

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

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

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

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

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

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

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

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

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

    |aName sym cls ns|

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

    (aName startsWith:'Smalltalk::') ifTrue:[
	aName := aName copyFrom:12.
	^ self at:(aName asSymbol) ifAbsent:nil.
    ].

    sym := aName asSymbol.

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

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

    "Modified: / 9.7.1999 / 01:18:07 / cg"
!

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

    ^ DoWhatIMeanSupport selectorCompletion:aPartialSymbolName inEnvironment:self
!

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

    ^ DoWhatIMeanSupport selectorCompletion:aPartialSymbolName inEnvironment:anEnvironment

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

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


!Smalltalk class methodsFor:'queries-system'!

dialectName
    ^ #SmalltalkX

    "
     Smalltalk dialectName
    "
!

dialectReleaseVersion
    ^ self versionString

    "
     Smalltalk dialectReleaseVersion
    "
!

isDolphinSmalltalk
    "return false here - this may be useful to write portable
     applications - add #isDolphinSmalltalk to your dolphin,
     returning true there."

    ^ false
!

isSmalltalkMT
    "return false here - this may be useful to write portable
     applications - add #isSmalltalkMT to your smalltalk-MT,
     returning true there."

    ^ false
!

isSmalltalkV
    "return false here - this may be useful to write portable
     applications - add #isSmalltalkV to your smalltalkV,
     returning true there."

    ^ false
!

isSmalltalkX
    "return true here - this may be useful to write portable
     applications - add #isSmalltalkX to your other smalltalks,
     returning false there."

    ^ true
!

isSqueak
    "return false here - this may be useful to write portable
     applications - add #isSqueak to your squeak,
     returning true there."

    ^ false
!

isVisualAge
    "return false here - this may be useful to write portable
     applications - add #isVisualAge to your visualAge,
     returning true there."

    ^ false
!

isVisualWorks
    "return false here - this may be useful to write portable
     applications - add #isVisualWorks to your visualWorks,
     returning true there."

    ^ false
! !


!Smalltalk class methodsFor:'startup'!

browserWindowStartup
    "invoked, when st/x is started as a plugin in a (currently firefox) browser.
     In contrast to squeak (where a single window is used to show the display bitmap),
     the browser window is used as a pseudo root-window for a single aplication window.
     If required, that app must ensure that multiple apps (if any) are setup as a
     multiwindow application.
     Actually, control is transferred to PluginSupport, which is suppoesed to know what to do"

    |windowIDString numericWindowID windowID params idx process|

    idx := CommandLineArguments indexOf:'--browserWindow:'.
    windowIDString := CommandLineArguments at:idx+1.
    numericWindowID := Integer fromString:windowIDString.
    windowID := ExternalAddress newAddress:numericWindowID.

    idx := CommandLineArguments indexOf:'--browserParameters:'.
    idx ~~ 0 ifTrue:[
	params := Dictionary new.
	(CommandLineArguments copyFrom:idx+1) pairWiseDo:[:key :value |
	    params at:key put:value.
	].
    ].

    'browserWindow is: ' errorPrint. windowID errorPrintCR.
    'browserParameters are: ' errorPrint. params errorPrintCR.
    'Display is: ' errorPrint. Display errorPrintCR.

    process := [
	PluginSupport
	    startInBrowserWithWindowID:windowID
	    parameters:params.
    ] newProcess.
    process priority:(Processor userSchedulingPriority).
    process name:'browser start handler'.
    process beGroupLeader.
    process resume.
    process := nil.

    Processor dispatchLoop.
    Smalltalk exit.

    "Modified: / 11-09-2010 / 14:06:59 / cg"
!

displayInitializationDone
    "inform the restart, that the display has been initialized"

    CallbackSignal raiseRequest.
!

executeStartBlocks
    |startBlocks|

    startBlocks := self startBlocks.
    startBlocks notNil ifTrue:[
	'Smalltalk [info]: execute startBlocks...' infoPrintCR.
	startBlocks do:[:aBlock|
	    Error handle:[:ex |
		InfoPrinting == true ifTrue:[
		    'Smalltalk [warning]: error cought in startBlock: ' infoPrint.
		    ex description infoPrintCR.
		    ex infoPrintCR.
		    thisContext fullPrintAll.
		].
	    ] do: aBlock
	].
	startBlocks removeAll.
    ].

    "Created: / 07-01-2012 / 12:58:39 / cg"
!

hideSplashWindow
%{
#ifdef WIN32
    extern void __win32_hideSplashScreen();

    __win32_hideSplashScreen();
#endif
%}
!

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

    |process imageName thisIsARestart idx|

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

    graphicalMode ifTrue:[
	Display isNil ifTrue:[
	    (StartupClass notNil
	    and:[ (StartupClass perform:#isHeadless ifNotUnderstood:false) ]) ifFalse:[
		self openDisplay.
	    ].
	].
    ].

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

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

    idx := CommandLineArguments indexOf:'--browserWindow:'.
    IsPlugin := (idx ~~ 0).
    IsPlugin ifTrue:[
	'Smalltalk [info]: startup browser window...' infoPrintCR.
	self browserWindowStartup.
	"/ not reached
    ].

    Initializing := false.

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

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

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

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

	    ObjectMemory changed:#returnFromSnapshot.
	]

    ] newProcess.

    process priority:(Processor userSchedulingPriority).
    process name:'start block handler'.
    process beGroupLeader.
    process resume.
    process := nil.

    ObjectMemory startBackgroundCollectorAt:5.
    ObjectMemory startBackgroundFinalizationAt:5.

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

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

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

	process := [
	    'Smalltalk [info]: startup process 2 active.' infoPrintCR.
	    StandAlone ifTrue:[
		AbortOperationRequest handle:[:ex |
		    'Smalltalk [info]: aborted - exit.' infoPrintCR.
		    OperatingSystem exit:1
		] do:[
		    ('Smalltalk [info]: call ',StartupSelector,' of ',StartupClass name,' (1)') infoPrintCR.
		    StartupClass perform:StartupSelector withArguments:StartupArguments.
		]
	    ] ifFalse:[
		('Smalltalk [info]: call ',StartupSelector,' of ',StartupClass name,' (2)') infoPrintCR.
		StartupClass perform:StartupSelector withArguments:StartupArguments.
	    ].

	    "/
	    "/ non-GUI apps exit after the startup;
	    "/ assume that GUI apps have created & opened some view ...
	    "/
	    Display isNil ifTrue:[
		'Smalltalk [info]: no Display - exit.' infoPrintCR.
		Smalltalk exit.
	    ].
	    "/
	    "/ GUI apps exit after the last user process has finished
	    "/
	    Display exitOnLastClose:true.
	    Processor exitWhenNoMoreUserProcesses:true.
	] newProcess.
	process priority:(Processor userSchedulingPriority).
	process name:'main'.
	process beGroupLeader.
	process resume.
	process := nil.    "do not refer to process"
    ].

    StandAlone ifTrue:[
	Display notNil ifTrue:[
	    FlyByHelp notNil ifTrue:[
		FlyByHelp start
	    ].
	].
    ].

    "
     if view-classes exist, start dispatching;
     otherwise go into a read-eval-print loop
    "
    ((Display notNil and:[graphicalMode])
     or:[process notNil
     or:[HeadlessOperation
     or:[StandAlone]]]) ifTrue:[
	Processor dispatchLoop.
	"done - the last process finished"
	'Smalltalk [info]: last process finished - exit.' infoPrintCR.
    ] ifFalse:[
	StandAlone ifFalse:[
	    self readEvalPrint
	]
    ].

    self exit

    "Created: / 18-07-1996 / 21:07:39 / cg"
    "Modified: / 09-09-1996 / 17:42:50 / stefan"
    "Modified: / 07-01-2012 / 12:59:23 / cg"
!

openDisplay
    "try to open a display connection.
     If so, also read display- and keyboard.rc"

    |commandName|

    commandName := Smalltalk commandName.
    (commandName, ' [info]: opening display...') infoPrintCR.

    Display isNil ifTrue:[
	Screen notNil ifTrue:[
	    [
		Screen openDefaultDisplay:nil.
	    ] on:Screen deviceOpenErrorSignal do:[:ex|
		('%1 [error]: No display connection to: %2' bindWith:commandName with:ex parameter) errorPrintCR.
		(commandName, ' [info]: Either set the DISPLAY environment variable,') infoPrintCR.
		(commandName, ' [info]: or start smalltalk with a -display argument.') infoPrintCR.
		HeadlessOperation == true ifFalse:[
		    OperatingSystem exit:1.
		].
	    ].

	    Display notNil ifTrue:[
		(self secureFileIn:'display.rc') ifFalse:[
		    "/ 'Smalltalk [warning]: no display.rc found; screen setting might be wrong.' errorPrintCR.
		    (self secureFileIn:'keyboard.rc') ifFalse:[
			"/ 'Smalltalk [warning]: no keyboard.rc found; shortkey setting might be wrong.' errorPrintCR.
		    ]
		]
	    ].
	]
    ]

    "Created: / 06-12-2006 / 15:38:17 / cg"
!

readEvalPrint
    "{ Pragma: +optSpace }"

    (ReadEvalPrintLoop new prompt:'ST> ') readEvalPrintLoop

    "Modified: / 07-12-2006 / 17:35:19 / cg"
!

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

     #earlySystemInstallation is sent for ST80 compatibility

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

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

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

    |deb insp transcript idx|

    "/
    "/ when we arrive here, all objects from our previous life
    "/ have been reloaded - however, some may still contain invalid device
    "/ handles, display information etc.
    "/ also, dynamically loaded modules have not yet been reloaded yet.
    "/ and the concrete OS, concrete FileName etc. are still refering to
    "/ the previous classes.

    Initializing := true.
    AbstractOperatingSystem initializeConcreteClass.

    ImageRestartTime := Timestamp now.

    CommandLine := CommandLineArguments copy.
    CommandLineArguments := CommandLineArguments asOrderedCollection.
    CommandName := CommandLineArguments removeFirst. "/ the command

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

    "/
    "/ start catching SIGSEGV and SIGBUS

    OperatingSystem enableHardSignalInterrupts.

    "/ reinit Filename
    Filename reinitialize.

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

    self flushPathCaches.

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

    self reinitStandardStreams.

    "/
    "/ redirect Transcript to Stderr during startup

    transcript := Transcript.
    Transcript := Stderr.

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

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

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

    ObjectFileLoader notNil ifTrue:[
	ObjectFileLoader reloadAllRememberedObjectFiles.
    ].

    "/
    "/ invalidate all display connections.
    "/ This is required to avoid trouble if someone accesses
    "/ a display during early startup.

    Screen notNil ifTrue:[
	Screen allScreens do:[:aDisplay |
	    aDisplay invalidateConnection
	].
    ].

    ObjectMemory changed:#earlySystemInstallation.

    "/
    "/ reinitialize the Processor - restartable processes
    "/ are now restarted here (but not yet scheduled).
    "/
    Processor reinitialize.

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

    ObjectMemory
	changed:#earlyRestart; changed:#restarted.

    "/
    "/ start catching SIGINT and SIGQUIT

    OperatingSystem enableUserInterrupts.
    OperatingSystem enableCrashSignalInterrupts.
    ObjectMemory restoreGarbageCollectorSettings.

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

    idx := CommandLineArguments indexOf:'--faststart'.
    idx == 0 ifTrue:[
	idx := CommandLineArguments indexOf:'--fastStart'.
    ].
    idx ~~ 0 ifTrue:[
	CommandLineArguments removeAtIndex:idx.
    ] ifFalse:[
	CallbackSignal := QuerySignal new.
	[
	    Class withoutUpdatingChangesDo:[
		(self fileIn:(self commandName , '_r.rc')) ifFalse:[
		    "no _r.rc file where executable is; try default smalltalk_r.rc"
		    self fileIn:'smalltalk_r.rc'
		].
	    ]
	] on:CallbackSignal do:[:ex|
	    "/ now, display and view-stuff works;
	    "/ back to the previous debugging interface

	    Inspector := insp.
	    Debugger := deb.

	    "/ reinstall Transcript, if not changed during restart.
	    "/ if there was no Transcript, go to stderr

	    (transcript notNil and:[Transcript == Stderr]) ifTrue:[
		Transcript := transcript.
	    ].
	    Initializing := false.
	    ex proceed.
	].
	CallbackSignal := nil.
    ].

    "/ reinitialization (restart) of Display is normally performed
    "/ in the restart script. If this has not been run for some reason,
    "/ do in now.
    Initializing ifTrue:[
	Display notNil ifTrue:[
	    [
		Display reinitializeFor:Screen defaultDisplayName.
	    ] on:Screen deviceOpenErrorSignal do:[
		'Smalltalk [error]: Cannot restart connection to: ' errorPrint.
		Screen defaultDisplayName errorPrintCR.
		OperatingSystem exit:1.
	    ].
	].
	"/ now, display and view-stuff works;
	"/ back to the previous debugging interface

	Inspector := insp.
	Debugger := deb.

	"/ reinstall Transcript, if not changed during restart.
	"/ if there was no Transcript, go to stderr

	(transcript notNil and:[Transcript == Stderr]) ifTrue:[
	    Transcript := transcript.
	].
	Initializing := false.
    ].
    Screen notNil ifTrue:[
	"clean up leftover screens (and views) that haven't been reopened.
	 Operate on a copy, since brokenConnection removes us from AllScreens"
	Screen allScreens copy do:[:eachDisplay |
	    eachDisplay isOpen ifFalse:[
		'Smalltalk [info]: cannot reopen secondary display: ' errorPrint.
		eachDisplay errorPrintCR.
		eachDisplay cleanupAfterDispatch; brokenConnection.
	    ]
	].
    ].

    deb := insp := transcript := nil.   "avoid dangling refs"
    (StartupClass perform:#keepSplashWindowOpen ifNotUnderstood:[false]) ifFalse:[
	self hideSplashWindow.   "/ if there is one, it's now time to hide it
    ].
    self mainStartup:true

    "Modified: / 03-08-1999 / 09:42:21 / stefan"
    "Modified: / 29-07-2011 / 17:58:23 / cg"
!

showSplashMessage:aString
    "put the message into the splash screen (if there is one).
     Use this for messages during startup"

    self showSplashMessage:aString color:nil.
!

showSplashMessage:aMessageStringOrNil color:rgbValueOrNil
    "put the message into the splash screen (if there is one)."

%{
#ifdef WIN32
    extern void __win32_splashMessage();
    char *msg = (char *)0;
    int clr = 0;

    if (__isStringLike(aMessageStringOrNil)) {
	msg = __stringVal(aMessageStringOrNil);
    }
    if (__isSmallInteger(rgbValueOrNil)) {
	clr = __intVal(rgbValueOrNil);
	__win32_splashMessageColor(clr);
    }
    __win32_splashMessage(msg);
#endif
%}
!

splashInfo:aString
    "like infoPrintCR,
     but in addition put the message into the splash screen (if there is one).
     Use this for info messages during startup"

    aString notNil ifTrue:[ aString infoPrintCR ].
    self showSplashMessage:aString color:nil.
!

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

    |idx graphicalMode arg didReadRCFile|

    graphicalMode := true.
    Initializing := true.

    (StartupClass perform:#keepSplashWindowOpen ifNotUnderstood:[false]) ifFalse:[
        self hideSplashWindow.   "/ if there is one, it's now time to hide it
    ].

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

        didReadRCFile := false.

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

            "/ look for a '--repl' argument
            "/ then go into a read-eval-print loop immediately
            idx := CommandLineArguments indexOf:'--repl'.
            idx ~~ 0 ifTrue:[
                CommandLineArguments removeAtIndex:idx.
                self startSchedulerAndBackgroundCollector.
                self readEvalPrint.
                self exit.
            ].

            "/ look for a '-e filename' or '--execute filename' argument
            "/ this will force fileIn of filename only, no standard startup.

            idx := CommandLineArguments indexOf:'-e'.
            idx == 0 ifTrue:[
                idx := CommandLineArguments indexOf:'--execute'.
                idx == 0 ifTrue:[
                    idx := CommandLineArguments indexOf:'--script'.
                    idx ~~ 0 ifTrue:[
                        SilentLoading := true.
                    ].
                ].
            ].
            idx ~~ 0 ifTrue:[
                |process|

                CommandName := arg := CommandLineArguments at:idx + 1.

                CommandLineArguments
                    removeAtIndex:idx+1; removeAtIndex:idx.

                self startSchedulerAndBackgroundCollector.
                Initializing := false.

                process := [
                    arg = '-' ifTrue:[
                        self fileInStream:Stdin
                               lazy:nil
                               silent:nil
                               logged:false
                               addPath:nil
                    ] ifFalse:[
                        IsSTScript := true.
                        self fileIn:arg.
                    ].
                    self exit.
                ] newProcess.
                process priority:(Processor userSchedulingPriority).
                process name:'main'.
                process beGroupLeader.
                process resume.

                Processor dispatchLoop.
                self exit
            ].

            "/ look for a '-E expr' or '--eval expr' argument
            "/ this will force evaluation of expr only, no standard startup
            idx := CommandLineArguments indexOf:'-E'.
            idx == 0 ifTrue:[
                idx := CommandLineArguments indexOf:'--eval'.
            ].
            idx ~~ 0 ifTrue:[
                arg := CommandLineArguments at:idx + 1.

                CommandLineArguments
                    removeAtIndex:idx+1; removeAtIndex:idx.

                self startSchedulerAndBackgroundCollector.
                Initializing := false.

                self
                    fileInStream:arg readStream
                    lazy:nil
                    silent:nil
                    logged:false
                    addPath:nil.

                self exit
            ].

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

            idx := CommandLineArguments indexOf:'-f'.
            idx == 0 ifTrue:[
                idx := CommandLineArguments indexOf:'--file'.
            ].
            idx ~~ 0 ifTrue:[
                CommandName := commandFile := CommandLineArguments at:idx+1.
                CommandLineArguments removeAtIndex:idx+1; removeAtIndex:idx.
            ].
        ].

        commandFile notNil ifTrue:[
            self startSchedulerAndBackgroundCollector.
            Initializing := false.

            (self secureFileIn:commandFile) ifFalse:[
                ('Smalltalk [error]: startup file "', commandFile, '" not found.') errorPrintCR.
                OperatingSystem exit:1.
            ].
        ] ifFalse:[
            "/ look for <command>.rc
            "/ if not found, read smalltalk.rc (or stxapp.rc for standAlone operation)

	    commandFile := self commandName asFilename withSuffix:'rc'.
	    (didReadRCFile := commandFile exists and:[self secureFileIn:commandFile]) ifFalse:[
		StandAlone ifFalse:[
		    defaultRC := 'smalltalk.rc' "/asFilename
		] ifTrue:[
		    defaultRC := 'stxapp.rc' "/asFilename
		].
		"JV@2011-11-01: DO NOT check defaultRC exist - this prevents smalltalk to
		    to be started with different working directory than stx/projects/smalltalk !!!!!!"

		"/didReadRCFile := defaultRC exists and:[self secureFileIn:defaultRC].
		didReadRCFile := self secureFileIn:defaultRC.
		didReadRCFile ifFalse:[
		    StandAlone ifFalse:[
			'Smalltalk [warning]: no startup rc-file found. Going into line-by-line interpreter.' infoPrintCR.
			graphicalMode := false.
		    ]
		]
	    ].

            "/ ('StandAlone is %1' bindWith:StandAlone) printCR.
            "/ ('Headless is %1' bindWith:HeadlessOperation) printCR.
            "/ ('Display is %1' bindWith:Display) printCR.
            "/ ('Screen is %1' bindWith:Screen) printCR.

            didReadRCFile ifFalse:[
                'private.rc' asFilename exists ifTrue:[ self secureFileIn:'private.rc' ].

                "/
                "/ No RC file found;
                "/ Setup more default stuff
                "/
                StandAlone ifFalse:[
                    "/ its a smalltalk - proceed in interpreter.
                    'Smalltalk [warning]: no startup rc-file found. Going into line-by-line interpreter.' infoPrintCR.
                    graphicalMode := false.
                ].

                "/ setup more defaults...
"/                ObjectMemory startBackgroundCollectorAt:5.
"/                ObjectMemory startBackgroundFinalizationAt:5.
                self addStartBlock:[
                    self startSchedulerAndBackgroundCollector
                ].
            ].
        ].
    ].

    HeadlessOperation ifTrue:[
        graphicalMode := false.
    ].

    self mainStartup:graphicalMode

    "Modified: / 07-08-2011 / 16:55:21 / cg"
!

startSchedulerAndBackgroundCollector
    Processor startTimeSlicing.
    Processor supportDynamicPriorities:true.

    ObjectMemory startBackgroundCollectorAt:5.
    ObjectMemory startBackgroundFinalizationAt:5.
    ObjectMemory backgroundCollectProcess priorityRange:(4 to:9).
    ObjectMemory backgroundFinalizationProcess priorityRange:(4 to:9).

    "Created: / 31-07-2011 / 20:01:33 / cg"
!

startStartBlockProcess
    "at the end of the smalltalk initialization, start all actions that
     were delayed until the ProcessorScheduler is running in a separate process"

    |p|

    p :=
	[
	    self executeStartBlocks.
	] newProcess.

    p
	priority:(Processor userSchedulingPriority);
	name:'start block handler';
	beGroupLeader;
	resume.

    "Modified: / 07-01-2012 / 12:59:01 / cg"
! !


!Smalltalk class methodsFor:'startup and exit'!

addExitBlock:aBlock
    "{ Pragma: +optSpace }"

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

     Better use: ObjectMemory>>#addDependent: and handle the change message
     #aboutToQuit."

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

addImageStartBlock:aBlock
    "{ Pragma: +optSpace }"

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

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

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

addStartBlock:aBlock
    "add a block to be executed in a separate process after
     everything has been initialized. These blocks will
     be executed only once and not be executed after an image restart.
     Initial processes such as the launcher are usually started here
     (see smalltalk.rc / private.rc)."

    "{ Pragma: +optSpace }"

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

    "Created: / 09-09-1996 / 16:46:53 / stefan"
    "Modified (comment): / 18-08-2011 / 09:18:42 / cg"
!

exit
    "{ Pragma: +optSpace }"

    "finish the Smalltalk system"

    self exit:0
    "not reached"

    "Be careful evaluating this
     Smalltalk exit
    "
!

exit:statusInteger
    "{ Pragma: +optSpace }"

    "finish the Smalltalk system"

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

    "Be careful evaluating this
     Smalltalk exit:1
    "
! !


!Smalltalk class methodsFor:'startup queries'!

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

    ^ CommandLine

    "
     Smalltalk commandLine
    "

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

commandLineArgumentNamed:aString
    "extract a named argument from the command line arguments."

    |args index|

    args := self commandLineArguments.
    index := args indexOf:aString.
    (index between:1 and:(args size - 1)) ifTrue:[
	^ args at:index+1
    ].
    ^ nil.

    "
     self commandLineArgumentNamed:'-display'
    "
!

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

    ^ CommandLineArguments

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

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

    ^ CommandName.

    "
     Smalltalk commandName
    "

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

hasNoConsole
    "return true, if this is a console-less application (i.e. I am winstx)
     i.e. there should be no writing to stdout/stderr"

    ^ HasNoConsole ? false

    "
     Smalltalk hasNoConsole
    "
!

isHeadless
    "return true, if this is a headless application
     i.e. no default Display connection is required/used"

    ^ HeadlessOperation ? false

    "
     Smalltalk isHeadless
    "
!

isPlugin
    "return true, if this is a plugin application
     i.e. running in a browserWindow"

    ^ IsPlugin ? false

    "
     Smalltalk isPlugin
    "
!

isSTScript
    "return true, if this is stscript. i.e. the stx scripting engine."

    ^ IsSTScript ? false

    "
     Smalltalk isSTScript
    "

    "Created: / 06-12-2006 / 16:41:21 / cg"
!

isSharedLibraryComponent
    "return true, if this is a shared library component of another application
     i.e. a dll within another app."

    ^ IsSharedLibraryComponent ? false

    "
     Smalltalk isSharedLibraryComponent
    "

    "Created: / 10-08-2006 / 13:09:34 / cg"
!

isSmalltalkDevelopmentSystem
    "return true, if this is a real smalltalk system
     i.e. NOT a stripped or a linked application (such as the webServer)
     and NOT a plugIn (i.e. running in a browser)
     and NOT a sharedLibrary component (i.e. a dll in another app).
     This is used to determine, wether debugging is possible or not."

    self isPlugin ifTrue:[^ false].                     "/ I am a browser-plugin
    self isSharedLibraryComponent ifTrue:[^ false].     "/ I am a COM-ponent
    self isSTScript ifTrue:[^ true ].                   "/ I am stScript
    ^ self isStandAloneApp not.

    "
     Smalltalk isSmalltalkDevelopmentSystem
    "

    "Created: / 10-08-2006 / 13:12:49 / cg"
    "Modified: / 06-12-2006 / 16:42:56 / cg"
!

isStandAloneApp
    "return true, if this is a standAlone application
     i.e. a stripped & linked application (such as the webServer)
     in contrast to a full smalltalk (development) system."

    ^ StandAlone ? false

    "
     Smalltalk isStandAloneApp
    "
!

isStandAloneDebug
    "return true, if this is a standAlone application which
     was started with the -debug option."

    ^ DebuggingStandAlone ? false

    "
     Smalltalk isStandAloneDebug
    "

    "Created: / 19-01-2012 / 10:17:41 / cg"
!

startupArguments
    "return the arguments passed to StartupClass when stx gets started.
     Usually these are nil,
     but saving an image with a non-nil StartupClass/StartupSelector/StartupArgs allows for
     a simple way to configure and create stand-alone applications"

    ^ StartupArguments

    "
     Smalltalk startupArguments
    "
!

startupClass
    "return the class, that will get the start message when smalltalk
     starts and its non-nil. Usually this is nil,
     but saving an image with a non-nil StartupClass/StartupSelector/StartupArgs allows for
     a simple way to configure and create stand-alone applications"

    ^ StartupClass

    "
     Smalltalk startupClass
    "
!

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

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

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

startupSelector
    "return the selector, that will be sent to StartupClass.
     Usually this is nil,
     but saving an image with a non-nil StartupClass/StartupSelector allows for
     a simple way to configure and create stand-alone applications"

    ^ StartupSelector

    "
     Smalltalk startupSelector
    "
!

wasStartedFromImage
    "return true, if this smalltalk was started from an image,
     as opposed to a fresh and clean startup"

    ^ ImageRestartTime notNil

    "
     Smalltalk wasStartedFromImage
    "
! !


!Smalltalk class methodsFor:'system environment'!

language
    "return the language setting"

    ^ Language

    "
     Smalltalk language
    "

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

language:aLanguageSymbol
    "set the language - send out change notifications"

    Language := aLanguageSymbol asSymbol.
    self changed:#Language

    "
     Smalltalk language:#de
    "

    "Modified: / 19-10-2006 / 23:17:29 / cg"
!

language:aLanguageSymbol territory:aTerritorySymbol
    "set the language & territory - send out change notifications"

    Language := aLanguageSymbol asSymbol.
    LanguageTerritory := aTerritorySymbol asSymbol.
    self changed:#Language

    "
     Smalltalk language:#de territory:#de
    "

    "Created: / 19-10-2006 / 22:16:22 / cg"
    "Modified: / 19-10-2006 / 23:17:36 / cg"
!

languageAndTerritory
    "return the language and territory in the format lang-terr (i.e. de-de, en-us)"

    ^ Language , '-' , (LanguageTerritory ? Language)

    "
     Smalltalk languageAndTerritory
    "

    "Created: / 16-01-2011 / 10:19:42 / cg"
!

languageTerritory
    "return the language territory setting"

    ^ LanguageTerritory
!

languageTerritory:aTerritorySymbol
    "set the language territory - send out change notifications"

    LanguageTerritory := aTerritorySymbol asSymbol.
    self changed:#LanguageTerritory

    "
     Time now

     Smalltalk languageTerritory:#us.
     Time now

     Smalltalk languageTerritory:#de.
     Time now
    "

    "Modified: / 19-10-2006 / 23:17:40 / cg"
!

setLanguage:aLanguageSymbol
    "set the language without change notification"

    Language := aLanguageSymbol.
!

setLanguage:aLanguageSymbol territory:aTerritorySymbol
    "set the language & territory - no change notification"

    Language := aLanguageSymbol asSymbol.
    LanguageTerritory := aTerritorySymbol asSymbol.
! !


!Smalltalk class methodsFor:'system management'!

compressSources
    "{ Pragma: +optSpace }"

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

    |newStream table source pos fileName|

    "
     first, find all methods which contain either a string-ref
     or an external string in the 'st.src' file
    "
    newStream := 'src.tmp' asFilename writeStream.

    table := IdentityDictionary new:100.

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

	source notNil ifTrue:[
	    pos := newStream position1Based.
	    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 syncData; close.

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

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

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

    "
     Smalltalk compressSources
    "

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

generateSingleSourceFile
    "{ Pragma: +optSpace }"

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

    |newStream table source pos fileName|

    newStream := 'src.tmp' asFilename writeStream.

    table := IdentityDictionary new:100.

    Method allSubInstancesDo:[:aMethod |
	source := aMethod source.
	source notNil ifTrue:[
	    pos := newStream position1Based.
	    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 syncData; 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"
!

installAutoloadedClassNamed:clsName category:cat package:package revision:revisionOrNil
    "create & install an autoload stub for a class named: clsName,
     to be loaded from package.
     If revisionOrNil is non-nil, set it up to load exactly that revision
     (otherwise, the newest revision will be loaded"

    ^ self
	installAutoloadedClassNamed:clsName
	category:cat
	package:package
	revision:revisionOrNil
	numClassInstVars:nil.
!

installAutoloadedClassNamed:clsName category:cat package:package revision:revisionOrNil numClassInstVars:numClassInstVarsOrNil
    "create & install an autoload stub for a class named: clsName,
     to be loaded from package.
     If revisionOrNil is non-nil, set it up to load exactly that revision
     (otherwise, the newest revision will be loaded"

    |clsSym cls|

    clsSym := clsName asSymbol.

    "/ install if not already compiled-in
    (cls := self at:clsSym) isNil ifTrue:[
	Autoload subclass:clsSym
	    instanceVariableNames:''
	    classVariableNames:''
	    poolDictionaries:''
	    category:cat
	    inEnvironment:Smalltalk.

	cls := self at:clsSym.
	cls isNil ifTrue:[
	    ('Smalltalk [warning]: failed to install ' , clsName , ' as autoloaded.') infoPrintCR.
	] ifFalse:[
	    cls package:package asSymbol.
	    revisionOrNil notNil ifTrue:[
		cls setBinaryRevision:revisionOrNil
	    ]
	]
    ] ifFalse:[
	"/ class already present - however, if unloaded, check for category/package change
	cls isLoaded ifFalse:[
	    package ~= cls package ifTrue:[
		cls withoutUpdatingChangesDo:[
		    cls package:package asSymbol.
		].
	    ].
	    cat ~= cls category ifTrue:[
		cls withoutUpdatingChangesDo:[
		    cls category:cat.
		].
	    ].
	].
    ].
    ^ cls.

    "Created: / 05-11-1998 / 15:10:25 / cg"
    "Modified: / 16-01-2007 / 12:56:18 / cg"

!

installAutoloadedClasses
    "scan all packages and install all classes found there as
     autoloaded. This takes some time ..."

    |dirsConsulted|

    dirsConsulted := Set new.

    "/ along the package-path
    self packagePath do:[:eachPathComponent |
	(dirsConsulted includes:eachPathComponent) ifFalse:[
	    self
		recursiveInstallAutoloadedClassesFrom:eachPathComponent
		rememberIn:dirsConsulted
		maxLevels:15
		noAutoload:false
		packageTop:eachPathComponent
		showSplashInLevels:2.
	]
    ].
    self splashInfo:nil.

    "
     Smalltalk installAutoloadedClasses
    "

    "Created: / 14.2.1997 / 17:32:57 / cg"
    "Modified: / 13.12.1999 / 11:56:50 / cg"
!

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

    |f s|

    f := self getSystemFileName:anAbbrevFilePath.
    f isNil ifTrue:[f := self getPackageFileName:anAbbrevFilePath].

    f notNil ifTrue:[
	f := f asFilename.
	f isDirectory ifTrue:[
	    f := f construct:'abbrev.stc'
	].
	[
	    s := f readStream.
	    self installAutoloadedClassesFromStream:s.
	    s close.
	] on:FileStream openErrorSignal
	do:[:ex| "do nothing"].
    ]

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

    "Modified: / 5.11.1998 / 15:10:51 / cg"
!

installAutoloadedClassesFromAbbrevFile:aFilename
    aFilename readingFileDo:[:abbrevStream |
	self installAutoloadedClassesFromStream:abbrevStream.
    ]

    "Created: / 29-07-2011 / 20:39:21 / cg"
!

installAutoloadedClassesFromStream:anAbbrevFileStream
    "read the given abbreviation file;
     install all classes found there as autoloaded, and also update the
     abbreviation (className-to-fileName mapping) table.
     This takes some time ..."

    |s2 l abbrevFileName info clsName cls abbrev package cat numClassInstVars words w|

    anAbbrevFileStream isFileStream ifTrue:[
	abbrevFileName := anAbbrevFileStream pathName.
	info := 'declared from: ', abbrevFileName.
    ].

    KnownPackages isNil ifTrue:[
	KnownPackages := Set new.
    ].

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

	[anAbbrevFileStream atEnd] whileFalse:[
	    l := anAbbrevFileStream nextLine withoutSeparators.
	    "Skip empty lines and comments"
	    (l notEmpty and:[l first ~= $#]) ifTrue:[
		"/ must do it manually, caring for quoted strings.
"/                words := line asCollectionOfWords.

		words := OrderedCollection new.
		s2 := l readStream.
		[s2 atEnd] whileFalse:[
		    s2 skipSeparators.
		    s2 peek == $' ifTrue:[
			s2 next.
			w := s2 upTo:$'.
			s2 skipSeparators.
		    ] ifFalse:[
			w := s2 upToSeparator
		    ].
		    words add:w
		].
		words size < 3 ifTrue:[
		    'Smalltalk [warning]: bad abbrev entry' errorPrint.
		    anAbbrevFileStream isFileStream ifTrue:[
			' (in ''' errorPrint.
			anAbbrevFileStream pathName errorPrint.
			''')' errorPrint
		    ].
		    ': ' errorPrint. l errorPrintCR
		] ifFalse:[
		    clsName := (words at:1) asSymbol.
		    abbrev := (words at:2).
		    package := (words at:3) asSymbol.
		    cat := words at:4 ifAbsent:nil.
		    numClassInstVars := words at:5 ifAbsent:'0'.
		    numClassInstVars := Integer readFrom:numClassInstVars onError:[0].

"/                KnownPackages add:package.

		    (cat size == 0) ifTrue:[
			cat := 'autoloaded'
		    ].

		    "/ on the fly, update the abbreviations
		    self setFilename:abbrev forClass:clsName package:package.

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

		    cls := self
			installAutoloadedClassNamed:clsName
			category:cat
			package:package
			revision:nil
			numClassInstVars:numClassInstVars.

"/                    info notNil ifTrue:[
"/                        cls setComment:info.
"/                    ].
		]
	    ]
	]
    ]
!

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

    ^ LoadBinaries
!

loadBinaries:aBoolean
    "{ Pragma: +optSpace }"

    "turn on/off loading of binary objects"

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

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

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

    ^ LogDoits

    "
     LogDoits := false
     LogDoits := true
    "
!

logDoits:aBoolean
    "{ Pragma: +optSpace }"

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

    LogDoits := aBoolean

!

makeBytecodeMethods
    "{ Pragma: +optSpace }"

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

    Method allSubInstancesDo:[:aMethod |
	|newMethod|

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

    "
     Smalltalk makeBytecodeMethods
    "

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

recursiveInstallAutoloadedClassesFrom:aTopDirectory
    "scan all packages and install all classes found there as
     autoloaded. This takes some time ..."

    |dirsConsulted|

    dirsConsulted := Set new.

    self
	recursiveInstallAutoloadedClassesFrom:aTopDirectory
	rememberIn:dirsConsulted
	maxLevels:15
	noAutoload:false
	packageTop:nil
	showSplashInLevels:-1.


    "
     Smalltalk recursiveInstallAutoloadedClassesFrom:'..\..\..\cg\private\euler'
    "

    "Created: / 31-07-2012 / 15:27:40 / cg"
!

recursiveInstallAutoloadedClassesFrom:aDirectory rememberIn:dirsConsulted maxLevels:maxLevels noAutoload:noAutoloadIn packageTop:packageTopPath
    "read all abbrev.stc files from and under aDirectory
     and install autoloaded classes.
     If a file called NOAUTOLOAD is found, no classes there and below are installed as autoloaded
     (however, the directories are searched for packages)
     If a file called NOPACKAGES is found, no further searching is done in that directory or below."

    self
	recursiveInstallAutoloadedClassesFrom:aDirectory rememberIn:dirsConsulted
	maxLevels:maxLevels noAutoload:noAutoloadIn packageTop:packageTopPath
	showSplashInLevels:0.

    "
     Smalltalk installAutoloadedClasses
    "

    "Modified: / 17-08-2006 / 16:48:43 / cg"
!

recursiveInstallAutoloadedClassesFrom:aDirectory rememberIn:dirsConsulted
maxLevels:maxLevels noAutoload:noAutoloadIn packageTop:packageTopPath
showSplashInLevels:showSplashInLevels
    "read all abbrev.stc files from and under aDirectory
     and install autoloaded classes.
     If a file called NOAUTOLOAD is found, no classes there and below are installed as autoloaded
     (however, the directories are searched for packages)
     If a file called NOPACKAGES is found, no further searching is done in that directory or below."

    |dir noAutoloadHere dirName pkgName directoryContents|

    maxLevels == 0 ifTrue:[
"/        'Smalltalk [warning]: max directory nesting reached.' infoPrintCR.
	^ self
    ].

    dir := aDirectory asFilename.
    dirName := dir pathName.

    (dirsConsulted includes:dirName) ifTrue:[
	^ self
    ].
    dirsConsulted add:dirName.

    (dir / 'NOPACKAGES') exists ifTrue:[
	^ self.
    ].
    (dir / 'NOSUBAUTOLOAD') exists ifTrue:[
	^ self.
    ].

    noAutoloadHere := noAutoloadIn.
    noAutoloadHere ifFalse:[
	(dir / 'NOAUTOLOAD') exists ifTrue:[
	    noAutoloadHere := true.
	].
    ] ifTrue:[
	(dir / 'AUTOLOAD') exists ifTrue:[
	    noAutoloadHere := false.
	].
    ].

    ((dir / 'loadAll') exists or:[(dir / 'abbrev.stc') exists]) ifTrue:[
	packageTopPath notNil ifTrue:[
	    KnownPackages isNil ifTrue:[
		KnownPackages := Set new.
	    ].
	    pkgName := dirName copyFrom:(packageTopPath asFilename pathName) size + 1 + 1.
	    KnownPackages add:pkgName
	].
    ].

    showSplashInLevels >= 0 ifTrue:[
	self showSplashMessage:('Smalltalk [info]: installing autoloaded classes found under "%1"...'
				bindWith:(dirName contractAtBeginningTo:35)).
    ].

    "/
    "/ suppress installation as autoloaded in this and everything
    "/ below; however, still traverse the directories to find packages ...
    "/
    noAutoloadHere ifFalse:[
	[
	    self installAutoloadedClassesFromAbbrevFile:(dir / 'abbrev.stc').
	] on:FileStream openErrorSignal do:[:ex| "ignore this file"].
    ].

    [
	directoryContents := dir directoryContents asSet.   "asSet to speed up remove"
    ] on:FileStream openErrorSignal do:[:ex|
	"non-accessable directory: we are done"
	^ self
    ].

    directoryContents removeAllFoundIn:#(
			    'objbc'
			    'objvc'
			    'doc'
			    'CVS'
			    'bitmaps'
			    'resources'
			    'source'
			    'not_delivered'
			    'not_ported'
			).
    dir baseName = 'stx' ifTrue:[
	directoryContents removeAllFoundIn:#(
			    'configurations'
			    'include'
			    'rules'
			    'stc'
			    'support'
			).
    ].

    directoryContents do:[:eachFilenameString |
	|f|

	f := dir / eachFilenameString.
	f isDirectory ifTrue:[
	     self
		recursiveInstallAutoloadedClassesFrom:f
		rememberIn:dirsConsulted
		maxLevels:maxLevels-1
		noAutoload:noAutoloadHere
		packageTop:packageTopPath
		showSplashInLevels:showSplashInLevels - 1.
	]
    ].

    showSplashInLevels >= 0 ifTrue:[
	self showSplashMessage:('Smalltalk [info]: installing autoloaded classes from "%1"...'
				bindWith:(dirName contractAtBeginningTo:35)).
    ].

    "
     Smalltalk installAutoloadedClasses
    "

    "Modified: / 31-07-2012 / 15:26:54 / cg"
!

replaceReferencesTo:anObject with:newRef
    "if the receiver refers to the argument, anObject, replace this reference with newRef.
     Return true, if any reference was changed.
     Notice: this does not change the class-reference."

    |toAdd|

    toAdd := OrderedCollection new.
    self keysAndValuesDo:[:key :val |
	(key == anObject) ifTrue:[
	    self shouldImplement.
	].
	(val == anObject ) ifTrue:[
	    toAdd add:(key -> newRef)
	].
    ].
    toAdd do:[:each |
	self at:(each key) put:(each value)
    ].
!

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

    SaveEmergencyImage := aBoolean

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

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

    ^ SystemOrganizer for:nil

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


!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.
     This method can load almost anything which makes sense:
	.st    - source files
	.cls   - binary smalltalk bytecode files
	.so    - binary compiled machine code class libraries
	[.class - java bytecode -- soon to come]"

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

    "
     Smalltalk fileIn:'source/TicTacToe.st'
     Smalltalk fileIn:'binary/TicTacToe.cls'
     Smalltalk fileIn:'binary/TicTacToe.so'
    "

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

fileIn:aFileName inPackage:aPackageID
    "read in the named file in a packages directory."

    |dir|

    dir := self getPackageDirectoryForPackage:aPackageID.
    dir isNil ifTrue:[^ false].

    dir := dir asFilename.
    ^ (self fileIn:(dir construct:aFileName))
      or:[ self fileIn:((dir construct:'source') construct:aFileName) ]
!

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.
     This method can load almost anything which makes sense:
	.st    - source files
	.cls   - binary smalltalk bytecode files
	.so    - binary compiled machine code class libraries
	[.class - java bytecode -- soon to come]"

    |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:[
	    path := self getSystemFileName:fileNameString.
	].
	path isNil ifTrue:[^ false].
	^ (ObjectFileLoader loadObjectFile:path) notNil
    ].

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

    aStream := self systemFileStreamFor:fileNameString.
    aStream isNil ifTrue:[^ false].

    (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.
    ].
    ^ self fileInStream:aStream lazy:lazy silent:silent logged:logged addPath:morePath

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

    "Modified: / 08-09-2006 / 19:21:16 / 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
    "
!

fileIn:aFileName silent:silent
    "read in the named file - look for it in some standard places;
     return true if ok, false if failed.
     If silent is true, no compiler messages are output to the transcript."

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

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

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

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

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

    "
     Smalltalk fileInChanges
    "
!

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

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

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

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

    |path ok|

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

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

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

    "Modified: / 04-11-2011 / 13:42:24 / cg"
!

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

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

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

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

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

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

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

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

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

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

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

    "Created: / 08-01-2007 / 10:06:09 / cg"
!

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

    |classFileName alternativeClassFileName libName newClass ok wasLazy wasSilent sharedLibExtension inStream mgr
     filenameToSet packageDir packageFile bos|

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

    classFileName := Smalltalk fileNameForClass:aClassName.
    (classFileName = aClassName) ifTrue:[
        "/ no abbrev.stc translation for className
        (aClassName includes:$:) ifTrue:[
            "/ a nameSpace name
            alternativeClassFileName := classFileName copyFrom:(classFileName lastIndexOf:$:)+1
        ].
    ].

    classFileName asFilename isAbsolute ifTrue:[
        classFileName asFilename suffix notEmptyOrNil ifTrue:[
            ok := self fileIn:classFileName lazy:loadLazy silent:beSilent.
        ] ifFalse:[
            ok := self fileInSourceFile:classFileName lazy:loadLazy silent:beSilent.
        ]
    ] ifFalse:[
        classFileName := classFileName copyReplaceAll:$: with:$_.
        [
            Class withoutUpdatingChangesDo:[
                |zarFn zar entry|

                ok := false.

                package notNil ifTrue:[
                    packageDir := package asPackageId projectDirectory.
                    "/ packageDir := package asString.
                    "/ packageDir := packageDir copyReplaceAll:$: with:$/.
                    packageDir isNil ifTrue:[
                        packageDir := self packageDirectoryForPackageId:package
                    ].
                ].

                Class packageQuerySignal answer:package do:[
                    "
                     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:(classFileName, sharedLibExtension))
                            ifFalse:[
                                sharedLibExtension ~= '.o' ifTrue:[
                                    ok := self fileInClass:aClassName fromObject:(classFileName, '.o')
                                ].
                                ok ifFalse:[
                                    alternativeClassFileName notNil ifTrue:[
                                        (ok := self fileInClass:aClassName fromObject:(alternativeClassFileName, sharedLibExtension))
                                        ifFalse:[
                                            sharedLibExtension ~= '.o' ifTrue:[
                                                ok := self fileInClass:aClassName fromObject:(alternativeClassFileName, '.o')
                                            ]
                                        ]
                                    ].
                                ].
                            ].
                        ].
                    ].

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

                            zarFn := self getPackageFileName:(packageDir , '/classes.zip').
                            zarFn notNil ifTrue:[
                                zar := ZipArchive oldFileNamed:zarFn.
                                zar notNil ifTrue:[
                                    entry := zar extract:(classFileName , '.cls').
                                    (entry isNil and:[alternativeClassFileName notNil]) ifTrue:[
                                        entry := zar extract:(alternativeClassFileName , '.cls').
                                    ].
                                    entry notNil ifTrue:[
                                        bos := BinaryObjectStorage onOld:(entry asByteArray readStream).
                                        bos next.
                                        bos close.
                                        ok := true
                                    ].
                                ]
                            ]
                        ]
                    ].

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

                        "
                         if that did not work,
                         look for a zipArchive containing a class entry.
                        "
                        ok ifFalse:[
                            zarFn := self getSourceFileName:'source.zip'.
                            zarFn notNil ifTrue:[
                                zar := ZipArchive oldFileNamed:zarFn.
                                zar notNil ifTrue:[
                                    entry := zar extract:(zarFn := classFileName , '.st').
                                    (entry isNil and:[alternativeClassFileName notNil]) ifTrue:[
                                        entry := zar extract:(zarFn := alternativeClassFileName , '.st').
                                    ].
                                    entry notNil ifTrue:[
                                        filenameToSet := zarFn.
                                        ok := self
                                                fileInStream:(entry asString readStream)
                                                lazy:loadLazy
                                                silent:beSilent
                                                logged:false
                                                addPath:nil
                                    ].
                                ]
                            ]
                        ].
                        ok ifFalse:[
                            "
                             if there is a sourceCodeManager, ask it for the classes sourceCode
                            "
                            (mgr := Smalltalk at:#SourceCodeManager) notNil ifTrue:[
                                inStream := mgr getMostRecentSourceStreamForClassNamed:aClassName inPackage:package.
                                inStream notNil ifTrue:[
                                    filenameToSet := nil.
                                    ok := self fileInStream:inStream lazy:loadLazy silent:beSilent logged:false addPath:nil.
                                ]
                            ].
                        ].
                    ].
                ]
            ].
        ] ensure:[
            Compiler compileLazy:wasLazy.
            wasSilent notNil ifTrue:[
                self silentLoading:wasSilent
            ]
        ].
    ].

    ok ifTrue:[
        newClass := self at:(aClassName asSymbol).
        newClass notNil ifTrue:[
            "set the classes name - but do not change if already set"
            filenameToSet notNil ifTrue:[
                newClass getClassFilename isNil ifTrue:[
                    newClass setClassFilename:(filenameToSet asFilename baseName)
                ].
            ].

            doInit ifTrue:[
                newClass initialize
            ]
        ]
    ].

    ^ newClass

    "Created: / 09-01-1998 / 14:40:32 / cg"
    "Modified: / 05-06-1999 / 14:53:01 / cg"
    "Modified: / 16-08-2009 / 14:52:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

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.
     Notice: the argument may not have an extension (by purpose);
	     the sharedLib extension (.dll / .so / .sl) is added here, to
	     make the caller independent of the underlying operatingSystem."

    |path fn|

    ObjectFileLoader isNil ifTrue:[^ false].

    fn := aClassLibraryName asFilename withSuffix:(ObjectFileLoader sharedLibrarySuffix).
    fn := fn pathName.

    path := self getBinaryFileName:fn.
    path isNil ifTrue:[
	path := self getSystemFileName:fn.
    ].
    path isNil ifTrue:[^ false].

    ^ (ObjectFileLoader loadObjectFile:path) notNil

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

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

fileInClassLibrary:aClassLibraryName inPackage:packageID
    "find an object file containing a binary class library in some standard places
     and load it. This installs all of its contained classes.
     Return true if ok, false if not.
     Notice: the argument may not have an extension (by purpose);
	     the sharedLib extension (.dll / .so / .sl) is added here, to
	     make the caller independent of the underlying operatingSystem."

    |baseName handle libraryFilename packagePath|

    ObjectFileLoader isNil ifTrue:[^ false].

    baseName := aClassLibraryName asFilename withSuffix:(ObjectFileLoader sharedLibrarySuffix).
    baseName exists ifTrue:[
	"/ load local file first...
	handle := ObjectFileLoader loadObjectFile:baseName.
    ].
    handle isNil ifTrue:[
	packagePath := self getPackageDirectoryForPackage:packageID.
	packagePath isNil ifTrue:[^ false].
	packagePath := packagePath asFilename.
	libraryFilename := packagePath / baseName.
	libraryFilename exists ifFalse:[
	    libraryFilename := nil.
	    #('objbc' 'objvc') do:[:eachPossibleCompiledCodeDir |
		"in windows, with Borland compiler, DLLs in development environment are under objbc;
		 with MSVC, they are under objvc"
		libraryFilename isNil ifTrue:[
		    libraryFilename := packagePath / eachPossibleCompiledCodeDir / baseName.
		    libraryFilename exists ifFalse:[ libraryFilename := nil ]
		].
	    ].
	].
	(libraryFilename notNil and:[libraryFilename exists]) ifTrue:[
	    handle := ObjectFileLoader loadObjectFile:libraryFilename pathName.
	].
    ].

"/    handle notNil ifTrue:[
"/        Transcript showCR:('    Smalltalk: loaded %1.' bindWith:libraryFilename pathName).
"/    ].
    ^ handle notNil

    "
     Smalltalk fileInClassLibrary:'libtable'
     Smalltalk fileInClassLibrary:'binary/libwidg3'
     Smalltalk fileInClassLibrary:'refactoryBrowser' inPackage:'stx:goodies/refactoryBrowser'
    "

    "Modified: / 08-10-2011 / 00:08:51 / cg"
!

fileInSourceFile:filename lazy:loadLazy silent:beSilent

    "Try all available programming languages"

    ProgrammingLanguage allDo:
	[:lang| | f |
	f := (filename endsWith: ('.' , lang sourceFileSuffix))
		    ifTrue:[filename]
		    ifFalse:[filename , '.' , lang sourceFileSuffix].
	(self fileIn:f lazy:loadLazy silent:beSilent)
		ifTrue:[^true]].
    ^false

    "Created: / 16-08-2009 / 14:45:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

fileInStream:streamArg
    ^ self fileInStream:streamArg lazy:nil silent:nil logged:false addPath:nil
!

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

    |inStream wasLazy wasSilent oldSystemPath oldRealPath|

    inStream := streamArg.
    inStream isNil ifTrue:[^ false].
    inStream := EncodedStream isNil
		    ifTrue:[ inStream ]
		    ifFalse:[ EncodedStream decodedStreamFor:inStream ].

    lazy notNil ifTrue:[wasLazy := Compiler compileLazy:lazy].
    silent notNil ifTrue:[wasSilent := self silentLoading:silent].
    morePath notNil ifTrue:[
	oldSystemPath := SystemPath copy.
	SystemPath addFirst:morePath.
	oldRealPath := RealSystemPath.
	RealSystemPath := nil.
    ].
    [
	(Class updateChangeFileQuerySignal , Class updateChangeListQuerySignal) answer:logged do:[
	    "JV: Changed to give ProgrammingLanguage to choose
	     proper reader"
	    (ProgrammingLanguage forStream: inStream)
		fileInStream: inStream
	]
    ] ensure:[
	morePath notNil ifTrue:[
	    "take care, someone could have changed SystemPath during fileIn!!"
	    (SystemPath copyFrom:2) = oldSystemPath ifTrue:[
		SystemPath := oldSystemPath.
		RealSystemPath := oldRealPath.
	    ] ifFalse:[
		(oldSystemPath includes:morePath) ifFalse:[
		    SystemPath remove:morePath ifAbsent:[].
		].
		RealSystemPath := nil.
	    ].
	].
	lazy notNil ifTrue:[Compiler compileLazy:wasLazy].
	silent notNil ifTrue:[self silentLoading:wasSilent].
	inStream close
    ].
    ^ true

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

    "Modified: / 05-11-1996 / 20:03:35 / cg"
    "Modified: / 16-08-2009 / 11:06:05 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

isClassLibraryLoaded:name
    "return true, if a particular class library is already loaded"

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

    ^ false

    "
     Smalltalk isClassLibraryLoaded:'libstx_libbasic'
     Smalltalk isClassLibraryLoaded:'libstx_libwidg3'
     Smalltalk isClassLibraryLoaded:'libstx_libboss'
    "

    "Modified: / 23-08-2006 / 15:54:46 / 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 ..."

    (self isClassLibraryLoaded: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 various errors during fileIn.
     Return true if ok, false if failed"

    |retVal|

    retVal := false.
    (SignalSet
	with:AbortOperationRequest
	with:TerminateProcessRequest
	with:Parser parseErrorSignal)
	    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."

    self silentlyLoadingDo:[
	self fileIn:aFilename
    ].
! !


!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 the SystemPath.
     Notice: this does not look in the package-specific bitmaps directories."

    |aString|

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

bitmapFromFileNamed:aFileName forClass:aClass
    "backward compatibility:
     search aFileName in some standard places:
     first in the redefinable bitmaps path,
     then in the classes own package directory if existing.
     Return an image or nil."

    ^ self imageFromFileNamed:aFileName forClass:aClass

    "
     Smalltalk bitmapFromFileNamed:'SmalltalkX.xbm' forClass:View
    "
!

bitmapFromFileNamed:aFileName inPackage:aPackage
    "backward compatibility:
     search aFileName in some standard places:
     first in the redefinable bitmaps path,
     then in the package directory if existing.
     Return an image or nil."

    ^ self imageFromFileNamed:aFileName inPackage:aPackage

    "
     Smalltalk bitmapFromFileNamed:'SmalltalkX.xbm' inPackage:'stx:libview'
     Smalltalk bitmapFromFileNamed:'SmalltalkX.xbm' inPackage:'stx:libtool'
    "
!

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
    "obsolete
     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 readStreamOrNil
    ].
    ^ nil
!

fileNameForClass:aClassOrClassName
    "return a actual or expected (or most wanted) filename for aClassOrClassName
     - only the base name (without directory part) and without suffix."

    |cls nonMetaclass nm nameWithPrefix nameWithoutPrefix compatQuery compatPkg |

"/  This was added as an extension of libsvn - should be no longer needed
"/  JV@2012-09-25: but it actually is. The problem is that class filename
"/  is stored in the class itself and used to generate abbrev.stc and
"/  prerequisites in makefiles. But if you renamed such a stc-compiled class,
"/  the filename remains the same, but SVN __ALWAYS__ keep container name
"/  and class name in sync. Therefore build files gets messed up. Indeed, this
"/  should be fixed in code that files-out the package and generates build files.
"/  Certainly a hack, but do not remove this until fixed elsewhere

    compatQuery := Smalltalk classNamed: 'SVN::CompatModeQuery'.
    (compatQuery notNil
      and:[compatQuery isLoaded
        and:[compatQuery query not]]) ifTrue:[
            nm := aClassOrClassName isBehavior
                ifTrue:[aClassOrClassName name]
                ifFalse:[aClassOrClassName].
            nm := nm copyReplaceAll:$: with:$_.
            ^nm
    ].

"/  Same for another query for new libscm...
    compatQuery := Smalltalk classNamed: 'SCMCompatModeQuery'.
    (compatQuery notNil
      and:[compatQuery isLoaded
        and:[(compatPkg := compatQuery query) notNil]]) ifTrue:[
            nm := aClassOrClassName isBehavior
                ifTrue:[aClassOrClassName name]
                ifFalse:[aClassOrClassName].
            cls := Smalltalk at: nm asSymbol.
            (cls notNil and:[cls package == compatPkg]) ifTrue:[
                nm := nm copyReplaceAll:$: with:$_.
                ^nm
            ].
    ].

    aClassOrClassName isBehavior ifTrue:[
        cls := aClassOrClassName.
    ] ifFalse:[
        cls := Smalltalk classNamed:aClassOrClassName.
        cls isNil ifTrue:[
            nameWithPrefix := aClassOrClassName.
            nameWithoutPrefix := (aClassOrClassName copyFrom:(aClassOrClassName lastIndexOf:$:)+1).
        ].
    ].

    cls notNil ifTrue:[
        nonMetaclass := cls theNonMetaclass.
        nm := nonMetaclass getClassFilename.
        nm isNil ifTrue:[
            cls revisionInfo notNil ifTrue:[
                nm := cls revisionInfo fileName.
            ].
        ].
        nm notNil ifTrue:[
            ^ nm asFilename withoutSuffix baseName
        ].
        nameWithPrefix := nonMetaclass name.
        nameWithoutPrefix := nonMetaclass nameWithoutPrefix.
    ].

    CachedAbbreviations notNil ifTrue:[
        nameWithPrefix := nameWithPrefix asSymbol.
        (CachedAbbreviations includesKey:nameWithPrefix) ifTrue:[
            ^ (CachedAbbreviations at:nameWithPrefix) asFilename baseName
        ].
        nameWithoutPrefix := nameWithoutPrefix asSymbol.
        (CachedAbbreviations includesKey:nameWithoutPrefix) ifTrue:[
            ^ (CachedAbbreviations at:nameWithoutPrefix) asFilename baseName
        ].
    ].

    ^ nameWithPrefix copyReplaceAll:$: with:$_

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

     Smalltalk fileNameForClass:HTML::Encoder
     Smalltalk fileNameForClass:OSI::FTAMOperation
     Smalltalk fileNameForClass:'OSI::Foobar'
     Smalltalk fileNameForClass:(Workflow::UnsuccessfulFinishReasons)
     Workflow::UnsuccessfulFinishReasons classFilename
    "

    "Modified: / 06-10-2006 / 16:16:01 / cg"
    "Modified: / 04-12-2012 / 17:44:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 05-12-2012 / 10:47:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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

    CachedAbbreviations isNil ifTrue:[
	self readAbbreviations
    ].
    ^ CachedAbbreviations

    "flush with:

     CachedAbbreviations := nil
    "
    "
     Smalltalk filenameAbbreviations
    "
!

findPackageDirectoryForPackage:aPackage
    "find a packages directory along a number of standard places"

    |relDir|

    relDir := Smalltalk relativePackagePathForPackage:aPackage.
    relDir asFilename isAbsolute ifTrue:[^ relDir].

    ^ Smalltalk getPackageFileName:relDir.

    "
     Smalltalk findPackageDirectoryForPackage:'stx:libview/resources'
     Smalltalk findPackageDirectoryForPackage:'stx:libview'
    "
!

flushPathCaches
    "{ Pragma: +optSpace }"

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

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

    "
     Smalltalk flushPathCaches
    "
!

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

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

    ^ self searchPath:BinaryPath for:aFileName in:BinaryDirName

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

getBitmapFileName:aFileName
    "for backward compatibility:
     search aFileName in some standard places
     (subdirectories named 'bitmaps' in SystemPath);
     Return the pathName or nil if none is found."

    ^ self getBitmapFileName:aFileName forPackage:nil

    "
     Smalltalk getBitmapFileName:'SBrowser.xbm'
    "

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

getBitmapFileName:aFileName forPackage:aPackageIDOrNil
    "for backward compatibility.
     search aFileName in some standard places:
     first in the redefinable bitmaps path,
     then in the package directory if existing.
     Return a path or nil.
     Search order is:
	bitmaps/<pkg>/file
	resources/<pkg>/bitmaps/file
	<pkg>/bitmaps/file
    "

    |f dir packageDir pF|

    ((f := aFileName asString) startsWith:'bitmaps/') ifTrue:[
	f := f copyFrom:('bitmaps/' size + 1).
    ].

    aPackageIDOrNil isNil ifTrue:[
	"/ this will be an error in the future
"/        'Smalltalk [warning]: bitmap file access without package: ' infoPrint. aFileName infoPrintCR.
"/        self halt.

	pF := self searchPath:(self realSystemPath) for:aFileName in:('bitmaps').
	pF notNil ifTrue:[
	    ^ pF.
	].
	f ~= aFileName ifTrue:[
	    pF := self searchPath:(self realSystemPath) for:f in:('bitmaps').
	    pF notNil ifTrue:[
		^ pF.
	    ].
	].
	^ nil
    ].

    dir := self projectDirectoryForPackage:aPackageIDOrNil.
    dir notNil ifTrue:[
	pF := dir asFilename / f.
	pF exists ifTrue:[
	    ^ pF.
	].
	pF := dir asFilename / 'bitmaps' /f.
	pF exists ifTrue:[
	    ^ pF.
	].
    ].

    packageDir := aPackageIDOrNil copyReplaceAll:$: with:$/.

    pF := self searchPath:(self realSystemPath) for:aFileName in:('bitmaps/',packageDir).
    pF notNil ifTrue:[
	^ pF.
    ].
    pF := self searchPath:(self realSystemPath) for:aFileName in:('resources/',packageDir,'/bitmaps').
    pF notNil ifTrue:[
	^ pF.
    ].

    ^ nil

    "
     Smalltalk imageFromFileNamed:'SmalltalkX.xbm' inPackage:'stx:libview'
     Smalltalk imageFromFileNamed:'SmalltalkX.xbm' inPackage:'stx:libtool'
     Smalltalk imageFromFileNamed:'bitmaps/gifImages/garfield.gif' inPackage:'stx:goodies'
     Smalltalk imageFromFileNamed:'CheckOn10_xp.xpm' inPackage:'stx:libwidg'
    "

    "Modified: / 11-10-2006 / 13:53:18 / cg"
!

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

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

    ^ self searchPath:FileInPath for:aFileName in:FileInDirName

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

getPackageDirectoryForPackage:aPackageID
    "search for a particular package; return its directory, or nil.
     Stand alone applications might get nil, if there are only binaries installed."

    |checkForPackageDirectory module packageSubDirectory|

    module := aPackageID asPackageId module.
    packageSubDirectory := aPackageID asPackageId directory.

    checkForPackageDirectory :=
	[:moduleDir |
	    |packageDir|

	    moduleDir isDirectory ifTrue:[
		packageDir := moduleDir / packageSubDirectory.
		packageDir isDirectory ifTrue:[
		    ^ packageDir
		]
	    ].
	].

    self packagePath do:[:aPath |
	|moduleDir|

	moduleDir := aPath asFilename / module.
	checkForPackageDirectory value:moduleDir.
    ].

    ^ nil

    "
     Smalltalk getPackageDirectoryForPackage:(Array package)
     Smalltalk getPackageDirectoryForPackage:'stx:goodies/bitmaps'
     Smalltalk getPackageDirectoryForPackage:'stx:libview'
    "

    "Modified: / 06-10-2006 / 11:49:27 / cg"
!

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

    |f|

    "/ search along packagePath ...
    f := self searchPath:self packagePath for:aFileName in:nil.
    f isNil ifTrue:[
	"/ search under packages-directory along systemPath ...
	f := self searchPath:self realSystemPath for:aFileName in:PackageDirName.
	"/ kludge - allow for stx-directory to be named differently
	f isNil ifTrue:[
	    (aFileName startsWith:('stx' , Filename separator)) ifTrue:[
		f := '../..' asFilename / (aFileName copyFrom:5).
		f exists ifTrue:[
		    ^ f pathName
		].
	    ]
	].
    ].
    (f notNil and:[(f := f asFilename) exists]) ifTrue:[
	^ f pathName
    ].
    ^ nil

    "
     Smalltalk getPackageFileName:'stx/libview/resources/normal.style'
     Smalltalk getPackageFileName:'stx/libview/source.zip'
    "
!

getPackageSourceFileName:filenameWithoutSuffix
    "search aFileName in some standard places and try all available languages"

    ProgrammingLanguage allDo:
	[:lang| | file |
	file := self getPackageFileName: filenameWithoutSuffix , '.' , lang sourceFileSuffix.
	file ifNotNil:[^file]].
    ^nil

    "Created: / 16-08-2009 / 14:44:58 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

getResourceFileName:aFileName
    <resource: #obsolete>

    "search aFileName in some standard places
     (subdirectories named 'resources' in SystemPath);
     return the absolute filename or nil if none is found.
     Obsolete: you must now provide a package argument."

    self obsoleteMethodWarning:'use getResourceFileName:forPackage:'.
    ^ self getResourceFileName:aFileName forPackage:nil

    "
     Smalltalk getResourceFileName:'SystemBrowser.rs'
    "

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

getResourceFileName:aFileName forClass:aClassOrNil
    "search aFileName in some standard places
     (subdirectories named 'resource' in SystemPath);
     and in aClasses package directory.
     Return the absolute filename or nil if none is found."

    |pkgOrNil|

    aClassOrNil notNil ifTrue:[
	pkgOrNil := aClassOrNil package.
    ].
    ^ self getResourceFileName:aFileName forPackage:pkgOrNil.

    "
     Smalltalk getResourceFileName:'de.rs' forClass:SystemBrowser
    "
!

getResourceFileName:aFileName forPackage:aPackageIDOrNil
    "search aFileName in some standard places
     (subdirectories named 'resource' in SystemPath);
     and in a packages directory.
     Return the absolute filename or nil if none is found.
     Search order is:
	resources/<pkg>/file
	<pkg>/resources/file
    "

    |pF f dir packageDir|

    ((f := aFileName asString) startsWith:'resources/') ifTrue:[
	f := aFileName copyFrom:('resources/' size + 1).
    ].

    aPackageIDOrNil isNil ifTrue:[
	"/ this will be an error in the future
"/        'Smalltalk [warning]: resource file access without package: ' infoPrint. aFileName infoPrintCR.
"/        self halt.

	pF := self searchPath:(self realSystemPath) for:aFileName in:('resources').
	pF notNil ifTrue:[
	    ^ pF.
	].
"/        pF := self searchPath:(self realSystemPath) for:aFileName in:('resources/styles').
"/        pF notNil ifTrue:[
"/            ^ pF.
"/        ].
	f ~= aFileName ifTrue:[
	    pF := self searchPath:(self realSystemPath) for:f in:('resources').
	    pF notNil ifTrue:[
		^ pF.
	    ].
"/            pF := self searchPath:(self realSystemPath) for:f in:('resources/styles').
"/            pF notNil ifTrue:[
"/                ^ pF.
"/            ].
	].
	^ nil
    ].

    packageDir := aPackageIDOrNil copyReplaceAll:$: with:$/.

    pF := self searchPath:(self realSystemPath) for:aFileName in:('resources/',packageDir).
    pF notNil ifTrue:[
	^ pF.
    ].

    "/ the following code finds the file within the IDE's own hierarchy
    dir := self projectDirectoryForPackage:aPackageIDOrNil.
    dir notNil ifTrue:[
	dir := dir asFilename.

	(pF := dir / 'resources' / f) exists ifTrue:[ ^ pF name ].
"/        (pF := dir / 'styles' / f) exists ifTrue:[ ^ pF name ].

	"resolve something like: 'ASN/definition.asn1'"
	(pF := dir / f) exists ifTrue:[ ^ pF name ].
    ].

    ^ nil

    "
     Smalltalk getResourceFileName:'SystemBrowser.rs' forPackage:'stx:libtool'
     Smalltalk getResourceFileName:'normal.style' forPackage:'stx:libview'
     Smalltalk getResourceFileName:'styles/normal.style' forPackage:'stx:libview'
     Smalltalk getResourceFileName:'styles/mswindowsXP.style' forPackage:'stx:libview'
     Smalltalk getResourceFileName:'Foo.rs' forPackage:'stx:libview'
    "

    "Modified: / 11-10-2006 / 13:53:43 / cg"
!

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

    |f|

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

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

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

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

getSystemFileName:aFileNameOrString
    "search aFileNameOrString in some standard places;
     return the absolute filename or nil if none is found.
     see comment in Smalltalk>>initSystemPath.
     This should be used to access resources such as bitmaps, doc-files,
     and other help files.
    "

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

    |fn nameString|

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

	^ nameString
    ].

    self realSystemPath do:[:dirName |
	|realName|

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

    "
     Smalltalk getSystemFileName:'doc/online/english/TOP.html'
     Smalltalk getSystemFileName:'bitmaps/SBrowser.xbm'
     Smalltalk getSystemFileName:'bitmaps/foo'
     Smalltalk getSystemFileName:'resources/View.rs'
     Smalltalk getSystemFileName:'resources/iris.style'
    "

    "Modified: / 6.5.1999 / 10:40:37 / cg"
!

imageFromFileNamed:aFileName forClass:aClass
    "search aFileName in some standard places:
     first in the redefinable bitmaps path, then in the classes
     own package directory if existing.
     Return an image or nil."

    |classPackage img|

    classPackage := aClass package.
    img := self imageFromFileNamed:aFileName inPackage:classPackage.
    img isNil ifTrue:[
	"/ try under the goodies package ...
	classPackage ~= 'stx:goodies' ifTrue:[
	    img := self imageFromFileNamed:aFileName inPackage:'stx:goodies'.
	]
    ].
    ^ img

    "
     Smalltalk imageFromFileNamed:'SmalltalkX.xbm' forClass:View
    "
!

imageFromFileNamed:aFileName inPackage:aPackage
    "search aFileName in some standard places:
     first in the redefinable bitmaps path,
     then in the package directory if existing.
     Return an image or nil.
     Search order is:
	bitmaps/<pkg>/file
	resources/<pkg>/bitmaps/file
	<pkg>/bitmaps/file
    "

    |path|

    path := self getBitmapFileName:aFileName forPackage:aPackage.
    path notNil ifTrue:[
	^ Image fromFile:path.
    ].
    ^ nil

    "
     Smalltalk imageFromFileNamed:'SmalltalkX.xbm' inPackage:'stx:libview'
     Smalltalk imageFromFileNamed:'SmalltalkX.xbm' inPackage:'stx:libtool'
     Smalltalk imageFromFileNamed:'bitmaps/gifImages/garfield.gif' inPackage:'stx:goodies'
     Smalltalk imageFromFileNamed:'CheckOn10_xp.xpm' inPackage:'stx:libwidg'
     Smalltalk imageFromFileNamed:'ComboDn_xp.xpm' inPackage:'stx:libwidg'
    "

    "Modified: / 08-09-2006 / 18:02:04 / cg"
!

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

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

    |aStream line words n aClassName|

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

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

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

    ^ nil

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

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

packagePath
    "return a collection of additional directorynames, where smalltalk
     looks for package directories.
     Notice, that directories named 'packages' under the systemPath are
     always consulted - even if not in the packagePath"

    ^ PackagePath

    "
     Smalltalk packagePath
     Smalltalk packagePath addLast:'/opt/smalltalk'
     Smalltalk packagePath addFirst:'/usr/local/otherPackages'
    "
!

packagePath:aPath
    "set the packagePath;
     a collection of additional directorynames, where smalltalk
     looks for package directories.
     Notice, that directories named 'packages' under the systemPath are
     always consulted - even if not in the packagePath"

    PackagePath := aPath asOrderedCollection

    "
     Smalltalk packagePath:#( '.' '/opt/stx' '/opt/smalltalk' '/usr/local/otherPackages')
    "
!

projectDirectoryForClass:aClass
    "given a class, return the path to its package directory;
     nil if not found."

    |pkg|

    pkg := aClass package.
    pkg isNil ifTrue:[^ nil].

    ^ self projectDirectoryForPackage:pkg.

    "
     Smalltalk projectDirectoryForClass:Array
     Smalltalk projectDirectoryForClass:View
    "
!

projectDirectoryForPackage:aPackage
    "given a packageID, return the path to its package directory;
     nil if not found."

    |prj prjDir|

    "/ there might be a package specific resource directory ...
    "/ in the directory, from which the project was loaded
    prj := Project projectWithId:aPackage.
    prj notNil ifTrue:[
	prjDir := prj directory.
    ].
    (prjDir notNil and:[prjDir asFilename exists]) ifFalse:[
	prjDir := Smalltalk getPackageFileName:(aPackage copyReplaceAll:$: with:$/).
    ].
    ^ prjDir

    "
     Smalltalk projectDirectoryForPackage:'stx:libbasic'
     Smalltalk projectDirectoryForPackage:'exept:smartcard'
     Smalltalk projectDirectoryForPackage:'stx'
     Smalltalk projectDirectoryForPackage:'bosch'
    "

    "Modified: / 07-10-2006 / 17:45:58 / cg"
!

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

    "since installAutoloadedClasses also reads all abbreviations, use it"

    CachedAbbreviations := IdentityDictionary new.
    self installAutoloadedClasses.
    ^ CachedAbbreviations.

    "
     Smalltalk readAbbreviations
    "

    "Modified: / 10.12.1999 / 17:48:53 / cg"
!

readAbbreviationsFromStream:aStream
    "read classname to filename mappings from aStream.
     sigh - all for those poor sys5.3 or MSDOS people with short filenames ..."

    self
	withAbbreviationsFromStream:aStream
	do:[:className :abbrev :pkg |
	    self setFilename:abbrev forClass:className package:pkg.
	].

    "Modified: / 13.12.1999 / 11:54:17 / cg"
!

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

    |nP|

    RealSystemPath isNil ifTrue:[
	OperatingSystem isVMSlike ifTrue:[
	    "/ temporary kludge: since we cannot currently
	    "/ check for existance of a name like 'volume:',
	    "/ leave those in the Path without a check.
	    RealSystemPath := SystemPath select:[:dirName |  |f|
		f := dirName asFilename.
		f isVolumeOnly or:[(f isDirectory) and:[f isReadable]]
	    ]
	] ifFalse:[
	    RealSystemPath := SystemPath
		select:[:eachDirectoryName |  |f|
		    f := eachDirectoryName asFilename.
		    (f isDirectory) and:[f isReadable]
		] thenCollect:[:eachDirectoryName|
		    eachDirectoryName asFilename pathName.
		].

	    "/ remove duplicates (but keep order)
	    nP := OrderedCollection new.
	    RealSystemPath do:[:p |
		(nP includes:p) ifFalse:[
		    nP add:p
		]
	    ].
	    (nP includes:'.') ifFalse:[
		nP add:'.'
	    ].
	    RealSystemPath := nP.
	].
    ].
    ^ RealSystemPath
!

recursiveReadAllAbbreviationsFrom:aDirectory
    self recursiveReadAllAbbreviationsFrom:aDirectory maxLevels:15
!

recursiveReadAllAbbreviationsFrom:aDirectory maxLevels:maxLevels
    "read all abbreviations from and under aDirectory."

    |abbrevStream dir directoryContents|

    maxLevels == 0 ifTrue:[
"/        'Smalltalk [warning]: max directory nesting reached.' infoPrintCR.
	^ self
    ].

    dir := aDirectory asFilename.
    dir exists ifFalse:[^ self].

    [
	abbrevStream := (dir / 'abbrev.stc') asFilename readStream.
	self readAbbreviationsFromStream:abbrevStream.
	abbrevStream close.
    ] on:FileStream openErrorSignal do:[:ex| "ignore this file"].

    [
	directoryContents := dir directoryContents.
    ] on:FileStream openErrorSignal do:[:ex|
	"non-accessable directory: we are done"
	^ self
    ].

    directoryContents do:[:aFilename |
	|f|

	(#(
	    'doc'
	    'CVS'
	    'bitmaps'
	    'resources'
	    'source'
	) includes:aFilename) ifFalse:[
	    f := dir / aFilename.
	    f isDirectory ifTrue:[
		self recursiveReadAllAbbreviationsFrom:f maxLevels:maxLevels-1
	    ]
	].
    ].
!

relativePackagePathForPackage:aPackage
    |path|

    PackageToPathMapping notNil ifTrue:[
	path := PackageToPathMapping at:aPackage ifAbsent:nil.
	PackageToPathMapping notNil ifTrue:[^ path].
    ].
    ^ aPackage copyReplaceAll:$: with:$/.

    "
     PackageToPathMapping := Dictionary new.
     PackageToPathMapping at:'expeccoNET:server' put:'expeccoNET_oldVersion/server'.
     PackageToPathMapping at:'expeccoNET:server/ui' put:'expeccoNET_oldVersion/server/ui'.

     Smalltalk relativePackagePathForPackage:'stx:libview/resources'
     Smalltalk relativePackagePathForPackage:'stx:libview'
    "
!

resourceDirectoryForPackage:aPackage
    "given a packageID, return the path to its resource directory;
     nil if not found."

    |prjDir rsrcDir|

    aPackage notNil ifTrue:[
	prjDir := self projectDirectoryForPackage:aPackage.

	(prjDir notNil
	and:[(prjDir := prjDir asFilename) exists
	and:[(rsrcDir := prjDir / 'resources') exists]]) ifTrue:[
	    ^ rsrcDir
	].
	rsrcDir := self getSystemFileName:('resources/' , (aPackage copyReplaceAll:$: with:$/)).
	rsrcDir notNil ifTrue:[
	    ^ rsrcDir asFilename
	].
    ].
    ^ nil

    "
     Smalltalk resourceDirectoryForPackage:'stx:libbasic'
     Smalltalk resourceDirectoryForPackage:'exept:expecco'
     Smalltalk resourceDirectoryForPackage:'exept:smartcard'
    "
!

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

    ^ self resourceFileStreamFor:aFileName forClass:nil
!

resourceFileStreamFor:aFileName forClass:aClassOrNil
    "search aFileName in some standard places and in the classes
     package-resource directory.
     Return a readonly fileStream or nil if not found.
     Searches in subdirectories named 'resource' in SystemPath"

    |aString|

    aString := self getResourceFileName:aFileName forClass:aClassOrNil.
    aString notNil ifTrue:[
	^ aString asFilename readStreamOrNil
    ].
    ^ nil
!

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

    |f|

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

    aPath notNil ifTrue:[
	aPath do:[:dirName |
	    |realName dir|

	    dir := dirName asFilename.
	    aDirName notNil ifTrue:[
		realName := dir / aDirName / aFileName.
	    ] ifFalse:[
		realName := dir / aFileName.
	    ].
	    (realName isReadable) ifTrue:[
		^ realName name
	    ]
	].
    ].

"/ not needed - executing dir is always in SearchPath
"/    realName := Filename currentDirectory / aFileName.
"/    (realName isReadable) ifTrue:[
"/        ^ realName name
"/    ].
    ^ nil.

    "Modified: / 29.4.1999 / 15:06:43 / cg"
!

setFilename:aFileNameString forClass:aClassNameString package:aPackageNameString
    |classNameSymbol oldAbbrev oldPath newPath cls abbrevs|

    CachedAbbreviations isNil ifTrue:[
	CachedAbbreviations := IdentityDictionary new.
    ].

    abbrevs := CachedAbbreviations.
    aClassNameString ~= aFileNameString ifTrue:[
	classNameSymbol := aClassNameString asSymbol.
	oldAbbrev := abbrevs at:classNameSymbol ifAbsent:nil.
	oldAbbrev notNil ifTrue:[
	    oldAbbrev ~= aFileNameString ifTrue:[
		oldAbbrev asFilename isAbsolute
		    ifTrue:[ oldPath := oldAbbrev ]
		    ifFalse:[ oldPath := (self projectDirectoryForPackage:aPackageNameString) asFilename constructString: oldAbbrev ].
		aFileNameString asFilename isAbsolute
		    ifTrue:[ newPath := aFileNameString ]
		    ifFalse:[ newPath := (self projectDirectoryForPackage:aPackageNameString) asFilename constructString: aFileNameString ].

		oldPath ~= newPath ifTrue:[
		    StandAlone ifFalse:[
			('Smalltalk [warning]: autoload path change for: ',aClassNameString,' in package ',aPackageNameString) infoPrintCR.
			('Smalltalk [info]: old: ',oldPath) infoPrintCR.
			('Smalltalk [info]: new: ',newPath) infoPrintCR.
		    ]
		]
	    ].
	    "overwrite old abbreviation with new one,
	     to allow fixing of bad abbrev files"
	].

	cls := self classNamed:aFileNameString.
	cls notNil ifTrue:[
	    cls name ~= aClassNameString ifTrue:[
		"/ ok, there is a class named after this abbrev ...
		"/ this is only a conflict, if the other class has no
		"/ abbreviation (or the same).
		(abbrevs at:(cls name asSymbol) ifAbsent:cls name) = aFileNameString ifTrue:[
		    cls isNameSpace ifFalse:[
			aPackageNameString = cls package ifTrue:[
			    StandAlone ifFalse:[
				('Smalltalk [warning]: conflict for: ' , cls name ,
				    ' in package ' , aPackageNameString) infoPrintCR.
				('Smalltalk [warning]: (' , aClassNameString , ' -> ' , aFileNameString
				    , ')') infoPrintCR
			    ]
			]
		    ]
		]
	    ]
	].
	abbrevs at:classNameSymbol put:aFileNameString.
    ]
!

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

    |aStream line words n aClassName|

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

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

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

    ^ nil

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

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

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

    |aString|

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

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

    |aString|

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

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

    ^ SystemPath

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

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

    SystemPath := aPath.
    self flushPathCaches

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

withAbbreviationsFromStream:aStream do:aBlock
    "read classname to filename mappings from aStream.
     Evaluate aBlock for each tuple:
	class-name , abbrev-name, package
     Sigh - all for those poor sys5.3 or MSDOS people with short filenames..."

    |line lineNo words nm abbrev pkg category size s w|

    lineNo := 0.
    [aStream atEnd] whileFalse:[
	line := aStream nextLine.
	lineNo := lineNo + 1.
	line notEmptyOrNil ifTrue:[
	    (line startsWith:'#') ifFalse:[

		"/ must do it manually, caring for quoted strings.
"/                words := line asCollectionOfWords.

		words := OrderedCollection new.
		s := line readStream.
		[s atEnd] whileFalse:[
		    s skipSeparators.
		    s peek == $' ifTrue:[
			s next.
			w := s upTo:$'.
			s skipSeparators.
		    ] ifFalse:[
			w := s upToSeparator
		    ].
		    words add:w
		].
		words size >= 3 ifTrue:[
		    nm := (words at:1) withoutSeparators.
		    abbrev := (words at:2) withoutSeparators.
		    pkg := (words at:3) withoutSeparators.
		    aBlock argumentCount = 3 ifTrue:[
			aBlock value:nm value:abbrev value:pkg.
		    ] ifFalse:[
			words size >= 4 ifTrue:[
			    category := words at:4.
			].
			words size = 5 ifTrue:[
			    size := (words at:5) asNumber
			].
			aBlock value:nm value:abbrev value:pkg value: category value: size
		    ]
		] ifFalse:[
		    ('Smalltalk [warning]: malformed line ', lineNo printString , ' in ' , (aStream pathName)) infoPrintCR.
		]
	    ]
	]
    ].

    "Modified: / 06-03-2011 / 18:17:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-08-2011 / 21:35:00 / cg"
! !


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

loadPackage:aPackageIdOrPackage
    "make certain, that some particular package is loaded into the system.
     Return true if loaded, false otherwise."

    ^ self loadPackage:aPackageIdOrPackage asAutoloaded:false

    "
     Smalltalk loadPackage:'stx:libbasic'
     Smalltalk loadPackage:'stx:goodies/persistency'
     Smalltalk loadPackage:'cg:cparser'
     Smalltalk loadPackage:'cg:rose'
    "
!

packageDirectoryForPackageId:aPackageId
    "used by classes to find the location of their resource- and bitmap directories.

     Notice that the directory structure is different between the development
     environment (top for packages is ../../../stx) and delivered stand alone executables,
     where the top is specified via a shell environment variable, and is typically ../lib.
     At runtime, Smalltalk knows about the systemPath setting."

    |packageDirName packageDir|

    packageDirName := aPackageId asPackageId string copyReplaceAll:$: with:$/.

    packageDir := self getPackageFileName:packageDirName.
    packageDir isNil ifTrue:[
        ^ nil.
    ].
    ^ packageDir asFilename

    "
     Smalltalk packageDirectoryForPackageId:'stx:libbasic'
     Smalltalk packageDirectoryForPackageId:'stx:goodies/persistency'
     Smalltalk packageDirectoryForPackageId:'exept:ctypes'
    "
!

unloadPackage:aPackageIdOrPackage
    |projectDefinition|

    projectDefinition := aPackageIdOrPackage.
    projectDefinition isProjectDefinition ifFalse:[
        projectDefinition := projectDefinition asPackageId projectDefinitionClass.
        projectDefinition isNil ifTrue:[
            'Smalltalk [info] trying to unload non-existing package: ' infoPrint. aPackageIdOrPackage infoPrintCR.
            ^ self.
        ].
    ].
    projectDefinition unloadPackage.

    "
     Smalltalk loadPackage:'stx:goodies/persistency'
     Smalltalk unloadPackage:'stx:goodies/persistency'
    "
! !


!Smalltalk class methodsFor:'system management-undeclared variables'!

clearUndeclaredVariables
    "remove all undeclared variables"

    (Smalltalk at:#Undeclared) do:[:eachKey |
	Smalltalk removeKey:(self undeclaredPrefix , eachKey) asSymbol.
    ].
    (Smalltalk at:#Undeclared) removeAll.
    Smalltalk removeKey:#Undeclared.
!

undeclaredPrefix
    "the prefix used for undeclared variables"

    ^ 'Undeclared:::'

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


!Smalltalk class methodsFor:'time-versions'!

configuration
    "{ Pragma: +optSpace }"

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

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

    RETURN (__MKSTRING(__getConfigurationString() COMMA_SND));
%}.
    ^ 'unknownOS/unknownCONF:unknownPACK'

    "
     Smalltalk configuration
    "
!

copyrightString
    "{ Pragma: +optSpace }"

    "return a copyright string"

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

    RETURN (__getCopyrightString());
%}.
    ^ self primitiveFailed

    "
     Smalltalk copyrightString
    "
!

distributorString
    "{ Pragma: +optSpace }"

    "return a string describing the distributor of this software"

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

    RETURN (__getDistributorString());
%}.
    ^ 'eXept Software AG, Germany'

    "
     Smalltalk distributorString
    "
!

expirationTime
    "{ Pragma: +optSpace }"

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

    |exp|

%{
    extern unsigned int __getExpirationTime();

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

    "
     Smalltalk expirationTime
    "
!

fullVersionString
    "{ Pragma: +optSpace }"

    "return a full version string"

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

    "
     Smalltalk fullVersionString
    "

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

hello
    "{ Pragma: +optSpace }"

    "return a greeting string"

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

    |proto lang|

    lang := Language.
    (lang == #de) ifTrue:[
	proto := 'Willkommen bei %1 (Version %2 von %3)'
    ] ifFalse:[ (lang == #fr) ifTrue:[
	proto := 'Salut, Bienvenue à %1 (version %2 de %3)'
    ] ifFalse:[ (lang == #it) ifTrue:[
	proto := 'Ciao, benvenuto al %1 (versione %2 di %3)'
    ] ifFalse:[ (lang == #es) ifTrue:[
"/        proto := 'Hola, bienvenida a %1 (versión %2 de %3)'
    ] ifFalse:[ (lang == #es) ifTrue:[
"/        proto := 'Oi, benvindo a %1 (versão %2 de %3)'
    ] ifFalse:[ (lang == #no) ifTrue:[
	proto := 'Hei, verdenmottakelse til %1 (versjon %2 av %3)'
    ]]]]]].

    "/ ... more needed here ...

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

    ^ proto bindWith:('SmallTalk/X' allBold)
		with:(self versionString)
		with:(self versionDate)

    "
     Smalltalk language:#us.
     Smalltalk hello

     Smalltalk language:#de.
     Smalltalk hello

     Smalltalk language:#no.
     Smalltalk hello

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

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

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

    ^ ImageRestartTime

    "
     Smalltalk imageStartTime
     Smalltalk imageRestartTime
    "

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

imageSaveTime
    "{ Pragma: +optSpace }"

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

    ^ ObjectMemory imageSaveTime
!

imageStartTime
    "{ Pragma: +optSpace }"

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

    ^ ImageStartTime

    "
     Smalltalk imageStartTime
     Smalltalk imageRestartTime
    "

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

majorVersionNr
    "{ Pragma: +optSpace }"

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

     ST/X revision Naming is:
	<major>.<minor>.<revision>.<release>"

    ^ 6

    "
     Smalltalk majorVersionNr
    "

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

minorVersionNr
    "{ Pragma: +optSpace }"

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

     ST/X revision Naming is:
	<major>.<minor>.<revision>.<release>"

    ^ 2

    "
     Smalltalk minorVersionNr
    "

    "Modified: / 16-08-2006 / 09:37:25 / cg"
!

releaseIdentification
    "{ Pragma: +optSpace }"

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

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

    RETURN (__getRel());
%}.
    ^ 'ST/X_experimental'

    "
     Smalltalk releaseIdentification
    "
!

releaseNr
    "{ Pragma: +optSpace }"

    "return the release number.
     Now releaseNr is the build number (BUILD_NUMBER from Jenkins)

     ST/X revision Naming is:
        <major>.<minor>.<revision>.<release>"

    |releaseNumber|

    releaseNumber := Smalltalk versionBuildNumber.
    releaseNumber isEmpty ifTrue:[
        ^ 0.
    ].
    ^ releaseNumber

    "
     Smalltalk releaseNr
     Smalltalk versionString
    "

    "Created: / 10-12-1995 / 01:42:19 / cg"
    "Modified: / 10-02-2007 / 14:49:51 / cg"
!

revisionNr
    "{ Pragma: +optSpace }"

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

     ST/X revision Naming is:
	<major>.<minor>.<revision>.<release>"

    ^ 3

    "
     Smalltalk revisionNr
     Smalltalk hello string
    "

    "Modified: / 18-07-2012 / 19:09:42 / cg"
!

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

    ^ ('''' , self timeStampString , '''') paddedTo:80 with:(Character space)
!

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

    aStream nextPutAll:(self timeStamp).

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

timeStampString
    "return a string useful for timestamping a file."

    |dateString|

    dateString := String streamContents:[:s | Date today printOn:s language:#en].  "/ MUST be english !!!!

    ^ ('From Smalltalk/X, Version:' , (Smalltalk versionString) , ' on '
       , dateString , ' at ' , Time now printString
       )
!

versionBuildNumber
    "{ Pragma: +optSpace }"

    "return the executables build number - that's the jenkins build #.
     Empty if not built by jenkins"

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

    RETURN (__MKSTRING(__getBuildNumberString() COMMA_SND) );
%}.
    ^ ''

    "
     Smalltalk versionBuildNumber
    "
!

versionDate
    "{ Pragma: +optSpace }"

    "return the executables build date - that's the date when the smalltalk
     executable was built"

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

    RETURN (__MKSTRING(__getBuildDateString() COMMA_SND) );
%}.
    ^ 'today'

    "
     Smalltalk versionDate
    "
!

versionString
    "{ Pragma: +optSpace }"

    "return the version string"

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


    "
     Smalltalk versionString
    "
!

vmMajorVersionNr
    "{ Pragma: +optSpace }"

    "return the VMs major version number."
%{
    RETURN (__mkSmallInteger(4));
%}.
    ^ 4

    "
     Smalltalk vmMajorVersionNr
    "
! !


!Smalltalk class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.1010 2013-03-05 09:41:57 stefan Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.1010 2013-03-05 09:41:57 stefan Exp $'
!

version_HG

    ^ '$Changeset: <not expanded> $'
!

version_SVN
    ^ '§ Id: Smalltalk.st 10648 2011-06-23 15:55:10Z vranyj1  §'
! !