*** empty log message ***
authorClaus Gittinger <cg@exept.de>
Wed, 07 Apr 2010 19:36:33 +0200
changeset 12854 3a3d3c02c3bd
parent 12853 3d15dcbe0057
child 12855 1790064d9d8e
*** empty log message ***
Context.st
Method.st
--- a/Context.st	Wed Apr 07 19:34:35 2010 +0200
+++ b/Context.st	Wed Apr 07 19:36:33 2010 +0200
@@ -12,11 +12,11 @@
 "{ Package: 'stx:libbasic' }"
 
 Object variableSubclass:#Context
-	instanceVariableNames:'flags sender* home receiver selector searchClass method lineNr
-		retvalTemp handle*'
-	classVariableNames:'InvalidReturnSignal SingleStepInterruptRequest'
-	poolDictionaries:''
-	category:'Kernel-Methods'
+        instanceVariableNames:'flags sender* home receiver selector searchClass method lineNr
+                retvalTemp handle*'
+        classVariableNames:'InvalidReturnSignal SingleStepInterruptRequest'
+        poolDictionaries:''
+        category:'Kernel-Methods'
 !
 
 !Context class methodsFor:'documentation'!
@@ -2381,11 +2381,11 @@
 !Context class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.156 2010-04-07 17:34:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.157 2010-04-07 17:36:33 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.156 2010-04-07 17:34:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.157 2010-04-07 17:36:33 cg Exp $'
 ! !
 
 Context initialize!
--- a/Method.st	Wed Apr 07 19:34:35 2010 +0200
+++ b/Method.st	Wed Apr 07 19:36:33 2010 +0200
@@ -12,19 +12,19 @@
 "{ Package: 'stx:libbasic' }"
 
 CompiledCode variableSubclass:#Method
-	instanceVariableNames:'source sourcePosition category package mclass'
-	classVariableNames:'PrivateMethodSignal LastFileReference LastSourceFileName
-		LastWhoClass LastFileLock LastMethodSources LastMethodSourcesLock
-		CompilationLock'
-	poolDictionaries:''
-	category:'Kernel-Methods'
+        instanceVariableNames:'source sourcePosition category package mclass'
+        classVariableNames:'PrivateMethodSignal LastFileReference LastSourceFileName
+                LastWhoClass LastFileLock LastMethodSources LastMethodSourcesLock
+                CompilationLock'
+        poolDictionaries:''
+        category:'Kernel-Methods'
 !
 
 Object subclass:#MethodWhoInfo
-	instanceVariableNames:'myClass mySelector'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Method
+        instanceVariableNames:'myClass mySelector'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Method
 !
 
 !Method class methodsFor:'documentation'!
@@ -116,7 +116,7 @@
 "
 !
 
-privacy 
+privacy
 "
     ST/X includes an EXPERIMENTAL implementation of method privacy.
     Individual methods may be set to private or protected via the
@@ -130,7 +130,7 @@
     Protected methods may be executed only when called via a self-send
     from the superclass-methods and self or super-sends from methods in the
     class itself or subclasses.
-    Private methods may not be called from subclasses-methods, 
+    Private methods may not be called from subclasses-methods,
     i.e. they may only be called via self sends from within the current class.
     (i.e. protected methods are less private than private ones)
 
@@ -143,7 +143,7 @@
     and leave it non nil during development).
 
     NOTICE: there is no (not yet ?) standard defined for method privacy,
-    however, the definition protocol was designed to be somewhat ENVY compatible 
+    however, the definition protocol was designed to be somewhat ENVY compatible
     (from what can be deduced by reading PD code).
 
     Also, the usability of privacy is still to be tested.
@@ -231,14 +231,14 @@
     ] ifFalse:[
         argNames := (1 to:nA) collect:[:i | 'arg' , i printString].
     ].
-    ^ self 
-        methodDefinitionTemplateForSelector:aSelector 
+    ^ self
+        methodDefinitionTemplateForSelector:aSelector
         andArgumentNames:argNames.
 
     "
-     Method methodDefinitionTemplateForSelector:#foo           
-     Method methodDefinitionTemplateForSelector:#+             
-     Method methodDefinitionTemplateForSelector:#foo:bar:baz:  
+     Method methodDefinitionTemplateForSelector:#foo
+     Method methodDefinitionTemplateForSelector:#+
+     Method methodDefinitionTemplateForSelector:#foo:bar:baz:
     "
 !
 
@@ -248,7 +248,7 @@
     aSelector numArgs > 0 ifTrue:[
         aSelector isKeyword ifTrue:[
             ^ String streamContents:[:stream |
-                aSelector keywords with:argNames do:[:eachKeyword :eachArgName| 
+                aSelector keywords with:argNames do:[:eachKeyword :eachArgName|
                     stream nextPutAll:eachKeyword; nextPutAll:eachArgName; space.
                 ].
                 stream backStep.   "remove the last space"
@@ -259,9 +259,9 @@
     ^ aSelector
 
     "
-     Method methodDefinitionTemplateForSelector:#foo          andArgumentNames:#()        
-     Method methodDefinitionTemplateForSelector:#+            andArgumentNames:#('aNumber') 
-     Method methodDefinitionTemplateForSelector:#foo:bar:baz: andArgumentNames:#('fooArg' 'barArg' 'bazArg') 
+     Method methodDefinitionTemplateForSelector:#foo          andArgumentNames:#()
+     Method methodDefinitionTemplateForSelector:#+            andArgumentNames:#('aNumber')
+     Method methodDefinitionTemplateForSelector:#foo:bar:baz: andArgumentNames:#('fooArg' 'barArg' 'bazArg')
     "
 !
 
@@ -304,7 +304,7 @@
 classIsMeta
     "return true, if this method is a class method"
 
-    ^ self mclass isMeta 
+    ^ self mclass isMeta
 !
 
 sendsSelector:aSelectorSymbol
@@ -338,7 +338,7 @@
                 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). 
+                Smalltalk changed:#methodCategory with:(Array with:cls with:self with:oldCategory).
             ]
         ]
     ]
@@ -349,7 +349,7 @@
 comment
     "return the methods comment.
      This is done by searching for and returning the first comment
-     from the methods source (excluding any double-quotes). 
+     from the methods source (excluding any double-quotes).
      Returns nil if there is no comment (or source is not available)."
 
     |src comment comments parser|
@@ -375,8 +375,8 @@
     ^ comment.
 
     "
-     (Method compiledMethodAt:#comment) comment  
-     (Object class compiledMethodAt:#infoPrinting:) comment  
+     (Method compiledMethodAt:#comment) comment
+     (Object class compiledMethodAt:#infoPrinting:) comment
     "
 
     "Modified: / 17.2.1998 / 14:50:00 / cg"
@@ -406,7 +406,7 @@
 !
 
 localSourceFilename:aFileName position:aNumber
-    "set the methods sourcefile/position indicating, that 
+    "set the methods sourcefile/position indicating, that
      this is a local file."
 
     source := aFileName.
@@ -434,7 +434,7 @@
 
 mclass:aClass
     "set the method's class"
-     
+
     mclass == aClass ifTrue:[ ^ self ].
 
 "/     (mclass notNil and:[aClass notNil]) ifTrue:[
@@ -487,7 +487,7 @@
         self changed:#package.                                              "/ will vanish
         cls changed:#methodPackage with:self selector.                      "/ will vanish
 
-        Smalltalk changed:#projectOrganization with:(Array with:cls with:self with:oldPackage). 
+        Smalltalk changed:#projectOrganization with:(Array with:cls with:self with:oldPackage).
         cls addChangeRecordForMethodPackage:self package:newPackage.
     ]
 
@@ -533,7 +533,7 @@
         ].
 
         LastFileLock critical:[
-            "have to protect sourceStream from being closed as a side effect 
+            "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.
@@ -641,7 +641,7 @@
      but no code is generated for it by stc, and the VM does not see
      it in its message lookup.
      (i.e. setting a method to #ignored, and sending that selector,
-      leads to either the superclasses implementation to be called, 
+      leads to either the superclasses implementation to be called,
       or a doesNotUnderstand exception to be raised)
 
      Notice: this is a nonstandard feature, not supported
@@ -708,7 +708,7 @@
 isRestricted
     "return the flag bit stating that this method is restricted.
      Execution of the receiver will only be allowed if the system is not in
-     'trap restricted mode' (-->ObjectMemory) otherise a runtime 
+     'trap restricted mode' (-->ObjectMemory) otherise a runtime
      error (PrivateMethodSignal) is raised.
 
      Notice: method restriction is a nonstandard feature, not supported
@@ -734,7 +734,7 @@
 primSetPrivacy:aSymbol
     "set the methods access rights (privacy) from a symbol;
      Currently, this must be one of #private, #protected, #public or #ignored.
-     #setPrivacy: simply sets the attribute. When changing methods, that 
+     #setPrivacy: simply sets the attribute. When changing methods, that
      have already been called, #privacy: should be used.
 
      Notice: method privacy is a nonstandard feature, not supported
@@ -762,7 +762,7 @@
         p = F_IGNORED;
     else
         RETURN(false);  /* illegal symbol */
-        
+
 
     f = (f & ~M_PRIVACY) | p;
     __INST(flags) = __mkSmallInteger(f);
@@ -846,7 +846,7 @@
         myClass notNil ifTrue:[
             mySelector notNil ifTrue:[
                 myClass changed:#methodPrivacy with:mySelector.      "/ will vanish
-                Smalltalk changed:#privacyOfMethod with:(Array with:myClass with:self with:oldPrivacy). 
+                Smalltalk changed:#privacyOfMethod with:(Array with:myClass with:self with:oldPrivacy).
                 myClass addChangeRecordForMethodPrivacy:self.
             ]
         ]
@@ -856,7 +856,7 @@
 !
 
 restricted:aBoolean
-    "set or clear the flag bit stating that this method is restricted. 
+    "set or clear the flag bit stating that this method is restricted.
      Execution of the receiver will only be allowed if the system is not in
      'trap restricted mode' (-->ObjectMemory) otherise a runtime
      error (PrivateMethodSignal) is raised.
@@ -875,7 +875,7 @@
     INT old;
 
     old = f;
-    if (aBoolean == true) 
+    if (aBoolean == true)
         f |= F_RESTRICTED;
     else
         f &= ~F_RESTRICTED;
@@ -896,7 +896,7 @@
 setPrivacy:aSymbol
     "set the methods access rights (privacy) from a symbol;
      Currently, this must be one of #private, #protected, #public or #ignored.
-     #setPrivacy: simply sets the attribute. When changing methods, that 
+     #setPrivacy: simply sets the attribute. When changing methods, that
      have already been called, #privacy: should be used.
 
      Notice: method privacy is a nonstandard feature, not supported
@@ -914,7 +914,7 @@
 setPrivacy:aSymbol flushCaches:doFlush
     "set the methods access rights (privacy) from a symbol;
      Currently, this must be one of #private, #protected, #public or #ignored.
-     #setPrivacy: simply sets the attribute. When changing methods, that 
+     #setPrivacy: simply sets the attribute. When changing methods, that
      have already been called, #privacy: should be used.
 
      Notice: method privacy is a nonstandard feature, not supported
@@ -956,7 +956,7 @@
      the methodDictionary of any class - just returned.
      If the method contains primitive code, this may return a method
      without bytecode.
-     Can be used to obtain a bytecode version of a machine-code method, 
+     Can be used to obtain a bytecode version of a machine-code method,
      for binary storage or dynamic recompilation (which is not yet finished)
      or to compile lazy methods down to executable ones."
 
@@ -983,7 +983,7 @@
 asByteCodeMethodWithSource:newSource
     |mthd|
 
-    ParserFlags 
+    ParserFlags
         withSTCCompilation:#never
         do:[
             mthd := self asExecutableMethodWithSource:newSource.
@@ -995,7 +995,7 @@
 !
 
 asExecutableMethod
-    "if the receiver has neither bytecodes nor machinecode, create & return a 
+    "if the receiver has neither bytecodes nor machinecode, create & return a
      method having semantics as the receivers source. This may be machine code,
      if the system supports dynamic loading of object code and the source includes
      primitive code. However, bytecode is preferred, since it compiles faster.
@@ -1027,7 +1027,7 @@
     "/
     "/ try to save a bit of memory, by sharing the source (whatever it is)
     "/
-    temporaryMethod sourceFilename:source position:sourcePosition. 
+    temporaryMethod sourceFilename:source position:sourcePosition.
     ^ temporaryMethod
 !
 
@@ -1049,7 +1049,7 @@
     CompilationLock critical:[
         "
          dont want this to go into the changes file,
-         dont want output on Transcript and definitely 
+         dont want output on Transcript and definitely
          dont want a lazy method ...
         "
         Class withoutUpdatingChangesDo:[
@@ -1079,9 +1079,9 @@
                                              install:false.
                     ] ifFalse:[
                         temporaryMethod := compiler new
-                                             compile:newSource 
-                                             in:cls 
-                                             notifying:nil 
+                                             compile:newSource
+                                             in:cls
+                                             notifying:nil
                                              ifFail:nil
                     ].
                 ].
@@ -1098,7 +1098,7 @@
     "/
     "/ try to save a bit of memory, by sharing the source (whatever it is)
     "/
-    temporaryMethod source:newSource. 
+    temporaryMethod source:newSource.
     "/
     "/ dont forget the methods class & package ...
     "/
@@ -1139,7 +1139,7 @@
      has been removed, and a method still tries to access this instvar)
 
      Thus, we arrive here, when playing around in a classes methodArray,
-     or compiler/runtime system is broken :-(, 
+     or compiler/runtime system is broken :-(,
      or you ignore the error messages during some recompile."
 
 %{
@@ -1460,7 +1460,7 @@
     "this error is triggered, if a private or protected method is called.
 
      If you continue in the debugger, the method will be called,
-     and further privacy exceptions will NOT be reported at this call location, 
+     and further privacy exceptions will NOT be reported at this call location,
      until any new method is compiled, or the privacy of any method changes,
      or the caches are flushed.
      (the reason is that after the continue, the method is enterred into the
@@ -1590,7 +1590,7 @@
     ^ 'unboundMethod'
 
     "
-     Method new whoString   
+     Method new whoString
      (Method compiledMethodAt:#whoString) whoString
     "
 
@@ -1671,7 +1671,7 @@
             "/ 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. 
+            "/ automatically if the file is not referenced for a while.
             "/ Neat trick.
 
             LastFileLock critical:[
@@ -1692,7 +1692,7 @@
     ].
 
     "/ a negative sourcePosition indicates
-    "/ that this is a local file 
+    "/ that this is a local file
     "/ (not to be requested via the sourceCodeManager)
     "/ This kludge was added, to allow sourceCode to be
     "/ saved to a local source file (i.e. 'st.src')
@@ -1769,7 +1769,7 @@
     ].
 
     "/
-    "/ nope - look in standard places 
+    "/ nope - look in standard places
     "/ (if there is a source-code manager - otherwise, we already did that)
     "/
     (mgr notNil and:[Class tryLocalSourceFirst not]) ifTrue:[
@@ -1816,7 +1816,7 @@
                 ].
             ]
         ]
-    ].                
+    ].
 
     ^ nil
 
@@ -1917,9 +1917,9 @@
     src := self source.
     src notNil ifTrue:[
         parser := Parser
-                        parseMethod:src 
-                        in:self containingClass 
-                        ignoreErrors:true 
+                        parseMethod:src
+                        in:self containingClass
+                        ignoreErrors:true
                         ignoreWarnings:true.
 
         (parser notNil and:[parser ~~ #Error]) ifTrue:[
@@ -1932,7 +1932,7 @@
 !
 
 containingClass
-    "return the class I am defined in. 
+    "return the class I am defined in.
      See comment in who."
 
     "based on who, which has been added for ST-80 compatibility"
@@ -1955,9 +1955,9 @@
     ^ nil
 
     "
-     (Object compiledMethodAt:#at:) containingClass   
-
-     (Object class compiledMethodAt:#version) containingClass   
+     (Object compiledMethodAt:#at:) containingClass
+
+     (Object class compiledMethodAt:#version) containingClass
     "
 !
 
@@ -2011,9 +2011,9 @@
     ^ self parse:#'parseMethodSilent:' return:#hasPrimitiveCode or:false
 
     "
-     (Method compiledMethodAt:#hasPrimitiveCode) hasPrimitiveCode 
-     (Object compiledMethodAt:#at:) hasPrimitiveCode   
-     (Object compiledMethodAt:#basicAt:) hasPrimitiveCode 
+     (Method compiledMethodAt:#hasPrimitiveCode) hasPrimitiveCode
+     (Object compiledMethodAt:#at:) hasPrimitiveCode
+     (Object compiledMethodAt:#basicAt:) hasPrimitiveCode
     "
 
     "Modified: 22.1.1997 / 00:03:45 / cg"
@@ -2065,18 +2065,18 @@
     ^ funcOrNil vtableIndex
 
     "
-     (Method compiledMethodAt:#hasPrimitiveCode) isOLECall  
-     (Method compiledMethodAt:#hasPrimitiveCode) indexOfOLECall 
-
-     (Win32OperatingSystem class compiledMethodAt:#primClosePrinter:) isOLECall    
-     (Win32OperatingSystem class compiledMethodAt:#primClosePrinter:) indexOfOLECall    
-     (Win32OperatingSystem class compiledMethodAt:#primClosePrinter:) isExternalLibraryFunctionCall    
-     (Win32OperatingSystem class compiledMethodAt:#primClosePrinter:) externalLibraryFunctionCall    
-
-     (IUnknownPointer compiledMethodAt:#invokeAddRef) isExternalLibraryFunctionCall    
-     (IUnknownPointer compiledMethodAt:#invokeAddRef) externalLibraryFunction    
-     (IUnknownPointer compiledMethodAt:#invokeAddRef) isOLECall    
-     (IUnknownPointer compiledMethodAt:#invokeAddRef) indexOfOLECall    
+     (Method compiledMethodAt:#hasPrimitiveCode) isOLECall
+     (Method compiledMethodAt:#hasPrimitiveCode) indexOfOLECall
+
+     (Win32OperatingSystem class compiledMethodAt:#primClosePrinter:) isOLECall
+     (Win32OperatingSystem class compiledMethodAt:#primClosePrinter:) indexOfOLECall
+     (Win32OperatingSystem class compiledMethodAt:#primClosePrinter:) isExternalLibraryFunctionCall
+     (Win32OperatingSystem class compiledMethodAt:#primClosePrinter:) externalLibraryFunctionCall
+
+     (IUnknownPointer compiledMethodAt:#invokeAddRef) isExternalLibraryFunctionCall
+     (IUnknownPointer compiledMethodAt:#invokeAddRef) externalLibraryFunction
+     (IUnknownPointer compiledMethodAt:#invokeAddRef) isOLECall
+     (IUnknownPointer compiledMethodAt:#invokeAddRef) indexOfOLECall
     "
 !
 
@@ -2164,7 +2164,7 @@
     and:[(AbstractSourceCodeManager isVersionMethodSelector:self selector)]
 
     "
-     (Method class compiledMethodAt:#version) isVersionMethod  
+     (Method class compiledMethodAt:#version) isVersionMethod
      (Method class compiledMethodAt:#documentation) isVersionMethod
     "
 !
@@ -2203,11 +2203,11 @@
      Uses Parser to parse methods source and extract the names.
      The returned collection includes all used message selectors (i.e. including super-send messages)"
 
-    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#messagesSent or:#() 
+    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#messagesSent or:#()
 
     "
-     (Method compiledMethodAt:#printOn:) messagesSent 
-     (Point compiledMethodAt:#x:) messagesSent 
+     (Method compiledMethodAt:#printOn:) messagesSent
+     (Point compiledMethodAt:#x:) messagesSent
     "
 !
 
@@ -2215,7 +2215,7 @@
     "return a collection with the message selectors sent to self by the receiver.
      Uses Parser to parse methods source and extract the names."
 
-    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#messagesSentToSelf or:#() 
+    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#messagesSentToSelf or:#()
 
 !
 
@@ -2223,7 +2223,7 @@
     "return a collection with the message selectors sent to super by the receiver.
      Uses Parser to parse methods source and extract the names."
 
-    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#messagesSentToSuper or:#() 
+    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#messagesSentToSuper or:#()
 
 !
 
@@ -2314,8 +2314,8 @@
 methodDefinitionTemplate
     "return the string that defines the method and the arguments"
 
-    ^ Method 
-        methodDefinitionTemplateForSelector:self selector 
+    ^ Method
+        methodDefinitionTemplateForSelector:self selector
         andArgumentNames:self methodArgNames
 
     "
@@ -2338,7 +2338,7 @@
 
 modificationTime
     "try to extract the modificationTime as a timeStamp from
-     the receivers source. If there is no source or no history line, 
+     the receivers source. If there is no source or no history line,
      we do not know the modification time, and nil is returned."
 
     |s list histLine|
@@ -2350,13 +2350,13 @@
     list := HistoryManager getAllHistoriesFrom:s.
     list size == 0 ifTrue:[^ nil].
     histLine := list last.
-    ^ Timestamp 
-        fromDate:histLine date 
+    ^ Timestamp
+        fromDate:histLine date
         andTime:histLine time
 
     "
      (Method compiledMethodAt:#modificationTime) modificationTime
-     (Method compiledMethodAt:#isMethod) modificationTime 
+     (Method compiledMethodAt:#isMethod) modificationTime
     "
 
     "Modified: 8.9.1995 / 15:08:22 / claus"
@@ -2371,7 +2371,7 @@
     "Created: / 9.11.1998 / 06:15:08 / cg"
 !
 
-parse:parseSelector return:accessSelector or:valueIfNoSource 
+parse:parseSelector return:accessSelector or:valueIfNoSource
     "helper for methodArgNames, methodVarNames etc.
      Get the source, let parser parse it using parseSelector,
      return parser-info using accessSelector"
@@ -2380,11 +2380,11 @@
 
     "
      (Method compiledMethodAt:#parse:return:or:)
-        parse:#'parseMethodSilent:' return:#sentMessages or:#() 
+        parse:#'parseMethodSilent:' return:#sentMessages or:#()
     "
 !
 
-parse:parseSelector with:arg2 return:accessSelector or:valueIfNoSource 
+parse:parseSelector with:arg2 return:accessSelector or:valueIfNoSource
     "helper for methodArgNames, methodVarNames etc.
      Get the source, let parser parse it using parseSelector,
      return parser-info using accessSelector"
@@ -2406,7 +2406,7 @@
 
     "
      (Method compiledMethodAt:#parse:return:or:)
-        parse:#'parseMethodSilent:' return:#sentMessages or:#() 
+        parse:#'parseMethodSilent:' return:#sentMessages or:#()
     "
 !
 
@@ -2425,7 +2425,7 @@
     ].
     "/ 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:[
@@ -2445,10 +2445,10 @@
     cls := self mclass.
     cls isNil ifTrue:[ ^ nil ].
 
-    ChangeSet current reverseDo:[:change | 
-        (change isMethodChange 
+    ChangeSet current reverseDo:[:change |
+        (change isMethodChange
         and:[ (change selector == sel)
-        and:[ change changeClass == cls ]]) 
+        and:[ change changeClass == cls ]])
         ifTrue:[
             previous := change previousVersion.
             previous notNil ifTrue:[
@@ -2470,7 +2470,7 @@
 "/                                    ] ifFalse:[
 "/                                        false
 "/                                    ]
-"/                             ] 
+"/                             ]
 "/                     ifNone:nil.
 "/    entry isNil ifTrue:[^nil].
 "/    ^ entry second.
@@ -2503,13 +2503,13 @@
 
     versions := OrderedCollection new.
 
-    ChangeSet current reverseDo:[:change | 
-         (change isMethodChange 
+    ChangeSet current reverseDo:[:change |
+         (change isMethodChange
         and:[ (change selector == sel)
-        and:[ change changeClass == cls ]]) 
+        and:[ change changeClass == cls ]])
         ifTrue:[
             versions addFirst:change.
-            lastChange := change.    
+            lastChange := change.
         ]
     ].
 
@@ -2519,8 +2519,8 @@
             firstSrc := last source.
             (firstSrc size > 0
             and:[ firstSrc ~= lastChange source]) ifTrue:[
-                versions addFirst:(MethodChange 
-                                    className:lastChange className 
+                versions addFirst:(MethodChange
+                                    className:lastChange className
                                     selector:lastChange selector
                                     source:firstSrc
                                     category:lastChange category).
@@ -2543,7 +2543,7 @@
 
 resourceType
     "ST-80 compatibility:
-     return the methods first resource specs key. 
+     return the methods first resource specs key.
      Returns either nil, or a single symbol."
 
     |resources|
@@ -2565,7 +2565,7 @@
 
 selector
     "return the selector under which I am found in my containingClasses
-     method-table. 
+     method-table.
      See comment in who."
 
     "based on who, which has been added for ST-80 compatibility"
@@ -2631,24 +2631,24 @@
     "return a collection with the global names referred to by the receiver.
      Uses Parser to parse methods source and extract them."
 
-    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#usedGlobals or:#() 
+    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#usedGlobals or:#()
 
     "
-     (Method compiledMethodAt:#resources) usedGlobals 
+     (Method compiledMethodAt:#resources) usedGlobals
     "
 !
 
 usedSymbols
     "return a collection with the symbols referred to by the receiver.
      Uses Parser to parse methods source and extract them.
-     This collection only includes implicit symbols references 
+     This collection only includes implicit symbols references
      (i.e. not messages sent)"
 
-    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#usedSymbols or:#() 
+    ^ self parse:#'parseMethodSilent:in:' with:self mclass return:#usedSymbols or:#()
 
     "
-     (Method compiledMethodAt:#usedSymbols) usedSymbols 
-     (Method compiledMethodAt:#usedSymbols) messagesSent 
+     (Method compiledMethodAt:#usedSymbols) usedSymbols
+     (Method compiledMethodAt:#usedSymbols) messagesSent
     "
 !
 
@@ -2656,28 +2656,28 @@
     "return the class and selector of where I am defined in;
      nil is returned for unbound methods.
 
-     ST/X special notice: 
+     ST/X special notice:
         returns an instance of MethodWhoInfo, which
         responds to #methodClass and #methodSelector query messages.
         For backward- (& ST-80) compatibility, the returned object also
         responds to #at:1 and #at:2 messages.
 
      Implementation notice:
-        Since there is no information of the containing class 
+        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 
+        - the information about which class the original method was
         defined in is lost in this case.
 
-     Problem: 
+     Problem:
         this is heavily called for in the debugger to create
         a readable context walkback. For unbound methods, it is
         slow, since the search (over all classes) will always fail.
 
-     Q: should we add a backref from the method to the class 
+     Q: should we add a backref from the method to the class
         and/or add a subclass of Method for unbound ones ?
      Q2: if so, what about the bad guy then, who copies methods around to
          other classes ?"
@@ -2737,7 +2737,7 @@
     ].
 
     "
-     first, limit the search to global classes only - 
+     first, limit the search to global classes only -
      since probability is high, that the receiver is found in there ...
     "
     classes := Smalltalk allClasses.
@@ -2775,8 +2775,8 @@
     "
      |m cls|
 
-     Object 
-        subclass:#FunnyClass 
+     Object
+        subclass:#FunnyClass
         instanceVariableNames:'foo'
         classVariableNames:''
         poolDictionaries:''
@@ -2994,11 +2994,11 @@
 !Method class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.346 2010-02-04 17:34:50 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.347 2010-04-07 17:36:33 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.346 2010-02-04 17:34:50 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.347 2010-04-07 17:36:33 cg Exp $'
 ! !
 
 Method initialize!