sdl2-2.5.4.0: Both high- and low-level bindings to the SDL library (version 2.0.6+).
Safe HaskellSafe-Inferred
LanguageHaskell2010

SDL.Input.Mouse

Synopsis

Relative Mouse Mode

data LocationMode Source #

Instances

Instances details
Data LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocationMode -> c LocationMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocationMode #

toConstr :: LocationMode -> Constr #

dataTypeOf :: LocationMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LocationMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocationMode) #

gmapT :: (forall b. Data b => b -> b) -> LocationMode -> LocationMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocationMode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocationMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocationMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocationMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocationMode -> m LocationMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocationMode -> m LocationMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocationMode -> m LocationMode #

Bounded LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

Enum LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

Generic LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep LocationMode :: Type -> Type #

Read LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

Show LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

Eq LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

Ord LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep LocationMode Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep LocationMode = D1 ('MetaData "LocationMode" "SDL.Input.Mouse" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) (C1 ('MetaCons "AbsoluteLocation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RelativeLocation" 'PrefixI 'False) (U1 :: Type -> Type))

setMouseLocationMode :: (Functor m, MonadIO m) => LocationMode -> m LocationMode Source #

Sets the current relative mouse mode.

When relative mouse mode is enabled, cursor is hidden and mouse position will not change. However, you will be delivered relative mouse position change events.

getMouseLocationMode :: MonadIO m => m LocationMode Source #

Check which mouse location mode is currently active.

Mouse and Touch Input

data MouseButton Source #

Constructors

ButtonLeft 
ButtonMiddle 
ButtonRight 
ButtonX1 
ButtonX2 
ButtonExtra !Int

An unknown mouse button.

Instances

Instances details
Data MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseButton -> c MouseButton #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseButton #

toConstr :: MouseButton -> Constr #

dataTypeOf :: MouseButton -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MouseButton) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseButton) #

gmapT :: (forall b. Data b => b -> b) -> MouseButton -> MouseButton #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseButton -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseButton -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseButton -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseButton -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

Generic MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep MouseButton :: Type -> Type #

Read MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Show MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Eq MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Ord MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

FromNumber MouseButton Word8 Source # 
Instance details

Defined in SDL.Input.Mouse

ToNumber MouseButton Word8 Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseButton = D1 ('MetaData "MouseButton" "SDL.Input.Mouse" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) ((C1 ('MetaCons "ButtonLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ButtonMiddle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ButtonRight" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ButtonX1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ButtonX2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ButtonExtra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))))

data MouseDevice Source #

Identifies what kind of mouse-like device this is.

Constructors

Mouse !Int

An actual mouse. The number identifies which mouse.

Touch

Some sort of touch device.

Instances

Instances details
Data MouseDevice Source # 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseDevice -> c MouseDevice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseDevice #

toConstr :: MouseDevice -> Constr #

dataTypeOf :: MouseDevice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MouseDevice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseDevice) #

gmapT :: (forall b. Data b => b -> b) -> MouseDevice -> MouseDevice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseDevice -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseDevice -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseDevice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseDevice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice #

Generic MouseDevice Source # 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep MouseDevice :: Type -> Type #

Read MouseDevice Source # 
Instance details

Defined in SDL.Input.Mouse

Show MouseDevice Source # 
Instance details

Defined in SDL.Input.Mouse

Eq MouseDevice Source # 
Instance details

Defined in SDL.Input.Mouse

Ord MouseDevice Source # 
Instance details

Defined in SDL.Input.Mouse

FromNumber MouseDevice Word32 Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseDevice Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseDevice = D1 ('MetaData "MouseDevice" "SDL.Input.Mouse" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) (C1 ('MetaCons "Mouse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Touch" 'PrefixI 'False) (U1 :: Type -> Type))

data MouseScrollDirection Source #

Identifies mouse scroll direction.

Instances

Instances details
Data MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseScrollDirection -> c MouseScrollDirection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseScrollDirection #

toConstr :: MouseScrollDirection -> Constr #

dataTypeOf :: MouseScrollDirection -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MouseScrollDirection) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseScrollDirection) #

gmapT :: (forall b. Data b => b -> b) -> MouseScrollDirection -> MouseScrollDirection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseScrollDirection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseScrollDirection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseScrollDirection -> m MouseScrollDirection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseScrollDirection -> m MouseScrollDirection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseScrollDirection -> m MouseScrollDirection #

Bounded MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

Enum MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

Generic MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep MouseScrollDirection :: Type -> Type #

Read MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

Show MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

Eq MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

Ord MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

FromNumber MouseScrollDirection Word32 Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseScrollDirection Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseScrollDirection = D1 ('MetaData "MouseScrollDirection" "SDL.Input.Mouse" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) (C1 ('MetaCons "ScrollNormal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScrollFlipped" 'PrefixI 'False) (U1 :: Type -> Type))

Mouse State

data ModalLocation Source #

Instances

Instances details
Generic ModalLocation Source # 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep ModalLocation :: Type -> Type #

Read ModalLocation Source # 
Instance details

Defined in SDL.Input.Mouse

Show ModalLocation Source # 
Instance details

Defined in SDL.Input.Mouse

Eq ModalLocation Source # 
Instance details

Defined in SDL.Input.Mouse

Ord ModalLocation Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep ModalLocation Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep ModalLocation = D1 ('MetaData "ModalLocation" "SDL.Input.Mouse" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) (C1 ('MetaCons "AbsoluteModalLocation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point V2 CInt))) :+: C1 ('MetaCons "RelativeModalLocation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V2 CInt))))

getModalMouseLocation :: MonadIO m => m ModalLocation Source #

Return proper mouse location depending on mouse mode

getAbsoluteMouseLocation :: MonadIO m => m (Point V2 CInt) Source #

Retrieve the current location of the mouse, relative to the currently focused window.

getRelativeMouseLocation :: MonadIO m => m (V2 CInt) Source #

Retrieve mouse motion

getMouseButtons :: MonadIO m => m (MouseButton -> Bool) Source #

Retrieve a mapping of which buttons are currently held down.

Warping the Mouse

data WarpMouseOrigin Source #

Constructors

WarpInWindow Window

Move the mouse pointer within a given Window.

WarpCurrentFocus

Move the mouse pointer within whichever Window currently has focus.

WarpGlobal

Move the mouse pointer in global screen space.

Instances

Instances details
Data WarpMouseOrigin Source # 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarpMouseOrigin -> c WarpMouseOrigin #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WarpMouseOrigin #

toConstr :: WarpMouseOrigin -> Constr #

dataTypeOf :: WarpMouseOrigin -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WarpMouseOrigin) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarpMouseOrigin) #

gmapT :: (forall b. Data b => b -> b) -> WarpMouseOrigin -> WarpMouseOrigin #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r #

gmapQ :: (forall d. Data d => d -> u) -> WarpMouseOrigin -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarpMouseOrigin -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarpMouseOrigin -> m WarpMouseOrigin #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarpMouseOrigin -> m WarpMouseOrigin #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarpMouseOrigin -> m WarpMouseOrigin #

Generic WarpMouseOrigin Source # 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep WarpMouseOrigin :: Type -> Type #

Show WarpMouseOrigin Source # 
Instance details

Defined in SDL.Input.Mouse

Eq WarpMouseOrigin Source # 
Instance details

Defined in SDL.Input.Mouse

Ord WarpMouseOrigin Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep WarpMouseOrigin Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep WarpMouseOrigin = D1 ('MetaData "WarpMouseOrigin" "SDL.Input.Mouse" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) (C1 ('MetaCons "WarpInWindow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)) :+: (C1 ('MetaCons "WarpCurrentFocus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WarpGlobal" 'PrefixI 'False) (U1 :: Type -> Type)))

warpMouse :: MonadIO m => WarpMouseOrigin -> Point V2 CInt -> m () Source #

Move the current location of a mouse pointer. The WarpMouseOrigin specifies the origin for the given warp coordinates.

Cursor Visibility

cursorVisible :: StateVar Bool Source #

Get or set whether the cursor is currently visible.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_ShowCursor and SDL_HideCursor for C documentation.

Cursor Shape

data Cursor Source #

Instances

Instances details
Eq Cursor Source # 
Instance details

Defined in SDL.Input.Mouse

Methods

(==) :: Cursor -> Cursor -> Bool #

(/=) :: Cursor -> Cursor -> Bool #

activeCursor :: StateVar Cursor Source #

Get or set the currently active cursor. You can create new Cursors with createCursor.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetCursor and SDL_GetCursor for C documentation.

createCursor Source #

Arguments

:: MonadIO m 
=> Vector Word8

Whether this part of the cursor is black. Use False for white and True for black.

-> Vector Word8

Whether or not pixels are visible. Use True for visible and False for transparent.

-> V2 CInt

The width and height of the cursor.

-> Point V2 CInt

The X- and Y-axis location of the upper left corner of the cursor relative to the actual mouse position

-> m Cursor 

Create a cursor using the specified bitmap data and mask (in MSB format).

createCursorFrom Source #

Arguments

:: MonadIO m 
=> Point V2 CInt

The X- and Y-axis location of the upper left corner of the cursor relative to the actual mouse position

-> [[Char]] 
-> m Cursor 

Create a cursor from a bit art painting of it.

The number of columns must be a multiple of 8.

Symbols used: (space) - transparent, . - visible black, # (or anything else) - visible white.

A minimal cursor template: source8x8 :: [[Char]] source8x8 = [ " " , " " , " " , " " , " " , " " , " " , " " ]

freeCursor :: MonadIO m => Cursor -> m () Source #

Free a cursor created with createCursor, createColorCusor and createSystemCursor.

See SDL_FreeCursor for C documentation.

createColorCursor Source #

Arguments

:: MonadIO m 
=> Surface 
-> Point V2 CInt

The location of the cursor hot spot

-> m Cursor 

Create a color cursor.

See SDL_CreateColorCursor for C documentation.

createSystemCursor :: MonadIO m => SystemCursor -> m Cursor Source #

Create system cursor.

See SDL_CreateSystemCursor for C documentation.