Autoload.st
author claus
Thu, 02 Jun 1994 18:22:49 +0200
changeset 88 81dacba7a63a
parent 68 59faa75185ba
child 92 0c73b48551ac
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'
       poolDictionaries:''
       category:'Kernel-Classes'
!

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

!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.8 1994-06-02 16:19:17 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 
					a faster load - however, expect short 
					pauses later.
"
! !

!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."

    ^ false
! !

!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:'loading'!

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

    |mySelf myName mySym newClass prev|

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

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

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

    LazyLoading ifTrue:[
	prev := Compiler compileLazy:true.
	[
	    Smalltalk fileInClass:myName.
	] valueNowOrOnUnwindDo:[
	    Compiler compileLazy:prev
	]
    ] ifFalse:[
        Smalltalk fileInClass:myName.
    ].

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

    newClass isNil ifTrue:[
        "no - forget it"
        self warn:('autoload of ' , myName , ' failed').
        ^ nil
    ].

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

    self become:newClass.
    ^ self  "this is now newClass"
! !

!Autoload class methodsFor:'message catching'!

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

    |newClass|

    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:#basicew)
!

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
    ^ 'not yet loaded'
! !

!Autoload class methodsFor:'fileout'!

fileOutDefinitionOn:aStream
    "print an expression to define myself on aStream"

    self == Autoload ifFalse:[
        aStream nextPutAll:'''' , self name , ' is not yet loaded'''
    ] ifTrue:[
        ^ super fileOutDefinitionOn:aStream
    ]
! !