El mié, 17-02-2010 a las 16:12 -0500, Dave Woodward escribió: > I got it working in OS X by also changing the tcp/ip IPv6 setting from > "Automatically" to "Off". I haven't tried it in Linux yet. Hope this > helps.
I don't understand, what you changed, the OS X settings or the image code settings (I didn't know about settings for ipv6 in pharo). Maybe unrelated, some months ago, my wife's macbook caused my linux laptop to disconnect every time she connected to the wireless network. We had any idea but after a while we noticed that even if I had a perfect working connection after she connected my connection crashed. I had to disconnect, she connected, and then after she had a connection I connected. After some research I found that OS X had a setting in the airport configuration about ipv6. I disabled it lefting only the ipv4 settings enabled. We never had a problem after that. As I said, maybe unrelated but... mac os, ipv6, problems. Cheers > > On 2/17/10 2:09 PM, Chris Muller wrote: > > The stable Magma production version cannot get out of the starting > > gate on a fresh Pharo RC2 (Pharo1.0-10508-rc2dev10.01.2) due to some > > sort of networking issue. I ensured useOldNetwork was set true, and > > tried your printOn: method, but getting primitive failure. > > > > The same exact version of Magma runs fine on Pharo1.0-10502-rc1dev09.12.2. > > > > The stack trace below. Thanks. > > > > - Chris > > > > THERE_BE_DRAGONS_HERE > > Error: a primitive has failed > > 17 February 2010 12:33:18 pm > > > > VM: unix - i686 - linux-gnu - Pharo0.1 of 16 May 2008 [latest update: > > #10074] > > Image: Pharo-1.0-10508-rc2 [Latest update: #10508] > > > > SecurityManager state: > > Restricted: false > > FileAccess: true > > SocketAccess: true > > > > NetNameResolver class(Object)>>error: > > Receiver: NetNameResolver > > Arguments and temporary variables: > > aString: 'a primitive has failed' > > Receiver's instance variables: > > superclass: Object > > methodDict: a MethodDictionary() > > format: 2 > > instanceVariables: nil > > organization: ('as yet unclassified') > > > > subclasses: nil > > name: #NetNameResolver > > classPool: a Dictionary(#DefaultHostName->'' > > #HaveNetwork->true > > #ResolverBusy->...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Network-Kernel' > > traitComposition: nil > > localSelectors: nil > > > > NetNameResolver class(Object)>>primitiveFailed > > Receiver: NetNameResolver > > Arguments and temporary variables: > > > > Receiver's instance variables: > > superclass: Object > > methodDict: a MethodDictionary() > > format: 2 > > instanceVariables: nil > > organization: ('as yet unclassified') > > > > subclasses: nil > > name: #NetNameResolver > > classPool: a Dictionary(#DefaultHostName->'' > > #HaveNetwork->true > > #ResolverBusy->...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Network-Kernel' > > traitComposition: nil > > localSelectors: nil > > > > NetNameResolver class>>primGetNameInfo:flags: > > Receiver: NetNameResolver > > Arguments and temporary variables: > > socketAddress: #[127 0 1 1] > > flags: 1 > > Receiver's instance variables: > > superclass: Object > > methodDict: a MethodDictionary() > > format: 2 > > instanceVariables: nil > > organization: ('as yet unclassified') > > > > subclasses: nil > > name: #NetNameResolver > > classPool: a Dictionary(#DefaultHostName->'' > > #HaveNetwork->true > > #ResolverBusy->...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Network-Kernel' > > traitComposition: nil > > localSelectors: nil > > > > SocketAddress>>hostNumber > > Receiver: #[127 0 1 1] > > Arguments and temporary variables: > > size: nil > > name: nil > > Receiver's instance variables: > > #[127 0 1 1] > > > > [] in Socket>>connectTo:port:waitForConnectionFor: > > Receiver: a Socket[unconnected] > > Arguments and temporary variables: > > hostAddress: #[127 0 1 1] > > port: 1316 > > Receiver's instance variables: > > semaphore: a Semaphore() > > socketHandle: #[59 33 134 75 0 0 0 0 200 212 50 9] > > readSemaphore: a Semaphore() > > writeSemaphore: a Semaphore() > > primitiveOnlySupportsOneSemaphore: false > > > > Socket>>waitForConnectionFor:ifTimedOut: > > Receiver: a Socket[unconnected] > > Arguments and temporary variables: > > timeout: 5 > > timeoutBlock: [closure] in > > Socket>>connectTo:port:waitForConnectionFor: > > startTime: 66537 > > msecsDelta: 5000 > > msecsEllapsed: nil > > status: 0 > > Receiver's instance variables: > > semaphore: a Semaphore() > > socketHandle: #[59 33 134 75 0 0 0 0 200 212 50 9] > > readSemaphore: a Semaphore() > > writeSemaphore: a Semaphore() > > primitiveOnlySupportsOneSemaphore: false > > > > Socket>>connectTo:port:waitForConnectionFor: > > Receiver: a Socket[unconnected] > > Arguments and temporary variables: > > hostAddress: #[127 0 1 1] > > port: 1316 > > timeout: 5 > > Receiver's instance variables: > > semaphore: a Semaphore() > > socketHandle: #[59 33 134 75 0 0 0 0 200 212 50 9] > > readSemaphore: a Semaphore() > > writeSemaphore: a Semaphore() > > primitiveOnlySupportsOneSemaphore: false > > > > [] in MaNetworkTestPlayerFacade>>isReady > > Receiver: a MaNetworkTestPlayerFacade > > Arguments and temporary variables: > > socket: #(nil) > > Receiver's instance variables: > > link: a MaNetworkServerLink chrisT60p:1316 > > name: 'server' > > testCaseClass: MagmaTestCase > > > > BlockClosure>>on:do: > > Receiver: [closure] in MaNetworkTestPlayerFacade>>isReady > > Arguments and temporary variables: > > exception: ConnectionTimedOut > > handlerAction: [closure] in MaNetworkTestPlayerFacade>>isReady > > handlerActive: true > > Receiver's instance variables: > > outerContext: MaNetworkTestPlayerFacade>>isReady > > startpc: 85 > > numArgs: 0 > > > > MaNetworkTestPlayerFacade>>isReady > > Receiver: a MaNetworkTestPlayerFacade > > Arguments and temporary variables: > > socket: #(nil) > > Receiver's instance variables: > > link: a MaNetworkServerLink chrisT60p:1316 > > name: 'server' > > testCaseClass: MagmaTestCase > > > > [] in MagmaTestCase class(MaNetworkTestCase class)>>waitForPlayerImages > > Receiver: MagmaTestCase > > Arguments and temporary variables: > > each: a MaNetworkTestPlayerFacade > > Receiver's instance variables: > > superclass: MaNetworkTestCase > > methodDict: a MethodDictionary(size 184) > > format: 162 > > instanceVariables: #('magmaConsole' 'peerConsole' > > 'clientSession' > > 'localRoot' '...etc... > > organization: ('initialize-release' abort abortClients > > assertForwardRecoverySig...etc... > > subclasses: {MagmaCollectionTester} > > name: #MagmaTestCase > > classPool: a Dictionary(#InitiateBackupPrereqsCompleted->a > > Set() > > #MagmaServerAd...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Magma tester-SUnit tests' > > traitComposition: {} > > localSelectors: nil > > history: a Dictionary(#errors->a Set() #failures->a Set() > > #passed->a Set() #tim...etc... > > > > [] in Dictionary(Collection)>>allSatisfy: > > Receiver: a Dictionary('client1'->a MaNetworkTestPlayerFacade > > 'client2'->a MaNetworkTestPlayerFacad...etc... > > Arguments and temporary variables: > > aBlock: a MaNetworkTestPlayerFacade > > each: [closure] in MagmaTestCase class(MaNetworkTestCase > > class)>>waitForPlayerI...etc... > > Receiver's instance variables: > > tally: 4 > > array: {nil. 'client1'->a MaNetworkTestPlayerFacade . > > 'client2'->a > > MaNetworkTes...etc... > > > > [] in Dictionary>>do: > > Receiver: a Dictionary('client1'->a MaNetworkTestPlayerFacade > > 'client2'->a MaNetworkTestPlayerFacad...etc... > > Arguments and temporary variables: > > aBlock: 'server'->a MaNetworkTestPlayerFacade > > assoc: [closure] in Dictionary(Collection)>>allSatisfy: > > Receiver's instance variables: > > tally: 4 > > array: {nil. 'client1'->a MaNetworkTestPlayerFacade . > > 'client2'->a > > MaNetworkTes...etc... > > > > Dictionary(Set)>>do: > > Receiver: a Dictionary('client1'->a MaNetworkTestPlayerFacade > > 'client2'->a MaNetworkTestPlayerFacad...etc... > > Arguments and temporary variables: > > aBlock: [closure] in Dictionary>>do: > > index: 4 > > each: 'server'->a MaNetworkTestPlayerFacade > > indexLimiT: 5 > > Receiver's instance variables: > > tally: 4 > > array: {nil. 'client1'->a MaNetworkTestPlayerFacade . > > 'client2'->a > > MaNetworkTes...etc... > > > > Dictionary>>do: > > Receiver: a Dictionary('client1'->a MaNetworkTestPlayerFacade > > 'client2'->a MaNetworkTestPlayerFacad...etc... > > Arguments and temporary variables: > > aBlock: [closure] in Dictionary(Collection)>>allSatisfy: > > Receiver's instance variables: > > tally: 4 > > array: {nil. 'client1'->a MaNetworkTestPlayerFacade . > > 'client2'->a > > MaNetworkTes...etc... > > > > Dictionary(Collection)>>allSatisfy: > > Receiver: a Dictionary('client1'->a MaNetworkTestPlayerFacade > > 'client2'->a MaNetworkTestPlayerFacad...etc... > > Arguments and temporary variables: > > aBlock: [closure] in MagmaTestCase > > class(MaNetworkTestCase > > class)>>waitForPlaye...etc... > > Receiver's instance variables: > > tally: 4 > > array: {nil. 'client1'->a MaNetworkTestPlayerFacade . > > 'client2'->a > > MaNetworkTes...etc... > > > > MagmaTestCase class(MaNetworkTestCase class)>>waitForPlayerImages > > Receiver: MagmaTestCase > > Arguments and temporary variables: > > > > Receiver's instance variables: > > superclass: MaNetworkTestCase > > methodDict: a MethodDictionary(size 184) > > format: 162 > > instanceVariables: #('magmaConsole' 'peerConsole' > > 'clientSession' > > 'localRoot' '...etc... > > organization: ('initialize-release' abort abortClients > > assertForwardRecoverySig...etc... > > subclasses: {MagmaCollectionTester} > > name: #MagmaTestCase > > classPool: a Dictionary(#InitiateBackupPrereqsCompleted->a > > Set() > > #MagmaServerAd...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Magma tester-SUnit tests' > > traitComposition: {} > > localSelectors: nil > > history: a Dictionary(#errors->a Set() #failures->a Set() > > #passed->a Set() #tim...etc... > > > > MagmaTestCase class(MaNetworkTestCase class)>>launchPlayerImages > > Receiver: MagmaTestCase > > Arguments and temporary variables: > > > > Receiver's instance variables: > > superclass: MaNetworkTestCase > > methodDict: a MethodDictionary(size 184) > > format: 162 > > instanceVariables: #('magmaConsole' 'peerConsole' > > 'clientSession' > > 'localRoot' '...etc... > > organization: ('initialize-release' abort abortClients > > assertForwardRecoverySig...etc... > > subclasses: {MagmaCollectionTester} > > name: #MagmaTestCase > > classPool: a Dictionary(#InitiateBackupPrereqsCompleted->a > > Set() > > #MagmaServerAd...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Magma tester-SUnit tests' > > traitComposition: {} > > localSelectors: nil > > history: a Dictionary(#errors->a Set() #failures->a Set() > > #passed->a Set() #tim...etc... > > > > MagmaTestCase class>>launchPlayerImages > > Receiver: MagmaTestCase > > Arguments and temporary variables: > > > > Receiver's instance variables: > > superclass: MaNetworkTestCase > > methodDict: a MethodDictionary(size 184) > > format: 162 > > instanceVariables: #('magmaConsole' 'peerConsole' > > 'clientSession' > > 'localRoot' '...etc... > > organization: ('initialize-release' abort abortClients > > assertForwardRecoverySig...etc... > > subclasses: {MagmaCollectionTester} > > name: #MagmaTestCase > > classPool: a Dictionary(#InitiateBackupPrereqsCompleted->a > > Set() > > #MagmaServerAd...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Magma tester-SUnit tests' > > traitComposition: {} > > localSelectors: nil > > history: a Dictionary(#errors->a Set() #failures->a Set() > > #passed->a Set() #tim...etc... > > > > MagmaTestCase class(MaNetworkTestCase class)>>setUpSuite > > Receiver: MagmaTestCase > > Arguments and temporary variables: > > > > Receiver's instance variables: > > superclass: MaNetworkTestCase > > methodDict: a MethodDictionary(size 184) > > format: 162 > > instanceVariables: #('magmaConsole' 'peerConsole' > > 'clientSession' > > 'localRoot' '...etc... > > organization: ('initialize-release' abort abortClients > > assertForwardRecoverySig...etc... > > subclasses: {MagmaCollectionTester} > > name: #MagmaTestCase > > classPool: a Dictionary(#InitiateBackupPrereqsCompleted->a > > Set() > > #MagmaServerAd...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Magma tester-SUnit tests' > > traitComposition: {} > > localSelectors: nil > > history: a Dictionary(#errors->a Set() #failures->a Set() > > #passed->a Set() #tim...etc... > > > > MagmaTestCase class>>setUpSuite > > Receiver: MagmaTestCase > > Arguments and temporary variables: > > > > Receiver's instance variables: > > superclass: MaNetworkTestCase > > methodDict: a MethodDictionary(size 184) > > format: 162 > > instanceVariables: #('magmaConsole' 'peerConsole' > > 'clientSession' > > 'localRoot' '...etc... > > organization: ('initialize-release' abort abortClients > > assertForwardRecoverySig...etc... > > subclasses: {MagmaCollectionTester} > > name: #MagmaTestCase > > classPool: a Dictionary(#InitiateBackupPrereqsCompleted->a > > Set() > > #MagmaServerAd...etc... > > sharedPools: nil > > environment: Smalltalk > > category: #'Magma tester-SUnit tests' > > traitComposition: {} > > localSelectors: nil > > history: a Dictionary(#errors->a Set() #failures->a Set() > > #passed->a Set() #tim...etc... > > > > MagmaTestCase(MaTestCase)>>setUpSuite > > Receiver: MagmaTestCase>>#testAdvance > > Arguments and temporary variables: > > > > Receiver's instance variables: > > testSelector: #testAdvance > > magmaConsole: nil > > peerConsole: nil > > clientSession: nil > > localRoot: a Dictionary() > > proxy: nil > > original34990: nil > > forwardRecoverySignaled: false > > timeToVerifyRestore: false > > shouldStopGeneratingSequenceNumbers: nil > > sequenceNumbers: nil > > dormantObject: nil > > objectToAdvance: nil > > forwardRecoveryRequirement: nil > > shouldStopFlooding: false > > refreshTestFixture: nil > > > > [] in [] in TestSuite>>maExecuteTestsUsing:result: > > Receiver: a TestSuite > > Arguments and temporary variables: > > > > Receiver's instance variables: > > tests: an OrderedCollection(MagmaTestCase>>#testAdvance > > MagmaTestCase>>#testBlo...etc... > > resources: nil > > name: nil > > > > BlockClosure>>on:do: > > Receiver: [closure] in [] in TestSuite>>maExecuteTestsUsing:result: > > Arguments and temporary variables: > > exception: MaNotification > > handlerAction: [closure] in [] in > > TestSuite>>maExecuteTestsUsing:result: > > handlerActive: true > > Receiver's instance variables: > > outerContext: [] in TestSuite>>maExecuteTestsUsing:result: > > startpc: 110 > > numArgs: 0 > > > > [] in TestSuite>>maExecuteTestsUsing:result: > > Receiver: a TestSuite > > Arguments and temporary variables: > > aSymbol: #maDebug: > > aResult: 0 run, 0 passes, 0 expected failures, 0 > > failures, 0 > > errors, 0 unexpect...etc... > > shouldRunTests: nil > > durationToRun: nil > > Receiver's instance variables: > > tests: an OrderedCollection(MagmaTestCase>>#testAdvance > > MagmaTestCase>>#testBlo...etc... > > resources: nil > > name: nil > > > > BlockClosure>>ensure: > > Receiver: [closure] in TestSuite>>maExecuteTestsUsing:result: > > Arguments and temporary variables: > > aBlock: [closure] in > > TestSuite>>maExecuteTestsUsing:result: > > returnValue: nil > > b: nil > > Receiver's instance variables: > > outerContext: TestSuite>>maExecuteTestsUsing:result: > > startpc: 104 > > numArgs: 0 > > > > TestSuite>>maExecuteTestsUsing:result: > > Receiver: a TestSuite > > Arguments and temporary variables: > > aSymbol: #maDebug: > > aResult: 0 run, 0 passes, 0 expected failures, 0 > > failures, 0 > > errors, 0 unexpect...etc... > > Receiver's instance variables: > > tests: an OrderedCollection(MagmaTestCase>>#testAdvance > > MagmaTestCase>>#testBlo...etc... > > resources: nil > > name: nil > > > > TestSuite>>maDebug: > > Receiver: a TestSuite > > Arguments and temporary variables: > > aResult: 0 run, 0 passes, 0 expected failures, 0 > > failures, 0 > > errors, 0 unexpect...etc... > > Receiver's instance variables: > > tests: an OrderedCollection(MagmaTestCase>>#testAdvance > > MagmaTestCase>>#testBlo...etc... > > resources: nil > > name: nil > > > > [] in TestSuite>>maRunUsing: > > Receiver: a TestSuite > > Arguments and temporary variables: > > aSymbol: #maDebug: > > result: 0 run, 0 passes, 0 expected failures, 0 > > failures, 0 errors, > > 0 unexpecte...etc... > > Receiver's instance variables: > > tests: an OrderedCollection(MagmaTestCase>>#testAdvance > > MagmaTestCase>>#testBlo...etc... > > resources: nil > > name: nil > > > > BlockClosure>>ensure: > > Receiver: [closure] in TestSuite>>maRunUsing: > > Arguments and temporary variables: > > aBlock: [closure] in TestSuite>>maRunUsing: > > returnValue: nil > > b: nil > > Receiver's instance variables: > > outerContext: TestSuite>>maRunUsing: > > startpc: 42 > > numArgs: 0 > > > > TestSuite>>maRunUsing: > > Receiver: a TestSuite > > Arguments and temporary variables: > > aSymbol: #maDebug: > > result: 0 run, 0 passes, 0 expected failures, 0 > > failures, 0 errors, > > 0 unexpecte...etc... > > Receiver's instance variables: > > tests: an OrderedCollection(MagmaTestCase>>#testAdvance > > MagmaTestCase>>#testBlo...etc... > > resources: nil > > name: nil > > > > TestSuite>>maDebug > > Receiver: a TestSuite > > Arguments and temporary variables: > > > > Receiver's instance variables: > > tests: an OrderedCollection(MagmaTestCase>>#testAdvance > > MagmaTestCase>>#testBlo...etc... > > resources: nil > > name: nil > > > > UndefinedObject>>DoIt > > Receiver: nil > > Arguments and temporary variables: > > > > Receiver's instance variables: > > nil > > > > Compiler>>evaluate:in:to:notifying:ifFail:logged: > > Receiver: a Compiler > > Arguments and temporary variables: > > textOrStream: a ReadWriteStream 'MaObjectSerializerTestCase > > suite > > > > OSProcess > > > > ...etc... > > aContext: nil > > receiver: nil > > aRequestor: a TextMorphForShoutEditor > > failBlock: [closure] in [] in > > TextMorphForShoutEditor(ParagraphEditor)>>evaluat...etc... > > logFlag: true > > methodNode: DoIt > > ^ MagmaTestCase fullSuite maDebug > > method: a CompiledMethod(1314: UndefinedObject>>DoIt) > > value: nil > > toLog: nil > > itsSelection: nil > > itsSelectionString: nil > > Receiver's instance variables: > > sourceStream: a ReadWriteStream 'MaObjectSerializerTestCase > > suite > > > > OSProcess > > > > ...etc... > > requestor: a TextMorphForShoutEditor > > class: UndefinedObject > > category: nil > > context: nil > > parser: a Parser > > > > [] in TextMorphForShoutEditor(ParagraphEditor)>>evaluateSelection > > Receiver: a TextMorphForShoutEditor > > Arguments and temporary variables: > > rcvr: nil > > ctxt: nil > > Receiver's instance variables: > > model: a SHWorkspace > > paragraph: a MultiNewParagraph > > startBlock: a CharacterBlock with index 78 and character > > Character > > cr and recta...etc... > > stopBlock: a CharacterBlock with index 47 and character $M > > and > > rectangle 0...@56 c...etc... > > beginTypeInBlock: nil > > emphasisHere: an Array(a TextColor code: (Color r: 0.0 g: 0.0 > > b: 0.5)) > > initialText: a Text for 'MaObjectSerializerTestCase suite > > > > OSProcess > > > > MagmaTes...etc... > > selectionShowing: false > > otherInterval: (75 to: 74) > > lastParentLocation: nil > > morph: a TextMorphForShout(1009) > > oldInterval: (75 to: 74) > > pivotBlock: a CharacterBlock with index 66 and character $u > > and > > rectangle 1...@5...etc... > > inBackTo: nil > > > > BlockClosure>>on:do: > > Receiver: [closure] in > > TextMorphForShoutEditor(ParagraphEditor)>>evaluateSelection > > Arguments and temporary variables: > > exception: OutOfScopeNotification > > handlerAction: [closure] in > > TextMorphForShoutEditor(ParagraphEditor)>>evaluateS...etc... > > handlerActive: true > > Receiver's instance variables: > > outerContext: > > TextMorphForShoutEditor(ParagraphEditor)>>evaluateSelection > > startpc: 116 > > numArgs: 0 > > > > TextMorphForShoutEditor(ParagraphEditor)>>evaluateSelection > > Receiver: a TextMorphForShoutEditor > > Arguments and temporary variables: > > result: nil > > rcvr: nil > > ctxt: nil > > Receiver's instance variables: > > model: a SHWorkspace > > paragraph: a MultiNewParagraph > > startBlock: a CharacterBlock with index 78 and character > > Character > > cr and recta...etc... > > stopBlock: a CharacterBlock with index 47 and character $M > > and > > rectangle 0...@56 c...etc... > > beginTypeInBlock: nil > > emphasisHere: an Array(a TextColor code: (Color r: 0.0 g: 0.0 > > b: 0.5)) > > initialText: a Text for 'MaObjectSerializerTestCase suite > > > > OSProcess > > > > MagmaTes...etc... > > selectionShowing: false > > otherInterval: (75 to: 74) > > lastParentLocation: nil > > morph: a TextMorphForShout(1009) > > oldInterval: (75 to: 74) > > pivotBlock: a CharacterBlock with index 66 and character $u > > and > > rectangle 1...@5...etc... > > inBackTo: nil > > > > TextMorphForShoutEditor(ParagraphEditor)>>doIt > > Receiver: a TextMorphForShoutEditor > > Arguments and temporary variables: > > > > Receiver's instance variables: > > model: a SHWorkspace > > paragraph: a MultiNewParagraph > > startBlock: a CharacterBlock with index 78 and character > > Character > > cr and recta...etc... > > stopBlock: a CharacterBlock with index 47 and character $M > > and > > rectangle 0...@56 c...etc... > > beginTypeInBlock: nil > > emphasisHere: an Array(a TextColor code: (Color r: 0.0 g: 0.0 > > b: 0.5)) > > initialText: a Text for 'MaObjectSerializerTestCase suite > > > > OSProcess > > > > MagmaTes...etc... > > selectionShowing: false > > otherInterval: (75 to: 74) > > lastParentLocation: nil > > morph: a TextMorphForShout(1009) > > oldInterval: (75 to: 74) > > pivotBlock: a CharacterBlock with index 66 and character $u > > and > > rectangle 1...@5...etc... > > inBackTo: nil > > > > [] in TextMorphForShoutEditor(ParagraphEditor)>>doIt: > > Receiver: a TextMorphForShoutEditor > > Arguments and temporary variables: > > > > Receiver's instance variables: > > model: a SHWorkspace > > paragraph: a MultiNewParagraph > > startBlock: a CharacterBlock with index 78 and character > > Character > > cr and recta...etc... > > stopBlock: a CharacterBlock with index 47 and character $M > > and > > rectangle 0...@56 c...etc... > > beginTypeInBlock: nil > > emphasisHere: an Array(a TextColor code: (Color r: 0.0 g: 0.0 > > b: 0.5)) > > initialText: a Text for 'MaObjectSerializerTestCase suite > > > > OSProcess > > > > MagmaTes...etc... > > selectionShowing: false > > otherInterval: (75 to: 74) > > lastParentLocation: nil > > morph: a TextMorphForShout(1009) > > oldInterval: (75 to: 74) > > pivotBlock: a CharacterBlock with index 66 and character $u > > and > > rectangle 1...@5...etc... > > inBackTo: nil > > > > > > --- The full stack --- > > NetNameResolver class(Object)>>error: > > NetNameResolver class(Object)>>primitiveFailed > > NetNameResolver class>>primGetNameInfo:flags: > > SocketAddress>>hostNumber > > [] in Socket>>connectTo:port:waitForConnectionFor: > > Socket>>waitForConnectionFor:ifTimedOut: > > Socket>>connectTo:port:waitForConnectionFor: > > [] in MaNetworkTestPlayerFacade>>isReady > > BlockClosure>>on:do: > > MaNetworkTestPlayerFacade>>isReady > > [] in MagmaTestCase class(MaNetworkTestCase class)>>waitForPlayerImages > > [] in Dictionary(Collection)>>allSatisfy: > > [] in Dictionary>>do: > > Dictionary(Set)>>do: > > Dictionary>>do: > > Dictionary(Collection)>>allSatisfy: > > MagmaTestCase class(MaNetworkTestCase class)>>waitForPlayerImages > > MagmaTestCase class(MaNetworkTestCase class)>>launchPlayerImages > > MagmaTestCase class>>launchPlayerImages > > MagmaTestCase class(MaNetworkTestCase class)>>setUpSuite > > MagmaTestCase class>>setUpSuite > > MagmaTestCase(MaTestCase)>>setUpSuite > > [] in [] in TestSuite>>maExecuteTestsUsing:result: > > BlockClosure>>on:do: > > [] in TestSuite>>maExecuteTestsUsing:result: > > BlockClosure>>ensure: > > TestSuite>>maExecuteTestsUsing:result: > > TestSuite>>maDebug: > > [] in TestSuite>>maRunUsing: > > BlockClosure>>ensure: > > TestSuite>>maRunUsing: > > TestSuite>>maDebug > > UndefinedObject>>DoIt > > Compiler>>evaluate:in:to:notifying:ifFail:logged: > > [] in TextMorphForShoutEditor(ParagraphEditor)>>evaluateSelection > > BlockClosure>>on:do: > > TextMorphForShoutEditor(ParagraphEditor)>>evaluateSelection > > TextMorphForShoutEditor(ParagraphEditor)>>doIt > > [] in TextMorphForShoutEditor(ParagraphEditor)>>doIt: > > - - - - - - - - - - - - - - - > > - - - - - - - - - - - - - - - - - - > > TextMorphForShoutEditor(ParagraphEditor)>>terminateAndInitializeAround: > > TextMorphForShoutEditor(ParagraphEditor)>>doIt: > > TextMorphForShoutEditor(ParagraphEditor)>>dispatchOnKeyEvent:with: > > TextMorphForShoutEditor(TextMorphEditor)>>dispatchOnKeyEvent:with: > > TextMorphForShoutEditor(ParagraphEditor)>>keystroke: > > TextMorphForShoutEditor(TextMorphEditor)>>keystroke: > > [] in [] in TextMorphForShout(TextMorph)>>keyStroke: > > TextMorphForShout(TextMorph)>>handleInteraction: > > TextMorphForShout(TextMorphForEditView)>>handleInteraction: > > [] in TextMorphForShout(TextMorph)>>keyStroke: > > ECToolSet class>>codeCompletionAround:textMorph:keyStroke: > > DEVToolSet class>>codeCompletionAround:textMorph:keyStroke: > > ToolSet class>>codeCompletionAround:textMorph:keyStroke: > > TextMorphForShout(TextMorph)>>keyStroke: > > TextMorphForShout(TextMorphForEditView)>>keyStroke: > > TextMorphForShout(TextMorph)>>handleKeystroke: > > KeyboardEvent>>sentTo: > > TextMorphForShout(Morph)>>handleEvent: > > TextMorphForShout(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 > > ------------------------------------------------------------ > > > > > > On Sun, Feb 14, 2010 at 2:14 PM, Adrian Lienhard<a...@netstyle.ch> wrote: > > > >> http://code.google.com/p/pharo/issues/detail?id=1884 > >> > >> This issue probably is the last obstacle for the 1.0 release. I've added > >> the following comment: > >> > >> --------- > >> > >> The preference proposed by Miguel does not solve the problem but puts the > >> burden on the user that needs to change the preference depending on which > >> implementation works for him. This will lead to many questions and > >> frustrated users. If possible, I'd prefer to make the legacy IPv4 > >> implementation work again until we have a proper IPv6 implementation. > >> > >> The problem with printing "NetNameResolver addressForName: > >> 'www.yahoo.com'" is not that the resolution does not work correctly but > >> that the printOn: implementation of SocketAddress assumes an IPv6 address. > >> I suggest to change the SocketAddress>>printOn: as follows. Maybe it's > >> just this simple change to makes IPv4 work again -- maybe more such > >> backward compatibility code is needed. > >> > >> SocketAddress>>printOn: aStream > >> NetNameResolver useOldNetwork ifTrue: [ ^ super printOn: aStream ]. > >> > >> aStream > >> nextPutAll: self hostNumber; > >> nextPut: $(; nextPutAll: self hostName; nextPut: $); > >> nextPut: $,; > >> nextPutAll: self serviceNumber; > >> nextPut: $(; nextPutAll: self serviceName; nextPut: $) > >> > >> --------- > >> > >> This change makes #addressForName: work again with useOldNetwork set to > >> true (as it is in recent PharoCore 1.0 images). > >> > >> Could people that experience problems with the network code update this > >> method and check out if other parts break? > >> > >> Cheers, > >> Adrian > >> > >> ___________________ > >> http://www.adrian-lienhard.ch/ > >> > >> > >> _______________________________________________ > >> Pharo-project mailing list > >> Pharo-project@lists.gforge.inria.fr > >> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project > >> > >> > > _______________________________________________ > > Pharo-project mailing list > > Pharo-project@lists.gforge.inria.fr > > http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project > > -- Miguel Cobá http://miguel.leugim.com.mx _______________________________________________ Pharo-project mailing list Pharo-project@lists.gforge.inria.fr http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project