I fixed it.
What you get now are the old mails :)

Stef

On Jun 2, 2009, at 4:07 PM, Gabriel Cotelli wrote:

> Hi Stef,
> I check that tonight... If I remember right there's some Yoshiki  
> change on notify: ...
>
> On Sun, May 31, 2009 at 6:46 PM, Stéphane Ducasse <[email protected] 
> > wrote:
> hi gabriel
>
> when you load the relicensing part 4 are you able to run the tests?
> Because when I do that I get a problem with the test
> IVsAndClassVarNamesConflictTest which opens a notifier.
> Could you check and let me know?
>
> Stef
>
>
> VM: Mac OS - intel - 1057 - Squeak3.8.1 of '28 Aug 2006' [latest
> update: #6747] Squeak VM 4.1.1b2
> Image: Pharo0.1 [Latest update: #10322]
>
> 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
>
> ClassBuilder(Object)>>notify:
>        Receiver: a ClassBuilder
>        Arguments and temporary variables:
>                aString:        'Class variables should begin with  
> upper case characters'
>        Receiver's instance variables:
>                environ:        Smalltalk
>                classMap:       nil
>                instVarMap:     an IdentityDictionary()
>                progress:       nil
>                maxClassIndex:  nil
>                currentClassIndex:      nil
>
> ClassBuilder>>validateClassvars:from:forSuper:
>        Receiver: a ClassBuilder
>        Arguments and temporary variables:
> <<error during printing>
>        Receiver's instance variables:
>                environ:        Smalltalk
>                classMap:       nil
>                instVarMap:     an IdentityDictionary()
>                progress:       nil
>                maxClassIndex:  nil
>                currentClassIndex:      nil
>
> [] in
> ClassBuilder
>  >
>  >
> name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category:unsafe
> :
>        Receiver: a ClassBuilder
>        Arguments and temporary variables:
> <<error during printing>
>        Receiver's instance variables:
>                environ:        Smalltalk
>                classMap:       nil
>                instVarMap:     an IdentityDictionary()
>                progress:       nil
>                maxClassIndex:  nil
>                currentClassIndex:      nil
>
> BlockClosure>>ensure:
>        Receiver: [closure] in
> ClassBuilder
>  >
>  >
> name:inEnvironment:subclassOf:type:instanceVariableNames:classV 
> ...etc...
>        Arguments and temporary variables:
>                aBlock:         [closure] in
> ClassBuilder>>name:inEnvironment:subclassOf:type:instanceV...etc...
>                returnValue:    nil
>                b:      nil
>        Receiver's instance variables:
>                outerContext:
> ClassBuilder
>  >>name:inEnvironment:subclassOf:type:instanceVariable...etc...
>                startpc:        346
>                numArgs:        0
>
> ClassBuilder
>  >
>  >
> name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category:unsafe
> :
>        Receiver: a ClassBuilder
>        Arguments and temporary variables:
> <<error during printing>
>        Receiver's instance variables:
>                environ:        Smalltalk
>                classMap:       nil
>                instVarMap:     an IdentityDictionary()
>                progress:       nil
>                maxClassIndex:  nil
>                currentClassIndex:      nil
>
> ClassBuilder
>  >
>  >
> name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category
> :
>        Receiver: a ClassBuilder
>        Arguments and temporary variables:
>                className:      #ClassForTestToBeDeleted
>                env:    Smalltalk
>                newSuper:       Object
>                type:   #normal
>                instVarString:  'a b c'
>                classVarString:         'a b c'
>                poolString:     ''
>                category:       #'KernelTests-Classes'
>        Receiver's instance variables:
>                environ:        Smalltalk
>                classMap:       nil
>                instVarMap:     an IdentityDictionary()
>                progress:       nil
>                maxClassIndex:  nil
>                currentClassIndex:      nil
>
> ClassBuilder
>  >
>  >
> superclass:subclass:instanceVariableNames:classVariableNames:poolDictionaries:category
> :
>        Receiver: a ClassBuilder
>        Arguments and temporary variables:
>                newSuper:       Object
>                t:      #ClassForTestToBeDeleted
>                f:      'a b c'
>                d:      'a b c'
>                s:      ''
>                cat:    #'KernelTests-Classes'
>        Receiver's instance variables:
>                environ:        Smalltalk
>                classMap:       nil
>                instVarMap:     an IdentityDictionary()
>                progress:       nil
>                maxClassIndex:  nil
>                currentClassIndex:      nil
>
> Object
> class
> (Class
> )>
>  >
> subclass:instanceVariableNames:classVariableNames:poolDictionaries:category
> :
>        Receiver: Object
>        Arguments and temporary variables:
>                t:      #ClassForTestToBeDeleted
>                f:      'a b c'
>                d:      'a b c'
>                s:      ''
>                cat:    #'KernelTests-Classes'
>        Receiver's instance variables:
>                superclass:     ProtoObject
>                methodDict:     a MethodDictionary(size 373)
>                format:         2
>                instanceVariables:      nil
>                organization:   ('*39deprecated')
> ('*monticello' isConflict)
> ('*morphic-newcurve-...etc...
>                subclasses:     {BalloonState . SoundCodec .  
> StandardFileMenuResult .
> UndefinedObje...etc...
>                name:   #Object
>                classPool:      a Dictionary(#DependentsFields->a
> WeakIdentityKeyDictionary(size 115...etc...
>                sharedPools:    nil
>                environment:    Smalltalk
>                category:       #'Kernel-Objects'
>                traitComposition:       {}
>                localSelectors:         nil
>
> [] in
> IVsAndClassVarNamesConflictTest
>  >>testIvNamesAndClassVarNamesShouldBeDifferent
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> [] in
> IVsAndClassVarNamesConflictTest(TestCase)>>executeShould:inScopeOf:
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
> <<error during printing>
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> BlockClosure>>on:do:
>        Receiver: [closure] in
> IVsAndClassVarNamesConflictTest(TestCase)>>executeShould:inScopeOf:
>        Arguments and temporary variables:
>                exception:      Exception
>                handlerAction:  [closure] in
> IVsAndClassVarNamesConflictTest(TestCase)>>executeS...etc...
>                handlerActive:  true
>        Receiver's instance variables:
>                outerContext:
> IVsAndClassVarNamesConflictTest
> (TestCase)>>executeShould:inScopeO...etc...
>                startpc:        26
>                numArgs:        0
>
> IVsAndClassVarNamesConflictTest(TestCase)>>executeShould:inScopeOf:
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
>                aBlock:         [closure] in
> IVsAndClassVarNamesConflictTest>>testIvNamesAndClassVarNam...etc...
>                anExceptionalEvent:     Exception
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> IVsAndClassVarNamesConflictTest(TestCase)>>should:raise:
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
>                aBlock:         [closure] in
> IVsAndClassVarNamesConflictTest>>testIvNamesAndClassVarNam...etc...
>                anExceptionalEvent:     Exception
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> IVsAndClassVarNamesConflictTest
>  >>testIvNamesAndClassVarNamesShouldBeDifferent
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> IVsAndClassVarNamesConflictTest(TestCase)>>performTest
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> [] in IVsAndClassVarNamesConflictTest(TestCase)>>runCase
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> BlockClosure>>ensure:
>        Receiver: [closure] in
> IVsAndClassVarNamesConflictTest(TestCase)>>runCase
>        Arguments and temporary variables:
>                aBlock:         [closure] in
> IVsAndClassVarNamesConflictTest(TestCase)>>runCase
>                returnValue:    nil
>                b:      nil
>        Receiver's instance variables:
>                outerContext:    
> IVsAndClassVarNamesConflictTest(TestCase)>>runCase
>                startpc:        33
>                numArgs:        0
>
> IVsAndClassVarNamesConflictTest(TestCase)>>runCase
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> [] in [] in TestResult>>runCase:
>        Receiver: 4256 run, 4226 passes, 1 expected failures, 19  
> failures, 10
> errors, 0 unexpected passes
>        Arguments and temporary variables:
> <<error during printing>
>        Receiver's instance variables:
>                timeStamp:      31 May 2009 11:09:54 pm
>                failures:       a Set(MCPackageTest>>#testUnload
> ClosureCompilerTest>>#testSourceRang...etc...
>                errors:         an
> OrderedCollection(HostSystemMenusTest>>#testCharacterChanging
> BlockC...etc...
>                passed:         an
> OrderedCollection(TraitMethodDescriptionTest>>#testArgumentNames
> Tra...etc...
>
> BlockClosure>>on:do:
>        Receiver: [closure] in [] in TestResult>>runCase:
>        Arguments and temporary variables:
>                exception:      TestFailure
>                handlerAction:  [closure] in [] in TestResult>>runCase:
>                handlerActive:  true
>        Receiver's instance variables:
>                outerContext:   [] in TestResult>>runCase:
>                startpc:        55
>                numArgs:        0
>
> [] in TestResult>>runCase:
>        Receiver: 4256 run, 4226 passes, 1 expected failures, 19  
> failures, 10
> errors, 0 unexpected passes
>        Arguments and temporary variables:
>                aTestCase:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldB...etc...
>                testCasePassed:         #(true)
>        Receiver's instance variables:
>                timeStamp:      31 May 2009 11:09:54 pm
>                failures:       a Set(MCPackageTest>>#testUnload
> ClosureCompilerTest>>#testSourceRang...etc...
>                errors:         an
> OrderedCollection(HostSystemMenusTest>>#testCharacterChanging
> BlockC...etc...
>                passed:         an
> OrderedCollection(TraitMethodDescriptionTest>>#testArgumentNames
> Tra...etc...
>
> BlockClosure>>on:do:
>        Receiver: [closure] in TestResult>>runCase:
>        Arguments and temporary variables:
>                exception:      Error
>                handlerAction:  [closure] in TestResult>>runCase:
>                handlerActive:  true
>        Receiver's instance variables:
>                outerContext:   TestResult>>runCase:
>                startpc:        50
>                numArgs:        0
>
> TestResult>>runCase:
>        Receiver: 4256 run, 4226 passes, 1 expected failures, 19  
> failures, 10
> errors, 0 unexpected passes
>        Arguments and temporary variables:
>                aTestCase:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldB...etc...
>                testCasePassed:         #(true)
>        Receiver's instance variables:
>                timeStamp:      31 May 2009 11:09:54 pm
>                failures:       a Set(MCPackageTest>>#testUnload
> ClosureCompilerTest>>#testSourceRang...etc...
>                errors:         an
> OrderedCollection(HostSystemMenusTest>>#testCharacterChanging
> BlockC...etc...
>                passed:         an
> OrderedCollection(TraitMethodDescriptionTest>>#testArgumentNames
> Tra...etc...
>
> IVsAndClassVarNamesConflictTest(TestCase)>>run:
>        Receiver:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldBeDifferent
>        Arguments and temporary variables:
>                aResult:        4256 run, 4226 passes, 1 expected  
> failures, 19 failures,
> 10 errors, 0 ...etc...
>        Receiver's instance variables:
>                testSelector:    
> #testIvNamesAndClassVarNamesShouldBeDifferent
>                class:  ClassForTestToBeDeleted
>                className:      #ClassForTestToBeDeleted
>
> TestRunner>>runTest:
>        Receiver: a TestRunner
>        Arguments and temporary variables:
>                aTestCase:
> IVsAndClassVarNamesConflictTest
>  >>#testIvNamesAndClassVarNamesShouldB...etc...
>        Receiver's instance variables:
>                categories:     #(#'KernelTests-Chronology'  
> #'KernelTests-Classes'
> #'KernelTests-Me...etc...
>                categoriesSelected:     a Set()
>                classes:        {TestCase . ATestCase .  
> AnnouncerTest . ArrayLiteralTest .
> AuthorTest ...etc...
>                classIndex:     0
>                classesSelected:        a Set(MCPackageTest ATestCase  
> ClosureCompilerTest
> TextLineTest...etc...
>                failedList:     #()
>                failedSelected:         nil
>                errorList:      #()
>                errorSelected:  nil
>                lastUpdate:     3421264688
>                result:         4256 run, 4226 passes, 1 expected  
> failures, 19 failures, 10
> errors, 0 u...etc...
>                previousRun:    nil
>
> [] in TestRunner>>runSuite:
>        Receiver: a TestRunner
>        Arguments and temporary variables:
> <<error during printing>
>        Receiver's instance variables:
>                categories:     #(#'KernelTests-Chronology'  
> #'KernelTests-Classes'
> #'KernelTests-Me...etc...
>                categoriesSelected:     a Set()
>                classes:        {TestCase . ATestCase .  
> AnnouncerTest . ArrayLiteralTest .
> AuthorTest ...etc...
>                classIndex:     0
>                classesSelected:        a Set(MCPackageTest ATestCase  
> ClosureCompilerTest
> TextLineTest...etc...
>                failedList:     #()
>                failedSelected:         nil
>                errorList:      #()
>                errorSelected:  nil
>                lastUpdate:     3421264688
>                result:         4256 run, 4226 passes, 1 expected  
> failures, 19 failures, 10
> errors, 0 u...etc...
>                previousRun:    nil
>
> [] in [] in
> OrderedCollection(SequenceableCollection)>>do:displayingProgress:
>        Receiver: an
> OrderedCollection(TraitMethodDescriptionTest>>#testArgumentNames
> TraitMethodDescription...etc...
>        Arguments and temporary variables:
> <<error during printing>
>        Receiver's instance variables:
>                array:  an  
> Array(TraitMethodDescriptionTest>>#testArgumentNames
> TraitMethodDescr...etc...
>                firstIndex:     1
>                lastIndex:      4586
>
> OrderedCollection(SequenceableCollection)>>withIndexDo:
>        Receiver: an
> OrderedCollection(TraitMethodDescriptionTest>>#testArgumentNames
> TraitMethodDescription...etc...
>        Arguments and temporary variables:
>                elementAndIndexBlock:   [closure] in [] in
> OrderedCollection(SequenceableCollecti...etc...
>                index:  4257
>                indexLimiT:     4586
>        Receiver's instance variables:
>                array:  an  
> Array(TraitMethodDescriptionTest>>#testArgumentNames
> TraitMethodDescr...etc...
>                firstIndex:     1
>                lastIndex:      4586
>
> [] in  
> OrderedCollection(SequenceableCollection)>>do:displayingProgress:
>        Receiver: an
> OrderedCollection(TraitMethodDescriptionTest>>#testArgumentNames
> TraitMethodDescription...etc...
>        Arguments and temporary variables:
> <<error during printing>
>        Receiver's instance variables:
>                array:  an  
> Array(TraitMethodDescriptionTest>>#testArgumentNames
> TraitMethodDescr...etc...
>                firstIndex:     1
>                lastIndex:      4586
>
> [] in ProgressInitiationException>>defaultAction
>        Receiver: ProgressInitiationException
>        Arguments and temporary variables:
>                progress:       [closure] in  
> SystemProgressMorph>>label:min:max:
>                result:         #(nil)
>        Receiver's instance variables:
>                messageText:    nil
>                tag:    nil
>                signalContext:   
> ProgressInitiationException(Exception)>>signal
>                handlerContext:         nil
>                outerContext:   nil
>                workBlock:      [closure] in
> OrderedCollection(SequenceableCollection)>>do:displayin...etc...
>                maxVal:         4586
>                minVal:         0
>                aPoint:         5...@499
>                progressTitle:  'Running 4586 Tests'
>
> BlockClosure>>ensure:
>        Receiver: [closure] in  
> ProgressInitiationException>>defaultAction
>        Arguments and temporary variables:
>                aBlock:         [closure] in  
> ProgressInitiationException>>defaultAction
>                returnValue:    nil
>                b:      nil
>        Receiver's instance variables:
>                outerContext:    
> ProgressInitiationException>>defaultAction
>                startpc:        49
>                numArgs:        0
>
> ProgressInitiationException>>defaultAction
>        Receiver: ProgressInitiationException
>        Arguments and temporary variables:
>                progress:       [closure] in  
> SystemProgressMorph>>label:min:max:
>                result:         #(nil)
>        Receiver's instance variables:
>                messageText:    nil
>                tag:    nil
>                signalContext:   
> ProgressInitiationException(Exception)>>signal
>                handlerContext:         nil
>                outerContext:   nil
>                workBlock:      [closure] in
> OrderedCollection(SequenceableCollection)>>do:displayin...etc...
>                maxVal:         4586
>                minVal:         0
>                aPoint:         5...@499
>                progressTitle:  'Running 4586 Tests'
>
> UndefinedObject>>handleSignal:
>        Receiver: nil
>        Arguments and temporary variables:
>                exception:      ProgressInitiationException
>        Receiver's instance variables:
> nil
>
> MethodContext(ContextPart)>>handleSignal:
>        Receiver: BlockClosure>>on:do:
>        Arguments and temporary variables:
>                exception:      ProgressInitiationException
>                val:    nil
>        Receiver's instance variables:
>                sender:         PasteUpMorph>>becomeActiveDuring:
>                pc:     17
>                stackp:         3
>                method:         a CompiledMethod (2306)
>                closureOrNil:   nil
>                receiver:       [closure] in  
> PasteUpMorph>>becomeActiveDuring:
>
> MethodContext(ContextPart)>>handleSignal:
>        Receiver: BlockClosure>>on:do:
>        Arguments and temporary variables:
>                exception:      ProgressInitiationException
>                val:    nil
>        Receiver's instance variables:
>                sender:          
> TextMorphEditor(ParagraphEditor)>>evaluateSelection
>                pc:     17
>                stackp:         3
>                method:         a CompiledMethod (2306)
>                closureOrNil:   nil
>                receiver:       [closure] in
> TextMorphEditor(ParagraphEditor)>>evaluateSelection
>
> ProgressInitiationException(Exception)>>signal
>        Receiver: ProgressInitiationException
>        Arguments and temporary variables:
>
>        Receiver's instance variables:
>                messageText:    nil
>                tag:    nil
>                signalContext:   
> ProgressInitiationException(Exception)>>signal
>                handlerContext:         nil
>                outerContext:   nil
>                workBlock:      [closure] in
> OrderedCollection(SequenceableCollection)>>do:displayin...etc...
>                maxVal:         4586
>                minVal:         0
>                aPoint:         5...@499
>                progressTitle:  'Running 4586 Tests'
>
> ProgressInitiationException>>display:at:from:to:during:
>        Receiver: ProgressInitiationException
>        Arguments and temporary variables:
>                argString:      'Running 4586 Tests'
>                argPoint:       5...@499
>                argMinVal:      0
>                argMaxVal:      4586
>                argWorkBlock:   [closure] in
> OrderedCollection(SequenceableCollection)>>do:displa...etc...
>        Receiver's instance variables:
>                messageText:    nil
>                tag:    nil
>                signalContext:   
> ProgressInitiationException(Exception)>>signal
>                handlerContext:         nil
>                outerContext:   nil
>                workBlock:      [closure] in
> OrderedCollection(SequenceableCollection)>>do:displayin...etc...
>                maxVal:         4586
>                minVal:         0
>                aPoint:         5...@499
>                progressTitle:  'Running 4586 Tests'
>
> ProgressInitiationException class>>display:at:from:to:during:
>        Receiver: ProgressInitiationException
>        Arguments and temporary variables:
>                aString:        'Running 4586 Tests'
>                aPoint:         5...@499
>                minVal:         0
>                maxVal:         4586
>                workBlock:      [closure] in
> OrderedCollection(SequenceableCollection)>>do:displayin...etc...
>        Receiver's instance variables:
>                superclass:     Exception
>                methodDict:     a MethodDictionary(#defaultAction->a  
> CompiledMethod
> (259) #defaultM...etc...
>                format:         150
>                instanceVariables:      #('workBlock' 'maxVal'  
> 'minVal' 'aPoint'
> 'progressTitle')
>                organization:   ('as yet unclassified' defaultAction
> defaultMorphicAction display...etc...
>                subclasses:     nil
>                name:   #ProgressInitiationException
>                classPool:      nil
>                sharedPools:    nil
>                environment:    Smalltalk
>                category:       #'Exceptions-Kernel'
>                traitComposition:       {}
>                localSelectors:         nil
>
> ByteString(String)>>displayProgressAt:from:to:during:
>        Receiver: 'Running 4586 Tests'
>        Arguments and temporary variables:
>                aPoint:         5...@499
>                minVal:         0
>                maxVal:         4586
>                workBlock:      [closure] in
> OrderedCollection(SequenceableCollection)>>do:displayin...etc...
>        Receiver's instance variables:
> 'Running 4586 Tests'
>
>
> --- The full stack ---
> ClassBuilder(Object)>>notify:
> ClassBuilder>>validateClassvars:from:forSuper:
> [] in
> ClassBuilder
>  >
>  >
> name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category:unsafe
> :
> BlockClosure>>ensure:
> ClassBuilder
>  >
>  >
> name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category:unsafe
> :
> ClassBuilder
>  >
>  >
> name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category
> :
> ClassBuilder
>  >
>  >
> superclass:subclass:instanceVariableNames:classVariableNames:poolDictionaries:category
> :
> Object
> class
> (Class
> )>
>  >
> subclass:instanceVariableNames:classVariableNames:poolDictionaries:category
> :
> [] in
> IVsAndClassVarNamesConflictTest
>  >>testIvNamesAndClassVarNamesShouldBeDifferent
> [] in
> IVsAndClassVarNamesConflictTest(TestCase)>>executeShould:inScopeOf:
> BlockClosure>>on:do:
> IVsAndClassVarNamesConflictTest(TestCase)>>executeShould:inScopeOf:
> IVsAndClassVarNamesConflictTest(TestCase)>>should:raise:
> IVsAndClassVarNamesConflictTest
>  >>testIvNamesAndClassVarNamesShouldBeDifferent
> IVsAndClassVarNamesConflictTest(TestCase)>>performTest
> [] in IVsAndClassVarNamesConflictTest(TestCase)>>runCase
> BlockClosure>>ensure:
> IVsAndClassVarNamesConflictTest(TestCase)>>runCase
> [] in [] in TestResult>>runCase:
> BlockClosure>>on:do:
> [] in TestResult>>runCase:
> BlockClosure>>on:do:
> TestResult>>runCase:
> IVsAndClassVarNamesConflictTest(TestCase)>>run:
> TestRunner>>runTest:
> [] in TestRunner>>runSuite:
> [] in [] in
> OrderedCollection(SequenceableCollection)>>do:displayingProgress:
> OrderedCollection(SequenceableCollection)>>withIndexDo:
> [] in  
> OrderedCollection(SequenceableCollection)>>do:displayingProgress:
> [] in ProgressInitiationException>>defaultAction
> BlockClosure>>ensure:
> ProgressInitiationException>>defaultAction
> UndefinedObject>>handleSignal:
> MethodContext(ContextPart)>>handleSignal:
> MethodContext(ContextPart)>>handleSignal:
> ProgressInitiationException(Exception)>>signal
> ProgressInitiationException>>display:at:from:to:during:
> ProgressInitiationException class>>display:at:from:to:during:
> ByteString(String)>>displayProgressAt:from:to:during:
>  - - - - - - - - - - - - - - -
>                        - - - - - - - - - - - - - - - - - -
> OrderedCollection(SequenceableCollection)>>do:displayingProgress:
> [] in TestRunner>>basicRunSuite:do:
> BlockClosure>>ensure:
> TestRunner>>basicRunSuite:do:
> TestRunner>>runSuite:
> TestRunner>>runAll
> ScriptLoader>>verifyNewUpdate
> ScriptLoader class>>DoIt
> Compiler>>evaluate:in:to:notifying:ifFail:logged:
> [] in TextMorphEditor(ParagraphEditor)>>evaluateSelection
> BlockClosure>>on:do:
> TextMorphEditor(ParagraphEditor)>>evaluateSelection
> TextMorphEditor(ParagraphEditor)>>doIt
> [] in TextMorphEditor(ParagraphEditor)>>doIt:
> TextMorphEditor(ParagraphEditor)>>terminateAndInitializeAround:
> TextMorphEditor(ParagraphEditor)>>doIt:
> TextMorphEditor(ParagraphEditor)>>dispatchOnKeyEvent:with:
> TextMorphEditor>>dispatchOnKeyEvent:with:
> TextMorphEditor(ParagraphEditor)>>keystroke:
> TextMorphEditor>>keystroke:
> [] in TextMorphForEditView(TextMorph)>>keyStroke:
> TextMorphForEditView(TextMorph)>>handleInteraction:
> TextMorphForEditView>>handleInteraction:
> TextMorphForEditView(TextMorph)>>keyStroke:
> TextMorphForEditView>>keyStroke:
> TextMorphForEditView(TextMorph)>>handleKeystroke:
> KeyboardEvent>>sentTo:
> TextMorphForEditView(Morph)>>handleEvent:
> TextMorphForEditView(Morph)>>handleFocusEvent:
> [] in HandMorph>>sendFocusEvent:to:clear:
> [] in PasteUpMorph>>becomeActiveDuring:
> BlockClosure>>on:do:
> PasteUpMorph>>becomeActiveDuring:
> HandMorph>>sendFocusEvent:to:clear:
> HandMorph>>sendEvent:focus:clear:
> HandMorph>>sendKeyboardEvent:
> HandMorph>>handleEvent:
> HandMorph>>processEvents
> [] in WorldState>>doOneCycleNowFor:
> Array(SequenceableCollection)>>do:
> WorldState>>handsDo:
> WorldState>>doOneCycleNowFor:
> WorldState>>doOneCycleFor:
> PasteUpMorph>>doOneCycle
> [] in Project class>>spawnNewProcess
> [] in BlockClosure>>newProcess
>
>
> _______________________________________________
> 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


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

Reply via email to