In trunk, offList has been deprecated and has no senders:
offList
        "OBSOLETE. Process>>suspend will atomically reset myList if the
process is suspended.
        There should never be a need to send #offList but some older users
may not be aware
        of the changed semantics to suspend and may try the old hickadidoo seen 
here:

                (suspendingList := process suspendingList) == nil
                        ifTrue: [process == Processor activeProcess ifTrue: 
[process suspend]]
                        ifFalse: [suspendingList remove: process ifAbsent:[].
                                        process offList].

        Usages like the above should be replaced by a simple 'process suspend' "
        myList := nil

In Pharo too, but still has one sender.
The problem is that suspend now return the list, not the process, so
harvesting of Andreas changes were incomplete... You should remove
offList and try merging a recent trunk Kernel.

Nicolas

2009/12/23 Stéphane Ducasse <[email protected]>:
> This is strange
> I did not get the time to look at it but I got a deep recursion in MC which 
> stressed the low space
> and ended up in this crash
>
> Stef
>
> ------------------------------------------------------------
>
> THERE_BE_DRAGONS_HERE
> MessageNotUnderstood: LinkedList>>offList
> 23 December 2009 8:56:10 pm
>
> VM: Mac OS - intel - 1062 - Squeak3.8.1 of '28 Aug 2006' [latest update: 
> #6747] Squeak VM 4.2.2b1
> Image: PharoCore1.1ALPHA [Latest update: #11112]
>
> SecurityManager state:
> Restricted: false
> FileAccess: true
> SocketAccess: true
> Working Dir /Users/ducasse/Workspace/FirstCircle/ActiveResearch/Pharo/Pharo
> Trusted Dir /foobar/tooBar/forSqueak/bogus
> Untrusted Dir /Users/ducasse/Library/Preferences/Squeak/Internet/My Squeak
>
> LinkedList(Object)>>doesNotUnderstand: #offList
>        Receiver: a LinkedList()
>        Arguments and temporary variables:
>                aMessage:       offList
>                exception:      MessageNotUnderstood: LinkedList>>offList
>                resumeValue:    nil
>        Receiver's instance variables:
>                firstLink:      nil
>                lastLink:       nil
>
> Project class>>interruptName:preemptedProcess:
>        Receiver: Project
>        Arguments and temporary variables:
>                labelString:    'Space is low'
>                theInterruptedProcess:  a Process in 
> ByteString(Object)>>shallowCopy
>                preemptedProcess:       a Process in 
> ByteString(Object)>>shallowCopy
>                projectProcess:         a Process in 
> ByteString(Object)>>shallowCopy
>        Receiver's instance variables:
>                superclass:     Model
>                methodDict:     a 
> MethodDictionary(#changeSet->(Project>>#changeSet "a CompiledMeth...etc...
>                format:         170
>                instanceVariables:      #('world' 'changeSet' 'transcript' 
> 'parentProject' 'previous...etc...
>                organization:   ('*Polymorph-Widgets' createTaskbarIfNecessary 
> moveCollapsedWindo...etc...
>                subclasses:     nil
>                name:   #Project
>                classPool:      a Dictionary(#AllProjects->an 
> OrderedCollection(a Project) #CurrentP...etc...
>                sharedPools:    nil
>                environment:    Smalltalk
>                category:       #'System-Support'
>                traitComposition:       {}
>                localSelectors:         nil
>
> SystemDictionary>>lowSpaceWatcher
>        Receiver: Smalltalk
>        Arguments and temporary variables:
>                free:   nil
>                preemptedProcess:       a Process in 
> ByteString(Object)>>shallowCopy
>        Receiver's instance variables:
>                tally:  1817
>                array:  an Array(nil nil nil 
> #SystemSettingBrowser->SystemSettingBrowser #EFontB...etc...
>                cachedClassNames:       nil
>
> [] in SystemDictionary>>installLowSpaceWatcher
>        Receiver: Smalltalk
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                tally:  1817
>                array:  an Array(nil nil nil 
> #SystemSettingBrowser->SystemSettingBrowser #EFontB...etc...
>                cachedClassNames:       nil
>
> [] in BlockClosure>>newProcess
>        Receiver: [closure] in SystemDictionary>>installLowSpaceWatcher
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                outerContext:   SystemDictionary>>installLowSpaceWatcher
>                startpc:        65
>                numArgs:        0
>
>
> --- The full stack ---
> LinkedList(Object)>>doesNotUnderstand: #offList
> Project class>>interruptName:preemptedProcess:
> SystemDictionary>>lowSpaceWatcher
> [] in SystemDictionary>>installLowSpaceWatcher
> [] in BlockClosure>>newProcess
> ------------------------------------------------------------
>
> THERE_BE_DRAGONS_HERE
> User Interrupt
> 23 December 2009 8:56:19 pm
>
> VM: Mac OS - intel - 1062 - Squeak3.8.1 of '28 Aug 2006' [latest update: 
> #6747] Squeak VM 4.2.2b1
> Image: PharoCore1.1ALPHA [Latest update: #11112]
>
> SecurityManager state:
> Restricted: false
> FileAccess: true
> SocketAccess: true
> Working Dir /Users/ducasse/Workspace/FirstCircle/ActiveResearch/Pharo/Pharo
> Trusted Dir /foobar/tooBar/forSqueak/bogus
> Untrusted Dir /Users/ducasse/Library/Preferences/Squeak/Internet/My Squeak
>
> ByteString(Object)>>shallowCopy
>        Receiver: 'Collections-Sequenceable'
>        Arguments and temporary variables:
>                class:  nil
>                newObject:      nil
>                index:  nil
>        Receiver's instance variables:
> 'Collections-Sequenceable'
> ByteString(Object)>>copy
>        Receiver: 'Collections-Sequenceable'
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
> 'Collections-Sequenceable'
> ByteString(String)>>asLowercase
>        Receiver: 'Collections-Sequenceable'
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
> 'Collections-Sequenceable'
> MCPackage>>hash
>        Receiver: a MCPackage(Collections-Sequenceable)
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                name:   'Collections-Sequenceable'
>
> Dictionary>>scanFor:
>        Receiver: a Dictionary(size 103)
>        Arguments and temporary variables:
>                anObject:       a MCPackage(Collections-Sequenceable)
>                element:        nil
>                start:  nil
>                finish:         234
>                index:  nil
>                index:  nil
>                indexLimiT:     nil
>        Receiver's instance variables:
>                tally:  103
>                array:  an Array(nil nil nil nil a MCPackage(Tests)->a 
> MCWorkingCopy(Tests) nil ...etc...
>
> Dictionary(Set)>>findElementOrNil:
>        Receiver: a Dictionary(size 103)
>        Arguments and temporary variables:
>                anObject:       a MCPackage(Collections-Sequenceable)
>                index:  nil
>        Receiver's instance variables:
>                tally:  103
>                array:  an Array(nil nil nil nil a MCPackage(Tests)->a 
> MCWorkingCopy(Tests) nil ...etc...
>
> Dictionary>>at:ifAbsent:
>        Receiver: a Dictionary(size 103)
>        Arguments and temporary variables:
>                key:    a MCPackage(Collections-Sequenceable)
>                aBlock:         [closure] in MCWorkingCopy 
> class(MCPackageManager class)>>forPackage:
>                assoc:  nil
>        Receiver's instance variables:
>                tally:  103
>                array:  an Array(nil nil nil nil a MCPackage(Tests)->a 
> MCWorkingCopy(Tests) nil ...etc...
>
> MCWorkingCopy class(MCPackageManager class)>>forPackage:
>        Receiver: MCWorkingCopy
>        Arguments and temporary variables:
>                aPackage:       a MCPackage(Collections-Sequenceable)
>        Receiver's instance variables:
>                superclass:     MCPackageManager
>                methodDict:     a 
> MethodDictionary(#adopt:->(MCWorkingCopy>>#adopt: "a CompiledMeth...etc...
>                format:         144
>                instanceVariables:      #('versionInfo' 'ancestry' 'counter' 
> 'repositoryGroup' 'requ...etc...
>                organization:   ('*scriptloader' theCachedRepository)
> ('accessing' ancestors ance...etc...
>                subclasses:     nil
>                name:   #MCWorkingCopy
>                classPool:      nil
>                sharedPools:    nil
>                environment:    Smalltalk
>                category:       #'Monticello-Versioning'
>                traitComposition:       nil
>                localSelectors:         nil
>                registry:       a Dictionary(size 103)
>
> MCPackage>>workingCopy
>        Receiver: a MCPackage(Collections-Sequenceable)
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                name:   'Collections-Sequenceable'
>
> [] in MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>                ea:     a MCPackage(Collections-Sequenceable)
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         a MCPackage(Collections-Sequenceable)
>                each:   [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection>>do:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in 
> OrderedCollection(Collection)>>anySatisfy:
>                index:  3
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>                ea:     a MCPackage(SLICE-SortBlock)
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         a MCPackage(SLICE-SortBlock)
>                each:   [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection>>do:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in 
> OrderedCollection(Collection)>>anySatisfy:
>                index:  4
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>                ea:     a MCPackage(SLICE-SortBlock)
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         a MCPackage(SLICE-SortBlock)
>                each:   [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection>>do:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in 
> OrderedCollection(Collection)>>anySatisfy:
>                index:  4
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>                ea:     a MCPackage(SLICE-SortBlock)
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         a MCPackage(SLICE-SortBlock)
>                each:   [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection>>do:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in 
> OrderedCollection(Collection)>>anySatisfy:
>                index:  4
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>                ea:     a MCPackage(SLICE-SortBlock)
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         a MCPackage(SLICE-SortBlock)
>                each:   [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection>>do:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in 
> OrderedCollection(Collection)>>anySatisfy:
>                index:  4
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>                ea:     a MCPackage(SLICE-SortBlock)
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
> [] in OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         a MCPackage(SLICE-SortBlock)
>                each:   [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection>>do:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in 
> OrderedCollection(Collection)>>anySatisfy:
>                index:  4
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> OrderedCollection(Collection)>>anySatisfy:
>        Receiver: an OrderedCollection(a MCPackage(Collections-Sequenceable) a 
> MCPackage(SLICE-SortBlock))
>        Arguments and temporary variables:
>                aBlock:         [closure] in MCWorkingCopy>>needsSaving
>        Receiver's instance variables:
>                array:  an Array(nil nil a MCPackage(Collections-Sequenceable) 
> a MCPackage(SLICE...etc...
>                firstIndex:     3
>                lastIndex:      4
>
> MCWorkingCopy>>needsSaving
>        Receiver: a MCWorkingCopy(SLICE-SortBlock)
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                package:        a MCPackage(SLICE-SortBlock)
>                modified:       false
>                versionInfo:    nil
>                ancestry:       a MCWorkingAncestry
>                counter:        2
>                repositoryGroup:        a MCRepositoryGroup
>                requiredPackages:       an OrderedCollection(a 
> MCPackage(Collections-Sequenceable) a ...etc...
>
>
> --- The full stack ---
> ByteString(Object)>>shallowCopy
> ByteString(Object)>>copy
> ByteString(String)>>asLowercase
> MCPackage>>hash
> Dictionary>>scanFor:
> Dictionary(Set)>>findElementOrNil:
> Dictionary>>at:ifAbsent:
> MCWorkingCopy class(MCPackageManager class)>>forPackage:
> MCPackage>>workingCopy
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
>  - - - - - - - - - - - - - - -
>                        - - - - - - - - - - - - - - - - - -
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> OrderedCollection>>do:
> OrderedCollection(Collection)>>anySatisfy:
> MCWorkingCopy>>needsSaving
> [] in MCWorkingCopy>>needsSaving
> [] in OrderedCollection(Collection)>>anySatisfy:
> -- and more not shown 
> --------------------------------------------------------------
>
>
>
> _______________________________________________
> Pharo-project mailing list
> [email protected]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>

_______________________________________________
Pharo-project mailing list
[email protected]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to