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.GameController

Synopsis

Documentation

data ControllerButton Source #

Identifies a gamepad button.

Instances

Instances details
Data ControllerButton Source # 
Instance details

Defined in SDL.Input.GameController

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 :: forall r r'. (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 #

Generic ControllerButton Source # 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerButton :: Type -> Type #

Read ControllerButton Source # 
Instance details

Defined in SDL.Input.GameController

Show ControllerButton Source # 
Instance details

Defined in SDL.Input.GameController

Eq ControllerButton Source # 
Instance details

Defined in SDL.Input.GameController

Ord ControllerButton Source # 
Instance details

Defined in SDL.Input.GameController

FromNumber ControllerButton Int32 Source # 
Instance details

Defined in SDL.Input.GameController

ToNumber ControllerButton Int32 Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerButton Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerButton = D1 ('MetaData "ControllerButton" "SDL.Input.GameController" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) ((((C1 ('MetaCons "ControllerButtonInvalid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonA" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerButtonB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ControllerButtonY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonBack" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerButtonGuide" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonStart" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ControllerButtonLeftStick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonRightStick" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerButtonLeftShoulder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonRightShoulder" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ControllerButtonDpadUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonDpadDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerButtonDpadLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonDpadRight" 'PrefixI 'False) (U1 :: Type -> Type)))))

data ControllerButtonState Source #

Identifies the state of a controller button.

Instances

Instances details
Data ControllerButtonState Source # 
Instance details

Defined in SDL.Input.GameController

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 :: forall r r'. (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 #

Generic ControllerButtonState Source # 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerButtonState :: Type -> Type #

Read ControllerButtonState Source # 
Instance details

Defined in SDL.Input.GameController

Show ControllerButtonState Source # 
Instance details

Defined in SDL.Input.GameController

Eq ControllerButtonState Source # 
Instance details

Defined in SDL.Input.GameController

Ord ControllerButtonState Source # 
Instance details

Defined in SDL.Input.GameController

FromNumber ControllerButtonState Word32 Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerButtonState Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerButtonState = D1 ('MetaData "ControllerButtonState" "SDL.Input.GameController" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) (C1 ('MetaCons "ControllerButtonPressed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ControllerButtonReleased" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonInvalidState" 'PrefixI 'False) (U1 :: Type -> Type)))

data ControllerDeviceConnection Source #

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

Instances

Instances details
Data ControllerDeviceConnection Source # 
Instance details

Defined in SDL.Input.GameController

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 :: forall r r'. (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 #

Generic ControllerDeviceConnection Source # 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerDeviceConnection :: Type -> Type #

Read ControllerDeviceConnection Source # 
Instance details

Defined in SDL.Input.GameController

Show ControllerDeviceConnection Source # 
Instance details

Defined in SDL.Input.GameController

Eq ControllerDeviceConnection Source # 
Instance details

Defined in SDL.Input.GameController

Ord ControllerDeviceConnection Source # 
Instance details

Defined in SDL.Input.GameController

FromNumber ControllerDeviceConnection Word32 Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerDeviceConnection Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerDeviceConnection = D1 ('MetaData "ControllerDeviceConnection" "SDL.Input.GameController" "sdl2-2.5.4.0-5A9XhcdhV3E4H3BzTUoh7w" 'False) (C1 ('MetaCons "ControllerDeviceAdded" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ControllerDeviceRemoved" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerDeviceRemapped" 'PrefixI 'False) (U1 :: Type -> Type)))