Method.st
changeset 5322 411b6c0f7250
parent 5294 f2d689cf7be4
child 5324 5c9959ce98af
--- a/Method.st	Fri Mar 24 12:53:57 2000 +0100
+++ b/Method.st	Fri Mar 24 12:54:44 2000 +0100
@@ -11,7 +11,7 @@
 "
 
 CompiledCode variableSubclass:#Method
-	instanceVariableNames:'source sourcePosition category package'
+	instanceVariableNames:'source sourcePosition category package mclass'
 	classVariableNames:'PrivateMethodSignal LastFileReference LastSourceFileName
 		LastWhoClass LastFileLock LastMethodSources CompilationLock'
 	poolDictionaries:''
@@ -71,26 +71,27 @@
 
     [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
-
+	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
+	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
+	Claus Gittinger
 "
 !
 
@@ -149,13 +150,13 @@
     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).
+	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).
 "
 ! !
 
@@ -165,16 +166,16 @@
     "create signals"
 
     PrivateMethodSignal isNil ifTrue:[
-        "EXPERIMENTAL"
-        PrivateMethodSignal := ExecutionErrorSignal newSignalMayProceed:true.
-        PrivateMethodSignal nameClass:self message:#privateMethodSignal.
-        PrivateMethodSignal notifierString:'attempt to execute private/protected method'.
+	"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.
+	LastFileLock := Semaphore forMutualExclusion name:'LastFileLock'.
+	LastFileReference := WeakArray new:1.
+	LastFileReference at:1 put:0.
     ].
 
     CompilationLock := Semaphore forMutualExclusion name:'MethodCompilation'.
@@ -313,7 +314,7 @@
     "set the methods category"
 
     aStringOrSymbol notNil ifTrue:[
-        category := aStringOrSymbol asSymbol
+	category := aStringOrSymbol asSymbol
     ]
 
     "Modified: / 13.11.1998 / 23:55:05 / cg"
@@ -335,14 +336,14 @@
     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 := 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.
 
@@ -388,16 +389,16 @@
     |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:(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].
+	aStream := fileName asFilename readStream.
+	aStream notNil ifTrue:[^ aStream].
     ].
     ^ nil
 !
@@ -410,9 +411,9 @@
      sourceCode is not lost."
 
     source notNil ifTrue:[
-        sourcePosition notNil ifTrue:[
-            self source:(self source)
-        ]
+	sourcePosition notNil ifTrue:[
+	    self source:(self source)
+	]
     ].
 !
 
@@ -444,40 +445,40 @@
     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.
-                ]
-            ].
-        ]
+	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.
+	LastMethodSources isNil ifTrue:[
+	    LastMethodSources := CacheDictionary new:20.
+	].
+	LastMethodSources at:self put:junk.
     ].
 
     ^ junk
@@ -547,24 +548,24 @@
     "/ 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 := 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
+	LastSourceFileName := source.
+	LastFileReference at:1 put:aStream.
+	^ aStream
     ].
 
     "/ a negative sourcePosition indicates
@@ -575,34 +576,34 @@
     "/ 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
-            ].
-        ].
+	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
-        ].
+	aStream := self localSourceStream.
+	aStream notNil ifTrue:[
+	    LastSourceFileName := source.
+	    LastFileReference at:1 put:aStream.
+	    ^ aStream
+	].
     ].
 
     "/
@@ -610,31 +611,31 @@
     "/
     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
-        ].
+	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
+	].
     ].
 
     "/
@@ -642,46 +643,46 @@
     "/ (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
-        ].
+	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
-        ].
+	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
-                ].
-            ]
-        ]
+	"/
+	"/ 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
@@ -806,18 +807,18 @@
 
 # ifdef F_PRIVATE
     case F_PRIVATE:
-        RETURN (@symbol(private));
-        break;
+	RETURN (@symbol(private));
+	break;
 # endif
 # ifdef F_CLASSPRIVATE
     case F_CLASSPRIVATE:
-        RETURN (@symbol(protected));
-        break;
+	RETURN (@symbol(protected));
+	break;
 # endif
 # ifdef F_IGNORED
     case F_IGNORED:
-        RETURN (@symbol(ignored));
-        break;
+	RETURN (@symbol(ignored));
+	break;
 # endif
     }
 #endif
@@ -848,7 +849,7 @@
     "/ no need to flush, if changing from private to public
     "/
     (aSymbol == #public and:[old ~~ #ignored]) ifFalse:[
-        ObjectMemory flushCaches.
+	ObjectMemory flushCaches.
     ]
 
     "Modified: / 27.8.1995 / 22:58:08 / claus"
@@ -915,15 +916,15 @@
     INT p;
 
     if (aSymbol == @symbol(public))
-        p = 0;
+	p = 0;
     else if (aSymbol == @symbol(private))
-        p = F_PRIVATE;
+	p = F_PRIVATE;
     else if (aSymbol == @symbol(protected))
-        p = F_CLASSPRIVATE;
+	p = F_CLASSPRIVATE;
     else if (aSymbol == @symbol(ignored))
-        p = F_IGNORED;
+	p = F_IGNORED;
     else
-        RETURN(false);  /* illegal symbol */
+	RETURN(false);  /* illegal symbol */
         
 
     f = (f & ~M_PRIVACY) | p;
@@ -981,21 +982,21 @@
     |temporaryMethod cls sourceString silent lazy|
 
     byteCode notNil ifTrue:[
-        "
-         is already a bytecoded method
-        "
-        ^ self
+	"
+	 is already a bytecoded method
+	"
+	^ self
     ].
 
     cls := self containingClass.
     cls isNil ifTrue:[
-        'Method [warning]: cannot generate bytecode (no class for compilation)' errorPrintCR.
-        ^ nil
+	'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
+	'Method [warning]: cannot generate bytecode (no source for compilation)' errorPrintCR.
+	^ nil
     ].
 
     "we have to sequentialize this using a lock-semaphore,
@@ -1005,51 +1006,51 @@
      (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:skipIfSame:)
-                    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.
-            ]
-        ].
+	"
+	 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:skipIfSame:)
+		    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.
+	'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)
@@ -1063,8 +1064,8 @@
 
 readBinaryContentsFrom: stream manager: manager
     self hasCode ifTrue:[
-        "built-in method - already complete"
-        ^ self
+	"built-in method - already complete"
+	^ self
     ].
 
     ^ super readBinaryContentsFrom: stream manager: manager
@@ -1087,26 +1088,26 @@
     |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
+	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.
@@ -1638,62 +1639,62 @@
     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 := ' !!'
-            ]
-        ].
+	(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.
+	privInfo := (' (* ' , p , ' *)') asText emphasizeAllWith:#italic.
     ].
 
     self isInvalid ifTrue:[
-        moreInfo := ' (** not executable **)'.
+	moreInfo := ' (** not executable **)'.
     ].
 
     (self isLazyMethod not and:[self isUnloaded]) ifTrue:[
-        moreInfo := ' (** unloaded **)'
+	moreInfo := ' (** unloaded **)'
     ].
 
     privInfo size ~~ 0 ifTrue:[
-        moreInfo := privInfo , ' ' , moreInfo
+	moreInfo := privInfo , ' ' , moreInfo
     ].
 
     s := selector.
     (cls := aClass) isNil ifTrue:[
-        cls := self containingClass
+	cls := self containingClass
     ].
     self package ~= cls package ifTrue:[
-        s := s , ' [' , (self package asText emphasizeAllWith:#italic), ']'
+	s := s , ' [' , (self package asText emphasizeAllWith:#italic), ']'
     ].
 
     moreInfo size == 0 ifTrue:[^ s].
@@ -1701,7 +1702,7 @@
     s := selector , moreInfo.
 
     self isInvalid ifTrue:[
-        s := s asText emphasizeAllWith:#color->Color red.
+	s := s asText emphasizeAllWith:#color->Color red.
     ].
     ^ s
 
@@ -2095,9 +2096,9 @@
     |resources|
 
     (resources := self resources) notNil ifTrue:[
-        resources keysAndValuesDo:[:key :val|
-            (self class resourceTypes includes:key) ifTrue:[^key]
-        ].
+	resources keysAndValuesDo:[:key :val|
+	    (self class resourceTypes includes:key) ifTrue:[^key]
+	].
     ].
     ^ nil
 
@@ -2114,19 +2115,19 @@
 
     src := self source.
     src isNil ifTrue:[
-        ^ nil "/ actually: dont know
+	^ nil "/ actually: dont know
     ].
 
     (src findString:'resource:') == 0 ifTrue:[
-        ^ nil "/ actually: error
+	^ nil "/ actually: error
     ].
     parser := Parser
-                    parseMethod:src 
-                    in:nil 
-                    ignoreErrors:true 
-                    ignoreWarnings:true.
+		    parseMethod:src 
+		    in:nil 
+		    ignoreErrors:true 
+		    ignoreWarnings:true.
     parser isNil ifTrue:[
-        ^ nil "/ actually error
+	^ nil "/ actually error
     ].
     ^ parser primitiveResources.
 
@@ -2163,30 +2164,30 @@
      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.
+	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.
+	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.
+	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 ?
+	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 ?"
+	 other classes ?"
 
     |classes cls sel fn clsName|
 
@@ -2195,23 +2196,23 @@
      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
-                ].
-            ]
-        ].
+	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
+		].
+	    ]
+	].
     ].
 
     "
@@ -2221,19 +2222,19 @@
      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
-            ].
-        ]
+	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
+	    ].
+	]
     ].
 
     "
@@ -2245,23 +2246,23 @@
      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
-        ].
+	|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
-        ].
+	|sel|
+
+	sel := aClass class selectorAtMethod:self.
+	sel notNil ifTrue:[ 
+	    LastWhoClass := aClass theNonMetaclass name.
+	    ^ MethodWhoInfo class:aClass class selector:sel
+	].
     ].
 
     LastWhoClass := nil.
@@ -2270,14 +2271,14 @@
      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
-            ]
-        ]
+	|sel|
+
+	(classes includes:someClass) ifFalse:[
+	    sel := someClass selectorAtMethod:self.
+	    sel notNil ifTrue:[
+		^ MethodWhoInfo class:someClass selector:sel
+	    ]
+	]
     ].
     "
      none found - sorry
@@ -2296,11 +2297,11 @@
      |m cls|
 
      Object 
-        subclass:#FunnyClass 
-        instanceVariableNames:'foo'
-        classVariableNames:''
-        poolDictionaries:''
-        category:'testing'.
+	subclass:#FunnyClass 
+	instanceVariableNames:'foo'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'testing'.
      cls := Smalltalk at:#FunnyClass.
      Smalltalk removeClass:cls.
 
@@ -2508,6 +2509,6 @@
 !Method class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.185 2000-03-10 18:12:34 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.186 2000-03-24 11:54:40 cg Exp $'
 ! !
 Method initialize!