[squeak-dev] The Trunk: Morphic-cmm.1454.mcz

karl ramberg karlramberg at gmail.com
Sun Sep 2 10:00:35 UTC 2018


This change breaks blue clicks for rotated morphs in  PasteUpMorph>>
tryInvokeHalo:
It does not bring up a halo anymore.
The variable stack is just #().

stack := (self morphsAt: aUserInputEvent position unlocked: true) select:
               [ : each | each wantsHaloFromClick or: [ each
handlesMouseDown: aUserInputEvent ] ].

Best,
Karl

On Sat, Jun 23, 2018 at 11:25 PM <commits at source.squeak.org> wrote:

> Chris Muller uploaded a new version of Morphic to project The Trunk:
> http://source.squeak.org/trunk/Morphic-cmm.1454.mcz
>
> ==================== Summary ====================
>
> Name: Morphic-cmm.1454
> Author: cmm
> Time: 23 June 2018, 4:23:51.324266 pm
> UUID: 7bd5a7a9-4493-4cf4-849f-be6d8f8bb991
> Ancestors: Morphic-hjh.1453
>
> - Fix ability of border styles of veryDeepCopied Morphs to be
> independently set.
> - Fix dispatch regression for Morphs that leave world based on mouseLeave.
> - Fix three UI-gesture inconsistencies related to invoking halos,
> depending on the position of existing halos:
>         1) halo activation was sometimes on mouseUp instead of mouseDown,
>         2) blue move/resize gestures sometimes operated on the background
> window instead of the foreground, and,
>         3) even with the (Shift) modifier key, it was sometimes selecting
> the outermost instead of the innermost.
> All three are fixed while reverting the increased dependence on
> #transferHalo:, putting us closer to considerations like multiple,
> independent, and custom halos.
> - Restore splitter bar thicknesses from 2 back to 4 pixels.
> - Restore blue-click functionality of splitters when Smart Splitters is
> off.
> - Let SystemWindows dismiss halos with any button, mouse or keyboard.
>
> =============== Diff against Morphic-hjh.1453 ===============
>
> Item was added:
> + ----- Method: ComplexBorder>>veryDeepInner: (in category 'copying') -----
> + veryDeepInner: aDeepCopier
> +       super veryDeepInner: aDeepCopier.
> +       style := style veryDeepCopyWith: aDeepCopier.
> +       colors := colors veryDeepCopyWith: aDeepCopier.
> +       lineStyles := lineStyles veryDeepCopyWith: aDeepCopier.!
>
> Item was changed:
>   ----- Method: Editor class>>dumbbellCursor (in category 'preferences')
> -----
>   dumbbellCursor
> +       <preference: 'Dumbbell Text Cursor'
> -       <preference: 'Dumbbell-shaped Text Cursor'
>                 category: 'Morphic'
> +               description: 'When enabled, the text cursor assumes the
> shape of a dumbbell, otherwise a vertical bar.'
> -               description: 'When true, the text cursor assumes the shape
> of a dumbbell, otherwise a vertical bar..'
>                 type: #Boolean>
>         ^ DumbbellCursor ifNil: [ false ]!
>
> Item was changed:
>   ----- Method: MorphicEventDispatcher>>dispatchFocusEventAllOver:with:
> (in category 'focus events') -----
>   dispatchFocusEventAllOver: evt with: focusMorph
>         "Like a full event dispatch BUT adds regular dispatch if the focus
> morph did nothing with the event. This is useful for letting the
> focusMorph's siblings handle the events instead. Take halo invocation as an
> example. See senders of me."
>
>         | result hand mouseFocus |
>         result := self dispatchFocusEventFully: evt with: focusMorph.
>
>         result == #rejected ifTrue: [^ result].
>         result wasIgnored ifTrue: [^ result].
>         result wasHandled ifTrue: [^ result].
> +       focusMorph world ifNil: [ ^ result ].
>
>         hand := evt hand.
>         mouseFocus := hand mouseFocus.
>
>         [
>                 "Avoid re-dispatching the event to the focus morph. See
> Morph >> #rejectsEvent:."
>                 focusMorph lock.
>
>                 "Handle side effect for mouse-enter and mouse-leave
> events."
>                 self flag: #hacky. "mt: Maybe we find a better way to
> synthesize enter/leave events in the future."
>                 hand newMouseFocus: nil.
>                 hand mouseOverHandler processMouseOver: hand lastEvent.
>
>                 "Give the morph's world a chance to normally dispatch the
> event."
> +               ^ focusMorph world ifNotNil: [ : world | world
> processEvent: evt using: self]
> -               ^ focusMorph world processEvent: evt using: self
>         ] ensure: [
>                 focusMorph unlock.
>                 evt hand newMouseFocus: mouseFocus].!
>
> Item was changed:
>   ----- Method: PasteUpMorph>>tryInvokeHalo: (in category
> 'events-processing') -----
> + tryInvokeHalo: aUserInputEvent
> +       "Invoke halos around the top-most world container at
> aUserInputEvent's #position.  If it was already halo'd, zero-in on its next
> inward component morph at that position.  Holding Shift during the click
> reverses this traversal order."
> +       | stack innermost haloTarget |
> +       Preferences noviceMode ifTrue: [ ^ self ].
> +       Morph haloForAll ifFalse: [ ^ self ].
> +       "the stack is the top-most morph to bottom-most."
> +       stack := (self morphsAt: aUserInputEvent position unlocked: true)
> select:
> +               [ : each | each wantsHaloFromClick or: [ each
> handlesMouseDown: aUserInputEvent ] ].
> +       innermost := aUserInputEvent hand halo
> +               ifNil: [ stack first ]
> +               ifNotNil:
> +                       [ : existingHalo | stack allButFirst "existingHalo
> is first on the stack, not a target"
> +                               detect: [ : each | each owner == self ]
> +                               ifFound:
> +                                       [ : worldContainer | "Is
> existingHalo's target part of the same worldContainer as the morph clicked?"
> +                                       (existingHalo target withAllOwners
> includes: worldContainer)
> +                                               ifTrue: [ "same hierarchy,
> let #transferHalo: continue to handle it for now."  ^ self ]
> +                                               ifFalse:
> +                                                       [ "different
> hierarchy, remove + add."
> +                                                       aUserInputEvent
> hand removeHalo.
> +                                                       aUserInputEvent
> shiftPressed
> +                                                               ifTrue: [
> stack second "first is still the just removed halo" ]
> +                                                               ifFalse: [
> worldContainer ] ] ]
> +                               ifNone: [ "Shouldn't get here, but
> defensive code."  self ] ].
> +       "If modifier key is pressed, start at innermost (the target),
> otherwise the outermost (direct child of the world (self))."
> +       haloTarget  := aUserInputEvent shiftPressed
> +               ifTrue: [ innermost ]
> +               ifFalse: [ innermost == self ifTrue: [innermost] ifFalse:
> [(innermost withAllOwners copyWithout: self) last] ].
> +       haloTarget wantsHaloFromClick ifFalse: [ "haloTarget has its own
> event handler." ^ self ].
> +       "Now that we have the haloTarget, show the halo."
> +       aUserInputEvent hand
> +               newMouseFocus: haloTarget
> +               event: aUserInputEvent.
> +       haloTarget invokeHaloOrMove: aUserInputEvent.
> +       "aUserInputEvent has been consumed, don't let it cause any further
> side-effects."
> +       aUserInputEvent ignore!
> - tryInvokeHalo: anEvent
> -
> -       | innerMost target |
> -       anEvent hand halo ifNotNil: [^ self "No invocation needed. Halo
> will handle transfer itself."].
> -       Preferences noviceMode ifTrue: [^ self "No halo in novice mode."].
> -       Morph haloForAll ifFalse: [^ self].
> -
> -       innerMost := (self morphsAt: anEvent position unlocked: true)
> first.
> -
> -       "1) Try to use innermost morph but skip all the ones that do not
> want to show a halo along the owner chain."
> -       target := innerMost.
> -       [target isNil or: [target wantsHaloFromClick]]
> -               whileFalse: [target := target owner].
> -       target ifNil: [^ self].
> -
> -       "2) Without a modifier, which is normal, find the outermost
> container for that inner morph."
> -       (innerMost == self or: [anEvent shiftPressed]) ifFalse: [
> -               | previousTargets |
> -               previousTargets := OrderedCollection new.
> -               [target notNil and: [target owner ~~ self]] whileTrue: [
> -                       previousTargets add: target.
> -                       target := target owner].
> -               target ifNil: [^ self].
> -               [previousTargets isEmpty or: [target wantsHaloFromClick]]
> whileFalse: [
> -                       target := previousTargets removeLast].
> -               target wantsHaloFromClick ifFalse: [^ self]].
> -
> -       "3) Now that we have the target, show the halo. Abort event
> dispatching, too, to avoid confusion."
> -       anEvent hand newMouseFocus: target event: anEvent.
> -       target invokeHaloOrMove: anEvent.
> -       anEvent ignore.!
>
> Item was changed:
>   ----- Method: ProportionalSplitterMorph>>balanceOffsets (in category
> 'layout') -----
>   balanceOffsets
>
> +       | fdx fdy |
> +
>         (self hasProperty: #fullDelta) ifFalse: [^ self].
>
> +       fdx := (self valueOfProperty: #fullDelta) x.
> +       fdy := (self valueOfProperty: #fullDelta) y.
> +
>         self layoutFrame hasFixedHeight ifTrue: [
>                 | otop obot ctop cbot topf |
>
>                 otop := (owner submorphs detect: [:m |
>                                         m layoutFrame topFraction isZero]
> ifNone: [^ self]) in: [:tm |
>                                                 tm top - (tm layoutFrame
> topOffset ifNil: [0])].
>
>                 obot := (owner submorphs detect: [:m |
>                                         m layoutFrame bottomFraction = 1]
> ifNone: [^ self]) in: [:tm |
>                                                 tm bottom - (tm
> layoutFrame bottomOffset ifNil: [0])].
>
>                 ctop := (self layoutFrame topFraction * (obot - otop))
> rounded
>                                         + otop + (self layoutFrame
> topOffset ifNil: [0]).
>                 cbot := (self layoutFrame bottomFraction * (obot - otop))
> rounded
>                                         + otop + (self layoutFrame
> bottomOffset ifNil: [0]).
>
>                 topf := self layoutFrame topFraction.
>                 self layoutFrame topFraction:  ((ctop + cbot) * 0.5 -
> otop) / (obot - otop) asFloat.
>                 self layoutFrame bottomFraction: self layoutFrame
> topFraction.
> +               self layoutFrame topOffset: self layoutFrame topOffset -
> fdy.
> +               self layoutFrame bottomOffset: self layoutFrame
> bottomOffset - fdy.
> -               self layoutFrame topOffset: ctop -
> -                       (self layoutFrame topFraction * (obot - otop) +
> otop) truncated.
> -               self layoutFrame bottomOffset: cbot -
> -                       (self layoutFrame bottomFraction * (obot - otop) +
> otop) rounded.
>
>                 (leftOrTop copy union: rightOrBottom) do: [:m |
>                         (m layoutFrame topFraction closeTo: topf) ifTrue: [
>                                 m layoutFrame topFraction: self
> layoutFrame topFraction.
> +                               m layoutFrame topOffset: m layoutFrame
> topOffset - fdy].
> -                               m layoutFrame topOffset:
> -                                       m layoutFrame topOffset - (self
> valueOfProperty: #fullDelta) y].
>                         (m layoutFrame bottomFraction closeTo: topf)
> ifTrue: [
>                                 m layoutFrame bottomFraction: self
> layoutFrame topFraction.
> +                               m layoutFrame bottomOffset: m layoutFrame
> bottomOffset - fdy]]] .
> -                               m layoutFrame bottomOffset:
> -                                       m layoutFrame bottomOffset - (self
> valueOfProperty: #fullDelta) y.]]] .
>
>         self layoutFrame hasFixedWidth ifTrue: [
>                 | oleft oright cleft cright leftf |
>
>                 oleft := (owner submorphs detect: [:m |
>                         m layoutFrame leftFraction isZero] ifNone: [^
> self]) in: [:tm |
>                                 tm left - (tm layoutFrame leftOffset
> ifNil: [0])].
>
>                 oright := (owner submorphs detect: [:m |
>                         m layoutFrame rightFraction = 1] ifNone: [^ self])
> in: [:tm |
>                                 tm right - (tm layoutFrame rightOffset
> ifNil: [0])].
>
>                 cleft := (self layoutFrame leftFraction * (oright -
> oleft)) rounded
>                                         + oleft + (self layoutFrame
> leftOffset ifNil: [0]).
>                 cright := (self layoutFrame rightFraction * (oright -
> oleft)) rounded
>                                         + oleft + (self layoutFrame
> rightOffset ifNil: [0]).
>
>                 leftf := self layoutFrame leftFraction.
>                 self layoutFrame leftFraction: ((cleft + cright) * 0.5 -
> oleft) / (oright - oleft) asFloat.
>                 self layoutFrame rightFraction: self layoutFrame
> leftFraction.
>
> -               self layoutFrame leftOffset: cleft -
> -                       (self layoutFrame leftFraction * (oright - oleft)
> + oleft) truncated.
> -               self layoutFrame rightOffset: cright -
> -                       (self layoutFrame rightFraction * (oright - oleft)
> + oleft) rounded.
>
> +               self layoutFrame leftOffset: self layoutFrame leftOffset -
> fdx.
> +               self layoutFrame rightOffset: self layoutFrame rightOffset
> - fdx.
> +
>                 (leftOrTop copy union: rightOrBottom) do: [:m |
>                         (m layoutFrame leftFraction closeTo: leftf)
> ifTrue: [
>                                 m layoutFrame leftFraction: self
> layoutFrame leftFraction.
> +                               m layoutFrame leftOffset: m layoutFrame
> leftOffset - fdx].
> -                               m layoutFrame leftOffset:
> -                                       m layoutFrame leftOffset - (self
> valueOfProperty: #fullDelta) x].
>                         (m layoutFrame rightFraction closeTo: leftf)
> ifTrue: [
>                                 m layoutFrame rightFraction: self
> layoutFrame leftFraction.
> +                               m layoutFrame rightOffset:      m
> layoutFrame rightOffset - fdx.]]] .
> +
> -                               m layoutFrame rightOffset:
> -                                       m layoutFrame rightOffset - (self
> valueOfProperty: #fullDelta) x.]]] .
> -
>         self removeProperty: #fullDelta.
>         owner layoutChanged
>   !
>
> Item was added:
> + ----- Method: ProportionalSplitterMorph>>stopStepping (in category
> 'events') -----
> + stopStepping
> +       super stopStepping.
> +       (self class smartVerticalSplitters or: [ self class
> smartHorizontalSplitters ]) ifFalse: [ self balanceOffsets ]!
>
> Item was changed:
>   ----- Method: SimpleHaloMorph>>transferHalo: (in category 'pop up') -----
>   transferHalo: event
> +       "Transfer the halo to the next likely recipient"
> -       "Transfer the halo to the next likely recipient. Switch between
> siblings if overlapping."
>
> -       (self target world morphsAt: event position) allButFirst "... the
> halo itself"
> -               detect: [:morph |
> -                       "Sibling found?"
> -                       (morph owner == self target owner
> -                               and: [morph ~~ self target])
> -                                       ifTrue: [
> -                                               ^ morph invokeHaloOrMove:
> event].
> -                       "No sibling possible anymore?"
> -                       morph == self target].
> -
>         self target
>                 transferHalo: (event transformedBy: (self target
> transformedFrom: self))
>                 from: self target.!
>
> Item was changed:
>   ----- Method: SystemWindow>>filterEvent:for: (in category 'events') -----
>   filterEvent: aKeyboardEvent for: anObject
>         "Provide keyboard shortcuts."
> +
> -
>         aKeyboardEvent isKeystroke
>                 ifFalse: [^ aKeyboardEvent].
> +
> +       aKeyboardEvent hand halo ifNotNil: [ : halo | halo target
> isSystemWindow ifTrue: [ aKeyboardEvent hand removeHalo ] ].
>
>         aKeyboardEvent commandKeyPressed ifTrue: [
> +               aKeyboardEvent keyCharacter caseOf: {
> -               aKeyboardEvent keyCharacter caseOf: {
>                         [$\] -> [self class sendTopWindowToBack].
>                         [Character escape] -> [self class deleteTopWindow].
>                         [$/] -> [self class bringWindowUnderHandToFront].
>                 } otherwise: [^ aKeyboardEvent "no hit"].
>                 ^ aKeyboardEvent ignore "hit!!"].
>
>         aKeyboardEvent controlKeyPressed ifTrue: [
>                 aKeyboardEvent keyCharacter caseOf: {
>                         [Character escape] -> [self world findWindow:
> aKeyboardEvent].
>                 } otherwise: [^ aKeyboardEvent "no hit"].
>                 ^ aKeyboardEvent ignore "hit!!"].
>
>         ^ aKeyboardEvent "no hit"!
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20180902/3d315a4f/attachment.html>


More information about the Squeak-dev mailing list