Hi,

Recently I encounter a strange error:
- I sometimes get a debugger due to some problems in my code
- when I try to investigate the trace, I get another debugger saying  
that "Invalid utf8 input detected'"

This second debugger I can investigate, the previous not. It looks  
like something got messed up with the text conversion of the sources.

I am working on 10306 using the 4.1.1b2 VM on Mac. The code I am  
working on is loaded from squeaksource (Moose, Glamour, Mondrian).

Anyone can confirm this problem?

Cheers,
Doru


----ERROR REPORT----

'17 May 2009 2:05:50 am

VM: Mac OS - intel - 1056 - Squeak3.8.1 of ''28 Aug 2006'' [latest  
update: #6747] Squeak VM 4.1.1b2
Image: Pharo0.1 [Latest update: #10306]

SecurityManager state:
Restricted: false
FileAccess: true
SocketAccess: true
Working Dir /Users/girba/Work/Code/squeakingmoose
Trusted Dir /foobar/tooBar/forSqueak/bogus
Untrusted Dir /Users/girba/Library/Preferences/Squeak/Internet/My Squeak

UTF8TextConverter(Object)>>error:
        Receiver: an UTF8TextConverter
        Arguments and temporary variables:
                aString:        ''Invalid utf8 input detected''
        Receiver''s instance variables:
an UTF8TextConverter

UTF8TextConverter>>errorMalformedInput
        Receiver: an UTF8TextConverter
        Arguments and temporary variables:

        Receiver''s instance variables:
an UTF8TextConverter

UTF8TextConverter>>nextFromStream:
        Receiver: an UTF8TextConverter
        Arguments and temporary variables:
                aStream:        MultiByteFileStream: ''/Users/girba/Work/Code/ 
squeakingmoose/moose.chan...etc...
                character1:     $
                value1:         160
                character2:     Character tab
                value2:         9
                unicode:        nil
                character3:     Character tab
                value3:         9
                character4:     nil
                value4:         nil
        Receiver''s instance variables:
an UTF8TextConverter

MultiByteFileStream>>next
        Receiver: MultiByteFileStream: ''/Users/girba/Work/Code/ 
squeakingmoose/moose.changes''
        Arguments and temporary variables:
                char:   nil
                secondChar:     nil
                state:  nil
        Receiver''s instance variables:


MultiByteFileStream(PositionableStream)>>nextChunk
        Receiver: MultiByteFileStream: ''/Users/girba/Work/Code/ 
squeakingmoose/moose.changes''
        Arguments and temporary variables:
                terminator:     $!
                out:    a WriteStream ''doesNotUnderstand: aMessage
         "Handle the fact that there ...etc...
                ch:     Character cr
        Receiver''s instance variables:


MultiByteFileStream(PositionableStream)>>nextChunkText
        Receiver: MultiByteFileStream: ''/Users/girba/Work/Code/ 
squeakingmoose/moose.changes''
        Arguments and temporary variables:
                string:         nil
                runsRaw:        nil
                strm:   nil
                runs:   nil
                peek:   nil
                pos:    nil
        Receiver''s instance variables:


[] in RemoteString>>text
        Receiver: a RemoteString
        Arguments and temporary variables:
                theFile:        MultiByteFileStream: ''/Users/girba/Work/Code/ 
squeakingmoose/moose.chan...etc...
        Receiver''s instance variables:
                sourceFileNumber:       2
                filePositionHi:         10007336

BlockClosure>>ensure:
        Receiver: [closure] in RemoteString>>text
        Arguments and temporary variables:
                aBlock:         [closure] in RemoteString>>text
                returnValue:    nil
                b:      nil
        Receiver''s instance variables:
                outerContext:   RemoteString>>text
                startpc:        72
                numArgs:        0

RemoteString>>text
        Receiver: a RemoteString
        Arguments and temporary variables:
                theFile:        MultiByteFileStream: ''/Users/girba/Work/Code/ 
squeakingmoose/moose.chan...etc...
        Receiver''s instance variables:
                sourceFileNumber:       2
                filePositionHi:         10007336

CompiledMethod>>getSourceFromFile
        Receiver: a CompiledMethod (838)
        Arguments and temporary variables:
                position:       10007336
        Receiver''s instance variables:
a CompiledMethod (838)

CompiledMethod>>methodNode
        Receiver: a CompiledMethod (838)
        Arguments and temporary variables:
                aClass:         Object
                source:         nil
        Receiver''s instance variables:
a CompiledMethod (838)

[] in DebuggerMethodMap class>>forMethod:
        Receiver: DebuggerMethodMap
        Arguments and temporary variables:
                aMethod:        a CompiledMethod (838)
        Receiver''s instance variables:
                superclass:     Object
                methodDict:     a MethodDictionary(#abstractSourceMap->a 
CompiledMethod  
(1628) #for...etc...
                format:         140
                instanceVariables:      #(''timestamp'' ''methodReference''  
''methodNode'' ''abstractSource...etc...
                organization:   (''initialize-release'' forMethod:methodNode:)
(''accessing'' markRec...etc...
                subclasses:     {DebuggerMethodMapForBlueBookMethods .  
DebuggerMethodMapForClosureC...etc...
                name:   #DebuggerMethodMap
                classPool:      a Dictionary(#MapCache->a 
WeakIdentityKeyDictionary(a  
CompiledMethod...etc...
                sharedPools:    nil
                environment:    Smalltalk
                category:       #''Tools-Debugger''
                traitComposition:       nil
                localSelectors:         nil

WeakIdentityKeyDictionary(Dictionary)>>at:ifAbsent:
        Receiver: a WeakIdentityKeyDictionary(a CompiledMethod (126)->a  
DebuggerMethodMapForClosureCompiledM...etc...
        Arguments and temporary variables:
                key:    a CompiledMethod (838)
                aBlock:         [closure] in DebuggerMethodMap class>>forMethod:
                assoc:  nil
        Receiver''s instance variables:
                tally:  16
                array:  an Array(nil nil a CompiledMethod (2402)->a  
DebuggerMethodMapForClosureC...etc...

DebuggerMethodMap class>>forMethod:
        Receiver: DebuggerMethodMap
        Arguments and temporary variables:
                aMethod:        a CompiledMethod (838)
        Receiver''s instance variables:
                superclass:     Object
                methodDict:     a MethodDictionary(#abstractSourceMap->a 
CompiledMethod  
(1628) #for...etc...
                format:         140
                instanceVariables:      #(''timestamp'' ''methodReference''  
''methodNode'' ''abstractSource...etc...
                organization:   (''initialize-release'' forMethod:methodNode:)
(''accessing'' markRec...etc...
                subclasses:     {DebuggerMethodMapForBlueBookMethods .  
DebuggerMethodMapForClosureC...etc...
                name:   #DebuggerMethodMap
                classPool:      a Dictionary(#MapCache->a 
WeakIdentityKeyDictionary(a  
CompiledMethod...etc...
                sharedPools:    nil
                environment:    Smalltalk
                category:       #''Tools-Debugger''
                traitComposition:       nil
                localSelectors:         nil

CompiledMethod>>debuggerMap
        Receiver: a CompiledMethod (838)
        Arguments and temporary variables:

        Receiver''s instance variables:
a CompiledMethod (838)

OTClosureContextNode>>selection
        Receiver: an OTClosureContextNode
        Arguments and temporary variables:

        Receiver''s instance variables:
                metaNode:       context

                navigation:     an OBDefaultEdgeNavigation
                process:        a Process in OTToolset  
class>>debug:context:label:contents:fullView:
                context:        Model class(Object)>>doesNotUnderstand: 
#fullName
                parseTree:      nil
                sourceMap:      nil
                debuggerMap:    nil

OTClosureContextNode(OTContextNode)>>definition
        Receiver: an OTClosureContextNode
        Arguments and temporary variables:

        Receiver''s instance variables:
                metaNode:       context

                navigation:     an OBDefaultEdgeNavigation
                process:        a Process in OTToolset  
class>>debug:context:label:contents:fullView:
                context:        Model class(Object)>>doesNotUnderstand: 
#fullName
                parseTree:      nil
                sourceMap:      nil
                debuggerMap:    nil

OTDefinitionPanel(OBDefinitionPanel)>>node:
        Receiver: an OTDefinitionPanel
        Arguments and temporary variables:
                aNode:  an OTClosureContextNode
        Receiver''s instance variables:
                browser:        an OTDebugger
                definition:     nil
                selection:      nil

OTDefinitionPanel(OBDefinitionPanel)>>selectionChanged:
        Receiver: an OTDefinitionPanel
        Arguments and temporary variables:
                ann:    an OBSelectionChanged
        Receiver''s instance variables:
                browser:        an OTDebugger
                definition:     nil
                selection:      nil

MessageSend>>valueWithArguments:
        Receiver: MessageSend(#selectionChanged: -> an OTDefinitionPanel)
        Arguments and temporary variables:
                anArray:        an Array(an OBSelectionChanged)
        Receiver''s instance variables:
                receiver:       an OTDefinitionPanel
                selector:       #selectionChanged:
                arguments:      #()

[] in ActionSequence>>valueWithArguments:
        Receiver: #(MessageSend(#relabel: -> an OTDebugger)
MessageSend(#selectionChanged: -> an OBColumnPan...etc...
        Arguments and temporary variables:
                anArray:        MessageSend(#selectionChanged: -> an 
OTDefinitionPanel)
                answer:         an Array(an OBSelectionChanged)
                each:   an Array(an OBFixedButtonPanel)
        Receiver''s instance variables:
#(MessageSend(#relabel: -> an OTDebugger)
MessageSend(#selectionChanged: -> an OBColumnPan...etc...

ActionSequence(SequenceableCollection)>>do:
        Receiver: #(MessageSend(#relabel: -> an OTDebugger)
MessageSend(#selectionChanged: -> an OBColumnPan...etc...
        Arguments and temporary variables:
                aBlock:         [closure] in ActionSequence>>valueWithArguments:
                index:  4
                indexLimiT:     6
        Receiver''s instance variables:
#(MessageSend(#relabel: -> an OTDebugger)
MessageSend(#selectionChanged: -> an OBColumnPan...etc...

ActionSequence>>valueWithArguments:
        Receiver: #(MessageSend(#relabel: -> an OTDebugger)
MessageSend(#selectionChanged: -> an OBColumnPan...etc...
        Arguments and temporary variables:
                anArray:        an Array(an OBSelectionChanged)
                answer:         an Array(an OBFixedButtonPanel)
        Receiver''s instance variables:
#(MessageSend(#relabel: -> an OTDebugger)
MessageSend(#selectionChanged: -> an OBColumnPan...etc...

[] in OBAnnouncer>>announce:
        Receiver: an OBAnnouncer
        Arguments and temporary variables:
<<error during printing>
        Receiver''s instance variables:
                subscriptions:  an IdentityDictionary(OBAboutToChange->an  
ActionSequence(Message...etc...

[] in IdentityDictionary(Dictionary)>>keysAndValuesDo:
        Receiver: an IdentityDictionary(OBAboutToChange->an  
ActionSequence(MessageSend(#aboutToChange: -> an...etc...
        Arguments and temporary variables:
                aBlock:         OBSelectionChanged->#(MessageSend(#relabel: -> 
an OTDebugger)
MessageSe...etc...
                assoc:  [closure] in OBAnnouncer>>announce:
        Receiver''s instance variables:
                tally:  12
                array:  {OBNodeCreated->an 
ActionSequence(MessageSend(#selectNode: - 
 > an OBColum...etc...

IdentityDictionary(Set)>>do:
        Receiver: an IdentityDictionary(OBAboutToChange->an  
ActionSequence(MessageSend(#aboutToChange: -> an...etc...
        Arguments and temporary variables:
                aBlock:         [closure] in 
IdentityDictionary(Dictionary)>>keysAndValuesDo:
                index:  6
                each:   OBSelectionChanged->#(MessageSend(#relabel: -> an 
OTDebugger)
MessageSend...etc...
                indexLimiT:     20
        Receiver''s instance variables:
                tally:  12
                array:  {OBNodeCreated->an 
ActionSequence(MessageSend(#selectNode: - 
 > an OBColum...etc...

IdentityDictionary(Dictionary)>>associationsDo:
        Receiver: an IdentityDictionary(OBAboutToChange->an  
ActionSequence(MessageSend(#aboutToChange: -> an...etc...
        Arguments and temporary variables:
                aBlock:         [closure] in 
IdentityDictionary(Dictionary)>>keysAndValuesDo:
        Receiver''s instance variables:
                tally:  12
                array:  {OBNodeCreated->an 
ActionSequence(MessageSend(#selectNode: - 
 > an OBColum...etc...

IdentityDictionary(Dictionary)>>keysAndValuesDo:
        Receiver: an IdentityDictionary(OBAboutToChange->an  
ActionSequence(MessageSend(#aboutToChange: -> an...etc...
        Arguments and temporary variables:
                aBlock:         [closure] in OBAnnouncer>>announce:
        Receiver''s instance variables:
                tally:  12
                array:  {OBNodeCreated->an 
ActionSequence(MessageSend(#selectNode: - 
 > an OBColum...etc...

OBAnnouncer>>announce:
        Receiver: an OBAnnouncer
        Arguments and temporary variables:
                anObject:       an OBSelectionChanged
                ann:    an OBSelectionChanged
        Receiver''s instance variables:
                subscriptions:  an IdentityDictionary(OBAboutToChange->an  
ActionSequence(Message...etc...

OBColumnPanel>>jumpTo:
        Receiver: an OBColumnPanel
        Arguments and temporary variables:
                aNode:  an OTClosureContextNode
                column:         an OBColumn(Model 
class(Object)>>doesNotUnderstand:  
#fullName)
        Receiver''s instance variables:
                browser:        an OTDebugger
                root:   an OTProcessNode
                current:        an OTClosureContextNode
                columns:        an OrderedCollection(an OBColumn(Model  
class(Object)>>doesNotUnderstan...etc...
                minPanes:       1
                maxPanes:       1

OTDebugger(OBBrowser)>>jumpTo:
        Receiver: an OTDebugger
        Arguments and temporary variables:
                aNode:  an OTClosureContextNode
        Receiver''s instance variables:
                panels:         an OrderedCollection(an OBColumnPanel an 
OBFixedButtonPanel  
an OTDefini...etc...
                announcer:      an OBAnnouncer
                cmdFactories:   an Array(OTCmdProceedDebugger OTCmdIntoDebugger 
 
OTCmdThroughDebug...etc...

OTDebugger class(OBBrowser class)>>metaNode:root:selection:panels:
        Receiver: OTDebugger
        Arguments and temporary variables:
                metaNode:       process
#longStack->context

                rootNode:       an OTProcessNode
                selectedNode:   an OTClosureContextNode
                panels:         an Array(an OBColumnPanel an OBFixedButtonPanel 
an  
OTDefinitionPanel an...etc...
                browser:        an OTDebugger
        Receiver''s instance variables:
                superclass:     OBBrowser
                methodDict:     a MethodDictionary(#cmdBrowse->a CompiledMethod 
(3978)  
#cmdDebug->a...etc...
                format:         136
                instanceVariables:      nil
                organization:   (''commands'' cmdBrowse cmdDebug cmdInspector)
(''updating'' debugger...etc...
                subclasses:     nil
                name:   #OTDebugger
                classPool:      nil
                sharedPools:    nil
                environment:    Smalltalk
                category:       #''OB-Tools-Debugger''
                traitComposition:       nil
                localSelectors:         nil

OTDebugger class(OBBrowser class)>>root:selection:
        Receiver: OTDebugger
        Arguments and temporary variables:
                rootNode:       an OTProcessNode
                selectedNode:   an OTClosureContextNode
        Receiver''s instance variables:
                superclass:     OBBrowser
                methodDict:     a MethodDictionary(#cmdBrowse->a CompiledMethod 
(3978)  
#cmdDebug->a...etc...
                format:         136
                instanceVariables:      nil
                organization:   (''commands'' cmdBrowse cmdDebug cmdInspector)
(''updating'' debugger...etc...
                subclasses:     nil
                name:   #OTDebugger
                classPool:      nil
                sharedPools:    nil
                environment:    Smalltalk
                category:       #''OB-Tools-Debugger''
                traitComposition:       nil
                localSelectors:         nil

OTDebugger class>>process:context:errorWasInUIProcess:
        Receiver: OTDebugger
        Arguments and temporary variables:
                aProcess:       a Process in OTToolset  
class>>debug:context:label:contents:fullView:
                aContext:       Model class(Object)>>doesNotUnderstand: 
#fullName
                aBool:  true
                processNode:    an OTProcessNode
                contextNode:    an OTClosureContextNode
        Receiver''s instance variables:
                superclass:     OBBrowser
                methodDict:     a MethodDictionary(#cmdBrowse->a CompiledMethod 
(3978)  
#cmdDebug->a...etc...
                format:         136
                instanceVariables:      nil
                organization:   (''commands'' cmdBrowse cmdDebug cmdInspector)
(''updating'' debugger...etc...
                subclasses:     nil
                name:   #OTDebugger
                classPool:      nil
                sharedPools:    nil
                environment:    Smalltalk
                category:       #''OB-Tools-Debugger''
                traitComposition:       nil
                localSelectors:         nil

OTDebugger class>>process:context:label:errorWasInUIProcess:
        Receiver: OTDebugger
        Arguments and temporary variables:
                aProcess:       a Process in OTToolset  
class>>debug:context:label:contents:fullView:
                aContext:       Model class(Object)>>doesNotUnderstand: 
#fullName
                aString:        ''MessageNotUnderstood: Model class>>fullName''
                aBool:  true
                debugger:       nil
        Receiver''s instance variables:
                superclass:     OBBrowser
                methodDict:     a MethodDictionary(#cmdBrowse->a CompiledMethod 
(3978)  
#cmdDebug->a...etc...
                format:         136
                instanceVariables:      nil
                organization:   (''commands'' cmdBrowse cmdDebug cmdInspector)
(''updating'' debugger...etc...
                subclasses:     nil
                name:   #OTDebugger
                classPool:      nil
                sharedPools:    nil
                environment:    Smalltalk
                category:       #''OB-Tools-Debugger''
                traitComposition:       nil
                localSelectors:         nil

OTDebugger class>>openProcess:context:label:errorWasInUIProcess:
        Receiver: OTDebugger
        Arguments and temporary variables:
                aProcess:       a Process in OTToolset  
class>>debug:context:label:contents:fullView:
                aContext:       Model class(Object)>>doesNotUnderstand: 
#fullName
                aString:        ''MessageNotUnderstood: Model class>>fullName''
                aBool:  true
        Receiver''s instance variables:
                superclass:     OBBrowser
                methodDict:     a MethodDictionary(#cmdBrowse->a CompiledMethod 
(3978)  
#cmdDebug->a...etc...
                format:         136
                instanceVariables:      nil
                organization:   (''commands'' cmdBrowse cmdDebug cmdInspector)
(''updating'' debugger...etc...
                subclasses:     nil
                name:   #OTDebugger
                classPool:      nil
                sharedPools:    nil
                environment:    Smalltalk
                category:       #''OB-Tools-Debugger''
                traitComposition:       nil
                localSelectors:         nil

[] in OTPreDebugNode>>debug:
        Receiver: an OTPreDebugNode
        Arguments and temporary variables:
                aRequestor:     an OTPreDebugPanel
                proc:   a Process in OTToolset  
class>>debug:context:label:contents:fullView:
        Receiver''s instance variables:
                metaNode:       Predebug

                navigation:     nil
                errorWasInUI:   true
                process:        nil
                context:        Model class(Object)>>doesNotUnderstand: 
#fullName
                label:  ''MessageNotUnderstood: Model class>>fullName''
                contents:       ''Model class(Object)>>doesNotUnderstand: 
#fullName
UtilitiesTest>>tes...etc...
                debugOnMouseClick:      true

WorldState>>runStepMethodsIn:
        Receiver: a WorldState
        Arguments and temporary variables:
                aWorld:         a PasteUpMorph(1622) [world]
                queue:  a SharedQueue
                numItems:       1
                i:      0
                limit:  200
                stamp:  12765762
        Receiver''s instance variables:
                hands:  an Array(a HandMorph(3216))
                viewBox:        0...@0 corner: 1...@807
                canvas:         a FormCanvas on: DisplayScreen(1440x807x32)
                damageRecorder:         a DamageRecorder
                stepList:       a Heap(StepMessage(#stepAt: -> a 
SystemWindow(3380))(a  
SystemWindow(3...etc...
                lastStepTime:   12791780
                lastStepMessage:        nil
                lastCycleTime:  12791800
                commandHistory:         a CommandHistory
                alarms:         a Heap()
                lastAlarmTime:  12791780

PasteUpMorph>>runStepMethods
        Receiver: a PasteUpMorph(1622) [world]
        Arguments and temporary variables:

        Receiver''s instance variables:
                bounds:         0...@0 corner: 1...@807
                owner:  nil
                submorphs:      an Array(a TaskbarMorph(3095) a 
SystemWindow(171) a  
PluggableStandar...etc...
                fullBounds:     nil
                color:  (Color r: 0.972 g: 0.972 b: 0.976)
                extension:      a MorphExtension (2543) [eventHandler = an  
EventHandler]  [other:  (...etc...
                borderWidth:    0
                borderColor:    (Color r: 0.03 g: 0.02 b: 0.0)
                presenter:      a Presenter (1246)
                model:  a MorphicModel(1926)
                cursor:         1
                padding:        3
                backgroundMorph:        nil
                isPartsBin:     nil
                autoLineLayout:         false
                indicateCursor:         nil
                resizeToFit:    nil
                wantsMouseOverHalos:    nil
                worldState:     a WorldState
                griddingOn:     nil


--- The full stack ---
UTF8TextConverter(Object)>>error:
UTF8TextConverter>>errorMalformedInput
UTF8TextConverter>>nextFromStream:
MultiByteFileStream>>next
MultiByteFileStream(PositionableStream)>>nextChunk
MultiByteFileStream(PositionableStream)>>nextChunkText
[] in RemoteString>>text
BlockClosure>>ensure:
RemoteString>>text
CompiledMethod>>getSourceFromFile
CompiledMethod>>methodNode
[] in DebuggerMethodMap class>>forMethod:
WeakIdentityKeyDictionary(Dictionary)>>at:ifAbsent:
DebuggerMethodMap class>>forMethod:
CompiledMethod>>debuggerMap
OTClosureContextNode>>selection
OTClosureContextNode(OTContextNode)>>definition
OTDefinitionPanel(OBDefinitionPanel)>>node:
OTDefinitionPanel(OBDefinitionPanel)>>selectionChanged:
MessageSend>>valueWithArguments:
[] in ActionSequence>>valueWithArguments:
ActionSequence(SequenceableCollection)>>do:
ActionSequence>>valueWithArguments:
[] in OBAnnouncer>>announce:
[] in IdentityDictionary(Dictionary)>>keysAndValuesDo:
IdentityDictionary(Set)>>do:
IdentityDictionary(Dictionary)>>associationsDo:
IdentityDictionary(Dictionary)>>keysAndValuesDo:
OBAnnouncer>>announce:
OBColumnPanel>>jumpTo:
OTDebugger(OBBrowser)>>jumpTo:
OTDebugger class(OBBrowser class)>>metaNode:root:selection:panels:
OTDebugger class(OBBrowser class)>>root:selection:
OTDebugger class>>process:context:errorWasInUIProcess:
OTDebugger class>>process:context:label:errorWasInUIProcess:
OTDebugger class>>openProcess:context:label:errorWasInUIProcess:
[] in OTPreDebugNode>>debug:
WorldState>>runStepMethodsIn:
PasteUpMorph>>runStepMethods
  - - - - - - - - - - - - - - -
                        - - - - - - - - - - - - - - - - - -
WorldState>>doOneCycleNowFor:
WorldState>>doOneCycleFor:
PasteUpMorph>>doOneCycle
[] in Project class>>spawnNewProcess
[] in BlockClosure>>newProcess
'



--
www.tudorgirba.com

"To lead is not to demand things, it is to make them happen."






_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to