Method.st
author Claus Gittinger <cg@exept.de>
Sun, 27 Aug 2000 16:48:50 +0200
changeset 5564 0f513f04c50f
parent 5562 76675d5a0da9
child 5582 737d121ae7de
permissions -rw-r--r--
#readsFields: and #writesField: for st80 compatibility

"
 COPYRIGHT (c) 1989 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' }"

CompiledCode variableSubclass:#Method
	instanceVariableNames:'source sourcePosition category package mclass'
	classVariableNames:'PrivateMethodSignal LastFileReference LastSourceFileName
		LastWhoClass LastFileLock LastMethodSources CompilationLock'
	poolDictionaries:''
	category:'Kernel-Methods'
!

Object subclass:#MethodWhoInfo
	instanceVariableNames:'myClass mySelector'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Method
!

!Method class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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 class defines protocol for executable methods;
    both compiled and interpreted methods are represented by this class.
    Compiled methods have a non-nil code field, while interpreted methods have
    a nil code field and non-nil byteCode field.
    If there are both non-nil code and bytecode fields, the VM will execute
    the machine-code of a method. If both are nil when executed, a noByteCode
    message is sent by the VM to the method where a signal is raised.

    The methods sourcecode is represented by source and sourcePosition:
    - if sourcePosition is a Number, the source-field is the fileName and
      sourcePosition is the character offset of the source-chunk in this source file.
    - If sourcePosition is nil, the source is the string in the source field.
    (an old version used ExternalString instances here, but that lead to
     10000 additional little objects ...)

    The flags field defines things like the number of method-locals,
    method arguments and stack requirements (for interpreted methods).
    Do not depend on any value in the flags field - it may change without
    notice.

    Notice, that in ST/X, method can be subclassed; executable code is
    identified not by being an instance of Block or Method, but instead by
    having the executable flag bit set in the class. The VM can execute anything
    which is identified as executable (assuming that the first instance variable
    is the machine-code address) - this allows for easy future extension.

    [Instance variables:]

	source          <String>        the source itself (if sourcePosition isNil)
					or the fileName where the source is found

	sourcePosition  <Integer>       the position of the methods chunk in the file

	category        <Symbol>        the methods category
	package         <Symbol>        the package, in which the methods was defined
	mclass          <Class>         the class in which I am defined
	indexed slots                   literals

    [Class variables:]

	PrivateMethodSignal             raised on privacy violation (see docu)

	LastFileReference               weak reference to the last sourceFile
	LastSourceFileName              to speedup source access via NFS

    WARNING: layout known by compiler and runtime system - dont change

    [author:]
	Claus Gittinger
"
!

dynamicMethods
"
    On systems which support dynamic loading of stc-compiled machine code (SYS5.4, Linux),
    methods may now be compiled to machine code from within the browser,
    and the resulting machine code object be loaded in.
    The ObjectFileLoader keeps (weak) handles to the resulting methods and
    invalidates the corresponding method objects, if the underlying methods
    object code is unloaded.
    Invalid methods will trap into the debugger when executed;
    also, the browser marks them as '(* not executable *)' in its method list.

    Notice: this has nothing to do with JIT compilation, which is always possible.
    JIT-compilation is done from bytecodes to a machineCode cache.
    In contrast, dynamic loading of stc-compiled code goes via intermediate C-code
    which is compiled by the machines native C-compiler.
    As opposed to JITted code, this allows for embedded primitive C-code.
"
!

privacy 
"
    ST/X includes an EXPERIMENTAL implementation of method privacy.
    Individual methods may be set to private or protected via the
    privacy:#private and privacy:#protected messages. Also, categories may be
    filedIn as a whole as private using #privateMethodsFor: or as
    protected using #protectedMethodsFor: instead of the well known #methodsFor:.

    The additional #publicMethodsFor: is for documentation purposes, and
    is equivalent to #methodsFor: (also to support fileIn of ENVY methods).

    Private methods may be executed only when called via a self-send
    from the superclass-methods and self or super-sends from methods in the
    class itself or subclasses.
    Protected methods may not be called from subclasses-methods, 
    i.e. they may only be called via self sends from within the current class.
    (i.e. private methods are less private than protected ones)

    When such a situation arises, the VM (runtime system) will raise the
    PrivateMethodSignal exception (if nonNil), which usually brings you into the
    debugger.

    If PrivateMethodSignal is nil, the VM will not check for this, and
    execution is as usual. (you may want to nil-it for production code,
    and leave it non nil during development).

    NOTICE: there is no (not yet ?) standard defined for method privacy,
    however, the definition protocol was designed to be somewhat ENVY compatible 
    (from what can be deduced by reading PD code).

    Also, the usability of privacy is still to be tested.
    This interface, the implementation and the rules for when a privacy violation
    may change (in case of some ANSI standard being defined).
    Be warned and send me suggestions & critics (constructive ;-)

    Late note (Feb 2000):
	the privacy feature has new been in ST/X for some years and was NOT heavily
	used - neither at eXept, nor by customers.
	In Smalltalk, it seems to be a very questionable feature, actually limiting
	code reusability.
	The privacy features are left in the system to demonstrate that it can be
	done in Smalltalk (for religious C++ fans ... to avoid useless discussions)
	(the check is not expensive, w.r.t. the VM runtime behavior).
"
! !

!Method class methodsFor:'initialization'!

initialize
    "create signals"

    PrivateMethodSignal isNil ifTrue:[
        "EXPERIMENTAL"
        PrivateMethodSignal := ExecutionErrorSignal newSignalMayProceed:true.
        PrivateMethodSignal nameClass:self message:#privateMethodSignal.
        PrivateMethodSignal notifierString:'attempt to execute private/protected method'.
    ].

    LastFileLock isNil ifTrue:[
        LastFileLock := Semaphore forMutualExclusion name:'LastFileLock'.
        LastFileReference := WeakArray new:1.
        LastFileReference at:1 put:0.
    ].

    CompilationLock := RecursionLock new name:'MethodCompilation'.

    "Modified: 22.4.1996 / 16:34:38 / cg"
    "Modified: 3.1.1997 / 16:58:16 / stefan"
! !

!Method class methodsFor:'Signal constants'!

privateMethodSignal
    "return the signal raised when a private/protected method is called
     by some other object (i.e. not a self- or super send)"

    ^ PrivateMethodSignal
! !

!Method class methodsFor:'binary storage'!

binaryDefinitionFrom: stream manager: manager
    "read my definition from stream."

    |cls sel|

    "type-byte"
    stream nextByte == 0 ifTrue:[
	"
	 built-in method
	"
	cls := manager nextObject.
	sel := manager nextObject.

	"
	 mhmh - on the source system, this was a machinecode
	 method, while here its an interpreted one ...
	"
	cls isLoaded ifFalse:[
	    cls autoload
	].
	^ cls compiledMethodAt:sel
    ].
    "
     bytecode method
    "
    ^ super binaryDefinitionFrom:stream manager:manager
!

binaryFullDefinitionFrom:stream manager:manager
    "retrieve a full bytecoded-method."

    |snapId cat flags code lits m sourceFilename sourcePos source|

    snapId := manager nextObject.
    cat := manager nextObject.
    flags := manager nextObject.
    lits := manager nextObject.
    sourceFilename := manager nextObject.
    sourcePos := manager nextObject.
    sourcePos isNil ifTrue:[
	source := manager nextObject.
    ].
    code := manager nextObject.

    snapId == ObjectMemory snapshotID ifTrue:[
	ObjectMemory incrementSnapshotID
    ].

    m := Method basicNew:(lits size).
    cat notNil ifTrue:[m category:cat].
    m flags:flags.
    m literals:lits.
    m byteCode:code.
    sourcePos isNil ifTrue:[
	m source:source
    ] ifFalse:[
	m sourceFilename:sourceFilename position:sourcePos
    ].
    ^ m

    "Created: 16.1.1996 / 14:44:08 / cg"
    "Modified: 24.6.1996 / 12:29:35 / stefan"
    "Modified: 5.1.1997 / 01:09:56 / cg"
! !

!Method class methodsFor:'queries'!

isBuiltInClass
    "return true if this class is known by the run-time-system.
     Here, true is returned for myself, false for subclasses."

    ^ self == Method

    "Modified: 23.4.1996 / 15:59:50 / cg"
!

methodPrivacySupported
    "return true, if the system was compiled to support methodPrivacy.
     You should not depend on that feature being available."

%{  /* NOCONTEXT */
#if defined(F_PRIVATE) || defined(F_CLASSPRIVATE)
    RETURN (true);
#else
    RETURN (false);
#endif
%}
!

resourceTypes
    "get the types of resources for which a spec definition and corresponding editor exist"

    ^#(canvas menu image fileImage help hierarchicalList tabList tableColumns)
! !

!Method class methodsFor:'special'!

flushSourceStreamCache
    LastSourceFileName := LastMethodSources := nil

    "Created: 9.2.1996 / 19:05:28 / cg"

"
self flushSourceStreamCache
"
! !

!Method methodsFor:'accessing'!

category
    "return the methods category or nil"

    ^ category
!

category:aStringOrSymbol
    "set the methods category"

    aStringOrSymbol notNil ifTrue:[
	category := aStringOrSymbol asSymbol
    ]

    "Modified: / 13.11.1998 / 23:55:05 / cg"
!

comment
    "return the methods comment.
     This is done by searching for and returning the first comment
     from the methods source (excluding any double-quotes). 
     Returns nil if there is no comment (or source is not available)."

    |src comment comments parser|

    src := self source.
    src isNil ifTrue:[^ nil].

    parser := Parser for:src in:nil.
    parser ignoreErrors; ignoreWarnings; saveComments:true.
    parser parseMethodSpec.
    comments := parser comments.
    comments size ~~ 0 ifTrue:[
	comment := comments first string.
	(comment withoutSpaces endsWith:'}') ifTrue:[
	    "if first comment is a pragma, take next comment"
	    comment := comments at:2 ifAbsent:nil.
	    comment notNil ifTrue:[
		comment := comment string.
	    ].
	].
    ].
    ^ comment.

    "
     (Method compiledMethodAt:#comment) comment  
     (Object class compiledMethodAt:#infoPrinting:) comment  
    "

    "Modified: / 17.2.1998 / 14:50:00 / cg"
    "Modified: / 23.2.1998 / 10:26:08 / stefan"
!

getSource
    "low-level access to the source instance-variable.
     For internal (compiler) use only.
     This is NOT always the methods source string"

    ^ source
!

getSourcePosition
    "low-level access to the sourcePosition instance-variable.
     For internal (compiler) use only.
     This is NOT always the methods sourcePosition"

    ^ sourcePosition
!

localSourceFilename:aFileName position:aNumber
    "set the methods sourcefile/position indicating, that 
     this is a local file."

    source := aFileName.
    sourcePosition := aNumber negated

    "Created: 16.1.1997 / 01:25:52 / cg"
!

localSourceStream
    "try to open a stream from a local source file,
     searching in standard places."

    |fileName aStream|

    package notNil ifTrue:[
	fileName := Smalltalk getSourceFileName:(package copyReplaceAll:$: with:$/) , '/' , source.
	fileName notNil ifTrue:[
	    aStream := fileName asFilename readStream.
	    aStream notNil ifTrue:[^ aStream].
	].
    ].
    fileName := Smalltalk getSourceFileName:source.
    fileName notNil ifTrue:[
	aStream := fileName asFilename readStream.
	aStream notNil ifTrue:[^ aStream].
    ].
    ^ nil
!

makeLocalStringSource
    "assure that the methods source code is stored locally as a string
     within the method (as opposed to an external string, which is accessed
     by reading the source code file).
     This is required, when a methods package is changed, to assure that its
     sourceCode is not lost."

    source notNil ifTrue:[
	sourcePosition notNil ifTrue:[
	    self source:(self source)
	]
    ].
!

mclass:aClass
    mclass notNil ifTrue:[
        'Method [warning]: mclass already set' errorPrintCR.
    ].
    mclass := aClass.
!

package
    "return the package-symbol"

    |cls|

    package notNil ifTrue:[ ^ package ].
    (cls := self mclass) isNil ifTrue:[
        ^ ''
    ].
    ^ cls package ? ''

    "Modified: / 29.12.1998 / 01:16:05 / cg"
!

package:aSymbol
    "set the package-symbol"

    self makeLocalStringSource.
    package := aSymbol
!

setPackage:aSymbol
    "set the package-symbol"

    package := aSymbol
!

source
    "return the sourcestring for the receiver"

    |aStream fileName junk who myClass mgr className|

    "
     if sourcePosition is nonNil, its the fileName and
     abs(sourcePosition) is the offset.
     Otherwise, source is the real source
    "
    sourcePosition isNil ifTrue:[^ source].

    source notNil ifTrue:[
	LastMethodSources notNil ifTrue:[
	    junk := LastMethodSources at:self ifAbsent:nil.
	    junk notNil ifTrue:[
		^ junk
	    ]
	].

	aStream := self sourceStream.
	aStream notNil ifTrue:[
	    Stream positionErrorSignal handle:[:ex |
		^ nil
	    ] do:[
		aStream position:sourcePosition abs.
	    ].
	    junk := aStream nextChunk.

	    OperatingSystem isMSDOSlike ifTrue:[
		"
		 kludge for now - somehow this does not work under win32 (sigh)
		"
		aStream close.
		(LastFileReference at:1) == aStream ifTrue:[
		    LastFileReference at:1 put:0.
		    LastSourceFileName := nil.
		]
	    ].
	]
    ].

    junk notNil ifTrue:[
	LastMethodSources isNil ifTrue:[
	    LastMethodSources := CacheDictionary new:20.
	].
	LastMethodSources at:self put:junk.
    ].

    ^ junk

    "Modified: / 7.1.1997 / 16:20:09 / stefan"
    "Modified: / 25.9.1999 / 23:31:52 / cg"
!

source:aString
    "set the methods sourcestring"

    source := aString.
    sourcePosition := nil
!

sourceFilename
    "return the sourcefilename if source is extern; nil otherwise"

    sourcePosition notNil ifTrue:[^ source].
    ^ nil
!

sourceFilename:aFileName position:aNumber
    "set the methods sourcefile/position"

    source := aFileName.
    sourcePosition := aNumber
!

sourceLineNumber
    "return the lineNumber of my source within the returned
     source sourcestring.
     For ST methods, the returned sourceString is always the
     methods pure source; therefore, the lineNumber is always 1."

    ^ 1

    "Created: 30.7.1997 / 15:42:01 / cg"
!

sourcePosition
    "return the sourceposition if source is extern; nil otherwise"

    sourcePosition isNil ifTrue:[^ sourcePosition].
    ^ sourcePosition abs

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

sourceStream
    "return an open sourceStream (needs positioning)"

    |aStream fileName junk who myClass mgr className sep dir mod|

    "
     if sourcePosition is nonNil, its the fileName and
     abs(sourcePosition) is the offset.
     Otherwise, source is the real source
    "
    source isNil ifTrue:[^ nil].
    sourcePosition isNil ifTrue:[^ source readStream].

    "/ keep the last source file open, because open/close
    "/ operations maybe slow on NFS-mounted file systems.
    "/ Since the reference to the file is weak, it will be closed
    "/ automatically if the file is not referenced for a while. 
    "/ Neat trick.

    LastFileLock critical:[
	aStream := LastFileReference at:1.
	LastFileReference at:1 put:0.

	aStream == 0 ifTrue:[
	    aStream := nil.
	] ifFalse:[
	    LastSourceFileName = source ifFalse:[
		aStream close.
		aStream := nil.
	    ]
	].
	LastSourceFileName := nil.
    ].

    aStream notNil ifTrue:[
	LastSourceFileName := source.
	LastFileReference at:1 put:aStream.
	^ aStream
    ].

    "/ a negative sourcePosition indicates
    "/ that this is a local file (not to be requested
    "/ via the sourceCodeManager)
    "/ This kludge was added, to allow sourceCode to be
    "/ saved to a local source file (i.e. 'st.src')
    "/ and having a clue for which file is meant later.

    sourcePosition < 0 ifTrue:[
	aStream := source asFilename readStream.
	aStream notNil ifTrue:[
	    LastSourceFileName := source.
	    LastFileReference at:1 put:aStream.
	    ^ aStream
	].

	fileName := Smalltalk getSourceFileName:source.
	fileName notNil ifTrue:[
	    aStream := fileName asFilename readStream.
	    aStream notNil ifTrue:[
		LastSourceFileName := source.
		LastFileReference at:1 put:aStream.
		^ aStream
	    ].
	].
    ].

    "/
    "/ if there is no SourceManager, look in local standard places first
    "/
    (mgr := Smalltalk at:#SourceCodeManager) isNil ifTrue:[
	aStream := self localSourceStream.
	aStream notNil ifTrue:[
	    LastSourceFileName := source.
	    LastFileReference at:1 put:aStream.
	    ^ aStream
	].
    ].

    "/
    "/ nope - ask my class for the source (this also invokes the SCMgr)
    "/
    who := self who.
    who notNil ifTrue:[
	myClass := who methodClass.

	(package notNil and:[package ~= myClass package]) ifTrue:[
	    mgr notNil ifTrue:[
		"/ try to get the source using my package information ...
		sep := package indexOfAny:'/\:'.
		sep ~~ 0 ifTrue:[
		    mod := package copyTo:sep - 1.
		    dir := package copyFrom:sep + 1.
		    aStream := mgr streamForClass:nil fileName:source revision:nil directory:dir module:mod cache:true.
		    aStream notNil ifTrue:[
			LastSourceFileName := source.
			LastFileReference at:1 put:aStream.
			^ aStream
		    ].
		].
	    ].
	].

	aStream := myClass sourceStreamFor:source.
	aStream notNil ifTrue:[
	    LastSourceFileName := source.
	    LastFileReference at:1 put:aStream.
	    ^ aStream
	].
    ].

    "/
    "/ nope - look in standard places 
    "/ (if there is a source-code manager - otherwise, we already did that)
    "/
    mgr notNil ifTrue:[
	aStream := self localSourceStream.
	aStream notNil ifTrue:[
	    LastSourceFileName := source.
	    LastFileReference at:1 put:aStream.
	    ^ aStream
	].
    ].

    "/
    "/ final chance: try current directory
    "/
    aStream isNil ifTrue:[
	aStream := source asFilename readStream.
	aStream notNil ifTrue:[
	    LastSourceFileName := source.
	    LastFileReference at:1 put:aStream.
	    ^ aStream
	].
    ].

    (who isNil and:[source notNil]) ifTrue:[
	"/
	"/ mhmh - seems to be a method which used to be in some
	"/ class, but has been overwritten by another or removed.
	"/ (i.e. it has no containing class anyMore)
	"/ try to guess the class from the sourceFileName.
	"/ and retry.
	"/
	className := Smalltalk classNameForFile:source.
	className knownAsSymbol ifTrue:[
	    myClass := Smalltalk at:className asSymbol ifAbsent:nil.
	    myClass notNil ifTrue:[
		aStream := myClass sourceStreamFor:source.
		aStream notNil ifTrue:[
		    LastSourceFileName := source.
		    LastFileReference at:1 put:aStream.
		    ^ aStream
		].
	    ]
	]
    ].                

    ^ nil
! !

!Method methodsFor:'accessing-visibility'!

isIgnored
    "return true, if this is an ignored method.
     Ignored methods are physically present in the source file,
     but no code is generated for it by stc, and the VM does not see
     it in its message lookup.
     (i.e. setting a method to #ignored, and sending that selector,
      leads to either the superclasses implementation to be called, 
      or a doesNotUnderstand exception to be raised)

     Notice: this is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

    ^ self privacy == #ignored

    "Modified: / 23.1.1998 / 15:23:02 / stefan"
!

isPrivate
    "return true, if this is a private method.
     Execution of private methods is only allowed via self/super sends
     from superclasses, the class itself or subclasses.
     If a private method is called by some other class, a runtime
     error (PrivateMethodSignal) is raised.
     Notice: method privacy is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

    ^ self privacy == #private

    "Modified: / 23.1.1998 / 15:23:13 / stefan"
!

isProtected
    "return true, if this is a protected method.
     Execution of protected methods is only allowed via self sends
     from superclasses or the class itself.
     If a protected method is called by some other class, a runtime
     error (PrivateMethodSignal) is raised.

     Notice: method privacy is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

    ^ self privacy == #protected

    "Modified: / 23.1.1998 / 15:23:27 / stefan"
!

isPublic
    "return true, if this is a public method - I.e. can be executed via any send.
     This is the default and how other smalltalk implementations treat all methods.

     Notice: method privacy is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

    ^ self privacy == #public

    "Modified: / 23.1.1998 / 15:23:40 / stefan"
!

isRestricted
    "return the flag bit stating that this method is restricted.
     Execution of the receiver will only be allowed if the system is not in
     'trap restricted mode' (-->ObjectMemory) otherise a runtime 
     error (PrivateMethodSignal) is raised.

     Notice: method restriction is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

%{  /* NOCONTEXT */
#ifdef F_RESTRICTED
    INT f = __intVal(__INST(flags));

    if (f & F_RESTRICTED) {
	RETURN (true);
    }
#endif
%}.
    ^ false
!

privacy
    "return a symbol describing the methods access rights (privacy);
     Currently, this is one of #private, #protected, #public or #ignored.

     Notice: method privacy is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.
     If at all, use it for debugging purposes, to catch messagesends
     which are not supposed to be sent by others.
     (especially, if working in a team, while integrating other peoples work)

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

%{  /* NOCONTEXT */
    /* I made this a primitive to get the define constant from stc.h */

#if defined(M_PRIVACY) && (defined(F_PRIVATE) || defined(F_CLASSPRIVATE) || defined(F_IGNORED))

    INT f = __intVal(__INST(flags));
    switch (f & M_PRIVACY) {

# ifdef F_PRIVATE
    case F_PRIVATE:
	RETURN (@symbol(private));
	break;
# endif
# ifdef F_CLASSPRIVATE
    case F_CLASSPRIVATE:
	RETURN (@symbol(protected));
	break;
# endif
# ifdef F_IGNORED
    case F_IGNORED:
	RETURN (@symbol(ignored));
	break;
# endif
    }
#endif
%}.

    ^ #public
!

privacy:aSymbol
    "set the methods access rights (privacy) from a symbol;
     Currently, this must be one of #private, #protected, #public or #ignored.

     Notice: method privacy is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.
     If at all, use it for debugging purposes, to catch messagesends
     which are not supposed to be sent by others.
     (especially, if working in a team, while integrating other peoples work)

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

    |old|

    old := self privacy.
    self setPrivacy:aSymbol.

    "/
    "/ no need to flush, if changing from private to public
    "/
    (aSymbol == #public and:[old ~~ #ignored]) ifFalse:[
	ObjectMemory flushCaches.
    ]

    "Modified: / 27.8.1995 / 22:58:08 / claus"
    "Modified: / 23.1.1998 / 15:19:07 / stefan"
!

restricted:aBoolean
    "set or clear the flag bit stating that this method is restricted. 
     Execution of the receiver will only be allowed if the system is not in
     'trap restricted mode' (-->ObjectMemory) otherise a runtime
     error (PrivateMethodSignal) is raised.

     Notice: method restriction is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

%{  /* NOCONTEXT */
    /* I made this a primitive to get the define constant from stc.h */

#ifdef F_RESTRICTED
    INT f = __intVal(__INST(flags));
    INT old;

    old = f;
    if (aBoolean == true) 
	f |= F_RESTRICTED;
    else
	f &= ~F_RESTRICTED;
    __INST(flags) = __MKSMALLINT(f);
    if (old & F_RESTRICTED)
	RETURN(true);
#endif
%}.
    ^ false

    "
     (ObjectMemory class compiledMethodAt:#compressingGarbageCollect) restricted:true
    "

    "Created: 7.11.1995 / 20:36:19 / stefan"
!

setPrivacy:aSymbol
    "set the methods access rights (privacy) from a symbol;
     Currently, this must be one of #private, #protected, #public or #ignored.
     #setPrivacy: simply sets the attribute. When changing methods, that 
     have already been called, #privacy: should be used.

     Notice: method privacy is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.
     If at all, use it for debugging purposes, to catch messagesends
     which are not supposed to be sent by others.
     (especially, if working in a team, while integrating other peoples work)

     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

%{  /* NOCONTEXT */

#if defined(M_PRIVACY)
    INT f = __intVal(__INST(flags));
    INT p;

    if (aSymbol == @symbol(public))
	p = 0;
    else if (aSymbol == @symbol(private))
	p = F_PRIVATE;
    else if (aSymbol == @symbol(protected))
	p = F_CLASSPRIVATE;
    else if (aSymbol == @symbol(ignored))
	p = F_IGNORED;
    else
	RETURN(false);  /* illegal symbol */
        

    f = (f & ~M_PRIVACY) | p;
    __INST(flags) = __MKSMALLINT(f);
#endif

%}.
    ^ true

    "Modified: 27.8.1995 / 22:58:08 / claus"
! !

!Method methodsFor:'binary storage'!

asByteCodeMethod
    "if the receiver has no bytecodes, create & return a method having
     the same semantics as the receiver, but uses interpreted bytecodes.
     Otherwise, return the receiver. The new method is not installed in
     the methodDictionary of any class - just returned.
     If the method contains primitive code, this may return a method
     without bytecode.
     Can be used to obtain a bytecode version of a machine-code method, 
     for binary storage or dynamic recompilation (which is not yet finished)
     or to compile lazy methods down to executable ones."

    |doMachineCode mthd|

    byteCode notNil ifTrue:[
	"
	 is already a bytecoded method
	"
	^ self
    ].
    doMachineCode := Compiler stcCompilation:#never.
    [
	mthd := self asExecutableMethod.
    ] valueNowOrOnUnwindDo:[
	Compiler stcCompilation:doMachineCode.
    ].
    ^ mthd

    "Created: 24.10.1995 / 14:02:32 / cg"
    "Modified: 5.1.1997 / 01:01:53 / cg"
!

asByteCodeMethodWithSource:newSource
    |doMachineCode mthd|

    doMachineCode := Compiler stcCompilation:#never.
    [
        mthd := self asExecutableMethodWithSource:newSource.
    ] valueNowOrOnUnwindDo:[
        Compiler stcCompilation:doMachineCode.
    ].
    ^ mthd

    "Created: 24.10.1995 / 14:02:32 / cg"
    "Modified: 5.1.1997 / 01:01:53 / cg"
!

asExecutableMethod
    "if the receiver has neither bytecodes nor machinecode, create & return a 
     method having semantics as the receivers source. This may be machine code,
     if the system supports dynamic loading of object code and the source includes
     primitive code. However, bytecode is preferred, since it compiles faster.
     Otherwise, return the receiver. The new method is not installed in
     the methodDictionary of any class - just returned.
     Can be used to compile lazy methods down to executable ones."

    |temporaryMethod cls sourceString silent lazy|

    byteCode notNil ifTrue:[
        "
         is already a bytecoded method
        "
        ^ self
    ].

    cls := self containingClass.
    cls isNil ifTrue:[
        'Method [warning]: cannot generate bytecode (no class for compilation)' errorPrintCR.
        ^ nil
    ].
    sourceString := self source.
    sourceString isNil ifTrue:[
        'Method [warning]: cannot generate bytecode (no source for compilation)' errorPrintCR.
        ^ nil
    ].

    "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)
    "
    CompilationLock critical:[
        "
         dont want this to go into the changes file,
         dont want output on Transcript and definitely 
         dont want a lazy method ...
        "
        Class withoutUpdatingChangesDo:[
            silent := Smalltalk silentLoading:true.
            lazy := Compiler compileLazy:false.

            [
                |compiler|

                Class nameSpaceQuerySignal answer:(cls nameSpace)
                do:[
                    compiler := cls compilerClass.

                    "/
                    "/ kludge - have to make ST/X's compiler protocol
                    "/ be compatible to ST-80's
                    "/
                    (compiler respondsTo:#compile:forClass:inCategory:notifying:install:)
                    ifTrue:[
                        temporaryMethod := compiler
                                             compile:sourceString
                                             forClass:cls
                                             inCategory:(self category)
                                             notifying:nil
                                             install:false.
                    ] ifFalse:[
                        temporaryMethod := compiler new
                                             compile:sourceString 
                                             in:cls 
                                             notifying:nil 
                                             ifFail:nil
                    ].
                ].
            ] valueNowOrOnUnwindDo:[
                Compiler compileLazy:lazy.
                Smalltalk silentLoading:silent.
            ]
        ].
    ].
    (temporaryMethod isNil or:[temporaryMethod == #Error]) ifTrue:[
        'Method [warning]: cannot generate bytecode (contains primitive code or error)' errorPrintCR.
        ^ nil.
    ].
    "/
    "/ try to save a bit of memory, by sharing the source (whatever it is)
    "/
    temporaryMethod sourceFilename:source position:sourcePosition. 
    "/
    "/ dont forget the methods class & package ...
    "/
    temporaryMethod setPackage:package.
    temporaryMethod mclass:mclass.
    ^ temporaryMethod

    "Created: 24.10.1995 / 14:02:30 / cg"
    "Modified: 10.1.1997 / 17:55:33 / cg"
!

asExecutableMethodWithSource:newSource
    |temporaryMethod cls silent lazy|

    cls := self containingClass.
    cls isNil ifTrue:[
        'Method [warning]: cannot generate bytecode (no class for compilation)' errorPrintCR.
        ^ nil
    ].

    "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)
    "
    CompilationLock critical:[
        "
         dont want this to go into the changes file,
         dont want output on Transcript and definitely 
         dont want a lazy method ...
        "
        Class withoutUpdatingChangesDo:[
            silent := Smalltalk silentLoading:true.
            lazy := Compiler compileLazy:false.

            [
                |compiler|

                Class nameSpaceQuerySignal answer:(cls nameSpace)
                do:[
                    compiler := cls compilerClass.

                    "/
                    "/ kludge - have to make ST/X's compiler protocol
                    "/ be compatible to ST-80's
                    "/
                    (compiler respondsTo:#compile:forClass:inCategory:notifying:install:)
                    ifTrue:[
                        temporaryMethod := compiler
                                             compile:newSource
                                             forClass:cls
                                             inCategory:(self category)
                                             notifying:nil
                                             install:false.
                    ] ifFalse:[
                        temporaryMethod := compiler new
                                             compile:newSource 
                                             in:cls 
                                             notifying:nil 
                                             ifFail:nil
                    ].
                ].
            ] valueNowOrOnUnwindDo:[
                Compiler compileLazy:lazy.
                Smalltalk silentLoading:silent.
            ]
        ].
    ].
    (temporaryMethod isNil or:[temporaryMethod == #Error]) ifTrue:[
        'Method [warning]: cannot generate bytecode (contains primitive code or error)' errorPrintCR.
        ^ nil.
    ].
    "/
    "/ try to save a bit of memory, by sharing the source (whatever it is)
    "/
    temporaryMethod source:newSource. 
    "/
    "/ dont forget the methods class & package ...
    "/
    temporaryMethod setPackage:package.
    temporaryMethod mclass:mclass.
    ^ temporaryMethod
!

readBinaryContentsFrom: stream manager: manager
    self hasCode ifTrue:[
	"built-in method - already complete"
	^ self
    ].

    ^ super readBinaryContentsFrom: stream manager: manager

    "Modified: / 13.11.1998 / 23:21:26 / cg"
!

storeBinaryDefinitionOn:stream manager:manager
    "store the receiver in a binary format on stream.
     This is an internal interface for binary storage mechanism.
     only store bytecode-methods - machinecode methods are stored
     as class/selector pair and a lookup is done when restored.

     If the receiver method is a built-in (i.e. machine coded)
     method, a temporary interpreted byte code method is created,
     and its bytecode stored. 
     This works only, if the source of the method is available and the
     method does not contain primitive code."

    |storedMethod who|

    byteCode isNil ifTrue:[
	self hasCode ifTrue:[
	    (who := self who) notNil ifTrue:[
		"
		 machine code only - assume its a built-in method,
		 and store the class/selector information.
		 The restored method may not be exactly the same ...
		"
		manager putIdOfClass:(self class) on:stream.
		stream nextPutByte:0.   "means: built-in method" 
		manager putIdOf:(who methodClass) on:stream.
		manager putIdOf:(who methodSelector) on:stream.
		^ self
	    ]
	].

	storedMethod := self asByteCodeMethod.
	storedMethod isNil ifTrue:[
	    self error:'store of built-in method failed'.
	].
	^ storedMethod storeBinaryDefinitionOn:stream manager:manager
    ].

    manager putIdOfClass:(self class) on:stream.
    stream nextPutByte:1.       "means: byte-coded method"
    self storeBinaryDefinitionBodyOn:stream manager:manager

    "Modified: / 13.11.1998 / 23:21:42 / cg"
!

storeFullBinaryDefinitionOn:stream manager:manager
    "store full bytecoded-method."

    |m code srcPos|

    "/ need a byteCode version of myself ...
    m := self.
    code := byteCode.
    code isNil ifTrue:[
	m := self asByteCodeMethod.
	code := m byteCode.
	code isNil ifTrue:[
	    m := self
	]
    ].

    ObjectMemory snapshotID storeBinaryOn:stream manager:manager.
    category storeBinaryOn:stream manager:manager.

    m flags storeBinaryOn:stream manager:manager.
    m literals storeBinaryOn:stream manager:manager.
    manager sourceMode == #discard ifTrue:[
	"/ add nil, nil, nil
	nil storeBinaryOn:stream manager:manager. "/ sourceFileName
	nil storeBinaryOn:stream manager:manager. "/ sourcePosition
	nil storeBinaryOn:stream manager:manager. "/ source
    ] ifFalse:[
	"/ add sourceFilename, srcPos
	"/ or  nil, nil, source
	m sourceFilename storeBinaryOn:stream manager:manager.
	manager sourceMode == #reference ifTrue:[
	    srcPos := m sourcePosition.
	] ifFalse:[
	    srcPos := nil
	].
	srcPos storeBinaryOn:stream manager:manager.
	srcPos isNil ifTrue:[
	    m source storeBinaryOn:stream manager:manager.
	].
    ].

    code storeBinaryOn:stream manager:manager.

    "Created: 16.1.1996 / 14:41:45 / cg"
    "Modified: 5.1.1997 / 00:39:29 / cg"
! !

!Method methodsFor:'copying'!

copy
    "redefined to change a source ref into a real string"

    |aCopy|

    aCopy := super copy.
    sourcePosition notNil ifTrue:[
	aCopy source:(self source)
    ].
    ^ aCopy

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

!Method methodsFor:'error handling'!

invalidCodeObject
    "{ Pragma: +optSpace }"

    "this method is triggered by the interpreter when a nil or non method
     is about to be executed.
     In this case, the VM sends this to the bad method (the receiver).

     Also, the Compiler creates methods with their code/bytecode set to
     this method if - after a class change - a method cannot be compiled
     and is therefore no longer executable (for example, after an instvar
     has been removed, and a method still tries to access this instvar)

     Thus, we arrive here, when playing around in a classes methodArray,
     or compiler/runtime system is broken :-(, 
     or you ignore the error messages during some recompile."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Modified: 4.11.1996 / 22:45:06 / cg"
!

invalidCodeObjectWith:arg
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 1 arg) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:16:16 / cg"
    "Modified: 4.11.1996 / 22:45:12 / cg"
!

invalidCodeObjectWith:arg with:arg2
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 2 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:16:41 / cg"
    "Modified: 4.11.1996 / 22:45:15 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 3 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:16:51 / cg"
    "Modified: 4.11.1996 / 22:45:18 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 4 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:17:00 / cg"
    "Modified: 4.11.1996 / 22:45:22 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 5 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:17:09 / cg"
    "Modified: 4.11.1996 / 22:45:25 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 6 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:17:17 / cg"
    "Modified: 4.11.1996 / 22:45:28 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 7 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:17:25 / cg"
    "Modified: 4.11.1996 / 22:45:31 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7 with:arg8
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 8 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:17:32 / cg"
    "Modified: 4.11.1996 / 22:45:38 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7 with:arg8 with:arg9
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 9 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:17:37 / cg"
    "Modified: 4.11.1996 / 22:45:41 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7 with:arg8 with:arg9 with:arg10
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 10 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:17:45 / cg"
    "Modified: 4.11.1996 / 22:45:44 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7 with:arg8 with:arg9 with:arg10 with:arg11
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 11 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:17:52 / cg"
    "Modified: 4.11.1996 / 22:45:47 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7 with:arg8 with:arg9 with:arg10 with:arg11 with:arg12
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 12 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 20:51:28 / cg"
    "Modified: 4.11.1996 / 22:46:01 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7 with:arg8 with:arg9 with:arg10 with:arg11 with:arg12 with:arg13
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 13 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:18:09 / cg"
    "Modified: 4.11.1996 / 22:45:57 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7 with:arg8 with:arg9 with:arg10 with:arg11 with:arg12 with:arg13 with:arg14
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 14 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:18:17 / cg"
    "Modified: 4.11.1996 / 22:45:55 / cg"
!

invalidCodeObjectWith:arg with:arg2 with:arg3 with:arg4 with:arg5 with:arg6 with:arg7 with:arg8 with:arg9 with:arg10 with:arg11 with:arg12 with:arg13 with:arg14 with:arg15
    "{ Pragma: +optSpace }"

    "When recompiling classes after a definition-change, all
     uncompilable methods (with 15 args) will be bound to this method here,
     so that evaluating such an uncompilable method will trigger an error."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseErrorString:'invalid method - not executable'.

    "Created: 4.11.1996 / 21:18:22 / cg"
    "Modified: 4.11.1996 / 22:45:52 / cg"
!

privateMethodCalled
    "{ Pragma: +optSpace }"

    "this error is triggered, if a private or protected method is called.

     If you continue in the debugger, the method will be called,
     and further privacy exceptions will NOT be reported at this call location, 
     until any new method is compiled, or the privacy of any method changes,
     or the caches are flushed.
     (the reason is that after the continue, the method is enterred into the
      calling cache, for which method privacy is not checked.
      Any of the above actions flushes this cache and a privacy check
      is performed again.)
     Future versions may not enter private methods into the cache, to fix this
     (unobvious) behavior. However, then you will get an exception for EVERY
     call to a private method ...

     Notice: method privacy is a nonstandard feature, not supported
     by other smalltalk implementations and not specified in the ANSI spec.
     This is EXPERIMENTAL - and being evaluated for usability.
     It may change or even vanish (if it shows to be not useful)."

    ^ PrivateMethodSignal raise

    "Modified: 4.11.1996 / 22:46:09 / cg"
!

uncompiledCodeObject
    "{ Pragma: +optSpace }"

    "this method is invoked by methods which contain primitive code,
     but have not been compiled to machine code (either due to an error
     when compiling, or simply because no stc is available.
     For those methods, the compiler generated a method object consisting
     of the original source code, but with this methods machine/byte code."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseRequestWith:self
	errorString:'invalid method - not compiled'.

    "Modified: 4.11.1996 / 22:58:02 / cg"
!

unloadedCodeObject
    "{ Pragma: +optSpace }"

    "this method is invoked by methods which have been binary-unloaded
     For those the source info consists
     of the original source code, but with this methods machine/byte code."

%{
    /*
     * for reasons too far from being explained here,
     * this MUST be a compiled method
     */
%}.
    ^ InvalidCodeSignal
	raiseRequestWith:self
	errorString:'invalid method - unloaded'.

    "Created: 4.11.1996 / 22:57:54 / cg"
    "Modified: 4.11.1996 / 22:58:28 / cg"
! !

!Method methodsFor:'printing & storing'!

printOn:aStream
    "put a printed representation of the receiver onto aStream.
     Since methods do not store their class/selector, we have to search
     for it here."

    |classAndSelector m wrapped|

    wrapped := false.

    aStream nextPutAll:(self classNameWithArticle).
    aStream nextPut:$(.

    classAndSelector := self who.
    classAndSelector isNil ifTrue:[
	"
	 not anchored in any class.
	 check if wrapped (to be more informative in inspectors)
	"
	m := self wrapper.
	m notNil ifTrue:[
	    classAndSelector := m who.
	    wrapped := true.
	]
    ].
    classAndSelector notNil ifTrue:[
	(classAndSelector methodClass) name printOn:aStream.
	aStream nextPutAll:' '.
	(classAndSelector methodSelector) printOn:aStream.
	wrapped ifTrue:[
	    aStream nextPutAll:'; wrapped'
	].
    ] ifFalse:[
	"
	 sorry, a method which is nowhere anchored
	"
	aStream nextPutAll:'unbound'
    ].
    aStream nextPut:$)

    "
     (Object compiledMethodAt:#at:) printOn:Transcript. Transcript cr.
     (Object compiledMethodAt:#at:) copy printOn:Transcript. Transcript cr.
    "

    "Modified: 1.11.1996 / 16:25:34 / cg"
!

printStringForBrowserWithSelector:selector inClass:aClass
    "return a printString to represent myself to the user in a browser.
     Defined here to allow for browsers to deal with nonStandard pseudoMethods"

    |s privInfo moreInfo p i n cls|

    moreInfo := ''.
    privInfo := ''.

    self isWrapped ifTrue:[
        (MessageTracer isCounting:self) ifTrue:[
            (MessageTracer isCountingMemoryUsage:self) ifTrue:[
                moreInfo := moreInfo , 
                     ' (mem usage avg: ' , (MessageTracer memoryUsageOfMethod:self) printString asText allBold , ' bytes)'.
            ] ifFalse:[
                moreInfo := moreInfo , 
                     ' (called ' , (MessageTracer executionCountOfMethod:self) printString asText allBold , ' times)'.
            ]
        ] ifFalse:[
            (MessageTracer isTiming:self) ifTrue:[
                i := MessageTracer executionTimesOfMethod:self.
                (i isNil or:[(n := i at:#count) == 0]) ifTrue:[
                    moreInfo := moreInfo , 
                                ' (cnt: ' , (i at:#count) printString , ')'
                ] ifFalse:[
                    n == 1 ifTrue:[
                        moreInfo := moreInfo , 
                                    ' (t: ' , (i at:#avgTime) printString asText allBold,
                                    'ms cnt: ' , (i at:#count) printString , ')'
                    ] ifFalse:[
                        moreInfo := moreInfo , 
                                    ' (avg: ' , (i at:#avgTime) printString asText allBold,
                                    'ms min: ' , (i at:#minTime) printString , 
                                    ' max: ' , (i at:#maxTime) printString ,
                                    ' cnt: ' , (i at:#count) printString , ')'
                    ].
                ].
            ] ifFalse:[
                moreInfo := ' !!'
            ]
        ].
    ]. 
    p := self privacy.

    p ~~ #public ifTrue:[
        privInfo := (' (* ' , p , ' *)') asText emphasizeAllWith:#italic.
    ].

"/    self isInvalid ifTrue:[
"/        moreInfo := ' (** not executable **)'.
"/    ].

    (self isLazyMethod not and:[self isUnloaded]) ifTrue:[
        moreInfo := ' (** unloaded **)'
    ].

    privInfo size ~~ 0 ifTrue:[
        moreInfo := privInfo , ' ' , moreInfo
    ].

    s := selector.
    (cls := aClass) isNil ifTrue:[
        cls := self containingClass
    ].
    (cls isNil or:[self package ~= cls package]) ifTrue:[
        s := s , ' [' , (self package asText emphasizeAllWith:(Array with:#italic with:(#color->Color red darkened))), ']'
    ].

    moreInfo size == 0 ifTrue:[^ s].

    s := selector , moreInfo.

    self isInvalid ifTrue:[
        s := s asText emphasizeAllWith:#color->Color red.
    ].
    ^ s

    "Modified: / 23.1.1998 / 13:15:15 / stefan"
    "Modified: / 31.7.1998 / 00:37:47 / cg"
    "Created: / 5.2.2000 / 22:55:56 / cg"
!

whoString
    "return a string as className>>selector, if this is not an unbound
     method. Otherwise return 'unbound'. Used with debugging."

    |who|

    who := self who.
    who notNil ifTrue:[
	^ (who methodClass) name , '>>' , (who methodSelector)
    ].
    ^ 'unbound'

    "
     Method new whoString
     (Method compiledMethodAt:#whoString) whoString
    "

    "Modified: 1.11.1996 / 16:27:04 / cg"
! !

!Method methodsFor:'private-compiler interface'!

primitiveNumber
    "for stx rel >= 5.x only:
     return the primitive number."

%{  /* NOCONTEXT */

#ifdef F_PRIMITIVE
    INT f = __intVal(__INST(flags));
    INT nr = nil;

    if (f & F_PRIMITIVE) {
        nr = __INST(code_);
    }
    RETURN (nr);
#endif
%}.
    self primitiveFailed



!

setPrimitiveNumber:aNumber
    "for stx rel >= 5.x only:
     mark the method as having primitive code."

%{  /* NOCONTEXT */

#ifdef F_PRIMITIVE
    INT f = __intVal(__INST(flags));

    f |= F_PRIMITIVE;
    __INST(flags) = __MKSMALLINT(f);
    __INST(code_) = aNumber;
    RETURN (self);
#endif
%}.
    self primitiveFailed



!

setResourceFlag
    "mark the method as having a <resource> definition in its
     source. 
     These resource definitions were found in ST-80 methods, and are
     currently not supported by ST/X (except for remembering this flag).
     It can be used to find resource-flagged methods quicker."

%{  /* NOCONTEXT */

#ifdef F_RESOURCE
    INT f = __intVal(__INST(flags));

    f |= F_RESOURCE;
    __INST(flags) = __MKSMALLINT(f);
#endif
%}
! !

!Method methodsFor:'queries'!

accessedInstVars
    "return a collection of instVarNames, which are accessed by
     the receiver method"

    |src parser|

    src := self source.
    src notNil ifTrue:[
	parser := Parser
			parseMethod:src 
			in:self containingClass 
			ignoreErrors:true 
			ignoreWarnings:true.

	(parser notNil and:[parser ~~ #Error]) ifTrue:[
	    ^ parser usedInstVars
	].
    ].
    ^ #() "/ actually: unknown

    "Modified: 19.6.1997 / 17:54:09 / cg"
!

containingClass
    "return the class I am defined in. 
     See comment in who."

    "based on who, which has been added for ST-80 compatibility"

    |who|

    mclass notNil ifTrue:[^ mclass].

    who := self who.
    who notNil ifTrue:[^ who methodClass].
    "
     none found - sorry
    "
    ^ nil

    "
     |m|
     m := Object compiledMethodAt:#at:.
     m containingClass   

     |m|
     m := Object class compiledMethodAt:#version.
     m containingClass   
    "

    "Modified: 1.11.1996 / 17:47:06 / cg"
!

hasPrimitiveCode
    "return true, if the method contains primitive code; false if not.
     Uses Parser to parse methods source and get the information."

    |src|

    "/ first a trivial reject, if the source does not
    "/ contain a '% {' sequence

    src := self source.
    src notNil ifTrue:[
        (src includesString:(String with:$% with:${) "<- no constant here - to avoid trouble with stupid scanners" ) ifFalse:[
            "/ cannot contain primitive code.
            ^ false
        ]
    ].

    "/ ok; it may or may not ...

    ^ self parse:#'parseMethodSilent:' return:#hasPrimitiveCode or:false

    "
     (Method compiledMethodAt:#hasPrimitiveCode) hasPrimitiveCode 
     (Object compiledMethodAt:#at:) hasPrimitiveCode   
     (Object compiledMethodAt:#basicAt:) hasPrimitiveCode 
    "

    "Modified: 22.1.1997 / 00:03:45 / cg"
!

hasResource
    "return true if the method had a <resource> definition in its
     source. This was found in ST-80 methods, and currently not supported
     by ST/X (except for remembering this flag).
     It can be used to find resource-flagged methods quicker."

%{  /* NOCONTEXT */

#ifdef F_RESOURCE
    RETURN (((INT)__INST(flags) & __MASKSMALLINT(F_RESOURCE)) ? true : false);
#endif
%}.
    ^ false


!

homeMethod
    "for common protocol with blocks: if the receiver is a method,
     return the receiver; otherwise, if its a block, return its home
     method."

    ^ self

    "Created: 19.6.1997 / 16:13:12 / cg"
!

isInvalid
    "return true, if this method is not executable due to
     a (re)-compilation error. Since invalidation is by patching the
     methods code-pointer to a trap function, check for that here.
     (see comment in Method>>invalidCodeObject)."

    |m myCode|

    myCode := self code.

    m := self trapMethodForNumArgs:(self numArgs).
    (m notNil and:[self ~~ m]) ifTrue:[
	(myCode notNil and:[myCode = m code]) ifTrue:[^ true].
	(byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
    ].

    m := Method compiledMethodAt:#uncompiledCodeObject.
    (m notNil and:[self ~~ m]) ifTrue:[
	(myCode notNil and:[myCode = m code]) ifTrue:[^ true].
	(byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
    ].

    m := Method compiledMethodAt:#unloadedCodeObject.
    (m notNil and:[self ~~ m]) ifTrue:[
	(myCode notNil and:[myCode = m code]) ifTrue:[^ true].
	(byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
    ].

    ^ false

    "Modified: 4.11.1996 / 23:34:24 / cg"
!

isMethod
    "return true, if the receiver is some kind of method;
     true returned here - the method is redefined from Object."

    ^ true
!

mclass
    "return the class in which the receiver was compiled.
     Same as #containingClass, for ST80 compatibility."

    ^ self containingClass

    "Created: 19.6.1997 / 16:26:13 / cg"
!

methodArgAndVarNames
    "return a collection with the methods argument and variable names.
     Uses Parser to parse methods source and extract the names.
     Returns nil if the source is not available, or some other
     syntax/parse error occurred. For methods with no args and no vars,
     an empty collection is returned."

    |parser sourceString argNames varNames|

    sourceString := self source.
    sourceString notNil ifTrue:[
	parser := Parser parseMethodArgAndVarSpecificationSilent:sourceString.
	(parser isNil or:[parser == #Error]) ifTrue:[^ nil].
	argNames := parser methodArgs.
	varNames := parser methodVars.
	argNames isNil ifTrue:[^ varNames].
	varNames isNil ifTrue:[^ argNames].
	^ (argNames , varNames)
    ].
    ^ nil

    "
     (Method compiledMethodAt:#printOn:) methodArgAndVarNames
    "
!

methodArgNames
    "return a collection with the methods argument names.
     Uses Parser to parse methods source and extract the names."

    ^ self parse:#'parseMethodSpecificationSilent:' return:#methodArgs or:nil

    "
     (Method compiledMethodAt:#printOn:) methodArgNames
    "

    "Modified: 31.10.1995 / 14:36:46 / cg"
!

methodComment
    "return the methods first comment, nil if there is none.
     This is a somewhat stupid implementation."

    |text line nQuote index qIndex qIndex2 comment|

    text := self source asCollectionOfLines.
    (text size < 2) ifTrue:[^nil].

    line := (text at:2).
    nQuote := line occurrencesOf:(Character doubleQuote).
    (nQuote == 2) ifTrue:[
	qIndex := line indexOf:(Character doubleQuote).
	qIndex2 := line indexOf:(Character doubleQuote) startingAt:(qIndex + 1).
	^ line copyFrom:(qIndex + 1) to:(qIndex2 - 1)
    ].
    (nQuote == 1) ifTrue:[
	qIndex := line indexOf:(Character doubleQuote).
	comment := line copyFrom:(qIndex + 1).

	index := 3.
	line := text at:index.
	nQuote := line occurrencesOf:(Character doubleQuote).
	[nQuote ~~ 1] whileTrue:[
	    comment := comment , Character cr asString , line withoutSpaces.
	    index := index + 1.
	    line := text at:index.
	    nQuote := line occurrencesOf:(Character doubleQuote)
	].
	qIndex := line indexOf:(Character doubleQuote).
	^ comment , Character cr asString , (line copyTo:(qIndex - 1)) withoutSpaces
    ].
    ^ nil

    "
     (Method compiledMethodAt:#methodComment) methodComment
    "
!

methodVarNames
    "return a collection with the methods local-variable names.
     Uses Parser to parse methods source and extract the names."

    ^ self parse:#'parseMethodArgAndVarSpecificationSilent:' return:#methodVars or:nil

    "
     (Method compiledMethodAt:#printOn:) methodVarNames
    "

    "Modified: 31.10.1995 / 14:36:49 / cg"
!

modificationTime
    "try to extract the modificationTime as a timeStamp from
     the receivers source. If there is no source or no history line, 
     we do not know the modification time, and nil is returned."

    |s list histLine|

    HistoryManager isNil ifTrue:[^ nil].

    s := self source.
    s isNil ifTrue:[^ nil].
    list := HistoryManager getAllHistoriesFrom:s.
    list size == 0 ifTrue:[^ nil].
    histLine := list last.
    ^ AbsoluteTime 
	fromDate:histLine date 
	andTime:histLine time

    "
     (Method compiledMethodAt:#modificationTime) modificationTime
     (Method compiledMethodAt:#isMethod) modificationTime 
    "

    "Modified: 8.9.1995 / 15:08:22 / claus"
    "Modified: 4.11.1996 / 22:28:17 / cg"
!

name
    "for compatibility with javaMethods"

    ^ self selector

    "Created: / 9.11.1998 / 06:15:08 / cg"
!

parse:parseSelector return:accessSelector or:valueIfNoSource 
    "helper for methodArgNames, methodVarNames etc.
     Get the source, let parser parse it using parseSelector,
     return parser-info using accessSelector"

    |parser sourceString|

    sourceString := self source.
    sourceString notNil ifTrue:[
        parser := Parser perform:parseSelector with:sourceString.
        (parser isNil or:[parser == #Error]) ifTrue:[^ valueIfNoSource].
        ^ parser perform:accessSelector
    ].
    ^ valueIfNoSource

    "
     (Method compiledMethodAt:#parse:return:or:)
        parse:#'parseMethodSilent:' return:#sentMessages or:#() 
    "
!

previousVersion
    |history entry|

    history := Class methodHistory.
    history isNil ifTrue:[^ nil].

    entry := history detect:[:entry | |type old new|
                                    type := entry first.
                                    type == #methodChange ifTrue:[
                                        old := entry second.
                                        new := entry third.
                                        new == self
                                    ] ifFalse:[
                                        false
                                    ]
                             ] 
                     ifNone:nil.
    entry isNil ifTrue:[^nil].
    ^ entry second.
"/    ^ history at:self ifAbsent:nil

    "Modified: 7.11.1996 / 19:06:22 / cg"
!

readsField:instVarIndex
    "return true, if the instvar at instVarIndex is read by the receiver.
     Uses parser (for now); could look at bytecode as well here..."

    |varName readInstVars|

    varName := (self mclass allInstVarNames) at:instVarIndex.
    readInstVars := self parse:#'parseMethodSilent:' return:#readInstVars or:#().
    ^ readInstVars includes:varName.
!

resourceType
    "ST-80 compatibility:
     return the methods first resource specs key; either nil, 
     or a single symbol containing in Method>>resourceTypes."

    |resources|

    (resources := self resources) notNil ifTrue:[
	resources keysAndValuesDo:[:key :val|
	    (self class resourceTypes includes:key) ifTrue:[^key]
	].
    ].
    ^ nil

    "Modified: / 22.4.1998 / 10:26:31 / cg"
!

resources
    "return the methods resource spec; either nil, a single symbol
     or a collection of symbols."

    |src parser|

    self hasResource ifFalse:[^ nil].

    src := self source.
    src isNil ifTrue:[
	^ nil "/ actually: dont know
    ].

    (src findString:'resource:') == 0 ifTrue:[
	^ nil "/ actually: error
    ].
    parser := Parser
		    parseMethod:src 
		    in:nil 
		    ignoreErrors:true 
		    ignoreWarnings:true.
    parser isNil ifTrue:[
	^ nil "/ actually error
    ].
    ^ parser primitiveResources.

    "Created: / 26.10.1997 / 16:23:18 / cg"
!

selector
    "return the selector under which I am found in my containingClasses
     method-table. 
     See comment in who."

    "based on who, which has been added for ST-80 compatibility"

    |who|

    who := self who.
    who notNil ifTrue:[^ who methodSelector].
    "
     none found - sorry
    "
    ^ nil

    "
     |m|
     m := Object compiledMethodAt:#at:.
     m selector
    "

    "Modified: 1.11.1996 / 16:25:48 / cg"
!

sends:aSelectorSymbol
    "return true, if this method contains a message-send
     with aSelectorSymbol as selector."

    (self referencesLiteral:aSelectorSymbol) ifTrue:[
        ^ self sentMessages includesIdentical:aSelectorSymbol
    ].
    ^ false
!

sentMessages
    "return a collection with the message selectors sent to by the receiver.
     Uses Parser to parse methods source and extract the names.
     The returned collection includes all used message selectors (i.e. including super-send messages)"

    ^ self parse:#'parseMethodSilent:' return:#sentMessages or:#() 

    "
     (Method compiledMethodAt:#printOn:) sentMessages
    "
!

sentSuperMessages
    "return a collection with the message selectors sent to super by the receiver.
     Uses Parser to parse methods source and extract the names."

    ^ self parse:#'parseMethodSilent:' return:#sentSuperMessages or:#() 


!

usedGlobals
    "return a collection with the global names referred to by the receiver.
     Uses Parser to parse methods source and extract them."

    ^ self parse:#'parseMethodSilent:' return:#usedGlobals or:#() 

    "
     (Method compiledMethodAt:#resources) usedGlobals 
    "
!

usedSymbols
    "return a collection with the symbols referred to by the receiver.
     Uses Parser to parse methods source and extract them.
     This collection only includes implicit symbols references (i.e. not
     messages sent)"

    ^ self parse:#'parseMethodSilent:' return:#usedSymbols or:#() 

    "
     (Method compiledMethodAt:#usedSymbols) usedSymbols 
    "
!

who
    "return the class and selector of where I am defined in;
     nil is returned for unbound methods.

     ST/X special notice: 
        returns an instance of MethodWhoInfo, which
        responds to #methodClass and #methodSelector query messages.
        For backward- (& ST-80) compatibility, the returned object also
        responds to #at:1 and #at:2 messages.

     Implementation notice:
        Since there is no information of the containing class 
        in the method, we have to do a search here.

        Normally, this is not a problem, except when a method is
        accepted in the debugger or redefined from within a method
        (maybe done indirectly, if #doIt is done recursively)
        - the information about which class the original method was 
        defined in is lost in this case.

     Problem: 
        this is heavily called for in the debugger to create
        a readable context walkback. For unbound methods, it is
        slow, since the search (over all classes) will always fail.

     Q: should we add a backref from the method to the class 
        and/or add a subclass of Method for unbound ones ?
     Q2: if so, what about the bad guy then, who copies methods around to
         other classes ?"

    |classes cls sel fn clsName|

    mclass notNil ifTrue:[
        sel := mclass selectorAtMethod:self.
        sel notNil ifTrue:[
            ^ MethodWhoInfo class:mclass selector:sel
        ].
    ].

    "
     speedup kludge: if my sourceFileName is valid,
     extract the className from it and try that class first.
    "
    (fn := self sourceFilename) notNil ifTrue:[
        clsName := fn asFilename withoutSuffix name.
        clsName := clsName asSymbolIfInterned.
        clsName notNil ifTrue:[
            cls := Smalltalk at:clsName ifAbsent:nil.
            cls notNil ifTrue:[
                sel := cls selectorAtMethod:self.
                sel notNil ifTrue:[
                    ^ MethodWhoInfo class:cls selector:sel
                ].

                cls := cls class.
                sel := cls selectorAtMethod:self.
                sel notNil ifTrue:[
                    ^ MethodWhoInfo class:cls selector:sel
                ].
            ]
        ].
    ].

    "
     then, look in the class we found something the last time
     this may often give a hit, when asking who repeatingly for
     a context chain. (keep last by its name, to not keep classes from
     being garbage collected)
    "
    LastWhoClass notNil ifTrue:[
        cls := Smalltalk at:LastWhoClass ifAbsent:nil.
        cls notNil ifTrue:[
            sel := cls selectorAtMethod:self.
            sel notNil ifTrue:[
                ^ MethodWhoInfo class:cls selector:sel
            ].

            cls := cls class.
            sel := cls selectorAtMethod:self.
            sel notNil ifTrue:[
                ^ MethodWhoInfo class:cls selector:sel
            ].
        ]
    ].

    "
     first, limit the search to global classes only - 
     since probability is high, that the receiver is found in there ...
    "
    classes := Smalltalk allClasses.
    "
     instance methods are usually more common - search those first
    "
    classes do:[:aClass |
        |sel|

        sel := aClass selectorAtMethod:self ifAbsent:nil.
        sel notNil ifTrue:[
            LastWhoClass := aClass theNonMetaclass name.
            ^ MethodWhoInfo class:aClass selector:sel
        ].
    ].

    classes do:[:aClass |
        |sel|

        sel := aClass class selectorAtMethod:self.
        sel notNil ifTrue:[ 
            LastWhoClass := aClass theNonMetaclass name.
            ^ MethodWhoInfo class:aClass class selector:sel
        ].
    ].

    LastWhoClass := nil.
    "
     mhmh - must be a method of some anonymous class (i.e. one not
     in the Smalltalk dictionary). Search all instances of Behavior
    "
    Behavior allSubInstancesDo:[:someClass |
        |sel|

        (classes includes:someClass) ifFalse:[
            sel := someClass selectorAtMethod:self.
            sel notNil ifTrue:[
                ^ MethodWhoInfo class:someClass selector:sel
            ]
        ]
    ].
    "
     none found - sorry
    "
    ^ nil

    "typical situation: some well-known class"
    "
     |m|
     m := Object compiledMethodAt:#copy.
     m who
    "

    "untypical situation: an anonymous class"
    "
     |m cls|

     Object 
        subclass:#FunnyClass 
        instanceVariableNames:'foo'
        classVariableNames:''
        poolDictionaries:''
        category:'testing'.
     cls := Smalltalk at:#FunnyClass.
     Smalltalk removeClass:cls.

     cls compile:'testMethod1:arg foo:=arg'.
     cls compile:'testMethod2 ^ foo'.
     m := cls compiledMethodAt:#testMethod1:.

     m who
    "

    "Modified: / 23.2.2000 / 11:32:49 / cg"
!

wrapper
    "only for wrapped methods: return the wrapper.
     Thats the WrapperMethod which contains myself."

    WrappedMethod allInstancesDo:[:m |
	m originalMethod == self ifTrue:[^ m].
    ].
    ^ nil
!

writesField:instVarIndex
    "return true, if the instvar at instVarIndex is written (modified) by the receiver.
     Uses parser (for now); could look at bytecode as well here..."

    |varName modifiedInstVars|

    varName := (self mclass allInstVarNames) at:instVarIndex.
    modifiedInstVars := self parse:#'parseMethodSilent:' return:#modifiedInstVars or:#().
    ^ modifiedInstVars includes:varName.
! !

!Method methodsFor:'trap methods'!

makeInvalid
    "make the receiver an invalid method, which raises an invalidCodeObject
     signal when executed. This is not for public use - it is required for
     the objectFileLoader to invalidate methods whose code is unloaded."

    |invldMethod|

    invldMethod := self trapMethodForNumArgs:(self numArgs).
    self code:invldMethod code.
    self byteCode:nil.

    "Created: 17.9.1995 / 15:00:52 / claus"
    "Modified: 4.11.1996 / 23:04:34 / cg"
!

makeUncompiled
    "make the receiver an uncompiled method, which raises an invalidCodeObject
     signal when executed. This is not for public use - it is required for
     the compiler to invalidate methods which cannot be compiled due to errors
     after a class definition change (for example: instvars are no longer there)."

    |invldMethod|

    invldMethod := self class compiledMethodAt:#uncompiledCodeObject.
    self code:invldMethod code.
    self byteCode:nil.

    "Created: 17.9.1995 / 15:01:14 / claus"
    "Modified: 4.11.1996 / 23:04:46 / cg"
!

makeUnloaded
    "make the receiver an unloaded method, which raises an invalidCodeObject
     signal when executed. This is not for public use - it is required for
     the objectFileLoader to invalidate methods for which a shared library has
     been removed."

    |invldMethod|

    invldMethod := self class compiledMethodAt:#unloadedCodeObject.
    self code:invldMethod code.
    self byteCode:nil.

    "Created: 4.11.1996 / 22:59:21 / cg"
    "Modified: 4.11.1996 / 23:04:52 / cg"
!

trapMethodForNumArgs:numArgs
    |trapSel|

    trapSel := #(
		  #'invalidCodeObject'
		  #'invalidCodeObjectWith:'
		  #'invalidCodeObjectWith:with:'
		  #'invalidCodeObjectWith:with:with:'
		  #'invalidCodeObjectWith:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with:with:'
		  #'invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with:with:with:'
		) at:(numArgs + 1).

    ^ Method compiledMethodAt:trapSel.

    "Created: 4.11.1996 / 21:58:58 / cg"
    "Modified: 4.11.1996 / 23:18:05 / cg"
! !

!Method::MethodWhoInfo class methodsFor:'documentation'!

documentation
"
    In earlier times, Method>>who returned an array filled
    with the methods class and selector.
    This was done, since a smalltalk method cannot return multiple
    values, but 2 values had to be returned from that method.
    Thus, the who-interface was used as:
	info := <someMethod> who.
	class := info at:1.
	sel := info at:2.

    Sure, this is ugly coding style, and the system has been changed to return
    an object (an instance of MethodWhoInfo) which responds to the two
    messages: #methodClass and #methodSelector.
    This allows to write things much more intuitive:
	info := <someMethod> who.
	class := info methodClass.
	sel := info methodSelector.

    However, to be backward compatible, the returned object still responds to
    the #at: message, but only allows inices of 1 and 2 to be used.

    The MethodWhoInfo class is private to Method - its not visible to other
    classes.

    [author:]
	Claus Gittinger

    [see also:]
	Method
"
! !

!Method::MethodWhoInfo class methodsFor:'instance creation'!

class:cls selector:sel
    "return a new MethodWhoInfo object;
     this is a private interface for Method"

    ^ self basicNew class:cls selector:sel

    "Modified: 2.1.1997 / 15:27:59 / cg"
! !

!Method::MethodWhoInfo methodsFor:'accessing'!

method
    ^ myClass compiledMethodAt:mySelector
!

methodClass
    "return the class which contains the method represented by myself"

    ^ myClass

    "
     (Method compiledMethodAt:#who) who methodClass
     (Method::MethodWhoInfo compiledMethodAt:#methodClass) who methodClass
    "

    "Modified: 2.1.1997 / 14:59:02 / cg"
!

methodSelector
    "return the selector under which the the method represented by myself
     is found in the class"

    ^ mySelector

    "Modified: 2.1.1997 / 14:59:24 / cg"
! !

!Method::MethodWhoInfo methodsFor:'compatibility'!

at:index
    "simulate the old behavior (when Method>>who returned an array)"

    index == 1 ifTrue:[
	^ myClass
    ].
    index == 2 ifTrue:[
	^ mySelector
    ].

    "/ sigh - full compatibility ?

    index isInteger ifFalse:[
	^ self indexNotInteger
    ].
    ^ self subscriptBoundsError:index

! !

!Method::MethodWhoInfo methodsFor:'private accessing'!

class:cls selector:sel
    myClass := cls.
    mySelector := sel


! !

!Method class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.204 2000-08-27 14:48:50 cg Exp $'
! !
Method initialize!