The Inbox: Morphic-cmm.1617.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
2 messages Options
Reply | Threaded
Open this post in threaded view
|

The Inbox: Morphic-cmm.1617.mcz

commits-2
Chris Muller uploaded a new version of Morphic to project The Inbox:
http://source.squeak.org/inbox/Morphic-cmm.1617.mcz

==================== Summary ====================

Name: Morphic-cmm.1617
Author: cmm
Time: 10 January 2020, 7:32:31.635312 pm
UUID: ce0033f9-62f5-4c12-9b75-24d613d56c50
Ancestors: Morphic-tpr.1616

- Fix inescapable modal dialog.
- Fix truncation of the first line of PluggableListMorphs when a font larger than the default is used.

=============== Diff against Morphic-tpr.1616 ===============

Item was added:
+ ----- Method: AlternatePluggableListMorphOfMany>>mouseLeaveDragging: (in category 'event handling') -----
+ mouseLeaveDragging: anEvent
+ "Dragging means changing the list's multi-selection state. Thus, there is no support for drag-and-drop of elements within a selection."
+
+ self hoverRow: nil.
+ self resetPotentialDropRow.!

Item was changed:
  ----- Method: DialogWindow>>getUserResponse (in category 'running') -----
  getUserResponse
 
  | hand world |
  self message ifEmpty: [messageMorph delete]. "Do not waste space."
  self paneMorph submorphs
  ifEmpty: ["Do not waste space and avoid strange button-row wraps."
  self paneMorph delete.
  self buttonRowMorph wrapDirection: #none].
 
  hand := self currentHand.
  world := self currentWorld.
 
  self fullBounds.
  self moveToPreferredPosition.
  self openInWorld: world.
 
  hand showTemporaryCursor: nil. "Since we are out of context, reset the cursor."
 
  hand keyboardFocus in: [:priorKeyboardFocus |
  hand mouseFocus in: [:priorMouseFocus |
  self exclusive ifTrue: [hand newMouseFocus: self].
  hand newKeyboardFocus: self.
 
  [[self isInWorld] whileTrue: [world doOneSubCycle]]
  ifCurtailed: [self cancelDialog].
 
  hand newKeyboardFocus: priorKeyboardFocus.
+ hand releaseMouseFocus]].
- hand newMouseFocus: priorMouseFocus]].
 
  ^ result!

Item was changed:
  ----- Method: FontChooserTool>>selectedPointSizeIndex: (in category 'point size') -----
  selectedPointSizeIndex: anIndex
 
  anIndex = 0 ifTrue: [^self].
  pointSize := (self pointSizeList at: anIndex) withBlanksTrimmed asNumber.
+ self changed: #selectedPointSizeIndex.
  self changed: #pointSizeList.
  self changed: #contents.!

Item was changed:
  Morph subclass: #HandMorph
+ instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners eventCaptureFilters mouseCaptureFilters keyboardCaptureFilters mouseClickState mouseOverHandler mouseWheelState lastMouseEvent targetOffset damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hardwareCursor hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor keyboardInterpreter'
+ classVariableNames: 'CompositionWindowManager DoubleClickTime DragThreshold EventStats NewEventRules NormalCursor PasteBuffer SendMouseWheelToKeyboardFocus ShowEvents SynthesizeMouseWheelEvents'
- instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners eventCaptureFilters mouseCaptureFilters keyboardCaptureFilters mouseClickState mouseOverHandler targetOffset lastMouseEvent damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hardwareCursor hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor keyboardInterpreter'
- classVariableNames: 'CompositionWindowManager DoubleClickTime DragThreshold EventStats MinimalWheelDelta NewEventRules NormalCursor PasteBuffer SendMouseWheelToKeyboardFocus ShowEvents SynthesizeMouseWheelEvents'
  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 removed:
- ----- Method: HandMorph class>>minimumWheelDelta (in category 'preferences') -----
- minimumWheelDelta
- <preference: 'Minimal Mouse Wheel Scroll Delta'
- categoryList: #(Morphic mouse)
- description: 'Answer the minimal scroll increment taken into account
- Defaults to 120, corresponding to a single mouse wheel notch.
- Use a lower value (20) if wanting smoother scrolling with trackpads.'
- type: #Number>
- ^MinimalWheelDelta ifNil: [120].!

Item was removed:
- ----- Method: HandMorph class>>minimumWheelDelta: (in category 'preferences') -----
- minimumWheelDelta: anInteger
- MinimalWheelDelta := anInteger ifNotNil: [anInteger clampLow: 20 high: 120]!

Item was changed:
  ----- Method: HandMorph>>generateMouseWheelEvent: (in category 'private events') -----
  generateMouseWheelEvent: evtBuf
  "Generate the appropriate mouse wheel event for the given raw event buffer"
 
+ | buttons modifiers deltaX deltaY stamp |
- | buttons modifiers deltaX deltaY stamp nextEvent |
  stamp := evtBuf second.
  stamp = 0 ifTrue: [stamp := Time eventMillisecondClock].
  deltaX := evtBuf third.
  deltaY := evtBuf fourth.
+ modifiers := evtBuf fifth.
+ buttons := (modifiers bitShift: 3) bitOr: (lastMouseEvent buttons bitAnd: 7).
- buttons := evtBuf fifth.
- modifiers := evtBuf sixth.
- [(deltaX abs + deltaY abs < self class minimumWheelDelta)
- and: [(nextEvent := Sensor peekEvent) notNil
- and: [nextEvent first = evtBuf first
- and: [nextEvent fifth = evtBuf fifth
- and: [nextEvent sixth = evtBuf sixth]
- and: [nextEvent third isZero = evtBuf third isZero "both horizontal or vertical"]]]]]
- whileTrue:
- ["nextEvent is similar.  Remove it from the queue, and check the next."
- nextEvent := Sensor nextEvent.
- deltaX := deltaX + nextEvent third.
- deltaY := deltaY + nextEvent fourth].
  ^ MouseWheelEvent new
  setType: #mouseWheel
  position: self position
  delta: deltaX@deltaY
+ direction: 2r0000
  buttons: buttons
  hand: self
  stamp: stamp!

Item was changed:
  ----- Method: HandMorph>>handleEvent: (in category 'events-processing') -----
  handleEvent: unfilteredEvent
 
  | filteredEvent |
  owner ifNil: [^ unfilteredEvent  "not necessary but good style -- see Morph >> #handleEvent:"].
 
  self logEvent: unfilteredEvent.
 
  "Mouse-over events occur really, really, really often. They are kind of the heart beat of the Morphic UI process."
  unfilteredEvent isMouseOver ifTrue: [^ self sendMouseEvent: unfilteredEvent].
 
  self showEvent: unfilteredEvent.
  self sendListenEvents: unfilteredEvent.
 
  filteredEvent := self sendFilterEventCapture: unfilteredEvent for: nil.
  "filteredEvent := unfilteredEvent" " <-- use this to disable global capture filters"
 
  filteredEvent wasIgnored ifTrue: [
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent].
 
  filteredEvent isWindowEvent ifTrue: [
  self sendEvent: filteredEvent focus: nil.
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent].
 
  filteredEvent isKeyboard ifTrue:[
  self sendKeyboardEvent: filteredEvent.
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent].
 
  filteredEvent isDropEvent ifTrue:[
  self sendEvent: filteredEvent focus: nil.
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent].
 
  filteredEvent isMouse ifFalse: [
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent].
 
  " ********** MOUSE EVENT *********** "
 
  lastMouseEvent := filteredEvent.
 
  "Check for pending drag or double click operations."
  mouseClickState ifNotNil:[
  (mouseClickState handleEvent: filteredEvent from: self) ifFalse:[
  "Possibly dispatched #click: or something and will not re-establish otherwise"
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent]].
 
  filteredEvent isMouseWheel ifTrue: [
+ mouseWheelState ifNil: [mouseWheelState := MouseWheelState new].
+ mouseWheelState handleEvent: filteredEvent from: self.
- self class sendMouseWheelToKeyboardFocus
- ifFalse: [self sendMouseEvent: filteredEvent]
- ifTrue: [self sendEvent: filteredEvent focus: self keyboardFocus clear: [self keyboardFocus: nil]].
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent].
 
  filteredEvent isMove ifTrue:[
  self position: filteredEvent position.
  self sendMouseEvent: filteredEvent.
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent].
 
  "Issue a synthetic move event if we're not at the position of the event"
  filteredEvent position = self position
  ifFalse: [self moveToEvent: filteredEvent].
 
  "Drop submorphs on button events"
  self hasSubmorphs
  ifTrue:[self dropMorphs: filteredEvent]
  ifFalse:[self sendMouseEvent: filteredEvent].
 
  self mouseOverHandler processMouseOver: lastMouseEvent.
  ^ filteredEvent "not necessary but good style -- see Morph >> #handleEvent:" !

Item was removed:
- ----- Method: MouseWheelEvent>>setDirection (in category 'initialization') -----
- setDirection
- delta x > 0 ifTrue: [self setWheelRight].
- delta x < 0 ifTrue: [self setWheelLeft].
-
- delta y > 0 ifTrue: [self setWheelUp].
- delta y < 0 ifTrue: [self setWheelDown].!

Item was removed:
- ----- Method: MouseWheelEvent>>setType:position:delta:buttons:hand:stamp: (in category 'private') -----
- setType: evtType position: evtPos delta: evtDelta buttons: evtButtons hand: evtHand stamp: stamp
- type := evtType.
- position := evtPos.
- buttons := evtButtons.
- source := evtHand.
- wasHandled := false.
- direction := 2r0000.
- delta := evtDelta.
- timeStamp := stamp.
- self setDirection!

Item was added:
+ Object subclass: #MouseWheelState
+ instanceVariableNames: 'currentDelta'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Morphic-Events'!

Item was added:
+ ----- Method: MouseWheelState>>handleEvent:from: (in category 'event processing') -----
+ handleEvent: aMouseWheelEvent from: aHand
+ "Every 120 units, raise the wheel flags for convenient mouse wheel programming. We choose not to send multiple mouse-wheel events for multiples of 120 because applications can always react to the actual delta values if they want to do more scrolling or zooming."
+
+ | sign |
+ currentDelta := currentDelta + aMouseWheelEvent wheelDelta.
+
+ sign := currentDelta sign.
+ currentDelta := currentDelta abs.
+
+ (currentDelta x // 120) > 0 ifTrue: [
+ sign x = 1
+ ifTrue: [aMouseWheelEvent setWheelRight]
+ ifFalse: [aMouseWheelEvent setWheelLeft]].
+
+ (currentDelta y // 120) > 0 ifTrue: [
+ sign y = 1
+ ifTrue: [aMouseWheelEvent setWheelUp]
+ ifFalse: [aMouseWheelEvent setWheelDown]].
+
+ currentDelta := currentDelta \\ 120.
+ currentDelta := currentDelta * sign.
+
+ "Finally, send the event."
+ HandMorph sendMouseWheelToKeyboardFocus
+ ifFalse: [aHand sendMouseEvent: aMouseWheelEvent]
+ ifTrue: [aHand sendEvent: aMouseWheelEvent focus: aHand keyboardFocus clear: [aHand keyboardFocus: nil]].
+ !

Item was added:
+ ----- Method: MouseWheelState>>initialize (in category 'initialize-release') -----
+ initialize
+
+ super initialize.
+ currentDelta := 0@0.!

Item was changed:
  ----- Method: PluggableListMorph>>initialize (in category 'initialization') -----
  initialize
-
  listMorph := self createListMorph.
  super initialize.
-
  self scroller
  layoutPolicy: TableLayout new;
  addMorph: listMorph.
+ self
+ minimumWidth: (self font widthOf: $m) * 5 ;
+ minimumHeight: self font height
 
- self minimumWidth: (self font widthOf: $m) * 5.
-
  !

Item was changed:
  ----- Method: PluggableListMorph>>mouseUp: (in category 'event handling') -----
  mouseUp: event
 
  | row |
  model okToChange ifFalse: [^ self].
+ (self containsPoint: event position) ifFalse: [^ self].
 
  row := self rowAtLocation: event position.
  row = self selectionIndex
  ifTrue: [(autoDeselect ifNil: [true]) ifTrue: [row = 0 ifFalse: [self changeModelSelection: 0] ]]
  ifFalse: [self changeModelSelection: (self modelIndexFor: row)].
 
  event hand newKeyboardFocus: self.
  hasFocus := true.
  Cursor normal show.!

Item was changed:
  ----- Method: ProportionalSplitterMorph>>topBoundary (in category 'queries - geometry') -----
  topBoundary
  "Answer the topmost x position the receiver could be moved to."
 
  | splitter morphs |
  splitter := self splitterAbove.
  morphs := self commonNeighbours: leftOrTop with: splitter.
-
  ^ (splitter
  ifNil: [owner isSystemWindow ifTrue: [owner panelRect top]
  ifFalse: [owner innerBounds top]]
  ifNotNil: [splitter bottom])
  + (self minimumHeightOf: morphs)!

Item was changed:
  ----- Method: ScrollPane>>mouseWheel: (in category 'event handling') -----
  mouseWheel: evt
 
+ evt isWheelUp ifTrue: [scrollBar scrollUp: 3].
+ evt isWheelDown ifTrue: [scrollBar scrollDown: 3].!
- evt isWheelUp ifTrue: [scrollBar scrollUp: (3 * evt wheelDelta y abs // 120 max: 1)].
- evt isWheelDown ifTrue: [scrollBar scrollDown: (3 * evt wheelDelta y abs // 120 max: 1)].
- evt isWheelLeft ifTrue: [hScrollBar scrollUp: (3 * evt wheelDelta x abs // 120 max: 1)].
- evt isWheelRight ifTrue: [hScrollBar scrollDown: (3 * evt wheelDelta x abs // 120 max: 1)].!

Item was changed:
  ----- Method: StringMorph>>contents: (in category 'accessing') -----
  contents: newContents
 
  newContents isText
  ifTrue: [^ self initializeFromText: newContents].
 
  contents = newContents
+ ifTrue: [^ self "No substantive change."].
- ifTrue: [^ self "no substantive change"].
 
  contents := newContents.
+ self changed. "New contents need to be drawn."
+
+ self fitContents. "Resize if necessary."!
-
- self fitContents.!

Item was changed:
  ----- Method: StringMorph>>fitContents (in category 'layout') -----
  fitContents
 
+ self extent: self measureContents.!
- | newBounds boundsChanged |
- newBounds := self measureContents.
- boundsChanged := bounds extent ~= newBounds.
- self extent: newBounds. "default short-circuits if bounds not changed"
- boundsChanged ifFalse: [self changed]!

Item was changed:
  ----- Method: UpdatingStringMorph>>fitContents (in category 'layout') -----
  fitContents
+ "Overridden to respect minimum and maximum widfth."
+
-
  | newExtent |
+ newExtent :=  self measureContents.
+ self extent: ((newExtent x max: self minimumWidth) min: self maximumWidth) @ newExtent y.!
- newExtent := self measureContents.
- newExtent := ((newExtent x max: self minimumWidth) min: self maximumWidth) @ newExtent y.
- (self extent = newExtent) ifFalse:
- [self extent: newExtent.
- self changed]
- !

Item was changed:
  ----- Method: UpdatingStringMorph>>updateContentsFrom: (in category 'stepping') -----
  updateContentsFrom: aValue
  self growable
  ifTrue:
+ [self contentsFitted: aValue]
- [self contents: aValue]
  ifFalse:
  [self contentsClipped: aValue]!


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Morphic-cmm.1617.mcz

Chris Muller-3
I'm not sure why, but this diff is showing a bunch of extra stuff.  Use MC's diff to see just the two changes.

On Fri, Jan 10, 2020 at 7:33 PM <[hidden email]> wrote:
Chris Muller uploaded a new version of Morphic to project The Inbox:
http://source.squeak.org/inbox/Morphic-cmm.1617.mcz

==================== Summary ====================

Name: Morphic-cmm.1617
Author: cmm
Time: 10 January 2020, 7:32:31.635312 pm
UUID: ce0033f9-62f5-4c12-9b75-24d613d56c50
Ancestors: Morphic-tpr.1616

- Fix inescapable modal dialog.
- Fix truncation of the first line of PluggableListMorphs when a font larger than the default is used.

=============== Diff against Morphic-tpr.1616 ===============

Item was added:
+ ----- Method: AlternatePluggableListMorphOfMany>>mouseLeaveDragging: (in category 'event handling') -----
+ mouseLeaveDragging: anEvent
+       "Dragging means changing the list's multi-selection state. Thus, there is no support for drag-and-drop of elements within a selection."
+       
+       self hoverRow: nil.
+       self resetPotentialDropRow.!

Item was changed:
  ----- Method: DialogWindow>>getUserResponse (in category 'running') -----
  getUserResponse

        | hand world |
        self message ifEmpty: [messageMorph delete]. "Do not waste space."
        self paneMorph submorphs
                ifEmpty: ["Do not waste space and avoid strange button-row wraps."
                        self paneMorph delete.
                        self buttonRowMorph wrapDirection: #none].

        hand := self currentHand.
        world := self currentWorld.

        self fullBounds.
        self moveToPreferredPosition.
        self openInWorld: world.

        hand showTemporaryCursor: nil. "Since we are out of context, reset the cursor."

        hand keyboardFocus in: [:priorKeyboardFocus |
                hand mouseFocus in: [:priorMouseFocus |
                        self exclusive ifTrue: [hand newMouseFocus: self].
                        hand newKeyboardFocus: self.

                        [[self isInWorld] whileTrue: [world doOneSubCycle]]
                                ifCurtailed: [self cancelDialog].

                        hand newKeyboardFocus: priorKeyboardFocus.
+                       hand releaseMouseFocus]].
-                       hand newMouseFocus: priorMouseFocus]].

        ^ result!

Item was changed:
  ----- Method: FontChooserTool>>selectedPointSizeIndex: (in category 'point size') -----
  selectedPointSizeIndex: anIndex

        anIndex = 0 ifTrue: [^self].
        pointSize := (self pointSizeList at: anIndex) withBlanksTrimmed asNumber.
+       self changed: #selectedPointSizeIndex.
        self changed: #pointSizeList.
        self changed: #contents.!

Item was changed:
  Morph subclass: #HandMorph
+       instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners eventCaptureFilters mouseCaptureFilters keyboardCaptureFilters mouseClickState mouseOverHandler mouseWheelState lastMouseEvent targetOffset damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hardwareCursor hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor keyboardInterpreter'
+       classVariableNames: 'CompositionWindowManager DoubleClickTime DragThreshold EventStats NewEventRules NormalCursor PasteBuffer SendMouseWheelToKeyboardFocus ShowEvents SynthesizeMouseWheelEvents'
-       instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners eventCaptureFilters mouseCaptureFilters keyboardCaptureFilters mouseClickState mouseOverHandler targetOffset lastMouseEvent damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hardwareCursor hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor keyboardInterpreter'
-       classVariableNames: 'CompositionWindowManager DoubleClickTime DragThreshold EventStats MinimalWheelDelta NewEventRules NormalCursor PasteBuffer SendMouseWheelToKeyboardFocus ShowEvents SynthesizeMouseWheelEvents'
        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 removed:
- ----- Method: HandMorph class>>minimumWheelDelta (in category 'preferences') -----
- minimumWheelDelta
-       <preference: 'Minimal Mouse Wheel Scroll Delta'
-               categoryList: #(Morphic mouse)
-               description: 'Answer the minimal scroll increment taken into account
- Defaults to 120, corresponding to a single mouse wheel notch.
- Use a lower value (20) if wanting smoother scrolling with trackpads.'
-               type: #Number>
-       ^MinimalWheelDelta ifNil: [120].!

Item was removed:
- ----- Method: HandMorph class>>minimumWheelDelta: (in category 'preferences') -----
- minimumWheelDelta: anInteger
-       MinimalWheelDelta := anInteger ifNotNil: [anInteger clampLow: 20 high: 120]!

Item was changed:
  ----- Method: HandMorph>>generateMouseWheelEvent: (in category 'private events') -----
  generateMouseWheelEvent: evtBuf
        "Generate the appropriate mouse wheel event for the given raw event buffer"

+       | buttons modifiers deltaX deltaY stamp |
-       | buttons modifiers deltaX deltaY stamp nextEvent |
        stamp := evtBuf second.
        stamp = 0 ifTrue: [stamp := Time eventMillisecondClock].
        deltaX := evtBuf third.
        deltaY := evtBuf fourth.
+       modifiers := evtBuf fifth.
+       buttons := (modifiers bitShift: 3) bitOr: (lastMouseEvent buttons bitAnd: 7).
-       buttons := evtBuf fifth.
-       modifiers := evtBuf sixth.
-       [(deltaX abs + deltaY abs < self class minimumWheelDelta)
-                       and: [(nextEvent := Sensor peekEvent) notNil
-                       and: [nextEvent first = evtBuf first
-                       and: [nextEvent fifth = evtBuf fifth
-                       and: [nextEvent sixth = evtBuf sixth]
-                       and: [nextEvent third isZero = evtBuf third isZero "both horizontal or vertical"]]]]]
-               whileTrue:
-                       ["nextEvent is similar.  Remove it from the queue, and check the next."
-                       nextEvent := Sensor nextEvent.
-                       deltaX := deltaX + nextEvent third.
-                       deltaY := deltaY + nextEvent fourth].
        ^ MouseWheelEvent new
                setType: #mouseWheel
                position: self position
                delta: deltaX@deltaY
+               direction: 2r0000
                buttons: buttons       
                hand: self
                stamp: stamp!

Item was changed:
  ----- Method: HandMorph>>handleEvent: (in category 'events-processing') -----
  handleEvent: unfilteredEvent

        | filteredEvent |
        owner ifNil: [^ unfilteredEvent  "not necessary but good style -- see Morph >> #handleEvent:"].

        self logEvent: unfilteredEvent.

        "Mouse-over events occur really, really, really often. They are kind of the heart beat of the Morphic UI process."
        unfilteredEvent isMouseOver ifTrue: [^ self sendMouseEvent: unfilteredEvent].

        self showEvent: unfilteredEvent.
        self sendListenEvents: unfilteredEvent.

        filteredEvent := self sendFilterEventCapture: unfilteredEvent for: nil.
        "filteredEvent := unfilteredEvent" " <-- use this to disable global capture filters"

        filteredEvent wasIgnored ifTrue: [
                self mouseOverHandler processMouseOver: lastMouseEvent.
                ^ filteredEvent].

        filteredEvent isWindowEvent ifTrue: [
                self sendEvent: filteredEvent focus: nil.
                self mouseOverHandler processMouseOver: lastMouseEvent.
                ^ filteredEvent].

        filteredEvent isKeyboard ifTrue:[
                self sendKeyboardEvent: filteredEvent.
                self mouseOverHandler processMouseOver: lastMouseEvent.
                ^ filteredEvent].

        filteredEvent isDropEvent ifTrue:[
                self sendEvent: filteredEvent focus: nil.
                self mouseOverHandler processMouseOver: lastMouseEvent.
                ^ filteredEvent].

        filteredEvent isMouse ifFalse: [
                self mouseOverHandler processMouseOver: lastMouseEvent.
                ^ filteredEvent].

        " ********** MOUSE EVENT *********** "

        lastMouseEvent := filteredEvent.

        "Check for pending drag or double click operations."
        mouseClickState ifNotNil:[
                (mouseClickState handleEvent: filteredEvent from: self) ifFalse:[
                        "Possibly dispatched #click: or something and will not re-establish otherwise"
                        self mouseOverHandler processMouseOver: lastMouseEvent.
                        ^ filteredEvent]].

        filteredEvent isMouseWheel ifTrue: [
+               mouseWheelState ifNil: [mouseWheelState := MouseWheelState new].
+               mouseWheelState handleEvent: filteredEvent from: self.
-               self class sendMouseWheelToKeyboardFocus
-                       ifFalse: [self sendMouseEvent: filteredEvent]
-                       ifTrue: [self sendEvent: filteredEvent focus: self keyboardFocus clear: [self keyboardFocus: nil]].
                self mouseOverHandler processMouseOver: lastMouseEvent.
                ^ filteredEvent].

        filteredEvent isMove ifTrue:[
                self position: filteredEvent position.
                self sendMouseEvent: filteredEvent.
                self mouseOverHandler processMouseOver: lastMouseEvent.
                ^ filteredEvent].

        "Issue a synthetic move event if we're not at the position of the event"
        filteredEvent position = self position
                ifFalse: [self moveToEvent: filteredEvent].

        "Drop submorphs on button events"
        self hasSubmorphs
                ifTrue:[self dropMorphs: filteredEvent]
                ifFalse:[self sendMouseEvent: filteredEvent].

        self mouseOverHandler processMouseOver: lastMouseEvent.
        ^ filteredEvent "not necessary but good style -- see Morph >> #handleEvent:"    !

Item was removed:
- ----- Method: MouseWheelEvent>>setDirection (in category 'initialization') -----
- setDirection
-       delta x > 0 ifTrue: [self setWheelRight].
-       delta x < 0 ifTrue: [self setWheelLeft].
-
-       delta y > 0 ifTrue: [self setWheelUp].
-       delta y < 0 ifTrue: [self setWheelDown].!

Item was removed:
- ----- Method: MouseWheelEvent>>setType:position:delta:buttons:hand:stamp: (in category 'private') -----
- setType: evtType position: evtPos delta: evtDelta buttons: evtButtons hand: evtHand stamp: stamp
-       type := evtType.
-       position := evtPos.
-       buttons := evtButtons.
-       source := evtHand.
-       wasHandled := false.
-       direction := 2r0000.
-       delta := evtDelta.
-       timeStamp := stamp.
-       self setDirection!

Item was added:
+ Object subclass: #MouseWheelState
+       instanceVariableNames: 'currentDelta'
+       classVariableNames: ''
+       poolDictionaries: ''
+       category: 'Morphic-Events'!

Item was added:
+ ----- Method: MouseWheelState>>handleEvent:from: (in category 'event processing') -----
+ handleEvent: aMouseWheelEvent from: aHand
+       "Every 120 units, raise the wheel flags for convenient mouse wheel programming. We choose not to send multiple mouse-wheel events for multiples of 120 because applications can always react to the actual delta values if they want to do more scrolling or zooming."
+       
+       | sign |
+       currentDelta := currentDelta + aMouseWheelEvent wheelDelta.
+
+       sign := currentDelta sign.
+       currentDelta := currentDelta abs.
+
+       (currentDelta x // 120) > 0 ifTrue: [
+               sign x = 1
+                       ifTrue: [aMouseWheelEvent setWheelRight]
+                       ifFalse: [aMouseWheelEvent setWheelLeft]].
+
+       (currentDelta y // 120) > 0 ifTrue: [
+               sign y = 1
+                       ifTrue: [aMouseWheelEvent setWheelUp]
+                       ifFalse: [aMouseWheelEvent setWheelDown]].
+               
+       currentDelta := currentDelta \\ 120.
+       currentDelta := currentDelta * sign.
+
+       "Finally, send the event."
+       HandMorph sendMouseWheelToKeyboardFocus
+               ifFalse: [aHand sendMouseEvent: aMouseWheelEvent]
+               ifTrue: [aHand sendEvent: aMouseWheelEvent focus: aHand keyboardFocus clear: [aHand keyboardFocus: nil]].
+ !

Item was added:
+ ----- Method: MouseWheelState>>initialize (in category 'initialize-release') -----
+ initialize
+
+       super initialize.
+       currentDelta := 0@0.!

Item was changed:
  ----- Method: PluggableListMorph>>initialize (in category 'initialization') -----
  initialize
-
        listMorph := self createListMorph.
        super initialize.
-
        self scroller
                layoutPolicy: TableLayout new;
                addMorph: listMorph.   
+       self
+               minimumWidth: (self font widthOf: $m) * 5 ;
+               minimumHeight: self font height

-       self minimumWidth: (self font widthOf: $m) * 5.
-       
        !

Item was changed:
  ----- Method: PluggableListMorph>>mouseUp: (in category 'event handling') -----
  mouseUp: event

        | row |
        model okToChange ifFalse: [^ self].
+       (self containsPoint: event position) ifFalse: [^ self].

        row := self rowAtLocation: event position.
        row = self selectionIndex
                ifTrue: [(autoDeselect ifNil: [true]) ifTrue: [row = 0 ifFalse: [self changeModelSelection: 0] ]]
                ifFalse: [self changeModelSelection: (self modelIndexFor: row)].

        event hand newKeyboardFocus: self.
        hasFocus := true.
        Cursor normal show.!

Item was changed:
  ----- Method: ProportionalSplitterMorph>>topBoundary (in category 'queries - geometry') -----
  topBoundary
        "Answer the topmost x position the receiver could be moved to."

        | splitter morphs |
        splitter := self splitterAbove.
        morphs := self commonNeighbours: leftOrTop with: splitter.
-       
        ^ (splitter
                ifNil: [owner isSystemWindow ifTrue: [owner panelRect top]
                                ifFalse: [owner innerBounds top]]
                ifNotNil: [splitter bottom])
                + (self minimumHeightOf: morphs)!

Item was changed:
  ----- Method: ScrollPane>>mouseWheel: (in category 'event handling') -----
  mouseWheel: evt

+       evt isWheelUp ifTrue: [scrollBar scrollUp: 3].
+       evt isWheelDown ifTrue: [scrollBar scrollDown: 3].!
-       evt isWheelUp ifTrue: [scrollBar scrollUp: (3 * evt wheelDelta y abs // 120 max: 1)].
-       evt isWheelDown ifTrue: [scrollBar scrollDown: (3 * evt wheelDelta y abs // 120 max: 1)].
-       evt isWheelLeft ifTrue: [hScrollBar scrollUp: (3 * evt wheelDelta x abs // 120 max: 1)].
-       evt isWheelRight ifTrue: [hScrollBar scrollDown: (3 * evt wheelDelta x abs // 120 max: 1)].!

Item was changed:
  ----- Method: StringMorph>>contents: (in category 'accessing') -----
  contents: newContents

        newContents isText
                ifTrue: [^ self initializeFromText: newContents].

        contents = newContents
+               ifTrue: [^ self "No substantive change."].
-               ifTrue: [^ self "no substantive change"].

        contents := newContents.
+       self changed. "New contents need to be drawn."
+               
+       self fitContents. "Resize if necessary."!
-       
-       self fitContents.!

Item was changed:
  ----- Method: StringMorph>>fitContents (in category 'layout') -----
  fitContents

+       self extent: self measureContents.!
-       | newBounds boundsChanged |
-       newBounds := self measureContents.
-       boundsChanged := bounds extent ~= newBounds.
-       self extent: newBounds.         "default short-circuits if bounds not changed"
-       boundsChanged ifFalse: [self changed]!

Item was changed:
  ----- Method: UpdatingStringMorph>>fitContents (in category 'layout') -----
  fitContents
+       "Overridden to respect minimum and maximum widfth."
+       
-
        | newExtent |
+       newExtent :=  self measureContents.
+       self extent: ((newExtent x max: self minimumWidth) min: self maximumWidth) @ newExtent y.!
-       newExtent := self measureContents.
-       newExtent := ((newExtent x max: self minimumWidth) min: self maximumWidth) @ newExtent y.
-       (self extent = newExtent) ifFalse:
-               [self extent: newExtent.
-               self changed]
- !

Item was changed:
  ----- Method: UpdatingStringMorph>>updateContentsFrom: (in category 'stepping') -----
  updateContentsFrom: aValue
        self growable
                ifTrue:
+                       [self contentsFitted: aValue]
-                       [self contents: aValue]
                ifFalse:
                        [self contentsClipped: aValue]!