In Pharo1.1 update #11411, evaluating
MIMEDocument guessTypeFromName: 'x.css' produces the attached traceback. Changing MIMEDocument>>guessTypeFromName: url "guesses a content type from the url" ^MIMEType forFileNameReturnSingleMimeTypeOrDefault: url asString asURI to MIMEDocument>>guessTypeFromName: url "guesses a content type from the url" ^MIMEType forFileNameReturnSingleMimeTypeOrDefault: url asString (removing asURI), makes it work as expected, answering 'css'. Is this a bug? Is my fix appropriate? I've made this change in my image. What is the process to get this addressed in the product? Thanks, TF
THERE_BE_DRAGONS_HERE MessageNotUnderstood: HierarchicalURI>>findLast: 26 October 2010 8:23:39 am VM: Mac OS - intel - 1064 - Squeak4.1 of 17 April 2010 [latest update: #9957] Seaside 3.0 Image: Pharo1.1 [Latest update: #11411] SecurityManager state: Restricted: false FileAccess: true SocketAccess: true Working Dir /Applications/Seaside.app/Contents/Resources Trusted Dir /foobar/tooBar/forSqueak/bogus Untrusted Dir /Users/tfleig/Library/Preferences/Squeak/Internet/My Squeak HierarchicalURI(Object)>>doesNotUnderstand: #findLast: Receiver: x.css Arguments and temporary variables: aMessage: findLast: [:c | c = delim] exception: MessageNotUnderstood: HierarchicalURI>>findLast: resumeValue: nil Receiver's instance variables: fragment: nil scheme: nil schemeSpecificPart: 'x.css' authority: nil query: nil pathComponents: nil FileDirectory class>>extensionFor: Receiver: FileDirectory Arguments and temporary variables: fileName: x.css delim: $. i: nil Receiver's instance variables: superclass: Object methodDict: a MethodDictionary(#/->(FileDirectory>>#/ "a CompiledMethod(9536798...etc... format: 132 instanceVariables: #('pathName') organization: ('*Network-MIME' fileSuffixesForMimeType: mimeTypesFor:) ('*Netwo...etc... subclasses: {UnixFileDirectory. AcornFileDirectory. MacFileDirectory. DosFileDi...etc... name: #FileDirectory classPool: a Dictionary(#DefaultDirectory->UnixFileDirectory on '/Applications/...etc... sharedPools: nil environment: a SystemDictionary(lots of globals) category: #'Files-Directories' traitComposition: nil localSelectors: nil MIMEType class>>forFileNameReturnMimeTypesOrNil: Receiver: MIMEType Arguments and temporary variables: fileName: x.css ext: nil Receiver's instance variables: superclass: Object methodDict: a MethodDictionary(#=->(MIMEType>>#= "a CompiledMethod(379846656)")...etc... format: 136 instanceVariables: #('main' 'sub' 'parameters') organization: ('accessing' main main: parameters: sub sub:) ('comparing' = begi...etc... subclasses: nil name: #MIMEType classPool: a Dictionary(#DefaultSuffixes->a Dictionary(size 115) #StandardMIMEM...etc... sharedPools: nil environment: a SystemDictionary(lots of globals) category: #'Network-MIME' traitComposition: nil localSelectors: nil MIMEType class>>forFileNameReturnMimeTypesOrDefault: Receiver: MIMEType Arguments and temporary variables: fileName: x.css mimeTypes: nil Receiver's instance variables: superclass: Object methodDict: a MethodDictionary(#=->(MIMEType>>#= "a CompiledMethod(379846656)")...etc... format: 136 instanceVariables: #('main' 'sub' 'parameters') organization: ('accessing' main main: parameters: sub sub:) ('comparing' = begi...etc... subclasses: nil name: #MIMEType classPool: a Dictionary(#DefaultSuffixes->a Dictionary(size 115) #StandardMIMEM...etc... sharedPools: nil environment: a SystemDictionary(lots of globals) category: #'Network-MIME' traitComposition: nil localSelectors: nil MIMEType class>>forFileNameReturnSingleMimeTypeOrDefault: Receiver: MIMEType Arguments and temporary variables: fileName: x.css types: nil Receiver's instance variables: superclass: Object methodDict: a MethodDictionary(#=->(MIMEType>>#= "a CompiledMethod(379846656)")...etc... format: 136 instanceVariables: #('main' 'sub' 'parameters') organization: ('accessing' main main: parameters: sub sub:) ('comparing' = begi...etc... subclasses: nil name: #MIMEType classPool: a Dictionary(#DefaultSuffixes->a Dictionary(size 115) #StandardMIMEM...etc... sharedPools: nil environment: a SystemDictionary(lots of globals) category: #'Network-MIME' traitComposition: nil localSelectors: nil MIMEDocument class>>guessTypeFromName: Receiver: MIMEDocument Arguments and temporary variables: url: 'x.css' Receiver's instance variables: superclass: Object methodDict: a MethodDictionary(#content->(MIMEDocument>>#content "a CompiledMet...etc... format: 138 instanceVariables: #('type' 'contents' 'contentStream' 'uri') organization: ('*seaside-pharo-core' seasideMimeDocument seasideMimeDocumentTyp...etc... subclasses: {MIMELocalFileDocument} name: #MIMEDocument classPool: nil sharedPools: nil environment: a SystemDictionary(lots of globals) category: #'Network-MIME' traitComposition: nil localSelectors: 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: 'MIMEDocument guessTypeFromName: ''x.css''' aContext: nil receiver: nil aRequestor: a TextMorphEditor failBlock: [FakeClassPool adopt: nil. ^ #failedDoit] logFlag: true methodNode: DoIt ^ MIMEDocument guessTypeFromName: 'x.css' method: (UndefinedObject>>#DoIt "a CompiledMethod(20447232)") value: nil toLog: nil itsSelection: nil itsSelectionString: nil Receiver's instance variables: sourceStream: a ReadStream 'MIMEDocument guessTypeFromName: ''x.css''' requestor: a TextMorphEditor class: UndefinedObject category: nil context: nil parser: a Parser [] in TextMorphEditor(ParagraphEditor)>>evaluateSelection Receiver: a TextMorphEditor Arguments and temporary variables: rcvr: nil ctxt: nil Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... BlockClosure>>on:do: Receiver: [rcvr class evaluatorClass new evaluate: self selection asString in: ctxt to: rcvr ...etc... Arguments and temporary variables: exception: OutOfScopeNotification handlerAction: [:ex | ex resume: true] handlerActive: true Receiver's instance variables: outerContext: TextMorphEditor(ParagraphEditor)>>evaluateSelection startpc: 120 numArgs: 0 TextMorphEditor(ParagraphEditor)>>evaluateSelection Receiver: a TextMorphEditor Arguments and temporary variables: result: nil rcvr: nil ctxt: nil Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... TextMorphEditor(ParagraphEditor)>>printIt Receiver: a TextMorphEditor Arguments and temporary variables: result: nil Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... [] in TextMorphEditor(ParagraphEditor)>>printIt: Receiver: a TextMorphEditor Arguments and temporary variables: Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... TextMorphEditor(ParagraphEditor)>>terminateAndInitializeAround: Receiver: a TextMorphEditor Arguments and temporary variables: aBlock: [self printIt] Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... TextMorphEditor(ParagraphEditor)>>printIt: Receiver: a TextMorphEditor Arguments and temporary variables: characterStream: a WriteStream '' Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... TextMorphEditor(ParagraphEditor)>>dispatchOnKeyEvent:with: Receiver: a TextMorphEditor Arguments and temporary variables: keyEvent: [keystroke '<Cmd-p>'] typeAheadStream: a WriteStream '' honorCommandKeys: true keyValue: 112 keyChar: $p char: $p action: #printIt: Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... TextMorphEditor>>dispatchOnKeyEvent:with: Receiver: a TextMorphEditor Arguments and temporary variables: keyEvent: [keystroke '<Cmd-p>'] typeAheadStream: a WriteStream '' Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... TextMorphEditor(ParagraphEditor)>>keystroke: Receiver: a TextMorphEditor Arguments and temporary variables: keyEvent: [keystroke '<Cmd-p>'] typeAhead: a WriteStream '' Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... TextMorphEditor>>keystroke: Receiver: a TextMorphEditor Arguments and temporary variables: keyEvent: [keystroke '<Cmd-p>'] Receiver's instance variables: model: a Workspace paragraph: a MultiNewParagraph startBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... stopBlock: a CharacterBlock with index 1 and character $M and rectangle 0...@0 cor...etc... beginTypeInBlock: nil emphasisHere: an Array(a TextFontChange font: 2) initialText: a Text for '|' selectionShowing: false otherInterval: (1 to: 39) lastParentLocation: 140 morph: a TextMorphForEditView(515899392) oldInterval: (1 to: 39) pivotBlock: a CharacterBlock with index 40 and rectangle 2...@0 corner: 2...@16 ...etc... [] in TextMorphForEditView(TextMorph)>>keyStroke: Receiver: a TextMorphForEditView(515899392) Arguments and temporary variables: evt: [keystroke '<Cmd-p>'] Receiver's instance variables: bounds: 0...@0 corner: 8...@18 owner: a TransformMorph(721682432) submorphs: #() fullBounds: 0...@0 corner: 8...@18 color: Color black extension: a MorphExtension (1051459584) [other: (blinkStart -> 2081777)] borderWidth: 0 borderColor: Color black textStyle: a TextStyle Bitmap DejaVu Sans 9 text: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' wrapFlag: true paragraph: a MultiNewParagraph editor: a TextMorphEditor container: nil predecessor: nil successor: nil backgroundColor: nil margins: nil editHistory: a TextMorphCommandHistory editView: a PluggableTextMorph(677642240) acceptOnCR: false TextMorphForEditView(TextMorph)>>handleInteraction: Receiver: a TextMorphForEditView(515899392) Arguments and temporary variables: interactionBlock: [editor keystroke: evt] oldEditor: a TextMorphEditor oldParagraph: a MultiNewParagraph oldText: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' Receiver's instance variables: bounds: 0...@0 corner: 8...@18 owner: a TransformMorph(721682432) submorphs: #() fullBounds: 0...@0 corner: 8...@18 color: Color black extension: a MorphExtension (1051459584) [other: (blinkStart -> 2081777)] borderWidth: 0 borderColor: Color black textStyle: a TextStyle Bitmap DejaVu Sans 9 text: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' wrapFlag: true paragraph: a MultiNewParagraph editor: a TextMorphEditor container: nil predecessor: nil successor: nil backgroundColor: nil margins: nil editHistory: a TextMorphCommandHistory editView: a PluggableTextMorph(677642240) acceptOnCR: false TextMorphForEditView>>handleInteraction: Receiver: a TextMorphForEditView(515899392) Arguments and temporary variables: interActionBlock: [editor keystroke: evt] Receiver's instance variables: bounds: 0...@0 corner: 8...@18 owner: a TransformMorph(721682432) submorphs: #() fullBounds: 0...@0 corner: 8...@18 color: Color black extension: a MorphExtension (1051459584) [other: (blinkStart -> 2081777)] borderWidth: 0 borderColor: Color black textStyle: a TextStyle Bitmap DejaVu Sans 9 text: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' wrapFlag: true paragraph: a MultiNewParagraph editor: a TextMorphEditor container: nil predecessor: nil successor: nil backgroundColor: nil margins: nil editHistory: a TextMorphCommandHistory editView: a PluggableTextMorph(677642240) acceptOnCR: false TextMorphForEditView(TextMorph)>>keyStroke: Receiver: a TextMorphForEditView(515899392) Arguments and temporary variables: evt: [keystroke '<Cmd-p>'] action: nil completionAllowed: true stringHolder: a Workspace Receiver's instance variables: bounds: 0...@0 corner: 8...@18 owner: a TransformMorph(721682432) submorphs: #() fullBounds: 0...@0 corner: 8...@18 color: Color black extension: a MorphExtension (1051459584) [other: (blinkStart -> 2081777)] borderWidth: 0 borderColor: Color black textStyle: a TextStyle Bitmap DejaVu Sans 9 text: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' wrapFlag: true paragraph: a MultiNewParagraph editor: a TextMorphEditor container: nil predecessor: nil successor: nil backgroundColor: nil margins: nil editHistory: a TextMorphCommandHistory editView: a PluggableTextMorph(677642240) acceptOnCR: false TextMorphForEditView>>keyStroke: Receiver: a TextMorphForEditView(515899392) Arguments and temporary variables: evt: [keystroke '<Cmd-p>'] view: a PluggableTextMorph(677642240) Receiver's instance variables: bounds: 0...@0 corner: 8...@18 owner: a TransformMorph(721682432) submorphs: #() fullBounds: 0...@0 corner: 8...@18 color: Color black extension: a MorphExtension (1051459584) [other: (blinkStart -> 2081777)] borderWidth: 0 borderColor: Color black textStyle: a TextStyle Bitmap DejaVu Sans 9 text: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' wrapFlag: true paragraph: a MultiNewParagraph editor: a TextMorphEditor container: nil predecessor: nil successor: nil backgroundColor: nil margins: nil editHistory: a TextMorphCommandHistory editView: a PluggableTextMorph(677642240) acceptOnCR: false TextMorphForEditView(TextMorph)>>handleKeystroke: Receiver: a TextMorphForEditView(515899392) Arguments and temporary variables: anEvent: [keystroke '<Cmd-p>'] pasteUp: nil Receiver's instance variables: bounds: 0...@0 corner: 8...@18 owner: a TransformMorph(721682432) submorphs: #() fullBounds: 0...@0 corner: 8...@18 color: Color black extension: a MorphExtension (1051459584) [other: (blinkStart -> 2081777)] borderWidth: 0 borderColor: Color black textStyle: a TextStyle Bitmap DejaVu Sans 9 text: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' wrapFlag: true paragraph: a MultiNewParagraph editor: a TextMorphEditor container: nil predecessor: nil successor: nil backgroundColor: nil margins: nil editHistory: a TextMorphCommandHistory editView: a PluggableTextMorph(677642240) acceptOnCR: false KeyboardEvent>>sentTo: Receiver: [keystroke '<Cmd-p>'] Arguments and temporary variables: anObject: a TextMorphForEditView(515899392) Receiver's instance variables: timeStamp: 2082933 source: a HandMorph(843055104) windowIndex: nil type: #keystroke buttons: 64 position: 2...@45 handler: nil wasHandled: true keyValue: 112 charCode: 112 scanCode: 35 TextMorphForEditView(Morph)>>handleEvent: Receiver: a TextMorphForEditView(515899392) Arguments and temporary variables: anEvent: [keystroke '<Cmd-p>'] Receiver's instance variables: bounds: 0...@0 corner: 8...@18 owner: a TransformMorph(721682432) submorphs: #() fullBounds: 0...@0 corner: 8...@18 color: Color black extension: a MorphExtension (1051459584) [other: (blinkStart -> 2081777)] borderWidth: 0 borderColor: Color black textStyle: a TextStyle Bitmap DejaVu Sans 9 text: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' wrapFlag: true paragraph: a MultiNewParagraph editor: a TextMorphEditor container: nil predecessor: nil successor: nil backgroundColor: nil margins: nil editHistory: a TextMorphCommandHistory editView: a PluggableTextMorph(677642240) acceptOnCR: false TextMorphForEditView(Morph)>>handleFocusEvent: Receiver: a TextMorphForEditView(515899392) Arguments and temporary variables: anEvent: [keystroke '<Cmd-p>'] Receiver's instance variables: bounds: 0...@0 corner: 8...@18 owner: a TransformMorph(721682432) submorphs: #() fullBounds: 0...@0 corner: 8...@18 color: Color black extension: a MorphExtension (1051459584) [other: (blinkStart -> 2081777)] borderWidth: 0 borderColor: Color black textStyle: a TextStyle Bitmap DejaVu Sans 9 text: a Text for 'MIMEDocument guessTypeFromName: ''x.css''' wrapFlag: true paragraph: a MultiNewParagraph editor: a TextMorphEditor container: nil predecessor: nil successor: nil backgroundColor: nil margins: nil editHistory: a TextMorphCommandHistory editView: a PluggableTextMorph(677642240) acceptOnCR: false [] in HandMorph>>sendFocusEvent:to:clear: Receiver: a HandMorph(843055104) Arguments and temporary variables: anEvent: [keystroke '<Cmd-p>'] focusHolder: a TextMorphForEditView(515899392) result: #(nil) Receiver's instance variables: bounds: 1...@471 corner: 1...@487 owner: a PasteUpMorph(425197568) [world] submorphs: #() fullBounds: 1...@471 corner: 1...@487 color: Color blue extension: a MorphExtension (141295616) [eventHandler = an EventHandler] mouseFocus: nil keyboardFocus: a PluggableButtonMorph(423100416) eventListeners: nil mouseListeners: nil keyboardListeners: nil mouseClickState: nil mouseOverHandler: a MouseOverHandler lastMouseEvent: [1...@471 1...@471 mouseMove CMD 2082647 nil] targetOffset: 1...@9 damageRecorder: a DamageRecorder cacheCanvas: nil cachedCanvasHasHoles: true temporaryCursor: nil temporaryCursorOffset: nil hardwareCursor: nil hasChanged: true savedPatch: nil userInitials: '' lastEventBuffer: #(1 2082647 1026 471 0 8 0 1) lastKeyScanCode: 35 combinedChar: nil [] in PasteUpMorph>>becomeActiveDuring: Receiver: a PasteUpMorph(425197568) [world] Arguments and temporary variables: aBlock: [ActiveHand := self. ActiveEvent := anEvent. result := focusHolder ...etc... Receiver's instance variables: bounds: 0...@0 corner: 1...@1148 owner: nil submorphs: an Array(a TaskbarMorph(811335680) a PreDebugWindow(231997440) a Sys...etc... fullBounds: nil color: (Color r: 0.191 g: 0.191 b: 0.191) extension: a MorphExtension (666632192) [eventHandler = an EventHandler] [othe...etc... borderWidth: 0 borderColor: (Color r: 0.03 g: 0.02 b: 0.0) model: a MorphicModel(504889344) cursor: 1 padding: 3 backgroundMorph: nil isPartsBin: nil autoLineLayout: false indicateCursor: nil resizeToFit: nil worldState: a WorldState griddingOn: nil BlockClosure>>on:do: Receiver: [aBlock value] Arguments and temporary variables: exception: Error handlerAction: [:ex | ActiveWorld := priorWorld. ActiveEvent := priorEvent. ...etc... handlerActive: false Receiver's instance variables: outerContext: PasteUpMorph>>becomeActiveDuring: startpc: 67 numArgs: 0 PasteUpMorph>>becomeActiveDuring: Receiver: a PasteUpMorph(425197568) [world] Arguments and temporary variables: aBlock: [ActiveHand := self. ActiveEvent := anEvent. result := focusHolder ...etc... priorWorld: a PasteUpMorph(425197568) [world] priorHand: a HandMorph(843055104) priorEvent: nil Receiver's instance variables: bounds: 0...@0 corner: 1...@1148 owner: nil submorphs: an Array(a TaskbarMorph(811335680) a PreDebugWindow(231997440) a Sys...etc... fullBounds: nil color: (Color r: 0.191 g: 0.191 b: 0.191) extension: a MorphExtension (666632192) [eventHandler = an EventHandler] [othe...etc... borderWidth: 0 borderColor: (Color r: 0.03 g: 0.02 b: 0.0) model: a MorphicModel(504889344) cursor: 1 padding: 3 backgroundMorph: nil isPartsBin: nil autoLineLayout: false indicateCursor: nil resizeToFit: nil worldState: a WorldState griddingOn: nil HandMorph>>sendFocusEvent:to:clear: Receiver: a HandMorph(843055104) Arguments and temporary variables: anEvent: [keystroke '<Cmd-p>'] focusHolder: a TextMorphForEditView(515899392) aBlock: [self keyboardFocus: nil] w: a PasteUpMorph(425197568) [world] result: #(nil) Receiver's instance variables: bounds: 1...@471 corner: 1...@487 owner: a PasteUpMorph(425197568) [world] submorphs: #() fullBounds: 1...@471 corner: 1...@487 color: Color blue extension: a MorphExtension (141295616) [eventHandler = an EventHandler] mouseFocus: nil keyboardFocus: a PluggableButtonMorph(423100416) eventListeners: nil mouseListeners: nil keyboardListeners: nil mouseClickState: nil mouseOverHandler: a MouseOverHandler lastMouseEvent: [1...@471 1...@471 mouseMove CMD 2082647 nil] targetOffset: 1...@9 damageRecorder: a DamageRecorder cacheCanvas: nil cachedCanvasHasHoles: true temporaryCursor: nil temporaryCursorOffset: nil hardwareCursor: nil hasChanged: true savedPatch: nil userInitials: '' lastEventBuffer: #(1 2082647 1026 471 0 8 0 1) lastKeyScanCode: 35 combinedChar: nil HandMorph>>sendEvent:focus:clear: Receiver: a HandMorph(843055104) Arguments and temporary variables: anEvent: [keystroke '<Cmd-p>'] focusHolder: a TextMorphForEditView(515899392) aBlock: [self keyboardFocus: nil] result: nil Receiver's instance variables: bounds: 1...@471 corner: 1...@487 owner: a PasteUpMorph(425197568) [world] submorphs: #() fullBounds: 1...@471 corner: 1...@487 color: Color blue extension: a MorphExtension (141295616) [eventHandler = an EventHandler] mouseFocus: nil keyboardFocus: a PluggableButtonMorph(423100416) eventListeners: nil mouseListeners: nil keyboardListeners: nil mouseClickState: nil mouseOverHandler: a MouseOverHandler lastMouseEvent: [1...@471 1...@471 mouseMove CMD 2082647 nil] targetOffset: 1...@9 damageRecorder: a DamageRecorder cacheCanvas: nil cachedCanvasHasHoles: true temporaryCursor: nil temporaryCursorOffset: nil hardwareCursor: nil hasChanged: true savedPatch: nil userInitials: '' lastEventBuffer: #(1 2082647 1026 471 0 8 0 1) lastKeyScanCode: 35 combinedChar: nil HandMorph>>sendKeyboardEvent: Receiver: a HandMorph(843055104) Arguments and temporary variables: anEvent: [keystroke '<Cmd-p>'] Receiver's instance variables: bounds: 1...@471 corner: 1...@487 owner: a PasteUpMorph(425197568) [world] submorphs: #() fullBounds: 1...@471 corner: 1...@487 color: Color blue extension: a MorphExtension (141295616) [eventHandler = an EventHandler] mouseFocus: nil keyboardFocus: a PluggableButtonMorph(423100416) eventListeners: nil mouseListeners: nil keyboardListeners: nil mouseClickState: nil mouseOverHandler: a MouseOverHandler lastMouseEvent: [1...@471 1...@471 mouseMove CMD 2082647 nil] targetOffset: 1...@9 damageRecorder: a DamageRecorder cacheCanvas: nil cachedCanvasHasHoles: true temporaryCursor: nil temporaryCursorOffset: nil hardwareCursor: nil hasChanged: true savedPatch: nil userInitials: '' lastEventBuffer: #(1 2082647 1026 471 0 8 0 1) lastKeyScanCode: 35 combinedChar: nil HandMorph>>handleEvent: Receiver: a HandMorph(843055104) Arguments and temporary variables: anEvent: [keystroke '<Cmd-p>'] evt: [keystroke '<Cmd-p>'] ofs: nil Receiver's instance variables: bounds: 1...@471 corner: 1...@487 owner: a PasteUpMorph(425197568) [world] submorphs: #() fullBounds: 1...@471 corner: 1...@487 color: Color blue extension: a MorphExtension (141295616) [eventHandler = an EventHandler] mouseFocus: nil keyboardFocus: a PluggableButtonMorph(423100416) eventListeners: nil mouseListeners: nil keyboardListeners: nil mouseClickState: nil mouseOverHandler: a MouseOverHandler lastMouseEvent: [1...@471 1...@471 mouseMove CMD 2082647 nil] targetOffset: 1...@9 damageRecorder: a DamageRecorder cacheCanvas: nil cachedCanvasHasHoles: true temporaryCursor: nil temporaryCursorOffset: nil hardwareCursor: nil hasChanged: true savedPatch: nil userInitials: '' lastEventBuffer: #(1 2082647 1026 471 0 8 0 1) lastKeyScanCode: 35 combinedChar: nil HandMorph>>processEvents Receiver: a HandMorph(843055104) Arguments and temporary variables: evt: [keystroke '<Cmd-p>'] evtBuf: #(2 2082933 112 0 8 112 0 1) type: 2 hadAny: true Receiver's instance variables: bounds: 1...@471 corner: 1...@487 owner: a PasteUpMorph(425197568) [world] submorphs: #() fullBounds: 1...@471 corner: 1...@487 color: Color blue extension: a MorphExtension (141295616) [eventHandler = an EventHandler] mouseFocus: nil keyboardFocus: a PluggableButtonMorph(423100416) eventListeners: nil mouseListeners: nil keyboardListeners: nil mouseClickState: nil mouseOverHandler: a MouseOverHandler lastMouseEvent: [1...@471 1...@471 mouseMove CMD 2082647 nil] targetOffset: 1...@9 damageRecorder: a DamageRecorder cacheCanvas: nil cachedCanvasHasHoles: true temporaryCursor: nil temporaryCursorOffset: nil hardwareCursor: nil hasChanged: true savedPatch: nil userInitials: '' lastEventBuffer: #(1 2082647 1026 471 0 8 0 1) lastKeyScanCode: 35 combinedChar: nil [] in WorldState>>doOneCycleNowFor: Receiver: a WorldState Arguments and temporary variables: h: a HandMorph(843055104) Receiver's instance variables: hands: an Array(a HandMorph(843055104)) viewBox: 0...@0 corner: 1...@1148 canvas: a FormCanvas on: DisplayScreen(1904x1148x32) damageRecorder: a DamageRecorder stepList: a Heap(StepMessage(#stepAt: -> a PreDebugWindow(231997440))(a PreDebu...etc... lastStepTime: 2082917 lastStepMessage: nil lastCycleTime: 2082957 commandHistory: a CommandHistory alarms: a Heap() lastAlarmTime: 2082917 menuBuilder: a PragmaMenuBuilder Array(SequenceableCollection)>>do: Receiver: an Array(a HandMorph(843055104)) Arguments and temporary variables: aBlock: [:h | ActiveHand := h. h processEvents. ActiveHand := nil] index: 1 indexLimiT: 1 Receiver's instance variables: an Array(a HandMorph(843055104)) --- The full stack --- HierarchicalURI(Object)>>doesNotUnderstand: #findLast: FileDirectory class>>extensionFor: MIMEType class>>forFileNameReturnMimeTypesOrNil: MIMEType class>>forFileNameReturnMimeTypesOrDefault: MIMEType class>>forFileNameReturnSingleMimeTypeOrDefault: MIMEDocument class>>guessTypeFromName: UndefinedObject>>DoIt Compiler>>evaluate:in:to:notifying:ifFail:logged: [] in TextMorphEditor(ParagraphEditor)>>evaluateSelection BlockClosure>>on:do: TextMorphEditor(ParagraphEditor)>>evaluateSelection TextMorphEditor(ParagraphEditor)>>printIt [] in TextMorphEditor(ParagraphEditor)>>printIt: TextMorphEditor(ParagraphEditor)>>terminateAndInitializeAround: TextMorphEditor(ParagraphEditor)>>printIt: 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 Pharo-project@lists.gforge.inria.fr http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project