<div id="__MailbirdStyleContent" style="font-size: 12pt;font-family: calibri;color: #000000">
                                        
                                        
                                            
                                        
                                        
                                        Hi Hannes,<div><br></div><div>the message #translateTo: is a simpler version of #transformedBy:, which was added back in 2000.</div><div><br></div><div>Basically, these are helper methods to cope with local coordinate systems in TransformMorphs. It is only used in MorphicEventDispatcher. The term "translate" means geometry like in Rectangle.</div><div><br></div><div>No morph should ever receive this message, only MorphicEvent (sub-)instances. I suppose there are some issues in BabySRE considering overrides of:</div><div><br></div><div>Morph >> #handleEvent:</div><div>Morph >> #handleFocusEvent:</div><div>Morph >> #processEvent:</div><div>Morph >> #processEvent:using:</div><div>Morph >> #processFocusEvent:</div><div>Morph >> #processFocusEvent:using:</div><div><br></div><div>All these methods must return an event object, not "self" (or a morph).</div><div><br></div><div>Best,</div><div>Marcel</div><div class="mb_sig"></div>
                                        
                                        <blockquote class="history_container" type="cite" style="border-left-style: solid;border-width: 1px;margin-top: 20px;margin-left: 0px;padding-left: 10px;min-width: 500px">
                        <p style="color: #AAAAAA; margin-top: 10px;">Am 11.05.2018 08:17:05 schrieb H. Hirzel <hannes.hirzel@gmail.com>:</p>Hello Marcel,
<br>
<br>could you please give some more background information about the
<br>method #translateTo: which seems to have been introduced with this
<br>change?
<br>
<br>I loaded BabySRE-hjh.44  (http://wiki.squeak.org/squeak/2551)
<br>
<br>into Squeak6.0alpha #17970 (current trunk) and got the error
<br>
<br>AConnectorSRE (a morph) does not understand #translateTo:
<br>
<br>
<br>--Hannes
<br>
<br>
<br>...........................................................................................................................
<br>
<br>translateTo: messages in current trunk:
<br>............................................................................................................................
<br>
<br>
<br>UserEvent>>translateTo: point
<br>
<br>      position := point.
<br>
<br>
<br>DropEvent>>translateTo: point
<br>
<br>      position := point.
<br>
<br>
<br>MorphicEvent>>translateTo: point
<br>"empty method body"
<br>
<br>
<br>
<br>
<br>On Mon, 20 Jun 2016 15:14:05.567 0000, commits@source.squeak.org
<br><commits@source.squeak.org> wrote:
<br>> Marcel Taeumel uploaded a new version of Morphic to project The Trunk:
<br>> http://source.squeak.org/trunk/Morphic-mt.1182.mcz
<br>>
<br>> ==================== Summary ====================
<br>>
<br>> Name: Morphic-mt.1182
<br>> Author: mt
<br>> Time: 20 June 2016, 5:13:55.570796 pm
<br>> UUID: 825d8e52-1878-af49-9f7a-437b23e68d8c
<br>> Ancestors: Morphic-mt.1181
<br>>
<br>> Moves implementation of focus event dispatching from various places into
<br>> MorphicEventDispatcher. This will ensure consistency in the future because
<br>> MorphicEventDispatcher encode the tree iteration with capturing and
<br>> bubbling. Doing a focus event is just a shortcut into the tree. TextMorphs
<br>> use that. Pop-up menus use that. Modal dialogs use that.
<br>>
<br>> Fixes missing coordinate transformations when capturing and bubbling for
<br>> focus events.
<br>>
<br>> Simplify focus-related code in MenuMorph, UserDialogBoxMorph, and
<br>> DockingBarMorph.
<br>>
<br>> At the time of writing, there seems to be no need anymore for Morph >>
<br>> #handleFocusEvent:. Still, keep it for compatibility to other projects.
<br>>
<br>> =============== Diff against Morphic-mt.1181 ===============
<br>>
<br>> Item was removed:
<br>> - ----- Method: DockingBarMorph>>handleFocusEvent: (in category
<br>> 'events-processing') -----
<br>> - handleFocusEvent: evt
<br>> -        "Handle focus events. Valid menu transitions are determined based on the
<br>> menu currently holding the focus after the mouse went down on one of its
<br>> children."
<br>> -
<br>> -        | result filteredEvent |
<br>> -        (evt isMouse and:[ evt isMouseUp ]) ifTrue:[^ evt].
<br>> -
<br>> -        result := self processEvent: evt.
<br>> -        filteredEvent := result == #rejected ifTrue: [evt] ifFalse: [result].
<br>> -
<br>> -        "Need to handle keyboard input if we have the focus."
<br>> -        filteredEvent isKeyboard ifTrue: [^ super handleFocusEvent:
<br>> filteredEvent].
<br>> -
<br>> -        "We need to handle button clicks outside and transitions to local popUps
<br>> so throw away everything else"
<br>> -        (filteredEvent isMouseOver or:[filteredEvent isMouse not])
<br>> ifTrue:[^filteredEvent].
<br>> -        "What remains are mouse buttons and moves"
<br>> -        filteredEvent isMove ifFalse:[^super handleFocusEvent: filteredEvent].
<br>> "handle clicks outside by regular means"
<br>> -        "Now it's getting tricky. On #mouseMove we might transfer control to
<br>> *either* the currently active submenu or the pop up owner, if any. Since the
<br>> active sub menu is always displayed upfront check it first."
<br>> -        selectedItem ifNotNil:[(selectedItem activateSubmenu: filteredEvent)
<br>> ifTrue:[^filteredEvent]].
<br>> - !
<br>>
<br>> Item was added:
<br>> + ----- Method: DockingBarMorph>>mouseMove: (in category
<br>> 'events-processing') -----
<br>> + mouseMove: evt
<br>> +        "We might transfer control to *either* the currently active submenu or
<br>> the pop up owner, if any. Since the active sub menu is always displayed
<br>> upfront check it first."
<br>> +        
<br>> +        selectedItem ifNotNil:[selectedItem activateSubmenu: evt].!
<br>>
<br>> Item was added:
<br>> + ----- Method: DockingBarMorph>>processFocusEvent:using: (in category
<br>> 'events-processing') -----
<br>> + processFocusEvent: evt using: dispatcher
<br>> +
<br>> +        ^ dispatcher dispatchFocusEventFully: evt with: self!
<br>>
<br>> Item was added:
<br>> + ----- Method: DockingBarMorph>>wantsEveryMouseMove (in category
<br>> 'events-processing') -----
<br>> + wantsEveryMouseMove
<br>> +        ^ true!
<br>>
<br>> Item was changed:
<br>>   ----- Method: HandMorph>>sendFocusEvent:to:clear: (in category 'private
<br>> events') -----
<br>>   sendFocusEvent: anEvent to: focusHolder clear: aBlock
<br>>          "Send the event to the morph currently holding the focus"
<br>> +
<br>>          | result w |
<br>>          w := focusHolder world ifNil:[aBlock value. ^ anEvent].
<br>>          w becomeActiveDuring:[
<br>>                  ActiveHand := self.
<br>>                  ActiveEvent := anEvent.
<br>> +                result := focusHolder processFocusEvent: anEvent.
<br>> -                result := focusHolder handleFocusEvent:
<br>> -                        (anEvent transformedBy: (focusHolder transformedFrom: self)).
<br>>          ].
<br>> +        ^ result == #rejected ifTrue: [anEvent] ifFalse: [result "filtered
<br>> event"]!
<br>> -        ^result == #rejected ifTrue: [anEvent] ifFalse: [result "filtered
<br>> event"]!
<br>>
<br>> Item was removed:
<br>> - ----- Method: MenuMorph>>handleFocusEvent: (in category 'events') -----
<br>> - handleFocusEvent: evt
<br>> -        "Handle focus events. Valid menu transitions are determined based on the
<br>> menu currently holding the focus after the mouse went down on one of its
<br>> children."
<br>> -        | result filteredEvent |
<br>> -        result := self processEvent: evt.
<br>> -        filteredEvent := result == #rejected ifTrue: [evt] ifFalse: [result].
<br>> -
<br>> -        "Need to handle keyboard input if we have the focus."
<br>> -        filteredEvent isKeyboard ifTrue: [^ super handleFocusEvent:
<br>> filteredEvent].
<br>> -
<br>> -        "We need to handle button clicks outside and transitions to local popUps
<br>> so throw away everything else"
<br>> -        (filteredEvent isMouseOver or:[filteredEvent isMouse not])
<br>> ifTrue:[^filteredEvent].
<br>> -        "What remains are mouse buttons and moves"
<br>> -        filteredEvent isMove ifFalse:[^super handleFocusEvent: filteredEvent].
<br>> "handle clicks outside by regular means"
<br>> -        "Now it's getting tricky. On #mouseMove we might transfer control to
<br>> *either* the currently active submenu or the pop up owner, if any. Since the
<br>> active sub menu is always displayed upfront check it first."        
<br>> -        selectedItem ifNotNil: [
<br>> -                (selectedItem activateSubmenu: filteredEvent)
<br>> -                        ifTrue: [ ^filteredEvent ]
<br>> -                        ifFalse: [
<br>> -                                (self containsPoint: filteredEvent position) ifFalse: [
<br>> -                                        self selectItem: nil event: filteredEvent ] ] ].
<br>> -        "Note: The following does not traverse upwards but it's the best I can do
<br>> for now"
<br>> -        popUpOwner ifNotNil:[(popUpOwner activateOwnerMenu: filteredEvent)
<br>> ifTrue:[^filteredEvent]].
<br>> -        ^ filteredEvent!
<br>>
<br>> Item was removed:
<br>> - ----- Method: MenuMorph>>handleMouseMove: (in category 'events') -----
<br>> - handleMouseMove: evt
<br>> -        " If the mouse moves over an item not selected, we try to set it as
<br>> selected.
<br>> -        If this happens depends on that the current selected item wants to
<br>> release
<br>> -        its selection. "
<br>> -
<br>> -        self selectedItem ifNil: [ ^super handleMouseMove: evt ].
<br>> -        (self selectedItem containsPoint: evt position) ifTrue: [ ^super
<br>> handleMouseMove: evt ].
<br>> -        self
<br>> -                selectItem: (
<br>> -                        self items
<br>> -                                detect: [ :each | each containsPoint: evt position ]
<br>> -                                ifNone: [ nil ])
<br>> -                event: evt.
<br>> -        super handleMouseMove: evt!
<br>>
<br>> Item was added:
<br>> + ----- Method: MenuMorph>>mouseMove: (in category 'events') -----
<br>> + mouseMove: evt
<br>> +        " If the mouse moves over an item not selected, we try to set it as
<br>> selected.
<br>> +        If this happens depends on that the current selected item wants to
<br>> release
<br>> +        its selection. "
<br>> +
<br>> +        self selectedItem ifNil: [ ^ self ].
<br>> +        (self selectedItem containsPoint: evt position) ifTrue: [ ^ self ].
<br>> +        self
<br>> +                selectItem: (
<br>> +                        self items
<br>> +                                detect: [ :each | each containsPoint: evt position ]
<br>> +                                ifNone: [ nil ])
<br>> +                event: evt.
<br>> +
<br>> +        "Transfer control to *either* the currently active submenu or the pop up
<br>> owner, if any. Since the active sub menu is always displayed upfront check
<br>> it first."  
<br>> +        selectedItem ifNotNil: [
<br>> +                (selectedItem activateSubmenu: evt)
<br>> +                        ifTrue: [ ^self ]
<br>> +                        ifFalse: [
<br>> +                                (self containsPoint: evt position) ifFalse: [
<br>> +                                        self selectItem: nil event: evt ] ] ].
<br>> +        
<br>> +        "Note: The following does not traverse upwards but it's the best I can do
<br>> for now"
<br>> +        popUpOwner ifNotNil:[popUpOwner activateOwnerMenu: evt]!
<br>>
<br>> Item was added:
<br>> + ----- Method: MenuMorph>>processFocusEvent:using: (in category 'events')
<br>> -----
<br>> + processFocusEvent: evt using: dispatcher
<br>> +
<br>> +        ^ dispatcher dispatchFocusEventFully: evt with: self!
<br>>
<br>> Item was added:
<br>> + ----- Method: MenuMorph>>wantsEveryMouseMove (in category 'events') -----
<br>> + wantsEveryMouseMove
<br>> +        ^ true!
<br>>
<br>> Item was changed:
<br>>   ----- Method: Morph>>handleFocusEvent: (in category 'events-processing')
<br>> -----
<br>>   handleFocusEvent: anEvent
<br>> +        "Handle the given event. This message is sent if the receiver currently
<br>> has the focus and is therefore receiving events directly from some hand.
<br>> However, it might already have been handled due to overrides in
<br>> #processFocusEvent:using:. We might want to get rid of this call-back in the
<br>> future..."
<br>> -        "Handle the given event. This message is sent if the receiver currently
<br>> has the focus and is therefore receiving events directly from some hand.
<br>>          
<br>> +        ^ anEvent wasHandled
<br>> +                ifTrue: [anEvent]
<br>> +                ifFalse: [self handleEvent: anEvent]!
<br>> -        1) Event bubbling. Do event bubbling known from MorphicEventDispatcher by
<br>> calling #handleEvent: also on all owners.
<br>> -        2) Event capture filters. Walk along the owner chain in reverse order and
<br>> apply capture filters as known from MorphicEventDispatcher.
<br>> -        
<br>> -        If you want to overwrite this in a subclass (for example to implement
<br>> modal dialogs) ensure to call super instead if #handleEvent: directly."
<br>> -
<br>> -        | filteredEvent |
<br>> -        filteredEvent := anEvent.
<br>> -        
<br>> -        "TODO: Add a check to ensure that our event dispatcher is actually of
<br>> kind MorphicEventDispatcher?!! We do copy its behavior though... like self
<br>> defaultEventDispatcher class == MorphicEventDispatcher? Or #isKindOf:?
<br>> Anyway, the outermost morph determines the event dispatcher. See HandMorph
<br>>>> #sendEvent:focus:clear: and PasteUpMorph >> #processEvent:."
<br>> -
<br>> -        "Event capturing. Filters only because the capturing phase was bypassed
<br>> by using the keyboard/mouse focus."
<br>> -        self withAllOwners reverseDo: [:morph | "reverse order to comply with
<br>> default MorphEventDispatcher"
<br>> -                        morph == anEvent hand ifFalse: [ "Fixes drag-and-drop bug."
<br>> -                                filteredEvent := morph sendFilterEventCapture: filteredEvent for:
<br>> morph.
<br>> -                                filteredEvent wasIgnored ifTrue: [^ filteredEvent]]].
<br>> -
<br>> -        "Event bubbling. Filters are processed in #handleEvent:."
<br>> -        self withAllOwnersDo: [:morph |
<br>> -                morph == anEvent hand ifFalse: [ "Fixes drag-and-drop bug."
<br>> -                        filteredEvent := morph handleEvent: filteredEvent.
<br>> -                        filteredEvent wasIgnored ifTrue: [^ filteredEvent]]].
<br>> -
<br>> -        ^ filteredEvent!
<br>>
<br>> Item was added:
<br>> + ----- Method: Morph>>processFocusEvent: (in category 'events-processing')
<br>> -----
<br>> + processFocusEvent: anEvent
<br>> +
<br>> +        ^self processFocusEvent: anEvent using: self defaultEventDispatcher!
<br>>
<br>> Item was added:
<br>> + ----- Method: Morph>>processFocusEvent:using: (in category
<br>> 'events-processing') -----
<br>> + processFocusEvent: anEvent using: defaultDispatcher
<br>> +        "Event dispatching shortcut."
<br>> +
<br>> +        ^ defaultDispatcher dispatchFocusEvent: anEvent with: self!
<br>>
<br>> Item was changed:
<br>> + ----- Method: MorphicEventDispatcher>>dispatchEvent:toSubmorphsOf: (in
<br>> category 'support') -----
<br>> - ----- Method: MorphicEventDispatcher>>dispatchEvent:toSubmorphsOf: (in
<br>> category 'private') -----
<br>>   dispatchEvent: anEvent toSubmorphsOf: aMorph
<br>>          "Dispatch the given event to the submorphs of the given morph. For
<br>> coordinate transformations, work only with copies. Either return the given
<br>> event or a copy of any filtered event to employ immutability to some extent.
<br>> --- PRIVATE!!"
<br>>
<br>>          | localEvent filteredEvent |    
<br>>          aMorph submorphsDo: [:child |
<br>>                  localEvent := anEvent transformedBy: (child transformedFrom: aMorph).
<br>>                  filteredEvent := child
<br>>                          processEvent: localEvent
<br>>                          using: self. "use same dispatcher"
<br>>                  filteredEvent == #rejected ifFalse: [ "some event or #rejected symbol"
<br>>                          self flag: #overlappingChildren. "mt: We cannot give two overlapping
<br>> siblings the chance to handle the event!!"  
<br>> +                        ^ self nextFromOriginal: anEvent local: localEvent filtered:
<br>> filteredEvent]].
<br>> -                        filteredEvent == localEvent
<br>> -                                ifTrue: [
<br>> -                                        localEvent wasHandled ifTrue: [anEvent copyHandlerState:
<br>> localEvent].
<br>> -                                        anEvent wasIgnored: localEvent wasIgnored.
<br>> -                                        ^ anEvent]
<br>> -                                ifFalse: [
<br>> -                                        filteredEvent := filteredEvent copy.
<br>> -                                        filteredEvent translateTo: anEvent position. "restore to
<br>> untransformed coordinates"
<br>> -                                        filteredEvent wasHandled ifFalse: [filteredEvent copyHandlerState:
<br>> anEvent]. "restore handler if needed"
<br>> -                                        ^ filteredEvent]]].
<br>>
<br>>          ^ #rejected!
<br>>
<br>> Item was changed:
<br>> + ----- Method: MorphicEventDispatcher>>dispatchEvent:withHandler:withMorph:
<br>> (in category 'support') -----
<br>> - ----- Method: MorphicEventDispatcher>>dispatchEvent:withHandler:withMorph:
<br>> (in category 'private') -----
<br>>   dispatchEvent: anEvent withHandler: aHandler withMorph: aMorph
<br>>          "Perform the actual event dispatch. Use the given object as handler. Ask
<br>> submorphs first to handle the event. Then bubble up. Stop if ignored. Note
<br>> that event rejection and event filters are two separete concepts. Filters
<br>> come from the outside. Rejection is a morph's decision.
<br>>          
<br>>          * The top-most chain of visible, unlocked morphs containing the event
<br>> position will get a chance to handle the event.
<br>>          * When travelling up, the prospective handler is always executed. The
<br>> handler needs to check if the event was handled before as well as checking
<br>> if somebody else's handler has been installed.
<br>>          * If another handler has been installed but the event was not handled it
<br>> means that somebody up in the hierarchy wants to handle the event."
<br>>          
<br>>          | result filteredEvent |
<br>>          
<br>>          result := self dispatchEvent: anEvent toSubmorphsOf: aMorph.
<br>>
<br>>          result == #rejected "Anybody?"
<br>>                  ifFalse: [filteredEvent := result]
<br>>                  ifTrue: [
<br>>                          "My submorphs did not want it. Do I want it anyway? It's about locked
<br>> children..."
<br>>                          (aMorph containsPoint: anEvent position event: anEvent)
<br>>                                  ifFalse: [^ #rejected].
<br>>                          filteredEvent := anEvent "there was no filtering, only basic
<br>> rejects"].
<br>>          
<br>>          "Receiver is in the top-most unlocked, visible chain."
<br>>          (aHandler notNil and: [filteredEvent wasIgnored not])
<br>>                  ifTrue: [filteredEvent := aHandler handleEvent: filteredEvent].
<br>>
<br>>          ^ filteredEvent!
<br>>
<br>> Item was added:
<br>> + ----- Method: MorphicEventDispatcher>>dispatchFocusEvent:with: (in
<br>> category 'focus events') -----
<br>> + dispatchFocusEvent: anEventWithGlobalPosition with: focusMorph
<br>> +        "Dispatch the given event to the given morph. Simulate capturing phase,
<br>> handle the event, then do bubbling."
<br>> +
<br>> +        | currentEvent |
<br>> +        "1) Capturing phase."
<br>> +        currentEvent := self doCapturingForFocusEvent: anEventWithGlobalPosition
<br>> with: focusMorph.
<br>> +        currentEvent == #rejected ifTrue: [^ #rejected].
<br>> +        currentEvent wasIgnored ifTrue: [^ currentEvent].
<br>> +        
<br>> +        "2) No sub-tree processing here. Use #dispatchFocusEventFully:with: if
<br>> you want that, too."
<br>> +        
<br>> +        "3) Let the focus morph handle the event."
<br>> +        currentEvent := self doHandlingForFocusEvent: currentEvent with:
<br>> focusMorph.
<br>> +        currentEvent wasIgnored ifTrue: [^ currentEvent].
<br>> +        
<br>> +        "4) Bubbling phase"
<br>> +        ^ self doBubblingForFocusEvent: currentEvent with: focusMorph!
<br>>
<br>> Item was added:
<br>> + ----- Method: MorphicEventDispatcher>>dispatchFocusEventFully:with: (in
<br>> category 'focus events') -----
<br>> + dispatchFocusEventFully: anEventWithGlobalPosition with: focusMorph
<br>> +        "Dispatch the given event to the given morph. Do capturing, processing in
<br>> sub-tree, and bubbling."
<br>> +        
<br>> +        | currentEvent |
<br>> +        "1) Capturing phase."
<br>> +        currentEvent := self doCapturingForFocusEvent: anEventWithGlobalPosition
<br>> with: focusMorph.
<br>> +        currentEvent == #rejected ifTrue: [^ #rejected].
<br>> +        currentEvent wasIgnored ifTrue: [^ currentEvent].
<br>> +        
<br>> +        "2) Sub-tree processing."
<br>> +        currentEvent := self doProcessingForFocusEvent: currentEvent with:
<br>> focusMorph.
<br>> +        currentEvent wasIgnored ifTrue: [^ currentEvent].
<br>> +
<br>> +        "3) Let the focus morph handle the event. Usually no effect because
<br>> previous sub-tree processing involved the focus morph already -- at least in
<br>> the bubbling phase. Skip it?"
<br>> +        currentEvent := self doHandlingForFocusEvent: currentEvent with:
<br>> focusMorph.
<br>> +        currentEvent wasIgnored ifTrue: [^ currentEvent].
<br>> +        
<br>> +        "4) Bubbling phase."
<br>> +        ^ self doBubblingForFocusEvent: currentEvent with: focusMorph!
<br>>
<br>> Item was added:
<br>> + ----- Method: MorphicEventDispatcher>>doBubblingForFocusEvent:with: (in
<br>> category 'support') -----
<br>> + doBubblingForFocusEvent: anEvent with: focusMorph
<br>> +        "Simulate real event bubbling up to the focused morph's outermost owner.
<br>> Applies event bubble filters via Morph >> #handleEvent:. Watch out for
<br>> coordinate transformations and some globals (ActiveWorld, ...)."
<br>> +
<br>> +        | currentEvent filteredEvent localEvent referenceMorph |
<br>> +        currentEvent := anEvent.
<br>> +        referenceMorph := anEvent hand.
<br>> +
<br>> +        focusMorph allOwnersDo: [:ownerMorph |
<br>> +                ownerMorph == anEvent hand ifFalse: [ "Never bubble up to the hand morph
<br>> but only up to the world."
<br>> +                        localEvent := currentEvent transformedBy: (ownerMorph transformedFrom:
<br>> referenceMorph).
<br>> +                        filteredEvent := ownerMorph handleEvent: localEvent.
<br>> +                        currentEvent := self nextFromOriginal: currentEvent local: localEvent
<br>> filtered: filteredEvent.
<br>> +                        currentEvent wasIgnored ifTrue: [^ currentEvent]]].
<br>> +
<br>> +        ^ currentEvent!
<br>>
<br>> Item was added:
<br>> + ----- Method: MorphicEventDispatcher>>doCapturingForFocusEvent:with: (in
<br>> category 'support') -----
<br>> + doCapturingForFocusEvent: anEvent with: focusMorph
<br>> +        "Simulate real event capturing down to the focused morph. Apply event
<br>> capture filters. Watch out for coordinate transformations. Keep the
<br>> filter-ignore-reject order like in Morph >> #processEvent:using:."
<br>> +
<br>> +        | currentEvent filteredEvent localEvent referenceMorph |
<br>> +        currentEvent := anEvent.
<br>> +        referenceMorph := anEvent hand.
<br>> +
<br>> +        "Event capturing. Filters only because the capturing phase was bypassed
<br>> by using the keyboard/mouse focus."
<br>> +        focusMorph withAllOwners reverseDo: [:ownerMorph | "reverse order to
<br>> comply with regular dispatching"
<br>> +                ownerMorph == anEvent hand ifFalse: [ "Never dispatch the hand morph. It
<br>> already did so."
<br>> +                        localEvent := currentEvent transformedBy: (ownerMorph transformedFrom:
<br>> referenceMorph).
<br>> +                        
<br>> +                        filteredEvent := ownerMorph sendFilterEventCapture: localEvent for:
<br>> ownerMorph.
<br>> +                        
<br>> +                        "Ignoring has higher priority but the reject-check must be with local
<br>> event coodinates."
<br>> +                        (filteredEvent wasIgnored not and: [ownerMorph rejectsEvent:
<br>> filteredEvent])
<br>> +                                ifTrue: [^ #rejected].
<br>> +                        
<br>> +                        currentEvent := self nextFromOriginal: currentEvent local: localEvent
<br>> filtered: filteredEvent.
<br>> +                        currentEvent wasIgnored ifTrue: [^ currentEvent]]].
<br>> +        
<br>> +        ^ currentEvent!
<br>>
<br>> Item was added:
<br>> + ----- Method: MorphicEventDispatcher>>doHandlingForFocusEvent:with: (in
<br>> category 'support') -----
<br>> + doHandlingForFocusEvent: currentEvent with: focusMorph
<br>> +
<br>> +        | localEvent filteredEvent |
<br>> +        localEvent := currentEvent transformedBy: (focusMorph transformedFrom:
<br>> currentEvent hand).
<br>> +        filteredEvent := focusMorph handleFocusEvent: localEvent.
<br>> +        ^ self nextFromOriginal: currentEvent local: localEvent filtered:
<br>> filteredEvent.!
<br>>
<br>> Item was added:
<br>> + ----- Method: MorphicEventDispatcher>>doProcessingForFocusEvent:with: (in
<br>> category 'support') -----
<br>> + doProcessingForFocusEvent: currentEvent with: focusMorph
<br>> +        "Sub-tree processing (including capturing from focus morph down to
<br>> something and bubbling up back to focus morph). Never reject in the end."
<br>> +        
<br>> +        | localEvent filteredEvent |
<br>> +        localEvent := currentEvent transformedBy: (focusMorph transformedFrom:
<br>> currentEvent hand).
<br>> +        filteredEvent := focusMorph processEvent: localEvent using: self.
<br>> +        ^ filteredEvent == #rejected
<br>> +                ifTrue: [currentEvent] "Can happen if you click, e.g., outside the
<br>> bounds of the focus morph"
<br>> +                ifFalse: [self nextFromOriginal: currentEvent local: localEvent
<br>> filtered: filteredEvent]!
<br>>
<br>> Item was added:
<br>> + ----- Method: MorphicEventDispatcher>>nextFromOriginal:local:filtered: (in
<br>> category 'support') -----
<br>> + nextFromOriginal: originalEvent local: localEvent filtered: filteredEvent
<br>> +        "Take the filtered event if different but always keep the original
<br>> coordinates."
<br>> +        
<br>> +        filteredEvent == localEvent
<br>> +                ifTrue: [ "Use original event but keep track of ignored flag."
<br>> +                        localEvent wasHandled ifTrue: [originalEvent copyHandlerState:
<br>> localEvent].
<br>> +                        originalEvent wasIgnored: localEvent wasIgnored.
<br>> +                        ^ originalEvent]
<br>> +                ifFalse: [ "There was an event transformation. Copy, revert coordinates,
<br>> keep handler state."
<br>> +                        | result |
<br>> +                        result := filteredEvent copy. "Never mutate position without copying.
<br>> MouseClickState etc. will break otherwise."
<br>> +                        result translateTo: originalEvent position. "restore to untransformed
<br>> coordinates"
<br>> +                        result wasHandled ifFalse: [result copyHandlerState: originalEvent].
<br>> +                        ^ result].
<br>> + !
<br>>
<br>> Item was removed:
<br>> - ----- Method: UserDialogBoxMorph>>handleFocusEvent: (in category
<br>> 'constructing') -----
<br>> - handleFocusEvent: evt
<br>> -        "Handle focus events. Valid menu transitions are determined based on the
<br>> menu currently holding the focus after the mouse went down on one of its
<br>> children. Need to handle keyboard input if we have the focus."
<br>> -
<br>> -        | result filteredEvent |
<br>> -        result := self processEvent: evt.
<br>> -        filteredEvent := result == #rejected ifTrue: [evt] ifFalse: [result].
<br>> -
<br>> -        ^ super handleFocusEvent: filteredEvent!
<br>>
<br>> Item was added:
<br>> + ----- Method: UserDialogBoxMorph>>processFocusEvent:using: (in category
<br>> 'events') -----
<br>> + processFocusEvent: evt using: dispatcher
<br>> +
<br>> +        ^ dispatcher dispatchFocusEventFully: evt with: self!
<br>>
<br>>
<br>>
<br></commits@source.squeak.org>
                        </blockquote></div>