changed: #annotationAtIndex:
authorClaus Gittinger <cg@exept.de>
Fri, 09 Sep 2011 06:17:24 +0200
changeset 13662 7d7ae1e5f589
parent 13661 8ad7c057fa25
child 13663 5e08299c39f1
changed: #annotationAtIndex:
Method.st
--- a/Method.st	Thu Sep 08 14:38:59 2011 +0200
+++ b/Method.st	Fri Sep 09 06:17:24 2011 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-	      All Rights Reserved
+              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
@@ -12,34 +12,34 @@
 "{ Package: 'stx:libbasic' }"
 
 CompiledCode variableSubclass:#Method
-	instanceVariableNames:'source sourcePosition category package mclass lookupObject
-		annotations'
-	classVariableNames:'PrivateMethodSignal LastFileReference LastSourceFileName
-		LastWhoClass LastFileLock LastMethodSources LastMethodSourcesLock
-		CompilationLock Overrides LastParseTreeCache'
-	poolDictionaries:''
-	category:'Kernel-Methods'
+        instanceVariableNames:'source sourcePosition category package mclass lookupObject
+                annotations'
+        classVariableNames:'PrivateMethodSignal LastFileReference LastSourceFileName
+                LastWhoClass LastFileLock LastMethodSources LastMethodSourcesLock
+                CompilationLock Overrides LastParseTreeCache'
+        poolDictionaries:''
+        category:'Kernel-Methods'
 !
 
 Object subclass:#MethodWhoInfo
-	instanceVariableNames:'myClass mySelector'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Method
+        instanceVariableNames:'myClass mySelector'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Method
 !
 
 Object subclass:#ParseTreeCacheEntry
-	instanceVariableNames:'parserClass method parser'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Method
+        instanceVariableNames:'parserClass method parser'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Method
 !
 
 Object subclass:#ParserCacheEntry
-	instanceVariableNames:'parserClass method parser'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Method
+        instanceVariableNames:'parserClass method parser'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Method
 !
 
 !Method class methodsFor:'documentation'!
@@ -47,7 +47,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-	      All Rights Reserved
+              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
@@ -88,27 +88,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
-	mclass          <Class>         the class in which I am defined
-	indexed slots                   literals
+        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
 "
 !
 
@@ -167,13 +167,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).
 "
 ! !
 
@@ -183,23 +183,23 @@
     "create signals"
 
     PrivateMethodSignal isNil ifTrue:[
-	"EXPERIMENTAL"
-	PrivateMethodSignal := ExecutionError newSignalMayProceed:true.
-	PrivateMethodSignal nameClass:self message:#privateMethodSignal.
-	PrivateMethodSignal notifierString:'attempt to execute private/protected method'.
+        "EXPERIMENTAL"
+        PrivateMethodSignal := ExecutionError newSignalMayProceed:true.
+        PrivateMethodSignal nameClass:self message:#privateMethodSignal.
+        PrivateMethodSignal notifierString:'attempt to execute private/protected method'.
     ].
 
     LastFileLock isNil ifTrue:[
-	LastFileLock := RecursionLock new name:'Method-LastFile'.
-	LastMethodSourcesLock := RecursionLock new name:'Method-LastMethodSources'.
-
-	"LastFileReference used to be a WeakArray. The problem was, that
-	 during some operations (generating project definition methods), lots of
-	 methods and classes are accessed. GC (scavenge) is done heavily,
-	 while finalization is a low prio process, so that the file limit
-	 is reached before finalization did close the old streams."
-	LastFileReference := Array new:1.
-	LastFileReference at:1 put:nil.
+        LastFileLock := RecursionLock new name:'Method-LastFile'.
+        LastMethodSourcesLock := RecursionLock new name:'Method-LastMethodSources'.
+
+        "LastFileReference used to be a WeakArray. The problem was, that
+         during some operations (generating project definition methods), lots of
+         methods and classes are accessed. GC (scavenge) is done heavily,
+         while finalization is a low prio process, so that the file limit
+         is reached before finalization did close the old streams."
+        LastFileReference := Array new:1.
+        LastFileReference at:1 put:nil.
     ].
 
     CompilationLock := RecursionLock new name:'MethodCompilation'.
@@ -210,7 +210,7 @@
 
 lastMethodSourcesLock
     LastMethodSourcesLock isNil ifTrue:[
-	self initialize
+        self initialize
     ].
     ^ LastMethodSourcesLock
 ! !
@@ -251,13 +251,13 @@
     |nA argNames|
 
     (nA := aSelector numArgs) == 1 ifTrue:[
-	argNames := #('arg')
+        argNames := #('arg')
     ] ifFalse:[
-	argNames := (1 to:nA) collect:[:i | 'arg' , i printString].
+        argNames := (1 to:nA) collect:[:i | 'arg' , i printString].
     ].
     ^ self
-	methodDefinitionTemplateForSelector:aSelector
-	andArgumentNames:argNames.
+        methodDefinitionTemplateForSelector:aSelector
+        andArgumentNames:argNames.
 
     "
      Method methodDefinitionTemplateForSelector:#foo
@@ -270,15 +270,15 @@
     "given a selector, return a prototype definition string"
 
     aSelector numArgs > 0 ifTrue:[
-	aSelector isKeyword ifTrue:[
-	    ^ String streamContents:[:stream |
-		aSelector keywords with:argNames do:[:eachKeyword :eachArgName|
-		    stream nextPutAll:eachKeyword; nextPutAll:eachArgName; space.
-		].
-		stream backStep.   "remove the last space"
-	     ].
-	].
-	^ aSelector , ' ' , (argNames at:1)
+        aSelector isKeyword ifTrue:[
+            ^ String streamContents:[:stream |
+                aSelector keywords with:argNames do:[:eachKeyword :eachArgName|
+                    stream nextPutAll:eachKeyword; nextPutAll:eachArgName; space.
+                ].
+                stream backStep.   "remove the last space"
+             ].
+        ].
+        ^ aSelector , ' ' , (argNames at:1)
     ].
     ^ aSelector
 
@@ -312,8 +312,8 @@
 
 flushSourceStreamCache
     LastFileLock critical:[
-	LastSourceFileName := LastMethodSources := nil.
-	LastFileReference at:1 put:0.
+        LastSourceFileName := LastMethodSources := nil.
+        LastFileReference at:1 put:0.
     ].
 
     "
@@ -329,23 +329,23 @@
     |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).
+                  #'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).
 
     ^ self compiledMethodAt:trapSel.
 
@@ -385,18 +385,18 @@
     | index |
     index := self annotationIndexOf: annotation key.
     index
-	ifNil:
-	    [annotations := annotations
-				ifNil:[Array with: annotation]
-				ifNotNil:[annotations copyWith:annotation]]
-	ifNotNil:
-	    [annotations at: index put: annotation].
+        ifNil:
+            [annotations := annotations
+                                ifNil:[Array with: annotation]
+                                ifNotNil:[annotations copyWith:annotation]]
+        ifNotNil:
+            [annotations at: index put: annotation].
 "/    annotation annotatesMethod: self.
 
     "
-	(Object >> #yourself) annotateWith: (Annotation namespace: 'Fictious').
-	(Object >> #yourself) annotations.
-	(Object >> #yourself) annotationAt: #namespace:
+        (Object >> #yourself) annotateWith: (Annotation namespace: 'Fictious').
+        (Object >> #yourself) annotations.
+        (Object >> #yourself) annotationAt: #namespace:
     "
 
     "Created: / 19-05-2010 / 16:20:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -412,7 +412,7 @@
     ^self annotationAtIndex: index.
 
     "
-	(Object >> #yourself) annotationAt: #namespace:
+        (Object >> #yourself) annotationAt: #namespace:
     "
 
     "Created: / 19-05-2010 / 16:16:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -446,9 +446,9 @@
 annotationsAt: key
 
     ^OrderedCollection streamContents:
-	[:annotStream|
-	self annotationsAt: key do:
-	    [:annot|annotStream nextPut: annot]]
+        [:annotStream|
+        self annotationsAt: key do:
+            [:annot|annotStream nextPut: annot]]
 
     "Created: / 16-07-2010 / 11:41:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -458,9 +458,9 @@
     | annots |
     annots := OrderedCollection new: 1.
     self annotationsDo:
-	[:annot|
-	annot key == key ifTrue:
-	    [block value: annot]]
+        [:annot|
+        annot key == key ifTrue:
+            [block value: annot]]
 
     "Created: / 16-07-2010 / 11:48:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -468,9 +468,9 @@
 annotationsAt: key1 orAt: key2
 
     ^OrderedCollection streamContents:
-	[:annotStream|
-	self annotationsAt: key1 orAt: key2 do:
-	    [:annot|annotStream nextPut: annot]]
+        [:annotStream|
+        self annotationsAt: key1 orAt: key2 do:
+            [:annot|annotStream nextPut: annot]]
 
     "Created: / 16-07-2010 / 11:41:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -480,9 +480,9 @@
     | annots |
     annots := OrderedCollection new: 1.
     self annotationsDo:
-	[:annot|
-	(annot key == key1 or:[annot key == key2]) ifTrue:
-	    [block value: annot]]
+        [:annot|
+        (annot key == key1 or:[annot key == key2]) ifTrue:
+            [block value: annot]]
 
     "Created: / 16-07-2010 / 11:47:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -491,7 +491,7 @@
 
     annotations ifNil:[^nil].
     1 to: annotations size do:
-	[:i|aBlock value: (self annotationAtIndex: i)].
+        [:i|aBlock value: (self annotationAtIndex: i)].
 
     "Created: / 02-07-2010 / 22:33:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 11-07-2010 / 19:38:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -509,18 +509,18 @@
     |newCategory oldCategory cls|
 
     aStringOrSymbol notNil ifTrue:[
-	newCategory := aStringOrSymbol.
-	newCategory ~= (oldCategory := category) ifTrue:[
-	    self setCategory:newCategory.
-
-	    cls := self mclass.
-	    cls notNil ifTrue:[
-		cls addChangeRecordForMethodCategory:self category:newCategory.
-		self changed:#category with:oldCategory.            "/ will vanish
-		cls changed:#organization with:self selector.       "/ will vanish
-		Smalltalk changed:#methodCategory with:(Array with:cls with:self with:oldCategory).
-	    ]
-	]
+        newCategory := aStringOrSymbol.
+        newCategory ~= (oldCategory := category) ifTrue:[
+            self setCategory:newCategory.
+
+            cls := self mclass.
+            cls notNil ifTrue:[
+                cls addChangeRecordForMethodCategory:self category:newCategory.
+                self changed:#category with:oldCategory.            "/ will vanish
+                cls changed:#organization with:self selector.       "/ will vanish
+                Smalltalk changed:#methodCategory with:(Array with:cls with:self with:oldCategory).
+            ]
+        ]
     ]
 
     "Modified: / 25-09-2007 / 16:15:24 / cg"
@@ -602,12 +602,12 @@
      sourceCode is not lost."
 
     source notNil ifTrue:[
-	sourcePosition notNil ifTrue:[
-	    "/ this looks wierd - but (self source) will retrieve the external source
-	    "/ (from the file) and store it. So afterwards, we will have the string and
-	    "/ sourcePosition will be nil
-	    self source:(self source)
-	]
+        sourcePosition notNil ifTrue:[
+            "/ this looks wierd - but (self source) will retrieve the external source
+            "/ (from the file) and store it. So afterwards, we will have the string and
+            "/ sourcePosition will be nil
+            self source:(self source)
+        ]
     ].
 !
 
@@ -637,12 +637,12 @@
     nsA ifNotNil:[^nsA nameSpace].
 
     ^(lang := self programmingLanguage) isSmalltalk
-	ifTrue:[nil]
-	ifFalse:[lang].
+        ifTrue:[nil]
+        ifFalse:[lang].
 
     "
-	(Method >> #nameSpace) nameSpace
-	(Object >> #yourself) nameSpace
+        (Method >> #nameSpace) nameSpace
+        (Object >> #yourself) nameSpace
 
     "
 
@@ -662,8 +662,8 @@
 
     | ns |
     ^(ns := self nameSpace)
-	ifNotNil:[ns name]
-	ifNil:['']
+        ifNotNil:[ns name]
+        ifNil:['']
 !
 
 originalMethodIfWrapped
@@ -680,7 +680,7 @@
 
     Overrides ifNil:[^nil].
     ^(Overrides includesKey: self)
-	ifTrue:[Overrides at: self]
+        ifTrue:[Overrides at: self]
 
     "Created: / 17-06-2009 / 19:09:58 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
@@ -704,12 +704,12 @@
 
     package notNil ifTrue:[ ^ package ].
     (cls := self mclass) isNil ifTrue:[
-	^ PackageId noProjectID.
+        ^ PackageId noProjectID.
     ].
     "/ set it.
     package := cls getPackage.
     package isNil ifTrue:[
-	^ PackageId noProjectID.
+        ^ PackageId noProjectID.
     ].
     ^ package
 
@@ -722,25 +722,25 @@
     |cls oldPackage newPackage|
 
     aSymbol == PackageId noProjectID ifTrue:[
-	newPackage := nil
+        newPackage := nil
     ] ifFalse:[
-	newPackage := aSymbol
+        newPackage := aSymbol
     ].
 
     package ~~ newPackage ifTrue:[
-	oldPackage := package.
-	"/ this is required, because otherwise I would no longer be able to
-	"/ reconstruct my sourcecode (as the connection to the source-file is lost).
-	self makeLocalStringSource.
-	package := newPackage.
-
-	cls := self mclass.
-
-	self changed:#package.                                              "/ will vanish
-	cls changed:#methodPackage with:self selector.                      "/ will vanish
-
-	Smalltalk changed:#projectOrganization with:(Array with:cls with:self with:oldPackage).
-	cls addChangeRecordForMethodPackage:self package:newPackage.
+        oldPackage := package.
+        "/ this is required, because otherwise I would no longer be able to
+        "/ reconstruct my sourcecode (as the connection to the source-file is lost).
+        self makeLocalStringSource.
+        package := newPackage.
+
+        cls := self mclass.
+
+        self changed:#package.                                              "/ will vanish
+        cls changed:#methodPackage with:self selector.                      "/ will vanish
+
+        Smalltalk changed:#projectOrganization with:(Array with:cls with:self with:oldPackage).
+        cls addChangeRecordForMethodPackage:self package:newPackage.
     ]
 
     "Modified: / 23-11-2006 / 17:01:02 / cg"
@@ -758,7 +758,7 @@
     "set the methods category (without change notification)"
 
     aStringOrSymbol notNil ifTrue:[
-	category := aStringOrSymbol asSymbol
+        category := aStringOrSymbol asSymbol
     ]
 
     "Modified: / 13.11.1998 / 23:55:05 / cg"
@@ -784,68 +784,68 @@
     source isNil ifTrue:[^ nil].
 
     self class lastMethodSourcesLock critical:[
-	LastMethodSources notNil ifTrue:[
-	    chunk := LastMethodSources at:self ifAbsent:nil.
-	].
+        LastMethodSources notNil ifTrue:[
+            chunk := LastMethodSources at:self ifAbsent:nil.
+        ].
     ].
     chunk notNil ifTrue:[
-	^ chunk
+        ^ chunk
     ].
 
     LastFileLock
-	critical:[
-	    "have to protect sourceStream from being closed as a side effect
-	     of some other process fetching some the source from a different source file"
-
-	    sourceStream := self sourceStreamUsingCache:true.
-	    sourceStream notNil ifTrue:[
-		[
-		    chunk := self sourceChunkFromStream:sourceStream.
-		] on:DecodingError do:[:ex|
-		    "CharacterEncoder>>#guessEncoding is not fail safe - retry with plain unencoded data"
-
-		    ('DecodingError ignored when reading <1p> (<2p>)' expandMacrosWith:self whoString with:ex description) infoPrintCR.
-		    sourceStream := self rawSourceStreamUsingCache:true.
-		    ex restart.
-		].
-	    ].
-	]
-	timeoutMs:100
-	ifBlocking:[
-	    "take care if LastFileLock is not available - maybe we are
-	     called by a debugger while someone holds the lock.
-	     Use uncached source streams"
-	    sourceStream := self sourceStreamUsingCache:false.
-	    sourceStream notNil ifTrue:[
-		[
-		    chunk := self sourceChunkFromStream:sourceStream.
-		    sourceStream close.
-		] on:DecodingError do:[:ex|
-		    "CharacterEncoder>>#guessEncoding is not fail safe - retry with plain unencoded data"
-		    ('DecodingError ignored when reading <1p> (<2p>)' expandMacrosWith:self whoString with:ex description) infoPrintCR.
-		    sourceStream close.
-		    sourceStream := self rawSourceStreamUsingCache:false.
-		    ex restart.
-		].
-	    ].
-	].
+        critical:[
+            "have to protect sourceStream from being closed as a side effect
+             of some other process fetching some the source from a different source file"
+
+            sourceStream := self sourceStreamUsingCache:true.
+            sourceStream notNil ifTrue:[
+                [
+                    chunk := self sourceChunkFromStream:sourceStream.
+                ] on:DecodingError do:[:ex|
+                    "CharacterEncoder>>#guessEncoding is not fail safe - retry with plain unencoded data"
+
+                    ('DecodingError ignored when reading <1p> (<2p>)' expandMacrosWith:self whoString with:ex description) infoPrintCR.
+                    sourceStream := self rawSourceStreamUsingCache:true.
+                    ex restart.
+                ].
+            ].
+        ]
+        timeoutMs:100
+        ifBlocking:[
+            "take care if LastFileLock is not available - maybe we are
+             called by a debugger while someone holds the lock.
+             Use uncached source streams"
+            sourceStream := self sourceStreamUsingCache:false.
+            sourceStream notNil ifTrue:[
+                [
+                    chunk := self sourceChunkFromStream:sourceStream.
+                    sourceStream close.
+                ] on:DecodingError do:[:ex|
+                    "CharacterEncoder>>#guessEncoding is not fail safe - retry with plain unencoded data"
+                    ('DecodingError ignored when reading <1p> (<2p>)' expandMacrosWith:self whoString with:ex description) infoPrintCR.
+                    sourceStream close.
+                    sourceStream := self rawSourceStreamUsingCache:false.
+                    ex restart.
+                ].
+            ].
+        ].
 
     "Cache the source of recently used methods"
     chunk notNil ifTrue:[
-	UserPreferences current keepMethodSourceCode ifTrue:[
-	    source := chunk.
-	    sourcePosition := nil.
-	    ^ source.
-	].
-
-	CacheDictionary notNil ifTrue:[
-	    self class lastMethodSourcesLock critical:[
-		LastMethodSources isNil ifTrue:[
-		    LastMethodSources := CacheDictionary new:50.
-		].
-		LastMethodSources at:self put:chunk.
-	    ]
-	].
+        UserPreferences current keepMethodSourceCode ifTrue:[
+            source := chunk.
+            sourcePosition := nil.
+            ^ source.
+        ].
+
+        CacheDictionary notNil ifTrue:[
+            self class lastMethodSourcesLock critical:[
+                LastMethodSources isNil ifTrue:[
+                    LastMethodSources := CacheDictionary new:50.
+                ].
+                LastMethodSources at:self put:chunk.
+            ]
+        ].
     ].
 
     ^ chunk
@@ -983,7 +983,7 @@
     INT f = __intVal(__INST(flags));
 
     if (f & F_RESTRICTED) {
-	RETURN (true);
+        RETURN (true);
     }
 #endif
 %}.
@@ -1014,15 +1014,15 @@
     INT p;
 
     if (aSymbol == @symbol(public))
-	p = 0;
+        p = 0;
     else if (aSymbol == @symbol(protected))
-	p = F_PRIVATE;
+        p = F_PRIVATE;
     else if (aSymbol == @symbol(private))
-	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;
@@ -1060,18 +1060,18 @@
 
 # ifdef F_PRIVATE
     case F_PRIVATE:
-	RETURN (@symbol(protected));
-	break;
+        RETURN (@symbol(protected));
+        break;
 # endif
 # ifdef F_CLASSPRIVATE
     case F_CLASSPRIVATE:
-	RETURN (@symbol(private));
-	break;
+        RETURN (@symbol(private));
+        break;
 # endif
 # ifdef F_IGNORED
     case F_IGNORED:
-	RETURN (@symbol(ignored));
-	break;
+        RETURN (@symbol(ignored));
+        break;
 # endif
     }
 #endif
@@ -1098,19 +1098,19 @@
     oldPrivacy := self privacy.
 
     (self setPrivacy:aSymbol flushCaches:true) ifTrue:[
-	|myClass mySelector|
-
-	myClass := self mclass.
-	mySelector := self selector.
-
-	self changed:#privacy.                                       "/ will vanish
-	myClass notNil ifTrue:[
-	    mySelector notNil ifTrue:[
-		myClass changed:#methodPrivacy with:mySelector.      "/ will vanish
-		Smalltalk changed:#privacyOfMethod with:(Array with:myClass with:self with:oldPrivacy).
-		myClass addChangeRecordForMethodPrivacy:self.
-	    ]
-	]
+        |myClass mySelector|
+
+        myClass := self mclass.
+        mySelector := self selector.
+
+        self changed:#privacy.                                       "/ will vanish
+        myClass notNil ifTrue:[
+            mySelector notNil ifTrue:[
+                myClass changed:#methodPrivacy with:mySelector.      "/ will vanish
+                Smalltalk changed:#privacyOfMethod with:(Array with:myClass with:self with:oldPrivacy).
+                myClass addChangeRecordForMethodPrivacy:self.
+            ]
+        ]
     ]
 
     "Modified: / 23-11-2006 / 17:03:20 / cg"
@@ -1137,12 +1137,12 @@
 
     old = f;
     if (aBoolean == true)
-	f |= F_RESTRICTED;
+        f |= F_RESTRICTED;
     else
-	f &= ~F_RESTRICTED;
+        f &= ~F_RESTRICTED;
     __INST(flags) = __mkSmallInteger(f);
     if (old & F_RESTRICTED)
-	RETURN(true);
+        RETURN(true);
 #endif
 %}.
     ^ false
@@ -1197,13 +1197,13 @@
     "/ no need to flush, if changing from private to public
     "/
     doFlush ifTrue:[
-	(aSymbol == #public and:[old ~~ #ignored]) ifFalse:[
-	    (sel := self selector) notNil ifTrue:[
-		ObjectMemory flushCachesForSelector:sel
-	    ] ifFalse:[
-		ObjectMemory flushCaches.
-	    ].
-	].
+        (aSymbol == #public and:[old ~~ #ignored]) ifFalse:[
+            (sel := self selector) notNil ifTrue:[
+                ObjectMemory flushCachesForSelector:sel
+            ] ifFalse:[
+                ObjectMemory flushCaches.
+            ].
+        ].
     ].
     ^ true
 ! !
@@ -1224,17 +1224,17 @@
     |mthd|
 
     byteCode notNil ifTrue:[
-	"
-	 is already a bytecoded method
-	"
-	^ self
+        "
+         is already a bytecoded method
+        "
+        ^ self
     ].
 
     ParserFlags
-	withSTCCompilation:#never
-	do:[
-	    mthd := self asExecutableMethod.
-	].
+        withSTCCompilation:#never
+        do:[
+            mthd := self asExecutableMethod.
+        ].
     ^ mthd
 
     "Created: 24.10.1995 / 14:02:32 / cg"
@@ -1245,10 +1245,10 @@
     |mthd|
 
     ParserFlags
-	withSTCCompilation:#never
-	do:[
-	    mthd := self asExecutableMethodWithSource:newSource.
-	].
+        withSTCCompilation:#never
+        do:[
+            mthd := self asExecutableMethodWithSource:newSource.
+        ].
     ^ mthd
 
     "Created: 24.10.1995 / 14:02:32 / cg"
@@ -1267,23 +1267,23 @@
     |temporaryMethod sourceString|
 
     byteCode notNil ifTrue:[
-	"
-	 is already a bytecoded method
-	"
-	^ self
+        "
+         is already a bytecoded method
+        "
+        ^ self
     ].
 
     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
     ].
 
     temporaryMethod := self asExecutableMethodWithSource:sourceString.
 
     (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)
@@ -1297,8 +1297,8 @@
 
     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
     ].
 
     "we have to sequentialize this using a lock-semaphore,
@@ -1308,53 +1308,53 @@
      (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 lazy|
-
-	    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
-		    ].
-		].
-	    ] ensure:[
-		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 lazy|
+
+            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
+                    ].
+                ].
+            ] ensure:[
+                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)
@@ -1377,7 +1377,7 @@
 
     aCopy := super copy.
     sourcePosition notNil ifTrue:[
-	aCopy source:(self source)
+        aCopy source:(self source)
     ].
     aCopy mclass:nil.
     ^ aCopy
@@ -1410,7 +1410,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Modified: 4.11.1996 / 22:45:06 / cg"
 !
@@ -1429,7 +1429,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:16:41 / cg"
     "Modified: 4.11.1996 / 22:45:15 / cg"
@@ -1449,7 +1449,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:16:51 / cg"
     "Modified: 4.11.1996 / 22:45:18 / cg"
@@ -1469,7 +1469,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:00 / cg"
     "Modified: 4.11.1996 / 22:45:22 / cg"
@@ -1489,7 +1489,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:09 / cg"
     "Modified: 4.11.1996 / 22:45:25 / cg"
@@ -1509,7 +1509,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:17 / cg"
     "Modified: 4.11.1996 / 22:45:28 / cg"
@@ -1529,7 +1529,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:25 / cg"
     "Modified: 4.11.1996 / 22:45:31 / cg"
@@ -1549,7 +1549,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:32 / cg"
     "Modified: 4.11.1996 / 22:45:38 / cg"
@@ -1569,7 +1569,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:37 / cg"
     "Modified: 4.11.1996 / 22:45:41 / cg"
@@ -1589,7 +1589,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:45 / cg"
     "Modified: 4.11.1996 / 22:45:44 / cg"
@@ -1609,7 +1609,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:52 / cg"
     "Modified: 4.11.1996 / 22:45:47 / cg"
@@ -1629,7 +1629,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 20:51:28 / cg"
     "Modified: 4.11.1996 / 22:46:01 / cg"
@@ -1649,7 +1649,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:18:09 / cg"
     "Modified: 4.11.1996 / 22:45:57 / cg"
@@ -1669,7 +1669,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:18:17 / cg"
     "Modified: 4.11.1996 / 22:45:55 / cg"
@@ -1689,7 +1689,7 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseErrorString:'invalid method - not executable'.
+        raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:18:22 / cg"
     "Modified: 4.11.1996 / 22:45:52 / cg"
@@ -1738,8 +1738,8 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseRequestWith:self
-	errorString:'invalid method - not compiled'.
+        raiseRequestWith:self
+        errorString:'invalid method - not compiled'.
 
     "Modified: 4.11.1996 / 22:58:02 / cg"
 !
@@ -1758,8 +1758,8 @@
      */
 %}.
     ^ InvalidCodeError
-	raiseRequestWith:self
-	errorString:'invalid method - unloaded'.
+        raiseRequestWith:self
+        errorString:'invalid method - unloaded'.
 
     "Created: 4.11.1996 / 22:57:54 / cg"
     "Modified: 4.11.1996 / 22:58:28 / cg"
@@ -1782,30 +1782,30 @@
 
     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.
-	]
+        "
+         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.
+        (classAndSelector methodClass) name printOn:aStream.
+        aStream nextPutAll:' '.
+        (classAndSelector methodSelector) printOn:aStream.
     ] ifFalse:[
-	"
-	 sorry, a method which is nowhere anchored
-	"
-	aStream nextPutAll:'unbound'
+        "
+         sorry, a method which is nowhere anchored
+        "
+        aStream nextPutAll:'unbound'
     ].
     aStream nextPut:$).
 
     wrapped ifTrue:[
-	aStream nextPutAll:'; wrapped'
+        aStream nextPutAll:'; wrapped'
     ].
 
     "
@@ -1827,7 +1827,7 @@
 
     who := self who.
     who notNil ifTrue:[
-	^ who methodClass name , ' >> ' , (who methodSelector storeString)
+        ^ who methodClass name , ' >> ' , (who methodSelector storeString)
     ].
     ^ 'unboundMethod'
 
@@ -1847,28 +1847,28 @@
      any raw annotation array is lazily
      initialized"
 
-    | annotation args |
+    | annotationOrArray annotation args |
     annotations ifNil:[^nil].
-    annotation := annotations at: index.
-    annotation isArray ifTrue:[
-	args := annotation size == 2
-		    ifTrue:[annotation second]
-		    ifFalse:[#()].
-	args isArray ifFalse:[args := Array with: args].
-	annotation := Annotation
-			method:self
-			key: annotation first
-			arguments: args.
-	annotation isUnknown ifFalse:[
-	    annotations at: index put: annotation.
+    annotationOrArray := annotation := annotations at: index.
+    annotationOrArray isArray ifTrue:[
+        args := annotationOrArray size == 2
+                    ifTrue:[annotationOrArray second]
+                    ifFalse:[#()].
+        args isArray ifFalse:[args := Array with: args].
+        annotation := Annotation
+                        method:self
+                        key: annotationOrArray first
+                        arguments: args.
+        annotation isUnknown ifFalse:[
+            annotations at: index put: annotation.
 "/            annotation annotatesMethod: self
-	].
+        ].
     ].
     ^annotation
 
     "Created: / 02-07-2010 / 22:30:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 11-07-2010 / 19:39:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 05-09-2011 / 08:50:43 / cg"
+    "Modified: / 09-09-2011 / 05:00:52 / cg"
 !
 
 annotationIndexOf: key
@@ -1879,10 +1879,10 @@
     annotations ifNil:[^nil].
 
     annotations keysAndValuesDo:
-	[:index :annotationOrArray|
-	annotationOrArray isArray
-	    ifTrue: [annotationOrArray first == key ifTrue:[^index]]
-	    ifFalse:[annotationOrArray key   == key ifTrue:[^index]]].
+        [:index :annotationOrArray|
+        annotationOrArray isArray
+            ifTrue: [annotationOrArray first == key ifTrue:[^index]]
+            ifFalse:[annotationOrArray key   == key ifTrue:[^index]]].
     ^nil.
 
     "Created: / 19-05-2010 / 16:40:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1895,14 +1895,14 @@
     |lastStream|
 
     (package notNil and:[package ~= PackageId noProjectID]) ifTrue:[
-	LastFileLock critical:[
-	    lastStream := LastFileReference at:1.
-	    (lastStream notNil and:[lastStream ~= 0 and:[lastStream isOpen]]) ifTrue:[
-		lastStream close.
-	    ].
-	    LastSourceFileName := package,'/',source.
-	    LastFileReference at:1 put:aStream.
-	].
+        LastFileLock critical:[
+            lastStream := LastFileReference at:1.
+            (lastStream notNil and:[lastStream ~= 0 and:[lastStream isOpen]]) ifTrue:[
+                lastStream close.
+            ].
+            LastSourceFileName := package,'/',source.
+            LastFileReference at:1 put:aStream.
+        ].
     ].
 !
 
@@ -1928,29 +1928,29 @@
     |dir fileName aStream|
 
     package notNil ifTrue:[
-	"/
-	"/ old: look in 'source/<filename>'
-	"/ this is still kept in order to find user-private
-	"/ classes in her currentDirectory.
-	"/
-	fileName := Smalltalk getSourceFileName:(package copyReplaceAll:$: with:$/) , '/' , source.
-	fileName notNil ifTrue:[
-	    aStream := fileName asFilename readStreamOrNil.
-	    aStream notNil ifTrue:[^ aStream].
-	].
-	"/
-	"/ new: look in package-dir
-	"/
-	dir := Smalltalk getPackageDirectoryForPackage:package.
-	dir notNil ifTrue:[
-	    fileName := dir construct:source.
-	    aStream := fileName asFilename readStreamOrNil.
-	    aStream notNil ifTrue:[^ aStream].
-	].
+        "/
+        "/ old: look in 'source/<filename>'
+        "/ this is still kept in order to find user-private
+        "/ classes in her currentDirectory.
+        "/
+        fileName := Smalltalk getSourceFileName:(package copyReplaceAll:$: with:$/) , '/' , source.
+        fileName notNil ifTrue:[
+            aStream := fileName asFilename readStreamOrNil.
+            aStream notNil ifTrue:[^ aStream].
+        ].
+        "/
+        "/ new: look in package-dir
+        "/
+        dir := Smalltalk getPackageDirectoryForPackage:package.
+        dir notNil ifTrue:[
+            fileName := dir construct:source.
+            aStream := fileName asFilename readStreamOrNil.
+            aStream notNil ifTrue:[^ aStream].
+        ].
     ].
     fileName := Smalltalk getSourceFileName:source.
     fileName notNil ifTrue:[
-	aStream := fileName asFilename readStreamOrNil.
+        aStream := fileName asFilename readStreamOrNil.
     ].
     ^ aStream
 !
@@ -1972,28 +1972,28 @@
     sourcePosition isNil ifTrue:[^ source readStream].
 
     usingCacheBoolean ifTrue:[
-	(package notNil and:[package ~= PackageId noProjectID]) ifTrue:[
-	    "/ 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.
-		(aStream isNil or:[aStream == 0 or:[aStream isOpen not]]) ifTrue:[
-		    aStream := nil.
-		    LastFileReference at:1 put:nil.
-		].
-		(aStream notNil and:[LastSourceFileName ~= (package,'/',source)]) ifTrue:[
-		    aStream := nil.
-		].
-	    ].
-
-	    aStream notNil ifTrue:[
-		^ aStream
-	    ].
-	].
+        (package notNil and:[package ~= PackageId noProjectID]) ifTrue:[
+            "/ 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.
+                (aStream isNil or:[aStream == 0 or:[aStream isOpen not]]) ifTrue:[
+                    aStream := nil.
+                    LastFileReference at:1 put:nil.
+                ].
+                (aStream notNil and:[LastSourceFileName ~= (package,'/',source)]) ifTrue:[
+                    aStream := nil.
+                ].
+            ].
+
+            aStream notNil ifTrue:[
+                ^ aStream
+            ].
+        ].
     ].
 
     "/ a negative sourcePosition indicates
@@ -2004,33 +2004,33 @@
     "/ and having a clue for which file is meant later.
 
     sourcePosition < 0 ifTrue:[
-	aStream := source asFilename readStreamOrNil.
-	aStream isNil ifTrue:[
-	    "/ search in some standard places
-	    fileName := Smalltalk getSourceFileName:source.
-	    fileName notNil ifTrue:[
-		aStream := fileName asFilename readStreamOrNil.
-	    ].
-	].
-	aStream notNil ifTrue:[
-	    usingCacheBoolean ifTrue:[
-		self cacheSourceStream:aStream.
-	    ].
-	    ^ aStream
-	].
+        aStream := source asFilename readStreamOrNil.
+        aStream isNil ifTrue:[
+            "/ search in some standard places
+            fileName := Smalltalk getSourceFileName:source.
+            fileName notNil ifTrue:[
+                aStream := fileName asFilename readStreamOrNil.
+            ].
+        ].
+        aStream notNil ifTrue:[
+            usingCacheBoolean ifTrue:[
+                self cacheSourceStream:aStream.
+            ].
+            ^ aStream
+        ].
     ].
 
     "/
     "/ if there is no SourceManager, look in local standard places first
     "/
     (Class tryLocalSourceFirst or:[(mgr := Smalltalk at:#SourceCodeManager) isNil]) ifTrue:[
-	aStream := self localSourceStream.
-	aStream notNil ifTrue:[
-	    usingCacheBoolean ifTrue:[
-		self cacheSourceStream:aStream.
-	    ].
-	    ^ aStream
-	].
+        aStream := self localSourceStream.
+        aStream notNil ifTrue:[
+            usingCacheBoolean ifTrue:[
+                self cacheSourceStream:aStream.
+            ].
+            ^ aStream
+        ].
     ].
 
     "/
@@ -2038,39 +2038,39 @@
     "/
     who := self who.
     who notNil ifTrue:[
-	myClass := who methodClass.
-
-	(package notNil and:[package ~= myClass package]) ifTrue:[
-	    "/ I am an extension
-	    mgr notNil ifTrue:[
-		"/ try to get the source using my package information ...
-		mod := package asPackageId module.
-		dir := package asPackageId directory.
-		aStream := mgr streamForExtensionFile:source package:package directory:dir module:mod cache:true.
-		aStream notNil ifTrue:[
-		    usingCacheBoolean ifTrue:[
-			self cacheSourceStream:aStream.
-		    ].
-		    ^ aStream
-		].
-	    ].
-	    "/ consult the local fileSystem
-	    aStream := self localSourceStream.
-	    aStream notNil ifTrue:[
-		usingCacheBoolean ifTrue:[
-		    self cacheSourceStream:aStream.
-		].
-		^ aStream
-	    ]
-	].
-
-	aStream := myClass sourceStreamFor:source.
-	aStream notNil ifTrue:[
-	    usingCacheBoolean ifTrue:[
-		self cacheSourceStream:aStream.
-	    ].
-	    ^ aStream
-	].
+        myClass := who methodClass.
+
+        (package notNil and:[package ~= myClass package]) ifTrue:[
+            "/ I am an extension
+            mgr notNil ifTrue:[
+                "/ try to get the source using my package information ...
+                mod := package asPackageId module.
+                dir := package asPackageId directory.
+                aStream := mgr streamForExtensionFile:source package:package directory:dir module:mod cache:true.
+                aStream notNil ifTrue:[
+                    usingCacheBoolean ifTrue:[
+                        self cacheSourceStream:aStream.
+                    ].
+                    ^ aStream
+                ].
+            ].
+            "/ consult the local fileSystem
+            aStream := self localSourceStream.
+            aStream notNil ifTrue:[
+                usingCacheBoolean ifTrue:[
+                    self cacheSourceStream:aStream.
+                ].
+                ^ aStream
+            ]
+        ].
+
+        aStream := myClass sourceStreamFor:source.
+        aStream notNil ifTrue:[
+            usingCacheBoolean ifTrue:[
+                self cacheSourceStream:aStream.
+            ].
+            ^ aStream
+        ].
     ].
 
     "/
@@ -2078,49 +2078,49 @@
     "/ (if there is a source-code manager - otherwise, we already did that)
     "/
     (mgr notNil and:[Class tryLocalSourceFirst not]) ifTrue:[
-	aStream := self localSourceStream.
-	aStream notNil ifTrue:[
-	    usingCacheBoolean ifTrue:[
-		self cacheSourceStream:aStream.
-	    ].
-	    ^ aStream
-	].
+        aStream := self localSourceStream.
+        aStream notNil ifTrue:[
+            usingCacheBoolean ifTrue:[
+                self cacheSourceStream:aStream.
+            ].
+            ^ aStream
+        ].
     ].
 
     "/
     "/ final chance: try current directory
     "/
     aStream isNil ifTrue:[
-	aStream := source asFilename readStreamOrNil.
-	aStream notNil ifTrue:[
-	    usingCacheBoolean ifTrue:[
-		self cacheSourceStream:aStream.
-	    ].
-	    ^ aStream
-	].
+        aStream := source asFilename readStreamOrNil.
+        aStream notNil ifTrue:[
+            usingCacheBoolean ifTrue:[
+                self cacheSourceStream: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.
-	(classNameSymbol := className asSymbolIfInterned) notNil ifTrue:[
-	    myClass := Smalltalk at:classNameSymbol ifAbsent:nil.
-	    myClass notNil ifTrue:[
-		aStream := myClass sourceStreamFor:source.
-		aStream notNil ifTrue:[
-		    usingCacheBoolean ifTrue:[
-			self cacheSourceStream: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.
+        (classNameSymbol := className asSymbolIfInterned) notNil ifTrue:[
+            myClass := Smalltalk at:classNameSymbol ifAbsent:nil.
+            myClass notNil ifTrue:[
+                aStream := myClass sourceStreamFor:source.
+                aStream notNil ifTrue:[
+                    usingCacheBoolean ifTrue:[
+                        self cacheSourceStream:aStream.
+                    ].
+                    ^ aStream
+                ].
+            ]
+        ]
     ].
 
     ^ nil
@@ -2139,9 +2139,9 @@
 
 sourceChunkFromStream:aStream
     PositionError handle:[:ex |
-	^ nil
+        ^ nil
     ] do:[
-	aStream position1Based:(sourcePosition ? 1) abs.
+        aStream position1Based:(sourcePosition ? 1) abs.
     ].
     ^ aStream nextChunk.
 !
@@ -2156,7 +2156,7 @@
 
     rawStream := self rawSourceStreamUsingCache:usingCacheBoolean.
     rawStream isNil ifTrue:[
-	^ nil.
+        ^ nil.
     ].
 
     "/ see if its utf8 encoded...
@@ -2176,7 +2176,7 @@
     OBJ nr = 0;
 
     if (f & F_PRIMITIVE) {
-	nr = __INST(code_);
+        nr = __INST(code_);
     }
     RETURN (nr);
 #endif
@@ -2230,15 +2230,15 @@
 
     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
-	].
+        parser := Parser
+                        parseMethod:src
+                        in:self containingClass
+                        ignoreErrors:true
+                        ignoreWarnings:true.
+
+        (parser notNil and:[parser ~~ #Error]) ifTrue:[
+            ^ parser usedInstVars
+        ].
     ].
     ^ #() "/ actually: unknown
 
@@ -2254,11 +2254,11 @@
     |who|
 
     mclass notNil ifTrue:[
-	"/ check if this (cached) info is still valid ...
-	(mclass containsMethod:self) ifTrue:[
-	    ^ mclass
-	].
-	mclass := nil.
+        "/ check if this (cached) info is still valid ...
+        (mclass containsMethod:self) ifTrue:[
+            ^ mclass
+        ].
+        mclass := nil.
     ].
 
     who := self who.
@@ -2282,38 +2282,38 @@
     |newMethod function|
 
     (self
-	literalsDetect:[:lit |
-	    #(
-		#'invoke'
-		#'invokeWith:'
-		#'invokeWith:with:'
-		#'invokeWith:with:with:'
-		#'invokeWith:with:with:with:'
-		#'invokeWithArguments:'
-		#'invokeCPPVirtualOn:'
-		#'invokeCPPVirtualOn:with:'
-		#'invokeCPPVirtualOn:with:with:'
-		#'invokeCPPVirtualOn:with:with:with:'
-		#'invokeCPPVirtualOn:with:with:with:with:'
-		#'invokeCPPVirtualOn:withArguments:'
-	    ) includes:lit
-	]
-	ifNone:nil) notNil
+        literalsDetect:[:lit |
+            #(
+                #'invoke'
+                #'invokeWith:'
+                #'invokeWith:with:'
+                #'invokeWith:with:with:'
+                #'invokeWith:with:with:with:'
+                #'invokeWithArguments:'
+                #'invokeCPPVirtualOn:'
+                #'invokeCPPVirtualOn:with:'
+                #'invokeCPPVirtualOn:with:with:'
+                #'invokeCPPVirtualOn:with:with:with:'
+                #'invokeCPPVirtualOn:with:with:with:with:'
+                #'invokeCPPVirtualOn:withArguments:'
+            ) includes:lit
+        ]
+        ifNone:nil) notNil
     ifTrue:[
-	"/ sigh - for stc-compiled code, this does not work:
-	function := self literalsDetect:[:lit | lit isExternalLibraryFunction] ifNone:nil.
-	function isNil ifTrue:[
-	    "/ parse it and ask the parser
-	    newMethod := Compiler compile:self source forClass:self mclass install:false.
-	    function := newMethod literalsDetect:[:lit | lit isExternalLibraryFunction] ifNone:nil.
-	].
-	^ function
+        "/ sigh - for stc-compiled code, this does not work:
+        function := self literalsDetect:[:lit | lit isExternalLibraryFunction] ifNone:nil.
+        function isNil ifTrue:[
+            "/ parse it and ask the parser
+            newMethod := Compiler compile:self source forClass:self mclass install:false.
+            function := newMethod literalsDetect:[:lit | lit isExternalLibraryFunction] ifNone:nil.
+        ].
+        ^ function
     ].
     ^ nil
 
     "
      (IDispatchPointer compiledMethodAt:#'invokeGetTypeInfo:_:_:')
-	externalLibraryFunction
+        externalLibraryFunction
     "
 !
 
@@ -2343,7 +2343,7 @@
 
     "
      Method allInstancesDo:[:m |
-	(m hasAnyResource:#(image canvas)) ifTrue:[self halt]
+        (m hasAnyResource:#(image canvas)) ifTrue:[self halt]
      ].
     "
 !
@@ -2380,10 +2380,10 @@
 
     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
-	]
+        (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 ...
@@ -2419,7 +2419,7 @@
 
     "
      Method allInstancesDo:[:m |
-	(m hasResource:#image) ifTrue:[self halt]
+        (m hasResource:#image) ifTrue:[self halt]
      ].
     "
 
@@ -2500,20 +2500,20 @@
 
     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].
+        (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].
+        (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].
+        (myCode notNil and:[myCode = m code]) ifTrue:[^ true].
+        (byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
     ].
 
     ^ false
@@ -2637,13 +2637,13 @@
     parserClass := self parserClass.
     sourceString := self source.
     (parserClass notNil and:[sourceString notNil]) ifTrue:[
-	parser := parserClass 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)
+        parser := parserClass 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
 
@@ -2677,30 +2677,30 @@
     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)
+        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).
-	(line indexOf:$/ startingAt:qIndex) == (qIndex+1) ifTrue:[
-	    "/ an EOL comment
-	    ^ (comment copyFrom:2) withoutSeparators
-	].
-
-	"/ not an EOL comment
-	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
+        qIndex := line indexOf:(Character doubleQuote).
+        comment := line copyFrom:(qIndex + 1).
+        (line indexOf:$/ startingAt:qIndex) == (qIndex+1) ifTrue:[
+            "/ an EOL comment
+            ^ (comment copyFrom:2) withoutSeparators
+        ].
+
+        "/ not an EOL comment
+        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
 
@@ -2713,8 +2713,8 @@
     "return the string that defines the method and the arguments"
 
     ^ Method
-	methodDefinitionTemplateForSelector:self selector
-	andArgumentNames:self methodArgNames
+        methodDefinitionTemplateForSelector:self selector
+        andArgumentNames:self methodArgNames
 
     "
       (self compiledMethodAt:#printOn:) methodDefinitionTemplate
@@ -2757,8 +2757,8 @@
     list size == 0 ifTrue:[^ nil].
     histLine := list last.
     ^ Timestamp
-	fromDate:histLine date
-	andTime:histLine time
+        fromDate:histLine date
+        andTime:histLine time
 
     "
      (Method compiledMethodAt:#modificationTime) modificationTime
@@ -2782,8 +2782,8 @@
     | mth |
     mth := self overriddenMethod.
     [ mth notNil ] whileTrue:
-	[mth == aMethod ifTrue:[^true].
-	mth := mth overriddenMethod].
+        [mth == aMethod ifTrue:[^true].
+        mth := mth overriddenMethod].
     ^false
 
     "Modified: / 18-06-2009 / 12:15:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -2798,7 +2798,7 @@
 
     "
      (Method compiledMethodAt:#parse:return:or:)
-	parse:#'parseMethodSilent:' return:#sentMessages or:#()
+        parse:#'parseMethodSilent:' return:#sentMessages or:#()
     "
 !
 
@@ -2815,34 +2815,34 @@
     "/ is very common with the new browser's info displays, we cache a few
     "/ of the. If the same is parsed soon after, we do not have to parse again.
     LastParseTreeCache notNil ifTrue:[
-	cachedInfo := LastParseTreeCache at:self ifAbsent:nil.
-	cachedInfo notNil ifTrue:[
-	    cachedInfo parserClass == parserClass ifTrue:[
-		"/ Transcript show:'hit '; showCR:self.
-		^ cachedInfo parser perform:accessSelector
-	    ]
-	]
+        cachedInfo := LastParseTreeCache at:self ifAbsent:nil.
+        cachedInfo notNil ifTrue:[
+            cachedInfo parserClass == parserClass ifTrue:[
+                "/ Transcript show:'hit '; showCR:self.
+                ^ cachedInfo parser perform:accessSelector
+            ]
+        ]
     ].
 
     sourceString := self source.
     (parserClass notNil and:[sourceString notNil]) ifTrue:[
-	parseSelector numArgs == 2 ifTrue:[
-	    parser := parserClass perform:parseSelector with:sourceString with:arg2.
-	] ifFalse:[
-	    parser := parserClass perform:parseSelector with:sourceString.
-	].
-	(parser isNil or:[parser == #Error]) ifTrue:[^ valueIfNoSource].
-	LastParseTreeCache isNil ifTrue:[
-	    LastParseTreeCache := CacheDictionary new:32.
-	].
-	LastParseTreeCache at:self put:(ParserCacheEntry new parserClass:parserClass method:self parser:parser).
-	^ parser perform:accessSelector
+        parseSelector numArgs == 2 ifTrue:[
+            parser := parserClass perform:parseSelector with:sourceString with:arg2.
+        ] ifFalse:[
+            parser := parserClass perform:parseSelector with:sourceString.
+        ].
+        (parser isNil or:[parser == #Error]) ifTrue:[^ valueIfNoSource].
+        LastParseTreeCache isNil ifTrue:[
+            LastParseTreeCache := CacheDictionary new:32.
+        ].
+        LastParseTreeCache at:self put:(ParserCacheEntry new parserClass:parserClass method:self parser:parser).
+        ^ parser perform:accessSelector
     ].
     ^ valueIfNoSource
 
     "
      (Method compiledMethodAt:#parse:return:or:)
-	parse:#'parseMethodSilent:' return:#sentMessages or:#()
+        parse:#'parseMethodSilent:' return:#sentMessages or:#()
     "
 
     "Modified: / 08-08-2011 / 19:13:24 / cg"
@@ -2856,15 +2856,15 @@
 
     src := self source.
     src isNil ifTrue:[
-	^ nil "/ actually: dont know
+        ^ nil "/ actually: dont know
     ].
 
     self parserClass isNil ifTrue:[
-	^ nil
+        ^ nil
     ].
     parser := self parserClass parseMethod: src.
     (parser isNil or: [parser == #Error]) ifTrue:[
-	^ nil "/ actually error
+        ^ nil "/ actually error
     ].
     ^ annotations := parser annotations.
 
@@ -2878,19 +2878,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
     ].
     "/ no need to parse all - only interested in resource-info
     self parserClass isNil ifTrue:[
-	^ nil
+        ^ nil
     ].
     parser := self parserClass parseMethodArgAndVarSpecificationSilent:src in:nil.
     parser isNil ifTrue:[
-	^ nil "/ actually error
+        ^ nil "/ actually error
     ].
     ^ parser primitiveResources.
 !
@@ -2907,15 +2907,15 @@
     cls isNil ifTrue:[ ^ nil ].
 
     ChangeSet current reverseDo:[:change |
-	(change isMethodChange
-	and:[ (change selector == sel)
-	and:[ change changeClass == cls ]])
-	ifTrue:[
-	    previous := change previousVersion.
-	    previous notNil ifTrue:[
-		^ previous
-	    ]
-	]
+        (change isMethodChange
+        and:[ (change selector == sel)
+        and:[ change changeClass == cls ]])
+        ifTrue:[
+            previous := change previousVersion.
+            previous notNil ifTrue:[
+                ^ previous
+            ]
+        ]
     ].
     ^ nil.
 
@@ -2965,28 +2965,28 @@
     versions := OrderedCollection new.
 
     ChangeSet current reverseDo:[:change |
-	 (change isMethodChange
-	and:[ (change selector == sel)
-	and:[ change changeClass == cls ]])
-	ifTrue:[
-	    versions addFirst:change.
-	    lastChange := change.
-	]
+         (change isMethodChange
+        and:[ (change selector == sel)
+        and:[ change changeClass == cls ]])
+        ifTrue:[
+            versions addFirst:change.
+            lastChange := change.
+        ]
     ].
 
     lastChange notNil ifTrue:[
-	last := lastChange previousVersion.
-	last notNil ifTrue:[
-	    firstSrc := last source.
-	    (firstSrc size > 0
-	    and:[ firstSrc ~= lastChange source]) ifTrue:[
-		versions addFirst:(MethodChange
-				    className:lastChange className
-				    selector:lastChange selector
-				    source:firstSrc
-				    category:lastChange category).
-	    ]
-	]
+        last := lastChange previousVersion.
+        last notNil ifTrue:[
+            firstSrc := last source.
+            (firstSrc size > 0
+            and:[ firstSrc ~= lastChange source]) ifTrue:[
+                versions addFirst:(MethodChange
+                                    className:lastChange className
+                                    selector:lastChange selector
+                                    source:firstSrc
+                                    category:lastChange category).
+            ]
+        ]
     ].
     ^ versions
 !
@@ -3010,9 +3010,9 @@
     |resources|
 
     (resources := self resources) notNil ifTrue:[
-	resources keysAndValuesDo:[:key :val|
-	    ^ key
-	].
+        resources keysAndValuesDo:[:key :val|
+            ^ key
+        ].
     ].
     ^ nil
 !
@@ -3026,8 +3026,8 @@
 
     resources := IdentityDictionary new.
     self annotationsAt: #resource: orAt: #resource:value: do:
-	[:annot|
-	resources at: annot type put: annot value ? true].
+        [:annot|
+        resources at: annot type put: annot value ? true].
     ^resources
 
     "Modified: / 16-07-2010 / 11:49:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -3063,7 +3063,7 @@
      with aSelectorSymbol as selector."
 
     (self referencesLiteral:aSelectorSymbol) ifTrue:[
-	^ self messagesSent includesIdentical:aSelectorSymbol
+        ^ self messagesSent includesIdentical:aSelectorSymbol
     ].
     ^ false
 !
@@ -3076,8 +3076,8 @@
     |msgs|
 
     ((self referencesLiteral:selectorSymbol1) or:[self referencesLiteral:selectorSymbol2]) ifTrue:[
-	msgs := self messagesSent.
-	^ (msgs includesIdentical:selectorSymbol1) or:[msgs includesIdentical:selectorSymbol2]
+        msgs := self messagesSent.
+        ^ (msgs includesIdentical:selectorSymbol1) or:[msgs includesIdentical:selectorSymbol2]
     ].
     ^ false
 
@@ -3091,8 +3091,8 @@
     |msgs|
 
     (aCollectionOfSelectorSymbols contains:[:sym | self referencesLiteral:sym]) ifTrue:[
-	msgs := self messagesSent.
-	^ aCollectionOfSelectorSymbols contains:[:sym | msgs includesIdentical:sym]
+        msgs := self messagesSent.
+        ^ aCollectionOfSelectorSymbols contains:[:sym | msgs includesIdentical:sym]
     ].
     ^ false
 
@@ -3145,53 +3145,53 @@
      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 checkBlock|
 
     mclass notNil ifTrue:[
-	sel := mclass selectorAtMethod:self.
-	sel notNil ifTrue:[
-	    ^ MethodWhoInfo class:mclass selector:sel
-	].
-	"/ flush outdated mclass info
-	mclass := nil.
+        sel := mclass selectorAtMethod:self.
+        sel notNil ifTrue:[
+            ^ MethodWhoInfo class:mclass selector:sel
+        ].
+        "/ flush outdated mclass info
+        mclass := nil.
     ].
 
     checkBlock := [:cls |
-	|sel|
-
-	sel := cls selectorAtMethod:self.
-	sel notNil ifTrue:[
-	    LastWhoClass := cls theNonMetaclass name.
-	    mclass isNil ifTrue:[
-		mclass := cls
-	    ].
-	    ^ MethodWhoInfo class:cls selector:sel
-	].
+        |sel|
+
+        sel := cls selectorAtMethod:self.
+        sel notNil ifTrue:[
+            LastWhoClass := cls theNonMetaclass name.
+            mclass isNil ifTrue:[
+                mclass := cls
+            ].
+            ^ MethodWhoInfo class:cls selector:sel
+        ].
     ].
 
     "
@@ -3199,15 +3199,15 @@
      extract the className from it and try that class first.
     "
     (fn := self sourceFilename) notNil ifTrue:[
-	clsName := fn asFilename nameWithoutSuffix.
-	clsName := clsName asSymbolIfInterned.
-	clsName notNil ifTrue:[
-	    cls := Smalltalk at:clsName ifAbsent:nil.
-	    cls notNil ifTrue:[
-		checkBlock value:cls theNonMetaclass.
-		checkBlock value:cls theMetaclass.
-	    ]
-	].
+        clsName := fn asFilename nameWithoutSuffix.
+        clsName := clsName asSymbolIfInterned.
+        clsName notNil ifTrue:[
+            cls := Smalltalk at:clsName ifAbsent:nil.
+            cls notNil ifTrue:[
+                checkBlock value:cls theNonMetaclass.
+                checkBlock value:cls theMetaclass.
+            ]
+        ].
     ].
 
     "
@@ -3217,11 +3217,11 @@
      being garbage collected)
     "
     LastWhoClass notNil ifTrue:[
-	cls := Smalltalk at:LastWhoClass ifAbsent:nil.
-	cls notNil ifTrue:[
-	    checkBlock value:cls theNonMetaclass.
-	    checkBlock value:cls theMetaclass.
-	]
+        cls := Smalltalk at:LastWhoClass ifAbsent:nil.
+        cls notNil ifTrue:[
+            checkBlock value:cls theNonMetaclass.
+            checkBlock value:cls theMetaclass.
+        ]
     ].
 
     "
@@ -3233,8 +3233,8 @@
      instance methods are usually more common - search those first
     "
     classes do:[:cls |
-	checkBlock value:cls theNonMetaclass.
-	checkBlock value:cls theMetaclass.
+        checkBlock value:cls theNonMetaclass.
+        checkBlock value:cls theMetaclass.
     ].
 
     LastWhoClass := nil.
@@ -3264,11 +3264,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.
 
@@ -3287,7 +3287,7 @@
      Thats the WrapperMethod which contains myself."
 
     WrappedMethod allInstancesDo:[:m |
-	m originalMethod == self ifTrue:[^ m].
+        m originalMethod == self ifTrue:[^ m].
     ].
     ^ nil
 !
@@ -3368,17 +3368,17 @@
     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.
+        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.
+        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.
@@ -3387,10 +3387,10 @@
     classes.
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 
     [see also:]
-	Method
+        Method
 "
 ! !
 
@@ -3439,10 +3439,10 @@
     "simulate the old behavior (when Method>>who returned an array)"
 
     index == 1 ifTrue:[
-	^ myClass
+        ^ myClass
     ].
     index == 2 ifTrue:[
-	^ mySelector
+        ^ mySelector
     ].
 
     "/ sigh - full compatibility ?
@@ -3539,11 +3539,11 @@
 !Method class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.372 2011-09-08 12:37:26 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.373 2011-09-09 04:17:24 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.372 2011-09-08 12:37:26 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.373 2011-09-09 04:17:24 cg Exp $'
 !
 
 version_SVN