Autoload.st
author claus
Thu, 09 Mar 1995 00:40:27 +0100
changeset 302 1f76060d58a4
parent 254 d31147d53ff7
child 326 d2902942491d
permissions -rw-r--r--
*** empty log message ***

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

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

Object subclass:#Autoload
       instanceVariableNames:''
       classVariableNames:'LazyLoading AutoloadFailedSignal LoadedClasses'
       poolDictionaries:''
       category:'Kernel-Classes'
!

Autoload comment:'
COPYRIGHT (c) 1991 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Autoload.st,v 1.18 1995-03-08 23:36:49 claus Exp $
'!

!Autoload class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1991 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.
"
! 

version
"
$Header: /cvs/stx/stx/libbasic/Autoload.st,v 1.18 1995-03-08 23:36:49 claus Exp $
"
!

documentation
"
    In memory limited systems (as my 8Mb 386 is) all seldom-used classes are made
    subclasses of this class. Autoload catches all messages and
    files-In the corresponding code when first used. Then the cought message
    is resent to the (now existing) class.

    Late addition: above comment is no longer true - I have made now almost
    all Demos & Goodies be autoloaded ... even for big systems.

    class variables:
        
	LazyLoading             <Boolean>       if true, the loaded classes 
						methods will NOT be compiled at 
						autoload time, but instead when 
						first called. This allows for a 
						faster load. However, expect short 
						pauses later when the methods are
						first executed.
                                     
	AutoloadFailedSignal    <Signal>        signal raised if an autoloaded 
						classes source is not available.
"
! !

!Autoload class methodsFor:'initialization'!

initialize
    AutoloadFailedSignal isNil ifTrue:[
	ErrorSignal isNil ifTrue:[super initialize].

	AutoloadFailedSignal := ErrorSignal newSignalMayProceed:true.
	AutoloadFailedSignal nameClass:self message:#autoloadFailedSignal.
	AutoloadFailedSignal notifierString:'autoload failed '.

	self setSuperclass:nil.
	ObjectMemory flushCaches.
    ]
! !

!Autoload class methodsFor:'signal access'!

autoloadFailedSignal
    "return the signal raised when an autoload fails"

    ^ AutoloadFailedSignal
! !

!Autoload class methodsFor:'queries'!

isLoaded
    "return true, if the class has been loaded; redefined in Autoload;
     see comment there. this allows testing for a class been already loaded."

    ^ (self == Autoload)
!

wasAutoloaded:aClass
    ^ LoadedClasses notNil and:[LoadedClasses includes:aClass]
! !

!Autoload class methodsFor:'lazy compilation'!

compileLazy:aBoolean
    "turn on/off lazy loading - if on, fileIn is much faster,
     but pauses are to be expected later.
     If you like it, add a line to your startup file."

    LazyLoading := aBoolean
! !

!Autoload class methodsFor:'adding autoloaded classes'!

addClass:aClassName
    self addClass:aClassName inCategory:'autoloaded-Classes'

    "
     Autoload addClass:'Clock'
    "
!

addClass:aClassName inCategory:aCategory
    |nameSymbol|

    nameSymbol := aClassName asSymbol.
    (Smalltalk at:nameSymbol) isNil ifTrue:[
	Autoload subclass:nameSymbol
	     instanceVariableNames:''
	     classVariableNames:''
	     poolDictionaries:''
	     category:aCategory.
    ]
    "
     Autoload addClass:'Clock' inCategory:'autoloaded-Demos'
    "
! !

!Autoload class methodsFor:'loading'!

autoload
    "use this to force loading
     - it is defined a noop in all non-autoloading clases"

    |mySelf myName newClass|

    mySelf := self.
    myName := self name asSymbol.

    "remove myself - to avoid recompilation"
    Smalltalk at:myName put:nil.

    "load it"
    Transcript showCr:('autoloading ', myName , ' ...'); endEntry.

    Smalltalk fileInClass:myName initialize:false lazy:LazyLoading.

    "did it work ?"
    newClass := Smalltalk at:myName.
    Smalltalk at:myName put:mySelf.   "will be undone by become:"

    "no - report the error"
    newClass isNil ifTrue:[
	"
	 this signal is raised, if an autoloaded class
	 cannot be loaded. Usually, this happends when
	 some sourcefile is missing, not readable or if 
	 an entry is missing in the abbreviation file.
	 Check for a readable file named <myName>.st 
	 in the 'source' directory and (if its a long fileName) 
	 for a corresponding entry in the abbreviation file
	 'include/abbrev.stc'.
	 Finally, your searchpath could be set wrong -
	 both 'source' and 'include' directories must be found in
	 one of the directories named in systemPath.

	 In the debugger, press 'abort' to continue execution.
	" 
	AutoloadFailedSignal
	    raiseRequestWith:self
	    errorString:('autoload of ' , myName , ' failed').
	^ nil
    ].

    LoadedClasses isNil ifTrue:[
	LoadedClasses := IdentitySet new.
    ].
    LoadedClasses add:self.

    "wow - it worked. now the big trick ..."

    self become:newClass.
    LoadedClasses rehash.
    self initialize.  "/ thats the new class now
    ^ self  "this is now the new class - see what doesNotUnderstand: does with it"
! !

!Autoload class methodsFor:'message catching'!

doesNotUnderstand:aMessage
    "cought a message; load class and retry"

    |newClass|

    self ~~ Autoload ifTrue:[
	newClass := self autoload.
	newClass notNil ifTrue:[
	    ^ newClass perform:(aMessage selector)
		 withArguments:(aMessage arguments)
	]
    ].
    super doesNotUnderstand:aMessage
!

new
    "catch new"

    ^ self doesNotUnderstand:(Message selector:#new)
!

basicNew
    "catch basicNew"

    ^ self doesNotUnderstand:(Message selector:#basicNew)
!

new:arg
    "catch new:"

    ^ self doesNotUnderstand:(Message selector:#new: with:arg)
!

basicNew:arg
    "catch basicNew:"

    ^ self doesNotUnderstand:(Message selector:#basicNew: with:arg)
!

subclass:a1 instanceVariableNames:a2 classVariableNames:a3 poolDictionaries:a4 category:a5
    "catch subclass creation - this forces missing superclasses to be 
     loaded first"

    |newClass sel args|

    "take care: subclassing Autoload must still be possible"
    (self == Autoload) ifTrue:[
	^ super 
	    subclass:a1 
	    instanceVariableNames:a2
	    classVariableNames:a3
	    poolDictionaries:a4
	    category:a5
    ].
    newClass := self autoload.
    sel := thisContext selector.
    args := thisContext args.
    newClass notNil ifTrue:[
	^ newClass perform:sel withArguments:args
    ].
    ^ nil
!

comment
    (self == Autoload) ifTrue:[^ super comment].
    ^ 'not yet loaded'
! !

!Autoload class methodsFor:'fileout'!

fileOutDefinitionOn:aStream
    "print an expression to define myself on aStream.
     Since autoloaded classes dont know their real definition, simply
     output some comment string making things clear."

    (self == Autoload) ifTrue:[^ super fileOutDefinitionOn:aStream].

    aStream nextPutAll:'''' , self name , ' is not yet loaded.'; cr.
    aStream nextPutAll:' to load, execute: '.
    aStream cr; cr; spaces:4; nextPutAll:self name , ' autoload'; cr.
    aStream nextPutAll:''''.
! !