Skip to content

Commit

Permalink
Merge pull request #7270 from ronsaldo/feature-sdl2-hidpi-apis
Browse files Browse the repository at this point in the history
Add APIs for querying dpi and computing scale factor to OSWindow
  • Loading branch information
Ducasse authored Sep 8, 2020
2 parents 2f509ea + d2f7d07 commit 1f0a7c5
Show file tree
Hide file tree
Showing 10 changed files with 225 additions and 12 deletions.
25 changes: 25 additions & 0 deletions src/OSWindow-Core/OSBackendWindow.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,11 @@ OSBackendWindow >> clipboardText: aString [
self subclassResponsibility
]

{ #category : #accessing }
OSBackendWindow >> diagonalDPI [
^ self screenScaleFactorBaseDPI
]

{ #category : #accessing }
OSBackendWindow >> extent [
^ self bounds extent
Expand All @@ -67,6 +72,11 @@ OSBackendWindow >> hide [
self subclassResponsibility
]

{ #category : #accessing }
OSBackendWindow >> horizontalDPI [
^ self screenScaleFactorBaseDPI
]

{ #category : #accessing }
OSBackendWindow >> icon: aForm [
]
Expand Down Expand Up @@ -160,6 +170,16 @@ OSBackendWindow >> resizable: aBoolean [

]

{ #category : #accessing }
OSBackendWindow >> screenScaleFactor [
^ 1
]

{ #category : #accessing }
OSBackendWindow >> screenScaleFactorBaseDPI [
^ OSPlatform current osWindowScreenScaleFactorBaseDPI
]

{ #category : #cursor }
OSBackendWindow >> setMouseCursor: cursorWithMask [
self setMouseCursor: cursorWithMask mask: cursorWithMask maskForm
Expand Down Expand Up @@ -194,6 +214,11 @@ OSBackendWindow >> title: aTitle [
self subclassResponsibility
]

{ #category : #accessing }
OSBackendWindow >> verticalDPI [
^ self screenScaleFactorBaseDPI
]

{ #category : #accessing }
OSBackendWindow >> windowId [
^ nil
Expand Down
6 changes: 6 additions & 0 deletions src/OSWindow-Core/OSPlatform.extension.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
Extension { #name : #OSPlatform }

{ #category : #'*OSWindow-Core' }
OSPlatform >> osWindowScreenScaleFactorBaseDPI [
^ 96
]
25 changes: 25 additions & 0 deletions src/OSWindow-Core/OSWindow.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -184,6 +184,11 @@ OSWindow >> destroy [
eventHandler := nil.
]

{ #category : #accessing }
OSWindow >> diagonalDPI [
^ self validHandle diagonalDPI
]

{ #category : #accessing }
OSWindow >> eventHandler [

Expand Down Expand Up @@ -228,6 +233,11 @@ OSWindow >> hide [
backendWindow hide
]

{ #category : #accessing }
OSWindow >> horizontalDPI [
^ self validHandle horizontalDPI
]

{ #category : #accessing }
OSWindow >> icon: aForm [
self validHandle icon: aForm
Expand Down Expand Up @@ -347,6 +357,16 @@ OSWindow >> restore [
self validHandle restore.
]

{ #category : #accessing }
OSWindow >> screenScaleFactor [
^ self validHandle screenScaleFactor
]

{ #category : #accessing }
OSWindow >> screenScaleFactorBaseDPI [
^ self validHandle screenScaleFactorBaseDPI
]

{ #category : #'window management' }
OSWindow >> setDraggableArea: aRectangle [

Expand Down Expand Up @@ -425,6 +445,11 @@ OSWindow >> validHandle [
^ backendWindow
]

{ #category : #accessing }
OSWindow >> verticalDPI [
^ self validHandle verticalDPI
]

{ #category : #accessing }
OSWindow >> windowId [
^ self validHandle windowId
Expand Down
4 changes: 4 additions & 0 deletions src/OSWindow-Core/OSWindowEventVisitor.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,10 @@ OSWindowEventVisitor >> visitWindowMoveEvent: anEvent [
OSWindowEventVisitor >> visitWindowResizeEvent: anEvent [
]

{ #category : #visiting }
OSWindowEventVisitor >> visitWindowResolutionChangeEvent: anEvent [
]

{ #category : #visiting }
OSWindowEventVisitor >> visitWindowShownEvent: anEvent [
]
28 changes: 20 additions & 8 deletions src/OSWindow-Core/OSWindowMorphicEventHandler.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,12 @@ OSWindowMorphicEventHandler >> convertModifiers: modifiers [
^ buttons
]

{ #category : #converting }
OSWindowMorphicEventHandler >> convertPosition: aPosition [
morphicWorld ifNil: [ ^ aPosition ].
^ morphicWorld worldState worldRenderer convertWindowMouseEventPosition: aPosition
]

{ #category : #events }
OSWindowMorphicEventHandler >> dispatchMorphicEvent: anEvent [
morphicWorld defer: [
Expand Down Expand Up @@ -256,15 +262,15 @@ OSWindowMorphicEventHandler >> visitMouseButtonPressEvent: anEvent [
anEvent isWheel ifTrue: [
^ MouseWheelEvent new
setType: #mouseWheel
position: anEvent position
position: (self convertPosition: anEvent position)
direction: anEvent wheelDirection
buttons: (self convertModifiers: anEvent modifiers)
hand: self activeHand
stamp: Time millisecondClockValue ].

^ MouseButtonEvent new
setType: #mouseDown
position: anEvent position
position: (self convertPosition: anEvent position)
which: (self convertButtonFromEvent: anEvent)
buttons: (self convertModifiers: anEvent modifiers) | (self convertButtonFromEvent: anEvent)
hand: self activeHand
Expand All @@ -277,7 +283,7 @@ OSWindowMorphicEventHandler >> visitMouseButtonReleaseEvent: anEvent [

^ MouseButtonEvent new
setType: #mouseUp
position: anEvent position
position: (self convertPosition: anEvent position)
which: (self convertButtonFromEvent: anEvent)
buttons: (self convertModifiers: anEvent modifiers)
hand: self activeHand
Expand All @@ -286,15 +292,15 @@ OSWindowMorphicEventHandler >> visitMouseButtonReleaseEvent: anEvent [

{ #category : #visiting }
OSWindowMorphicEventHandler >> visitMouseMoveEvent: anEvent [
| oldPos |
| oldPos newPos |
oldPos := morphicWorld activeHand ifNil: [ 0@0 ] ifNotNil: [:hand | hand position ].
morphicWorld beCursorOwner.

newPos := self convertPosition: anEvent position.
^ MouseMoveEvent basicNew
setType: #mouseMove
startPoint: oldPos
endPoint: anEvent position
trail: { oldPos. anEvent position }
endPoint: newPos
trail: { oldPos. newPos }
buttons: (self convertModifiers: anEvent modifiers)
hand: self activeHand
stamp: Time millisecondClockValue
Expand All @@ -308,7 +314,7 @@ OSWindowMorphicEventHandler >> visitMouseWheelEvent: anEvent [

^ MouseWheelEvent new
setType: #mouseWheel
position: anEvent position
position: (self convertPosition: anEvent position)
direction: (vertical > 0 ifTrue: [Character arrowUp] ifFalse: [Character arrowDown])
buttons: (self convertModifiers: anEvent modifiers)
hand: self activeHand
Expand Down Expand Up @@ -374,3 +380,9 @@ OSWindowMorphicEventHandler >> visitWindowResizeEvent: anEvent [
"window resized"
morphicWorld worldState worldRenderer checkForNewScreenSize.
]

{ #category : #visiting }
OSWindowMorphicEventHandler >> visitWindowResolutionChangeEvent: anEvent [
"Resolution (dpi) changed. For now just check for a new size."
morphicWorld worldState worldRenderer checkForNewScreenSize.
]
59 changes: 59 additions & 0 deletions src/OSWindow-Core/OSWindowResolutionChangeEvent.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
"
I am delivered when the per-pixel resolution measured in DPI of a window is changed.
"
Class {
#name : #OSWindowResolutionChangeEvent,
#superclass : #OSWindowEvent,
#instVars : [
'screenScaleFactor',
'horizontalDPI',
'verticalDPI',
'diagonalDPI'
],
#category : #'OSWindow-Core-Events'
}

{ #category : #visitor }
OSWindowResolutionChangeEvent >> accept: visitor [
^ visitor visitWindowResolutionChangeEvent: self
]

{ #category : #accessing }
OSWindowResolutionChangeEvent >> diagonalDPI [
^ diagonalDPI
]

{ #category : #accessing }
OSWindowResolutionChangeEvent >> diagonalDPI: anObject [
diagonalDPI := anObject
]

{ #category : #accessing }
OSWindowResolutionChangeEvent >> horizontalDPI [
^ horizontalDPI
]

{ #category : #accessing }
OSWindowResolutionChangeEvent >> horizontalDPI: anObject [
horizontalDPI := anObject
]

{ #category : #accessing }
OSWindowResolutionChangeEvent >> screenScaleFactor [
^ screenScaleFactor
]

{ #category : #accessing }
OSWindowResolutionChangeEvent >> screenScaleFactor: anObject [
screenScaleFactor := anObject
]

{ #category : #accessing }
OSWindowResolutionChangeEvent >> verticalDPI [
^ verticalDPI
]

{ #category : #accessing }
OSWindowResolutionChangeEvent >> verticalDPI: anObject [
verticalDPI := anObject
]
5 changes: 5 additions & 0 deletions src/OSWindow-Core/OSWorldRenderer.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,11 @@ OSWorldRenderer >> clipboardText: aString [
osWindow clipboardText: aString asString
]

{ #category : #events }
OSWorldRenderer >> convertWindowMouseEventPosition: aPosition [
^ aPosition
]

{ #category : #initialization }
OSWorldRenderer >> deactivate [

Expand Down
Loading

0 comments on commit 1f0a7c5

Please sign in to comment.