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

Safe HaskellNone
LanguageHaskell2010

SDL.Input.Joystick

Synopsis

Documentation

numJoysticks :: MonadIO m => m CInt Source #

Count the number of joysticks attached to the system.

See SDL_NumJoysticks for C documentation.

availableJoysticks :: MonadIO m => m (Vector JoystickDevice) Source #

Enumerate all connected joysticks, retrieving a description of each.

data JoystickDevice Source #

A description of joystick that can be opened using openJoystick. To retrieve a list of connected joysticks, use availableJoysticks.

Instances

Eq JoystickDevice Source # 
Ord JoystickDevice Source # 
Read JoystickDevice Source # 
Show JoystickDevice Source # 
Generic JoystickDevice Source # 

Associated Types

type Rep JoystickDevice :: * -> * #

type Rep JoystickDevice Source # 
type Rep JoystickDevice = D1 (MetaData "JoystickDevice" "SDL.Input.Joystick" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) (C1 (MetaCons "JoystickDevice" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "joystickDeviceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "joystickDeviceId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CInt))))

openJoystick Source #

Arguments

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

The device to open. Use availableJoysticks to find JoystickDevicess

-> m Joystick 

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

See SDL_JoystickOpen for C documentation.

closeJoystick :: MonadIO m => Joystick -> m () Source #

Close a joystick previously opened with openJoystick.

See SDL_JoystickClose for C documentation.

getJoystickID :: MonadIO m => Joystick -> m Int32 Source #

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

See SDL_JoystickInstanceID for C documentation.

data Joystick Source #

Instances

Eq Joystick Source # 
Data Joystick Source # 

Methods

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

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

toConstr :: Joystick -> Constr #

dataTypeOf :: Joystick -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Joystick Source # 
Show Joystick Source # 
Generic Joystick Source # 

Associated Types

type Rep Joystick :: * -> * #

Methods

from :: Joystick -> Rep Joystick x #

to :: Rep Joystick x -> Joystick #

type Rep Joystick Source # 
type Rep Joystick = D1 (MetaData "Joystick" "SDL.Internal.Types" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" True) (C1 (MetaCons "Joystick" PrefixI True) (S1 (MetaSel (Just Symbol "joystickPtr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Joystick)))

buttonPressed Source #

Arguments

:: (Functor m, MonadIO m) 
=> Joystick 
-> CInt

The index of the button. You can use numButtons to determine how many buttons a given joystick has.

-> m Bool 

Determine if a given button is currently held.

See SDL_JoystickGetButton for C documentation.

ballDelta Source #

Arguments

:: MonadIO m 
=> Joystick 
-> CInt

The index of the joystick ball. You can use numBalls to determine how many balls a given joystick has.

-> m (V2 CInt) 

Get the ball axis change since the last poll.

See SDL_JoystickGetBall for C documentation.

axisPosition :: MonadIO m => Joystick -> CInt -> m Int16 Source #

Get the current state of an axis control on a joystick.

Returns a 16-bit signed integer representing the current position of the axis. The state is a value ranging from -32768 to 32767.

On most modern joysticks the x-axis is usually represented by axis 0 and the y-axis by axis 1. The value returned by axisPosition is a signed integer (-32768 to 32767) representing the current position of the axis. It may be necessary to impose certain tolerances on these values to account for jitter.

Some joysticks use axes 2 and 3 for extra buttons.

See SDL_JoystickGetAxis for C documentation.

numAxes :: MonadIO m => Joystick -> m CInt Source #

Get the number of general axis controls on a joystick.

See SDL_JoystickNumAxes for C documentation.

numButtons :: MonadIO m => Joystick -> m CInt Source #

Get the number of buttons on a joystick.

See SDL_JoystickNumButtons for C documentation.

numBalls :: MonadIO m => Joystick -> m CInt Source #

Get the number of trackballs on a joystick.

See SDL_JoystickNumBalls for C documentation.

data JoyHatPosition Source #

Identifies the state of the POV hat on a joystick.

Constructors

HatCentered

Centered position

HatUp

Up position

HatRight

Right position

HatDown

Down position

HatLeft

Left position

HatRightUp

Right-up position

HatRightDown

Right-down position

HatLeftUp

Left-up position

HatLeftDown

Left-down position

Instances

Eq JoyHatPosition Source # 
Data JoyHatPosition Source # 

Methods

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

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

toConstr :: JoyHatPosition -> Constr #

dataTypeOf :: JoyHatPosition -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JoyHatPosition Source # 
Read JoyHatPosition Source # 
Show JoyHatPosition Source # 
Generic JoyHatPosition Source # 

Associated Types

type Rep JoyHatPosition :: * -> * #

FromNumber JoyHatPosition Word8 Source # 
type Rep JoyHatPosition Source # 
type Rep JoyHatPosition = D1 (MetaData "JoyHatPosition" "SDL.Input.Joystick" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "HatCentered" PrefixI False) U1) (C1 (MetaCons "HatUp" PrefixI False) U1)) ((:+:) (C1 (MetaCons "HatRight" PrefixI False) U1) (C1 (MetaCons "HatDown" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "HatLeft" PrefixI False) U1) (C1 (MetaCons "HatRightUp" PrefixI False) U1)) ((:+:) (C1 (MetaCons "HatRightDown" PrefixI False) U1) ((:+:) (C1 (MetaCons "HatLeftUp" PrefixI False) U1) (C1 (MetaCons "HatLeftDown" PrefixI False) U1)))))

getHat Source #

Arguments

:: (Functor m, MonadIO m) 
=> Joystick 
-> CInt

The index of the POV hat. You can use numHats to determine how many POV hats a given joystick has.

-> m JoyHatPosition 

Get current position of a POV hat on a joystick.

See SDL_JoystickGetHat for C documentation.

numHats :: MonadIO m => Joystick -> m CInt Source #

Get the number of POV hats on a joystick.

See SDL_JoystickNumHats for C documentation.