"mouseOverHandler" is *absolutely* depreciated everywhere, iOS, Android AND
Windows 8 ... tablet useforms dominate Desktop useforms more and more.

just my 2ct.
Am 22.02.2012 08:32 schrieb "Stéphane Ducasse" <stephane.duca...@inria.fr>:

> >
> > People might mistakenly think that we wanna change things solely for
> > the sake of change. But it is not like that.
> > We need these changes , need to fix our infrastructure, because
> > without solid basement you cannot build anything good.
> >
> Thanks Igor. Let us take a concrete example.
> I'm convinced that having support for multitouch event/ genie and others
> works (for iPad = $$$$) is important.
> If you happen to know how we can get this code plug and play let me know
> :) but I guess that you will not easily.
>
> But really read it! Really read it it is worth the 2 min you can people vs
> the days giro and me are spending there (and this is not about just coding
> but understanding the situation and building a better one).
> Because we are far from doing stuff for research. We are not doing
> research in interaction design!
>
> I could show you some of the compiler code too.
>
>
> Stef
>
>
>
> HandMorph>>handleEvent: anEvent
>        | evt ofs |
>        owner ifNil:[^self].
>        evt := anEvent.
>        self logEventStats: evt.
>
>        evt isMouse ifTrue:[
>                 "just for record, to be used by capture block"
>                lastMouseEvent := evt].
>
>        captureBlock ifNotNil: [ ^ captureBlock value: anEvent ].
>        evt isMouseOver ifTrue:[^self sendMouseEvent: evt].
>
>        self showDebugEvent: evt.
>
>        "Notify listeners"
>        self sendListenEvent: evt to: self eventListeners.
>
>        evt isWindowEvent ifTrue: [
>                self sendEvent: evt focus: nil.
>                ^self mouseOverHandler processMouseOver: lastMouseEvent].
>
>
>        evt isKeyboard ifTrue:[
>                self sendListenEvent: evt to: self keyboardListeners.
>                self sendKeyboardEvent: evt.
>                ^self mouseOverHandler processMouseOver: lastMouseEvent].
>
>        evt isDropEvent ifTrue:[
>                self sendEvent: evt focus: nil.
>                ^self mouseOverHandler processMouseOver: lastMouseEvent].
>
>        evt isMouse ifTrue:[
>                self sendListenEvent: evt to: self mouseListeners.
>                lastMouseEvent := evt].
>
>        "Check for pending drag or double click operations."
>        mouseClickState ifNotNil:[
>                (mouseClickState handleEvent: evt from: self) ifFalse:[
>                        "Possibly dispatched #click: or something and will
> not re-establish otherwise"
>                        ^self mouseOverHandler processMouseOver:
> lastMouseEvent]].
>
>        evt isMove ifTrue:[
>                self position: evt position.
>                self sendMouseEvent: evt.
>        ] ifFalse:[
>                "Issue a synthetic move event if we're not at the position
> of the event"
>                (evt position = self position) ifFalse:[self moveToEvent:
> evt].
>                "Drop submorphs on button events"
>                (self hasSubmorphs)
>                        ifTrue:[self dropMorphs: evt]
>                        ifFalse:[self sendMouseEvent: evt].
>        ].
>        self showMouseFocusEvent: evt.
>        self mouseOverHandler processMouseOver: lastMouseEvent.
>
>
> HandMorph>>processEvents
>        "Process user input events from the local input devices."
>
>        | evt evtBuf type hadAny |
>        ActiveEvent ifNotNil:
>                        ["Meaning that we were invoked from within an event
> response.
>                Make sure z-order is up to date"
>
>                        self mouseOverHandler processMouseOver:
> lastMouseEvent].
>        hadAny := false.
>        [(evtBuf := Sensor nextEvent) isNil] whileFalse:
>                        [evt := nil.    "for unknown event types"
>                        type := evtBuf first.
>                        type = EventTypeMouse ifTrue: [recentModifiers :=
> evtBuf sixth. evt := self generateMouseEvent: evtBuf].
>                        type = EventTypeKeyboard
>                                ifTrue: [recentModifiers := evtBuf fifth.
> evt := self generateKeyboardEvent: evtBuf].
>                        type = EventTypeDragDropFiles
>                                ifTrue: [evt := self
> generateDropFilesEvent: evtBuf].
>                        type = EventTypeWindow
>                                ifTrue:[evt := self generateWindowEvent:
> evtBuf].
>                        "All other events are ignored"
>                        (type ~= EventTypeDragDropFiles and: [evt isNil])
> ifTrue: [^self].
>                        evt isNil
>                                ifFalse:
>                                        ["Finally, handle it"
>
>                                        self handleEvent: evt.
>                                        hadAny := true.
>
>                                        "For better user feedback, return
> immediately after a mouse event has been processed."
>                                        (evt isMouse and: [evt isMouseWheel
> not]) ifTrue: [^self]]].
>        "note: if we come here we didn't have any mouse events"
>        mouseClickState notNil
>                ifTrue:
>                        ["No mouse events during this cycle. Make sure
> click states time out accordingly"
>
>                        mouseClickState handleEvent: lastMouseEvent
> asMouseMove from: self].
>        hadAny
>                ifFalse:
>                        ["No pending events. Make sure z-order is up to
> date"
>
>                        self mouseOverHandler processMouseOver:
> lastMouseEvent]
>
>
> HandMorph>>generateMouseEvent: evtBuf
>        "Generate the appropriate mouse event for the given raw event
> buffer"
>
>        | position buttons modifiers type trail stamp oldButtons evtChanged
> |
>        evtBuf first = lastEventBuffer first
>                ifTrue:
>                        ["Workaround for Mac VM bug, *always* generating 3
> events on clicks"
>
>                        evtChanged := false.
>                        3 to: evtBuf size
>                                do: [:i | (lastEventBuffer at: i) = (evtBuf
> at: i) ifFalse: [evtChanged := true]].
>                        evtChanged ifFalse: [^nil]].
>        stamp := evtBuf second.
>        stamp = 0 ifTrue: [stamp := Time millisecondClockValue].
>        position := evtBuf third @ evtBuf fourth.
>        buttons := evtBuf fifth.
>        modifiers := evtBuf sixth.
>        type := buttons = 0
>                ifTrue:
>                        [lastEventBuffer fifth = 0 ifTrue: [#mouseMove]
> ifFalse: [#mouseUp]]
>                ifFalse:
>                        [lastEventBuffer fifth = 0
>                                                ifTrue: [#mouseDown]
>                                                ifFalse: [#mouseMove]].
>        buttons := buttons bitOr: (modifiers bitShift: 3).
>        oldButtons := lastEventBuffer fifth
>                                bitOr: (lastEventBuffer sixth bitShift: 3).
>        lastEventBuffer := evtBuf.
>        type == #mouseMove
>                ifTrue:
>                        [trail := self mouseTrailFrom: evtBuf.
>                        ^MouseMoveEvent basicNew
>                                setType: type
>                                startPoint: (self position)
>                                endPoint: trail last
>                                trail: trail
>                                buttons: buttons
>                                hand: self
>                                stamp: stamp].
>        ^MouseButtonEvent basicNew
>                setType: type
>                position: position
>                which: (oldButtons bitXor: buttons)
>                buttons: buttons
>                hand: self
>                stamp: stamp
>

Reply via email to