Skip to content

Commit

Permalink
Merge pull request #2724 from jecisc/2590-We-can-get-two-times-the-mo…
Browse files Browse the repository at this point in the history
…useEntermouseLeave-event-when-subscribing-to-the-eventHandler-of-a-Morph

2590-We-can-get-two-times-the-mouseEntermouseLeave-event-when-subscribing-to-the-eventHandler-of-a-Morph
  • Loading branch information
MarcusDenker committed Apr 26, 2019
2 parents e99e9d2 + c3cd91d commit 9ca8696
Show file tree
Hide file tree
Showing 3 changed files with 86 additions and 20 deletions.
42 changes: 22 additions & 20 deletions src/Morphic-Core/Morph.class.st
Expand Up @@ -2928,32 +2928,34 @@ Morph >> handleMouseDown: anEvent [
{ #category : #'events-processing' }
Morph >> handleMouseEnter: anEvent [
"System level event handling."
(anEvent isDraggingEvent) ifTrue:[
(self handlesMouseOverDragging: anEvent) ifTrue:[
anEvent wasHandled: true.
self mouseEnterDragging: anEvent].
^ self eventHandler ifNotNil: [:handler | handler mouseEnterDragging: anEvent fromMorph: self ]].
self wantsBalloon
ifTrue:[anEvent hand triggerBalloonFor: self after: self balloonHelpDelayTime].
(self handlesMouseOver: anEvent) ifTrue:[
anEvent wasHandled: true.
self mouseEnter: anEvent ].
^ self eventHandler ifNotNil: [:handler | handler mouseEnter: anEvent fromMorph: self ].

anEvent isDraggingEvent
ifTrue: [ (self handlesMouseOverDragging: anEvent)
ifTrue: [ anEvent wasHandled: true.
self mouseEnterDragging: anEvent ].
^ self eventHandler ifNotNil: [ :handler | handler mouseEnterDragging: anEvent fromMorph: self ] ].
self wantsBalloon ifTrue: [ anEvent hand triggerBalloonFor: self after: self balloonHelpDelayTime ].

^ (self handlesMouseOver: anEvent)
ifTrue: [ anEvent wasHandled: true.
self mouseEnter: anEvent ]
ifFalse: [ self eventHandler ifNotNil: [ :handler | handler mouseEnter: anEvent fromMorph: self ] ]
]

{ #category : #'events-processing' }
Morph >> handleMouseLeave: anEvent [
"System level event handling."

anEvent hand removePendingBalloonFor: self.
anEvent isDraggingEvent ifTrue:[
(self handlesMouseOverDragging: anEvent) ifTrue:[
anEvent wasHandled: true.
self mouseLeaveDragging: anEvent].
^ self eventHandler ifNotNil: [:handler | handler mouseLeave: anEvent fromMorph: self ]].
(self handlesMouseOver: anEvent) ifTrue:[
anEvent wasHandled: true.
self mouseLeave: anEvent ].
^ self eventHandler ifNotNil: [:handler | handler mouseLeave: anEvent fromMorph: self ]
anEvent isDraggingEvent
ifTrue: [ (self handlesMouseOverDragging: anEvent)
ifTrue: [ anEvent wasHandled: true.
self mouseLeaveDragging: anEvent ].
^ self eventHandler ifNotNil: [ :handler | handler mouseLeave: anEvent fromMorph: self ] ].
^ (self handlesMouseOver: anEvent)
ifTrue: [ anEvent wasHandled: true.
self mouseLeave: anEvent ]
ifFalse: [ self eventHandler ifNotNil: [ :handler | handler mouseLeave: anEvent fromMorph: self ] ]
]

{ #category : #'events-processing' }
Expand Down
43 changes: 43 additions & 0 deletions src/Morphic-Tests/MockObjectForEventTests.class.st
@@ -0,0 +1,43 @@
Class {
#name : #MockObjectForEventTests,
#superclass : #Object,
#instVars : [
'stringMorph',
'counter'
],
#category : #'Morphic-Tests-Event'
}

{ #category : #accessing }
MockObjectForEventTests >> counter [
^ counter
]

{ #category : #accessing }
MockObjectForEventTests >> counter: anObject [
counter := anObject
]

{ #category : #initialization }
MockObjectForEventTests >> initialize [
super initialize.
counter := 0
]

{ #category : #accessing }
MockObjectForEventTests >> mockStringMorph [
^ StringMorph new
contents: 'Test';
on: #mouseEnter send: #mouseEnter:from: to: self;
yourself
]

{ #category : #accessing }
MockObjectForEventTests >> mouseEnter: a from: b [
counter := counter + 1
]

{ #category : #accessing }
MockObjectForEventTests >> stringMorph [
^ stringMorph ifNil: [ stringMorph := self mockStringMorph ]
]
21 changes: 21 additions & 0 deletions src/Morphic-Tests/MorphicEventHandlerTest.class.st
Expand Up @@ -73,6 +73,27 @@ MorphicEventHandlerTest >> testMouseEnterDraggingFromMorph [
self assert: ((morph handleMouseEnter: event) == true)
]

{ #category : #tests }
MorphicEventHandlerTest >> testMouseEnterEventIsNotDuplicated [
| mockObject window evt |
mockObject := MockObjectForEventTests new.

[ window := mockObject stringMorph openInWindow.
evt := MouseButtonEvent new
setType: nil
position: mockObject stringMorph center
which: MouseButtonEvent redButton
buttons: MouseButtonEvent redButton
hand: nil
stamp: nil.

self assert: mockObject counter equals: 0.

mockObject stringMorph handleMouseEnter: evt.
self assert: mockObject counter equals: 1 ]
ensure: [ window ifNotNil: #close ]
]

{ #category : #'tests-events' }
MorphicEventHandlerTest >> testMouseEnterFromMorph [

Expand Down

0 comments on commit 9ca8696

Please sign in to comment.