sdl2-2.5.5.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 ControllerDevice Source #

A description of game controller that can be opened using openController. To retrieve a list of connected game controllers, use availableControllers.

Instances

Instances details
Generic ControllerDevice Source # 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerDevice :: Type -> Type Source #

Read ControllerDevice Source # 
Instance details

Defined in SDL.Input.GameController

Show ControllerDevice Source # 
Instance details

Defined in SDL.Input.GameController

Eq ControllerDevice Source # 
Instance details

Defined in SDL.Input.GameController

Ord ControllerDevice Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerDevice Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerDevice = D1 ('MetaData "ControllerDevice" "SDL.Input.GameController" "sdl2-2.5.5.0-inplace" 'False) (C1 ('MetaCons "ControllerDevice" 'PrefixI 'True) (S1 ('MetaSel ('Just "gameControllerDeviceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "gameControllerDeviceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))

availableControllers :: MonadIO m => m (Vector ControllerDevice) Source #

Enumerate all connected Controllers, retrieving a description of each.

openController Source #

Arguments

:: (Functor m, MonadIO m) 
=> ControllerDevice

The device to open. Use availableControllers to find JoystickDevicess

-> m GameController 

Open a controller so that you can start receiving events from interaction with this controller.

See SDL_GameControllerOpen for C documentation.

closeController :: MonadIO m => GameController -> m () Source #

Close a controller previously opened with openController.

See SDL_GameControllerClose for C documentation.

controllerAttached :: MonadIO m => GameController -> m Bool Source #

Check if a controller has been opened and is currently connected.

See SDL_GameControllerGetAttached for C documentation.

getControllerID :: MonadIO m => GameController -> m Int32 Source #

Get the instance ID of an opened controller. The instance ID is used to identify the controller in future SDL events.

See SDL_GameControllerInstanceID for C documentation.

controllerMapping :: MonadIO m => GameController -> m Text Source #

Get the current mapping of a Game Controller.

See SDL_GameControllerMapping for C documentation.

addControllerMapping :: MonadIO m => ByteString -> m () Source #

Add support for controllers that SDL is unaware of or to cause an existing controller to have a different binding.

See SDL_GameControllerAddMapping for C documentation.

addControllerMappingsFromFile :: MonadIO m => FilePath -> m () Source #

Use this function to load a set of Game Controller mappings from a file, filtered by the current SDL_GetPlatform(). A community sourced database of controllers is available here (on GitHub).

See SDL_GameControllerAddMappingsFromFile for C 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 Source #

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

toConstr :: ControllerButton -> Constr Source #

dataTypeOf :: ControllerButton -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic ControllerButton Source # 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerButton :: Type -> Type Source #

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.5.0-inplace" '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 Source #

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

toConstr :: ControllerButtonState -> Constr Source #

dataTypeOf :: ControllerButtonState -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic ControllerButtonState Source # 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerButtonState :: Type -> Type Source #

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.5.0-inplace" '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)))

controllerButton :: MonadIO m => GameController -> ControllerButton -> m ControllerButtonState Source #

Get the current state of a button on a game controller.

See SDL_GameControllerGetButton for C documentation.

data ControllerAxis Source #

Instances

Instances details
Data ControllerAxis 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) -> ControllerAxis -> c ControllerAxis Source #

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

toConstr :: ControllerAxis -> Constr Source #

dataTypeOf :: ControllerAxis -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic ControllerAxis Source # 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerAxis :: Type -> Type Source #

Read ControllerAxis Source # 
Instance details

Defined in SDL.Input.GameController

Show ControllerAxis Source # 
Instance details

Defined in SDL.Input.GameController

Eq ControllerAxis Source # 
Instance details

Defined in SDL.Input.GameController

Ord ControllerAxis Source # 
Instance details

Defined in SDL.Input.GameController

FromNumber ControllerAxis Int32 Source # 
Instance details

Defined in SDL.Input.GameController

ToNumber ControllerAxis Int32 Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerAxis Source # 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerAxis = D1 ('MetaData "ControllerAxis" "SDL.Input.GameController" "sdl2-2.5.5.0-inplace" 'False) (((C1 ('MetaCons "ControllerAxisInvalid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerAxisLeftX" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerAxisLeftY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerAxisRightX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ControllerAxisRightY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerAxisTriggerLeft" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerAxisTriggerRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerAxisMax" 'PrefixI 'False) (U1 :: Type -> Type))))

controllerAxis :: MonadIO m => GameController -> ControllerAxis -> m Int16 Source #

Get the current state of an axis control on a game controller.

See SDL_GameControllerGetAxis for C documentation.

data ControllerDeviceConnection Source #

Identifies 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 Source #

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

toConstr :: ControllerDeviceConnection -> Constr Source #

dataTypeOf :: ControllerDeviceConnection -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic ControllerDeviceConnection Source # 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerDeviceConnection :: Type -> Type Source #

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.5.0-inplace" '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)))