sdl2-2.4.1.0: Both high- and low-level bindings to the SDL library (version 2.0.4+).

Safe HaskellSafe
LanguageHaskell2010

SDL.Input.GameController

Synopsis

Documentation

data ControllerButton Source #

Identifies a gamepad button.

Instances

Eq ControllerButton Source # 
Data ControllerButton Source # 

Methods

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

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

toConstr :: ControllerButton -> Constr #

dataTypeOf :: ControllerButton -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ControllerButton Source # 
Read ControllerButton Source # 
Show ControllerButton Source # 
Generic ControllerButton Source # 
FromNumber ControllerButton Int32 Source # 
type Rep ControllerButton Source # 
type Rep ControllerButton = D1 * (MetaData "ControllerButton" "SDL.Input.GameController" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ControllerButtonInvalid" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonA" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ControllerButtonB" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonX" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "ControllerButtonY" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonBack" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ControllerButtonGuide" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonStart" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ControllerButtonLeftStick" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonRightStick" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ControllerButtonLeftShoulder" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonRightShoulder" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "ControllerButtonDpadUp" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonDpadDown" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ControllerButtonDpadLeft" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonDpadRight" PrefixI False) (U1 *))))))

data ControllerButtonState Source #

Identifies the state of a controller button.

Instances

Eq ControllerButtonState Source # 
Data ControllerButtonState Source # 

Methods

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

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

toConstr :: ControllerButtonState -> Constr #

dataTypeOf :: ControllerButtonState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ControllerButtonState Source # 
Read ControllerButtonState Source # 
Show ControllerButtonState Source # 
Generic ControllerButtonState Source # 
FromNumber ControllerButtonState Word32 Source # 
type Rep ControllerButtonState Source # 
type Rep ControllerButtonState = D1 * (MetaData "ControllerButtonState" "SDL.Input.GameController" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * (C1 * (MetaCons "ControllerButtonPressed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ControllerButtonReleased" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerButtonInvalidState" PrefixI False) (U1 *))))

data ControllerDeviceConnection Source #

Identified whether the game controller was added, removed, or remapped.

Instances

Eq ControllerDeviceConnection Source # 
Data ControllerDeviceConnection Source # 

Methods

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

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

toConstr :: ControllerDeviceConnection -> Constr #

dataTypeOf :: ControllerDeviceConnection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ControllerDeviceConnection Source # 
Read ControllerDeviceConnection Source # 
Show ControllerDeviceConnection Source # 
Generic ControllerDeviceConnection Source # 
FromNumber ControllerDeviceConnection Word32 Source # 
type Rep ControllerDeviceConnection Source # 
type Rep ControllerDeviceConnection = D1 * (MetaData "ControllerDeviceConnection" "SDL.Input.GameController" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * (C1 * (MetaCons "ControllerDeviceAdded" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ControllerDeviceRemoved" PrefixI False) (U1 *)) (C1 * (MetaCons "ControllerDeviceRemapped" PrefixI False) (U1 *))))