[squeak-dev] The Trunk: Morphic-mtf.521.mcz

Chris Muller asqueaker at gmail.com
Thu Mar 3 04:46:51 UTC 2011


Ever since this change, I have been getting quite a few accidental
drags when selecting methods, which is distracting because, with Maui
loaded, it instantiates a naked-object view from the dragged method
and I have to close it.

The DragThreshold variable is a good idea, but drag-threshold function
exists for a reason has effectively been nullified by the default
value of 0.

Therefore, I would like to change the default value back to 5, and
Cobalt will have to adjust it to 0..

 - Chris

On Mon, Feb 21, 2011 at 3:31 PM,  <commits at source.squeak.org> wrote:
> Matthew Fulmer uploaded a new version of Morphic to project The Trunk:
> http://source.squeak.org/trunk/Morphic-mtf.521.mcz
>
> ==================== Summary ====================
>
> Name: Morphic-mtf.521
> Author: mtf
> Time: 21 February 2011, 4:29:10.979 pm
> UUID: cf57b307-096f-4311-a02e-b1f53d206e9c
> Ancestors: Morphic-nice.520
>
> created HandMorph >> dragThreshold to hold the default drag threshold
>
> Changed drag users to use this setting rather than make up their own thresholds
>
> Finished a partial change of SystemWindow from simulating its own dragging to using the builtin drag mechanism
>
> Made the default drag threshold zero pixels. it was previously 0, 5, or 10 pixels, depending on the morph
>
> =============== Diff against Morphic-nice.520 ===============
>
> Item was changed:
>  ----- Method: ClickExerciser>>mouseDown: (in category 'event handling') -----
>  mouseDown: evt
>        "Do nothing upon mouse-down except inform the hand to watch for a
>        double-click; wait until an ensuing click:, doubleClick:, or drag:
>        message gets dispatched"
>        Preferences disable: #NewClickTest .
>        evt hand
>                waitForClicksOrDrag: self
>                event: evt
>                selectors: self selectors
> +               threshold: HandMorph dragThreshold!
> -               threshold: 10
> -       !
>
> Item was changed:
>  ----- Method: HaloMorph>>blueButtonDown: (in category 'meta-actions') -----
>  blueButtonDown: event
>        "Transfer the halo to the next likely recipient"
>        target ifNil:[^self delete].
>        event hand obtainHalo: self.
>        positionOffset := event position - (target point: target position in: owner).
>        self isMagicHalo ifTrue:[
>                self isMagicHalo: false.
>                ^self magicAlpha: 1.0].
>        "wait for drags or transfer"
>        event hand
>                waitForClicksOrDrag: self
>                event: event
>                selectors: { #transferHalo:. nil. nil. #dragTarget:. }
> +               threshold: HandMorph dragThreshold!
> -               threshold: 5.!
>
> Item was changed:
>  Morph subclass: #HandMorph
>        instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners mouseClickState mouseOverHandler lastMouseEvent targetOffset damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hardwareCursor hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor keyboardInterpreter'
> +       classVariableNames: 'CompositionWindowManager DoubleClickTime DragThreshold EventStats NewEventRules NormalCursor PasteBuffer ShowEvents'
> -       classVariableNames: 'CompositionWindowManager DoubleClickTime EventStats NewEventRules NormalCursor PasteBuffer ShowEvents'
>        poolDictionaries: 'EventSensorConstants'
>        category: 'Morphic-Kernel'!
>
>  !HandMorph commentStamp: '<historical>' prior: 0!
>  The cursor may be thought of as the HandMorph.  The hand's submorphs hold anything being carried by dragging.
>
>  There is some minimal support for multiple hands in the same world.!
>
> Item was added:
> + ----- Method: HandMorph class>>dragThreshold (in category 'accessing') -----
> + dragThreshold
> +
> +       ^ DragThreshold
> + !
>
> Item was added:
> + ----- Method: HandMorph class>>dragThreshold: (in category 'accessing') -----
> + dragThreshold: pixels
> +
> +       DragThreshold := pixels!
>
> Item was changed:
>  ----- Method: HandMorph class>>initialize (in category 'class initialization') -----
>  initialize
>        "HandMorph initialize"
>
>        PasteBuffer := nil.
>        DoubleClickTime := 350.
> +       DragThreshold := 0.
>        NormalCursor := CursorWithMask normal asCursorForm.
>  !
>
> Item was changed:
>  ----- Method: HandMorph>>waitForClicksOrDrag:event: (in category 'double click support') -----
>  waitForClicksOrDrag: aMorph event: evt
>        "Wait for mouse button and movement events, informing aMorph about events interesting to it via callbacks.
>        This message is typically sent to the Hand by aMorph when it first receives a mouse-down event.
>        The callback methods invoked on aMorph (which are passed a copy of evt) are:
>                #click: sent when the mouse button goes up within doubleClickTime.
>                #doubleClick:   sent when the mouse goes up, down, and up again all within DoubleClickTime.
>                #doubleClickTimeout:  sent when the mouse does not have a doubleClick within DoubleClickTime.
>                #startDrag:     sent when the mouse moves more than 10 pixels from evt's position within DoubleClickTime.
>        Note that mouseMove: and mouseUp: events are not sent to aMorph until it becomes the mouse focus,
>        which is typically done by aMorph in its click:, doubleClick:, or drag: methods."
>
> +       ^self waitForClicksOrDrag: aMorph event: evt selectors: #( #click: #doubleClick: #doubleClickTimeout: #startDrag:) threshold: HandMorph dragThreshold!
> -       ^self waitForClicksOrDrag: aMorph event: evt selectors: #( #click: #doubleClick: #doubleClickTimeout: #startDrag:) threshold: 10
> - !
>
> Item was changed:
>  ----- Method: Morph>>blueButtonDown: (in category 'meta-actions') -----
>  blueButtonDown: anEvent
>        "Special gestures (cmd-mouse on the Macintosh; Alt-mouse on Windows and Unix) allow a mouse-sensitive morph to be moved or bring up a halo for the morph."
>        | h tfm doNotDrag |
>        h := anEvent hand halo.
>        "Prevent wrap around halo transfers originating from throwing the event back in"
>        doNotDrag := false.
>        h ifNotNil:[
>                (h innerTarget == self) ifTrue:[doNotDrag := true].
>                (h innerTarget hasOwner: self) ifTrue:[doNotDrag := true].
>                (self hasOwner: h target) ifTrue:[doNotDrag := true]].
>
>        tfm := (self transformedFrom: nil) inverseTransformation.
>
>        "cmd-drag on flexed morphs works better this way"
>        h := self addHalo: (anEvent transformedBy: tfm).
>        h ifNil: [^ self].
>        doNotDrag ifTrue:[^self].
>        "Initiate drag transition if requested"
>        anEvent hand
>                waitForClicksOrDrag: h
>                event: (anEvent transformedBy: tfm)
>                selectors: { nil. nil. nil. #dragTarget:. }
> +               threshold: HandMorph dragThreshold.
> -               threshold: 5.
>        "Pass focus explicitly here"
>        anEvent hand newMouseFocus: h.!
>
> Item was changed:
>  ----- Method: PasteUpMorph>>mouseDown: (in category 'event handling') -----
>  mouseDown: evt
>        "Handle a mouse down event."
>        | grabbedMorph handHadHalos |
>
>        (Preferences generalizedYellowButtonMenu
>                        and: [evt yellowButtonPressed])
>                ifTrue: [^ self yellowButtonActivity: evt shiftPressed].
>
>        grabbedMorph := self morphToGrab: evt.
>        grabbedMorph ifNotNil:[
>                grabbedMorph isSticky ifTrue:[^self].
>                self isPartsBin ifFalse:[^evt hand grabMorph: grabbedMorph].
>                grabbedMorph := grabbedMorph partRepresented duplicate.
>                grabbedMorph restoreSuspendedEventHandler.
>                (grabbedMorph fullBounds containsPoint: evt position)
>                        ifFalse:[grabbedMorph position: evt position].
>                "Note: grabbedMorph is ownerless after duplicate so use #grabMorph:from: instead"
>                ^ evt hand grabMorph: grabbedMorph from: self].
>
>        (super handlesMouseDown: evt)
>                ifTrue:[^super mouseDown: evt].
>
>        handHadHalos := evt hand halo notNil.
>
>        evt hand removeHalo. "shake off halos"
>        evt hand releaseKeyboardFocus. "shake of keyboard foci"
>
>        self submorphs
>                select:[:each | each hasProperty: #morphHierarchy]
>                thenDo:[:each | each delete].
>
>        Preferences noviceMode
>                ifTrue:[
>                        self submorphs
>                                select:[:each | (each isKindOf: MenuMorph) and:[each stayUp not]]
>                                thenDo:[:each | each delete].
>                ].
>
>        (evt shiftPressed not
>                        and:[ self isWorldMorph not
>                        and:[ self wantsEasySelection not ]])
>        ifTrue:[
>                "explicitly ignore the event if we're not the world and we'll not select,
>                so that we could be picked up if need be"
>                evt wasHandled: false.
>                ^ self.
>        ].
>
>        ( evt shiftPressed or: [ self wantsEasySelection ] ) ifTrue:[
>                "We'll select on drag, let's decide what to do on click"
>                | clickSelector |
>
>                clickSelector := nil.
>
>                evt shiftPressed ifTrue:[
>                        clickSelector := #findWindow:.
>                ]
>                ifFalse:[
>                        self isWorldMorph ifTrue:[
>                                clickSelector := handHadHalos
>                                                                                ifTrue: [ #delayedInvokeWorldMenu: ]
>                                                                                ifFalse: [ #invokeWorldMenu: ]
>                        ]
>                ].
>
>                evt hand
>                                waitForClicksOrDrag: self
>                                event: evt
>                                selectors: { clickSelector. nil. nil. #dragThroughOnDesktop: }
> +                               threshold: HandMorph dragThreshold.
> -                               threshold: 5.
>        ]
>        ifFalse:[
>                "We wont select, just bring world menu if I'm the world"
>                self isWorldMorph ifTrue:[
>                        handHadHalos
>                                ifTrue: [ self delayedInvokeWorldMenu: evt ]
>                                ifFalse: [ self invokeWorldMenu: evt ]
>                ]
>        ].
>  !
>
> Item was changed:
>  ----- Method: PluggableListMorph>>mouseDown: (in category 'events') -----
>  mouseDown: evt
>        | selectors row |
>        evt yellowButtonPressed  "First check for option (menu) click"
>                ifTrue: [^ self yellowButtonActivity: evt shiftPressed].
>        row := self rowAtLocation: evt position.
>        row = 0  ifTrue: [^super mouseDown: evt].
>        "self dragEnabled ifTrue: [aMorph highlightForMouseDown]."
>        selectors := Array
>                with: #click:
>                with: (doubleClickSelector ifNotNil:[#doubleClick:])
>                with: nil
>                with: (self dragEnabled ifTrue:[#startDrag:] ifFalse:[nil]).
> +       evt hand waitForClicksOrDrag: self event: evt selectors: selectors threshold: HandMorph dragThreshold "pixels".!
> -       evt hand waitForClicksOrDrag: self event: evt selectors: selectors threshold: 10 "pixels".!
>
> Item was removed:
> - ----- Method: PluggableSystemWindowWithLabelButton>>mouseDown: (in category 'events') -----
> - mouseDown: evt
> -       | wasInactive |
> -       wasInactive := TopWindow ~~ self.
> -       self valueOfProperty: #clickPoint ifPresentDo:
> -               [:firstClick |
> -               (labelButton containsPoint: evt cursorPoint) ifTrue:
> -                       [^labelButton mouseDown: evt]].
> -       super mouseDown: evt.
> -       (wasInactive
> -        and: [model windowActiveOnFirstClick not
> -        and: [labelButton containsPoint: evt cursorPoint]]) ifTrue:
> -               [^labelButton mouseDown: evt]!
>
> Item was removed:
> - ----- Method: PluggableSystemWindowWithLabelButton>>passivate (in category 'top window') -----
> - passivate
> -       super passivate.
> -       self removeProperty: #clickPoint!
>
> Item was changed:
>  ----- Method: SimpleHierarchicalListMorph>>mouseDown: (in category 'event handling') -----
>  mouseDown: evt
>        | aMorph selectors |
>        aMorph := self itemFromPoint: evt position.
>        (aMorph notNil and:[aMorph inToggleArea: (aMorph point: evt position from: self)])
>                ifTrue:[^self toggleExpandedState: aMorph event: evt].
>        evt yellowButtonPressed  "First check for option (menu) click"
>                ifTrue: [^ self yellowButtonActivity: evt shiftPressed].
>        aMorph ifNil:[^super mouseDown: evt].
>        aMorph highlightForMouseDown.
>        selectors := Array
>                with: #click:
>                with: nil
>                with: nil
>                with: (self dragEnabled ifTrue:[#startDrag:] ifFalse:[nil]).
> +       evt hand waitForClicksOrDrag: self event: evt selectors: selectors threshold: HandMorph dragThreshold "pixels".!
> -       evt hand waitForClicksOrDrag: self event: evt selectors: selectors threshold: 10 "pixels".!
>
> Item was changed:
>  ----- Method: SystemWindow>>handlesMouseDown: (in category 'events') -----
>  handlesMouseDown: evt
>        "If I am not the topWindow, then I will only respond to dragging by the title bar.
>        Any other click will only bring me to the top"
>
> -       (self labelRect containsPoint: evt cursorPoint)
> -               ifTrue: [^ true].
>        ^ self activeOnlyOnTop and: [self ~~ TopWindow]!
>
> Item was changed:
>  ----- Method: SystemWindow>>mouseDown: (in category 'events') -----
>  mouseDown: evt
>
> -       self setProperty: #clickPoint toValue: evt cursorPoint.
>        TopWindow == self ifFalse:
>                [evt hand releaseKeyboardFocus.
>                self activate].
> +
> +       "the window was locked, thus we got the event. re-send it now that the window is unlocked again"
> +       evt wasHandled: false.
> +       model windowActiveOnFirstClick
> +               ifTrue: [self processEvent: evt] "re-dispatch to any submorphs"
> +               ifFalse: [label processEvent: evt]. "dispatch to label so dragging works"
> +       evt wasHandled: true.
> -       model windowActiveOnFirstClick ifTrue:
> -               ["Normally window keeps control of first click.
> -               Need explicit transmission for first-click activity."
> -               submorphs do: [:m | (m containsPoint: evt cursorPoint) ifTrue: [m mouseDown: evt]]]
> -
>  !
>
> Item was removed:
> - ----- Method: SystemWindow>>mouseMove: (in category 'events') -----
> - mouseMove: evt
> -       "Handle a mouse-move event"
> -
> -       | cp |
> -       cp := evt cursorPoint.
> -       self valueOfProperty: #clickPoint ifPresentDo:
> -               [:firstClick |
> -               ((self labelRect containsPoint: firstClick) and: [(cp dist: firstClick) > 3]) ifTrue:
> -               ["If this is a drag that started in the title bar, then pick me up"
> -               ^ self isSticky ifFalse:
> -                       [self fastFramingOn
> -                               ifTrue: [self doFastFrameDrag: firstClick]
> -                               ifFalse: [evt hand grabMorph: self topRendererOrSelf]]]].
> -       model windowActiveOnFirstClick ifTrue:
> -               ["Normally window takes control on first click.
> -               Need explicit transmission for first-click activity."
> -               submorphs do: [:m | (m containsPoint: cp) ifTrue: [m mouseMove: evt]]]!
>
> Item was changed:
>  ----- Method: SystemWindow>>startDragFromLabel: (in category 'events') -----
>  startDragFromLabel: evt
>        "When label events are active, we need to pass dragging to the window explicitely
>         The window only recognizes a drag with an offset of more than 3 pixels"
>
> +       self isSticky ifTrue: [^ self].
> +       self fastFramingOn
> +               ifTrue: [self doFastFrameDrag: evt cursorPoint]
> +               ifFalse: [evt hand grabMorph: self topRendererOrSelf]
> + !
> -       self setProperty: #clickPoint toValue: evt cursorPoint - 4.
> -       self mouseMove: evt.!
>
>
>



More information about the Squeak-dev mailing list