LazyMethod.st
author claus
Fri, 11 Aug 1995 18:04:27 +0200
changeset 103 f4a69d7dd387
parent 102 77e4d1119ff2
child 126 aca2139a3526
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1994 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.
"

Method subclass:#LazyMethod
	 instanceVariableNames:''
	 classVariableNames:'Access CompilationFailedSignal'
	 poolDictionaries:''
	 category:'Kernel-Methods'
!

LazyMethod comment:'
COPYRIGHT (c) 1994 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libcomp/LazyMethod.st,v 1.13 1995-08-11 16:03:08 claus Exp $
'!

!LazyMethod class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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/libcomp/LazyMethod.st,v 1.13 1995-08-11 16:03:08 claus Exp $
"
!

documentation
"
    Instances of LazyMethod are created when doing a lazy autoload.
    They do not contain any code (neither byte- nor machinecode), but
    keep their sourcecode only.

    When executed, these will trigger an error in the VM (noByteCode),
    which is cought here to create a real method from the receiver,
    amd re-execute the method.

    This allows faster loading of code, which will be later compiled
    when first executed; for classes with a large number of methods, of
    which only a small subset is actually used, this can also save
    lots of memory (beside making autoloading faster).
"
! !

!LazyMethod class methodsFor:'initialization'!

initialize
    CompilationFailedSignal isNil ifTrue:[
	CompilationFailedSignal := ExecutionErrorSignal newSignalMayProceed:true.
	CompilationFailedSignal nameClass:self message:#compilationFailedSignal.
	CompilationFailedSignal notifierString:'compilation of lazy method failed'.

	Access := Semaphore forMutualExclusion.
	"/ Access := RecursionLock new.
    ]
! !

!LazyMethod class methodsFor:'Signal constants'!

compilationFailedSignal
    ^ CompilationFailedSignal
! !

!LazyMethod methodsFor:'queries'!

isLazyMethod
    ^ true
! !

!LazyMethod methodsFor:'compiling'!

makeRealMethod
    "make the receiver a real method; i.e. compile the sourcecode and
     fill in the bytecode. This must be done in order to execute the receiver."

    |m|

    "compile the method"

    "we have to sequentialize this using a lock-semaphore,
     to make sure only one method is compiled at a time.
     Otherwise, we might get into trouble, if (due to a timeout)
     another recompile is forced while compiling this one ...
     (happened when autoloading animation demos)
    "
    [
	Access critical:[
	    m := self asByteCodeMethod.
	].
    ] valueUninterruptably.

    (m isNil or:[(byteCode := m byteCode) isNil]) ifTrue:[
	"
	 compilation failed
	"
	^ nil
    ].
    literals := m literals.
    flags := m flags.
    self changeClassToThatOf:m.
    ^ self
! !

!LazyMethod methodsFor:'error handling'!

noByteCode 
    "this is triggered by the interpreter when a lazy method is about to 
     be executed (by sending the to-be executed  method this message).
     Hard-compile the method, install its bytecode in the receiver,
     and recall it."

    |sender spec class selector|

    "compile the method"

    self makeRealMethod isNil ifTrue:[
	"
	 compilation failed
	"
	selector := thisContext sender selector.

	class := self containingClass.
	class notNil ifTrue:[
	    spec := class name , '>>' , selector
	] ifFalse:[
	    spec := 'unknown>>' , selector
	].
	"
	 this error is triggered, if the compilation of a lazy method
	 failed - this happens for example, if a lazy methods code has been
	 changed in a fileBrowser without checking the code for syntactical
	 correctnes, or if the instvars of an autoloaded classes superclass 
	 have been changed without changing the subclasses code ...
	 You should enter the SystemBrowser on this method, and try accepting 
	 to see what the problem is.
	 The methods class is found in the local 'class',
	 the selector is found in the local 'selector'.

	 As a general rule: never edit autoloaded classes from anything
	 except the browser - to check that they work and are compilable.
	"
	^ CompilationFailedSignal raiseRequestWith:self
				  errorString:('compilation of lazy method ' , spec , ' failed')
    ].

    "
     Now, the receiver method has mutated into a real (non-lazy) one.
     Get the original message receiver and args, and execute the method.

     ThisContext sender is the context of the original send (the failed one)
    "
    sender := thisContext sender.
    ObjectMemory flushCaches.

    ^ self valueWithReceiver:(sender receiver)
		   arguments:(sender args)
		    selector:(sender selector)
		      search:nil
		      sender:nil
! !