| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
SDL.Input.Joystick
Synopsis
- numJoysticks :: MonadIO m => m CInt
- availableJoysticks :: MonadIO m => m (Vector JoystickDevice)
- data JoystickDevice = JoystickDevice {}
- openJoystick :: (Functor m, MonadIO m) => JoystickDevice -> m Joystick
- closeJoystick :: MonadIO m => Joystick -> m ()
- getJoystickID :: MonadIO m => Joystick -> m Int32
- data Joystick
- data JoyButtonState
- buttonPressed :: (Functor m, MonadIO m) => Joystick -> CInt -> m Bool
- ballDelta :: MonadIO m => Joystick -> CInt -> m (V2 CInt)
- axisPosition :: MonadIO m => Joystick -> CInt -> m Int16
- numAxes :: MonadIO m => Joystick -> m CInt
- numButtons :: MonadIO m => Joystick -> m CInt
- numBalls :: MonadIO m => Joystick -> m CInt
- data JoyHatPosition
- getHat :: (Functor m, MonadIO m) => Joystick -> CInt -> m JoyHatPosition
- numHats :: MonadIO m => Joystick -> m CInt
- data JoyDeviceConnection
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.
Constructors
| JoystickDevice | |
| Fields | |
Instances
Arguments
| :: (Functor m, MonadIO m) | |
| => JoystickDevice | The device to open. Use  | 
| -> 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.
Instances
| Eq Joystick Source # | |
| Data Joystick Source # | |
| Defined in SDL.Internal.Types 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 :: forall r r'. (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 # | |
| Defined in SDL.Internal.Types | |
| Show Joystick Source # | |
| Generic Joystick Source # | |
| type Rep Joystick Source # | |
| Defined in SDL.Internal.Types | |
data JoyButtonState Source #
Identifies the state of a joystick button.
Constructors
| JoyButtonPressed | |
| JoyButtonReleased | 
Instances
Arguments
| :: (Functor m, MonadIO m) | |
| => Joystick | |
| -> CInt | The index of the button. You can use  | 
| -> m Bool | 
Determine if a given button is currently held.
See SDL_JoystickGetButton for C documentation.
Arguments
| :: MonadIO m | |
| => Joystick | |
| -> CInt | The index of the joystick ball. You can use  | 
| -> 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
Arguments
| :: (Functor m, MonadIO m) | |
| => Joystick | |
| -> CInt | The index of the POV hat. You can use  | 
| -> 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.
data JoyDeviceConnection Source #
Identifies whether a joystick has been connected or disconnected.
Constructors
| JoyDeviceAdded | |
| JoyDeviceRemoved |