{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
module SDL.Input.Joystick
( numJoysticks
, availableJoysticks
, JoystickDevice(..)
, openJoystick
, closeJoystick
, getJoystickID
, Joystick
, JoyButtonState(..)
, buttonPressed
, ballDelta
, axisPosition
, numAxes
, numButtons
, numBalls
, JoyHatPosition(..)
, getHat
, numHats
, JoyDeviceConnection(..)
) where
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Data (Data)
import Data.Int
import Data.Text (Text)
import Data.Traversable (for)
import Data.Typeable
import Data.Word
import Foreign.C.Types
import Foreign.Marshal.Alloc
import Foreign.Storable
import GHC.Generics (Generic)
import SDL.Vect
import SDL.Internal.Exception
import SDL.Internal.Numbered
import SDL.Internal.Types
import qualified Data.ByteString as BS
import qualified Data.Text.Encoding as Text
import qualified Data.Vector as V
import qualified SDL.Raw as Raw
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
data JoystickDevice = JoystickDevice
{ JoystickDevice -> Text
joystickDeviceName :: Text
, JoystickDevice -> CInt
joystickDeviceId :: CInt
} deriving (JoystickDevice -> JoystickDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoystickDevice -> JoystickDevice -> Bool
$c/= :: JoystickDevice -> JoystickDevice -> Bool
== :: JoystickDevice -> JoystickDevice -> Bool
$c== :: JoystickDevice -> JoystickDevice -> Bool
Eq, forall x. Rep JoystickDevice x -> JoystickDevice
forall x. JoystickDevice -> Rep JoystickDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoystickDevice x -> JoystickDevice
$cfrom :: forall x. JoystickDevice -> Rep JoystickDevice x
Generic, ReadPrec [JoystickDevice]
ReadPrec JoystickDevice
Int -> ReadS JoystickDevice
ReadS [JoystickDevice]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JoystickDevice]
$creadListPrec :: ReadPrec [JoystickDevice]
readPrec :: ReadPrec JoystickDevice
$creadPrec :: ReadPrec JoystickDevice
readList :: ReadS [JoystickDevice]
$creadList :: ReadS [JoystickDevice]
readsPrec :: Int -> ReadS JoystickDevice
$creadsPrec :: Int -> ReadS JoystickDevice
Read, Eq JoystickDevice
JoystickDevice -> JoystickDevice -> Bool
JoystickDevice -> JoystickDevice -> Ordering
JoystickDevice -> JoystickDevice -> JoystickDevice
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JoystickDevice -> JoystickDevice -> JoystickDevice
$cmin :: JoystickDevice -> JoystickDevice -> JoystickDevice
max :: JoystickDevice -> JoystickDevice -> JoystickDevice
$cmax :: JoystickDevice -> JoystickDevice -> JoystickDevice
>= :: JoystickDevice -> JoystickDevice -> Bool
$c>= :: JoystickDevice -> JoystickDevice -> Bool
> :: JoystickDevice -> JoystickDevice -> Bool
$c> :: JoystickDevice -> JoystickDevice -> Bool
<= :: JoystickDevice -> JoystickDevice -> Bool
$c<= :: JoystickDevice -> JoystickDevice -> Bool
< :: JoystickDevice -> JoystickDevice -> Bool
$c< :: JoystickDevice -> JoystickDevice -> Bool
compare :: JoystickDevice -> JoystickDevice -> Ordering
$ccompare :: JoystickDevice -> JoystickDevice -> Ordering
Ord, Int -> JoystickDevice -> ShowS
[JoystickDevice] -> ShowS
JoystickDevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoystickDevice] -> ShowS
$cshowList :: [JoystickDevice] -> ShowS
show :: JoystickDevice -> String
$cshow :: JoystickDevice -> String
showsPrec :: Int -> JoystickDevice -> ShowS
$cshowsPrec :: Int -> JoystickDevice -> ShowS
Show, Typeable)
data JoyButtonState = JoyButtonPressed | JoyButtonReleased
deriving (Typeable JoyButtonState
JoyButtonState -> DataType
JoyButtonState -> Constr
(forall b. Data b => b -> b) -> JoyButtonState -> JoyButtonState
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> JoyButtonState -> u
forall u. (forall d. Data d => d -> u) -> JoyButtonState -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyButtonState -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyButtonState -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyButtonState -> m JoyButtonState
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyButtonState -> m JoyButtonState
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyButtonState
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> JoyButtonState -> c JoyButtonState
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyButtonState)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyButtonState)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyButtonState -> m JoyButtonState
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyButtonState -> m JoyButtonState
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyButtonState -> m JoyButtonState
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyButtonState -> m JoyButtonState
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyButtonState -> m JoyButtonState
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyButtonState -> m JoyButtonState
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> JoyButtonState -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> JoyButtonState -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> JoyButtonState -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> JoyButtonState -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyButtonState -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyButtonState -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyButtonState -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyButtonState -> r
gmapT :: (forall b. Data b => b -> b) -> JoyButtonState -> JoyButtonState
$cgmapT :: (forall b. Data b => b -> b) -> JoyButtonState -> JoyButtonState
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyButtonState)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyButtonState)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyButtonState)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyButtonState)
dataTypeOf :: JoyButtonState -> DataType
$cdataTypeOf :: JoyButtonState -> DataType
toConstr :: JoyButtonState -> Constr
$ctoConstr :: JoyButtonState -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyButtonState
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyButtonState
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> JoyButtonState -> c JoyButtonState
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> JoyButtonState -> c JoyButtonState
Data, JoyButtonState -> JoyButtonState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoyButtonState -> JoyButtonState -> Bool
$c/= :: JoyButtonState -> JoyButtonState -> Bool
== :: JoyButtonState -> JoyButtonState -> Bool
$c== :: JoyButtonState -> JoyButtonState -> Bool
Eq, forall x. Rep JoyButtonState x -> JoyButtonState
forall x. JoyButtonState -> Rep JoyButtonState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoyButtonState x -> JoyButtonState
$cfrom :: forall x. JoyButtonState -> Rep JoyButtonState x
Generic, Eq JoyButtonState
JoyButtonState -> JoyButtonState -> Bool
JoyButtonState -> JoyButtonState -> Ordering
JoyButtonState -> JoyButtonState -> JoyButtonState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JoyButtonState -> JoyButtonState -> JoyButtonState
$cmin :: JoyButtonState -> JoyButtonState -> JoyButtonState
max :: JoyButtonState -> JoyButtonState -> JoyButtonState
$cmax :: JoyButtonState -> JoyButtonState -> JoyButtonState
>= :: JoyButtonState -> JoyButtonState -> Bool
$c>= :: JoyButtonState -> JoyButtonState -> Bool
> :: JoyButtonState -> JoyButtonState -> Bool
$c> :: JoyButtonState -> JoyButtonState -> Bool
<= :: JoyButtonState -> JoyButtonState -> Bool
$c<= :: JoyButtonState -> JoyButtonState -> Bool
< :: JoyButtonState -> JoyButtonState -> Bool
$c< :: JoyButtonState -> JoyButtonState -> Bool
compare :: JoyButtonState -> JoyButtonState -> Ordering
$ccompare :: JoyButtonState -> JoyButtonState -> Ordering
Ord, ReadPrec [JoyButtonState]
ReadPrec JoyButtonState
Int -> ReadS JoyButtonState
ReadS [JoyButtonState]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JoyButtonState]
$creadListPrec :: ReadPrec [JoyButtonState]
readPrec :: ReadPrec JoyButtonState
$creadPrec :: ReadPrec JoyButtonState
readList :: ReadS [JoyButtonState]
$creadList :: ReadS [JoyButtonState]
readsPrec :: Int -> ReadS JoyButtonState
$creadsPrec :: Int -> ReadS JoyButtonState
Read, Int -> JoyButtonState -> ShowS
[JoyButtonState] -> ShowS
JoyButtonState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoyButtonState] -> ShowS
$cshowList :: [JoyButtonState] -> ShowS
show :: JoyButtonState -> String
$cshow :: JoyButtonState -> String
showsPrec :: Int -> JoyButtonState -> ShowS
$cshowsPrec :: Int -> JoyButtonState -> ShowS
Show, Typeable)
instance FromNumber JoyButtonState Word8 where
fromNumber :: Word8 -> JoyButtonState
fromNumber Word8
n = case Word8
n of
Word8
Raw.SDL_PRESSED -> JoyButtonState
JoyButtonPressed
Word8
Raw.SDL_RELEASED -> JoyButtonState
JoyButtonReleased
Word8
_ -> JoyButtonState
JoyButtonReleased
numJoysticks :: MonadIO m => m (CInt)
numJoysticks :: forall (m :: Type -> Type). MonadIO m => m CInt
numJoysticks = forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Input.Joystick.availableJoysticks" Text
"SDL_NumJoysticks" forall (m :: Type -> Type). MonadIO m => m CInt
Raw.numJoysticks
availableJoysticks :: MonadIO m => m (V.Vector JoystickDevice)
availableJoysticks :: forall (m :: Type -> Type). MonadIO m => m (Vector JoystickDevice)
availableJoysticks = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
CInt
n <- forall (m :: Type -> Type). MonadIO m => m CInt
numJoysticks
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. [a] -> Vector a
V.fromList) forall a b. (a -> b) -> a -> b
$
forall (t :: Type -> Type) (f :: Type -> Type) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [CInt
0 .. (CInt
n forall a. Num a => a -> a -> a
- CInt
1)] forall a b. (a -> b) -> a -> b
$ \CInt
i -> do
Ptr CChar
cstr <-
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Input.Joystick.availableJoysticks" Text
"SDL_JoystickNameForIndex" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => CInt -> m (Ptr CChar)
Raw.joystickNameForIndex CInt
i
Text
name <- ByteString -> Text
Text.decodeUtf8 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CChar -> IO ByteString
BS.packCString Ptr CChar
cstr
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Text -> CInt -> JoystickDevice
JoystickDevice Text
name CInt
i)
openJoystick :: (Functor m,MonadIO m)
=> JoystickDevice
-> m Joystick
openJoystick :: forall (m :: Type -> Type).
(Functor m, MonadIO m) =>
JoystickDevice -> m Joystick
openJoystick (JoystickDevice Text
_ CInt
x) =
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Joystick -> Joystick
Joystick forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Input.Joystick.openJoystick" Text
"SDL_OpenJoystick" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => CInt -> m Joystick
Raw.joystickOpen CInt
x
closeJoystick :: MonadIO m => Joystick -> m ()
closeJoystick :: forall (m :: Type -> Type). MonadIO m => Joystick -> m ()
closeJoystick (Joystick Joystick
j) = forall (m :: Type -> Type). MonadIO m => Joystick -> m ()
Raw.joystickClose Joystick
j
getJoystickID :: MonadIO m => Joystick -> m Raw.JoystickID
getJoystickID :: forall (m :: Type -> Type). MonadIO m => Joystick -> m JoystickID
getJoystickID (Joystick Joystick
j) =
forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Input.Joystick.getJoystickID" Text
"SDL_JoystickInstanceID" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => Joystick -> m JoystickID
Raw.joystickInstanceID Joystick
j
buttonPressed :: (Functor m, MonadIO m)
=> Joystick
-> CInt
-> m Bool
buttonPressed :: forall (m :: Type -> Type).
(Functor m, MonadIO m) =>
Joystick -> CInt -> m Bool
buttonPressed (Joystick Joystick
j) CInt
buttonIndex = (forall a. Eq a => a -> a -> Bool
== Word8
1) forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: Type -> Type).
MonadIO m =>
Joystick -> CInt -> m Word8
Raw.joystickGetButton Joystick
j CInt
buttonIndex
ballDelta :: MonadIO m
=> Joystick
-> CInt
-> m (V2 CInt)
ballDelta :: forall (m :: Type -> Type).
MonadIO m =>
Joystick -> CInt -> m (V2 CInt)
ballDelta (Joystick Joystick
j) CInt
ballIndex = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
xptr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
yptr -> do
forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m ()
throwIfNeg_ Text
"SDL.Input.Joystick.ballDelta" Text
"SDL_JoystickGetBall" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type).
MonadIO m =>
Joystick -> CInt -> Ptr CInt -> Ptr CInt -> m CInt
Raw.joystickGetBall Joystick
j CInt
ballIndex Ptr CInt
xptr Ptr CInt
yptr
forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
xptr forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
yptr
axisPosition :: MonadIO m => Joystick -> CInt -> m Int16
axisPosition :: forall (m :: Type -> Type).
MonadIO m =>
Joystick -> CInt -> m Int16
axisPosition (Joystick Joystick
j) CInt
axisIndex = forall (m :: Type -> Type).
MonadIO m =>
Joystick -> CInt -> m Int16
Raw.joystickGetAxis Joystick
j CInt
axisIndex
numAxes :: (MonadIO m) => Joystick -> m CInt
numAxes :: forall (m :: Type -> Type). MonadIO m => Joystick -> m CInt
numAxes (Joystick Joystick
j) = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Input.Joystick.numAxis" Text
"SDL_JoystickNumAxes" (forall (m :: Type -> Type). MonadIO m => Joystick -> m CInt
Raw.joystickNumAxes Joystick
j)
numButtons :: (MonadIO m) => Joystick -> m CInt
numButtons :: forall (m :: Type -> Type). MonadIO m => Joystick -> m CInt
numButtons (Joystick Joystick
j) = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Input.Joystick.numButtons" Text
"SDL_JoystickNumButtons" (forall (m :: Type -> Type). MonadIO m => Joystick -> m CInt
Raw.joystickNumButtons Joystick
j)
numBalls :: (MonadIO m) => Joystick -> m CInt
numBalls :: forall (m :: Type -> Type). MonadIO m => Joystick -> m CInt
numBalls (Joystick Joystick
j) = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Input.Joystick.numBalls" Text
"SDL_JoystickNumBalls" (forall (m :: Type -> Type). MonadIO m => Joystick -> m CInt
Raw.joystickNumBalls Joystick
j)
data JoyHatPosition
= HatCentered
| HatUp
| HatRight
| HatDown
| HatLeft
| HatRightUp
| HatRightDown
| HatLeftUp
| HatLeftDown
deriving (Typeable JoyHatPosition
JoyHatPosition -> DataType
JoyHatPosition -> Constr
(forall b. Data b => b -> b) -> JoyHatPosition -> JoyHatPosition
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> JoyHatPosition -> u
forall u. (forall d. Data d => d -> u) -> JoyHatPosition -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyHatPosition -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyHatPosition -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyHatPosition -> m JoyHatPosition
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyHatPosition -> m JoyHatPosition
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyHatPosition
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> JoyHatPosition -> c JoyHatPosition
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyHatPosition)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyHatPosition)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyHatPosition -> m JoyHatPosition
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyHatPosition -> m JoyHatPosition
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyHatPosition -> m JoyHatPosition
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyHatPosition -> m JoyHatPosition
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyHatPosition -> m JoyHatPosition
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyHatPosition -> m JoyHatPosition
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> JoyHatPosition -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> JoyHatPosition -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> JoyHatPosition -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> JoyHatPosition -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyHatPosition -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyHatPosition -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyHatPosition -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyHatPosition -> r
gmapT :: (forall b. Data b => b -> b) -> JoyHatPosition -> JoyHatPosition
$cgmapT :: (forall b. Data b => b -> b) -> JoyHatPosition -> JoyHatPosition
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyHatPosition)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyHatPosition)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyHatPosition)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyHatPosition)
dataTypeOf :: JoyHatPosition -> DataType
$cdataTypeOf :: JoyHatPosition -> DataType
toConstr :: JoyHatPosition -> Constr
$ctoConstr :: JoyHatPosition -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyHatPosition
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyHatPosition
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> JoyHatPosition -> c JoyHatPosition
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> JoyHatPosition -> c JoyHatPosition
Data, JoyHatPosition -> JoyHatPosition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoyHatPosition -> JoyHatPosition -> Bool
$c/= :: JoyHatPosition -> JoyHatPosition -> Bool
== :: JoyHatPosition -> JoyHatPosition -> Bool
$c== :: JoyHatPosition -> JoyHatPosition -> Bool
Eq, forall x. Rep JoyHatPosition x -> JoyHatPosition
forall x. JoyHatPosition -> Rep JoyHatPosition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoyHatPosition x -> JoyHatPosition
$cfrom :: forall x. JoyHatPosition -> Rep JoyHatPosition x
Generic, Eq JoyHatPosition
JoyHatPosition -> JoyHatPosition -> Bool
JoyHatPosition -> JoyHatPosition -> Ordering
JoyHatPosition -> JoyHatPosition -> JoyHatPosition
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JoyHatPosition -> JoyHatPosition -> JoyHatPosition
$cmin :: JoyHatPosition -> JoyHatPosition -> JoyHatPosition
max :: JoyHatPosition -> JoyHatPosition -> JoyHatPosition
$cmax :: JoyHatPosition -> JoyHatPosition -> JoyHatPosition
>= :: JoyHatPosition -> JoyHatPosition -> Bool
$c>= :: JoyHatPosition -> JoyHatPosition -> Bool
> :: JoyHatPosition -> JoyHatPosition -> Bool
$c> :: JoyHatPosition -> JoyHatPosition -> Bool
<= :: JoyHatPosition -> JoyHatPosition -> Bool
$c<= :: JoyHatPosition -> JoyHatPosition -> Bool
< :: JoyHatPosition -> JoyHatPosition -> Bool
$c< :: JoyHatPosition -> JoyHatPosition -> Bool
compare :: JoyHatPosition -> JoyHatPosition -> Ordering
$ccompare :: JoyHatPosition -> JoyHatPosition -> Ordering
Ord, ReadPrec [JoyHatPosition]
ReadPrec JoyHatPosition
Int -> ReadS JoyHatPosition
ReadS [JoyHatPosition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JoyHatPosition]
$creadListPrec :: ReadPrec [JoyHatPosition]
readPrec :: ReadPrec JoyHatPosition
$creadPrec :: ReadPrec JoyHatPosition
readList :: ReadS [JoyHatPosition]
$creadList :: ReadS [JoyHatPosition]
readsPrec :: Int -> ReadS JoyHatPosition
$creadsPrec :: Int -> ReadS JoyHatPosition
Read, Int -> JoyHatPosition -> ShowS
[JoyHatPosition] -> ShowS
JoyHatPosition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoyHatPosition] -> ShowS
$cshowList :: [JoyHatPosition] -> ShowS
show :: JoyHatPosition -> String
$cshow :: JoyHatPosition -> String
showsPrec :: Int -> JoyHatPosition -> ShowS
$cshowsPrec :: Int -> JoyHatPosition -> ShowS
Show, Typeable)
instance FromNumber JoyHatPosition Word8 where
fromNumber :: Word8 -> JoyHatPosition
fromNumber Word8
n = case Word8
n of
Word8
Raw.SDL_HAT_CENTERED -> JoyHatPosition
HatCentered
Word8
Raw.SDL_HAT_UP -> JoyHatPosition
HatUp
Word8
Raw.SDL_HAT_RIGHT -> JoyHatPosition
HatRight
Word8
Raw.SDL_HAT_DOWN -> JoyHatPosition
HatDown
Word8
Raw.SDL_HAT_LEFT -> JoyHatPosition
HatLeft
Word8
Raw.SDL_HAT_RIGHTUP -> JoyHatPosition
HatRightUp
Word8
Raw.SDL_HAT_RIGHTDOWN -> JoyHatPosition
HatRightDown
Word8
Raw.SDL_HAT_LEFTUP -> JoyHatPosition
HatLeftUp
Word8
Raw.SDL_HAT_LEFTDOWN -> JoyHatPosition
HatLeftDown
Word8
_ -> JoyHatPosition
HatCentered
getHat :: (Functor m, MonadIO m)
=> Joystick
-> CInt
-> m JoyHatPosition
getHat :: forall (m :: Type -> Type).
(Functor m, MonadIO m) =>
Joystick -> CInt -> m JoyHatPosition
getHat (Joystick Joystick
j) CInt
hatIndex = forall a b. FromNumber a b => b -> a
fromNumber forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: Type -> Type).
MonadIO m =>
Joystick -> CInt -> m Word8
Raw.joystickGetHat Joystick
j CInt
hatIndex
numHats :: (MonadIO m) => Joystick -> m CInt
numHats :: forall (m :: Type -> Type). MonadIO m => Joystick -> m CInt
numHats (Joystick Joystick
j) = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Input.Joystick.numHats" Text
"SDL_JoystickNumHats" (forall (m :: Type -> Type). MonadIO m => Joystick -> m CInt
Raw.joystickNumHats Joystick
j)
data JoyDeviceConnection = JoyDeviceAdded | JoyDeviceRemoved
deriving (Typeable JoyDeviceConnection
JoyDeviceConnection -> DataType
JoyDeviceConnection -> Constr
(forall b. Data b => b -> b)
-> JoyDeviceConnection -> JoyDeviceConnection
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> JoyDeviceConnection -> u
forall u.
(forall d. Data d => d -> u) -> JoyDeviceConnection -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyDeviceConnection -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyDeviceConnection -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyDeviceConnection -> m JoyDeviceConnection
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyDeviceConnection -> m JoyDeviceConnection
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyDeviceConnection
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> JoyDeviceConnection
-> c JoyDeviceConnection
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyDeviceConnection)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyDeviceConnection)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyDeviceConnection -> m JoyDeviceConnection
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyDeviceConnection -> m JoyDeviceConnection
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyDeviceConnection -> m JoyDeviceConnection
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> JoyDeviceConnection -> m JoyDeviceConnection
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyDeviceConnection -> m JoyDeviceConnection
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> JoyDeviceConnection -> m JoyDeviceConnection
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> JoyDeviceConnection -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> JoyDeviceConnection -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> JoyDeviceConnection -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> JoyDeviceConnection -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyDeviceConnection -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> JoyDeviceConnection -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyDeviceConnection -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> JoyDeviceConnection -> r
gmapT :: (forall b. Data b => b -> b)
-> JoyDeviceConnection -> JoyDeviceConnection
$cgmapT :: (forall b. Data b => b -> b)
-> JoyDeviceConnection -> JoyDeviceConnection
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyDeviceConnection)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c JoyDeviceConnection)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyDeviceConnection)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c JoyDeviceConnection)
dataTypeOf :: JoyDeviceConnection -> DataType
$cdataTypeOf :: JoyDeviceConnection -> DataType
toConstr :: JoyDeviceConnection -> Constr
$ctoConstr :: JoyDeviceConnection -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyDeviceConnection
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c JoyDeviceConnection
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> JoyDeviceConnection
-> c JoyDeviceConnection
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> JoyDeviceConnection
-> c JoyDeviceConnection
Data, JoyDeviceConnection -> JoyDeviceConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
$c/= :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
== :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
$c== :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
Eq, forall x. Rep JoyDeviceConnection x -> JoyDeviceConnection
forall x. JoyDeviceConnection -> Rep JoyDeviceConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoyDeviceConnection x -> JoyDeviceConnection
$cfrom :: forall x. JoyDeviceConnection -> Rep JoyDeviceConnection x
Generic, Eq JoyDeviceConnection
JoyDeviceConnection -> JoyDeviceConnection -> Bool
JoyDeviceConnection -> JoyDeviceConnection -> Ordering
JoyDeviceConnection -> JoyDeviceConnection -> JoyDeviceConnection
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JoyDeviceConnection -> JoyDeviceConnection -> JoyDeviceConnection
$cmin :: JoyDeviceConnection -> JoyDeviceConnection -> JoyDeviceConnection
max :: JoyDeviceConnection -> JoyDeviceConnection -> JoyDeviceConnection
$cmax :: JoyDeviceConnection -> JoyDeviceConnection -> JoyDeviceConnection
>= :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
$c>= :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
> :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
$c> :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
<= :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
$c<= :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
< :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
$c< :: JoyDeviceConnection -> JoyDeviceConnection -> Bool
compare :: JoyDeviceConnection -> JoyDeviceConnection -> Ordering
$ccompare :: JoyDeviceConnection -> JoyDeviceConnection -> Ordering
Ord, ReadPrec [JoyDeviceConnection]
ReadPrec JoyDeviceConnection
Int -> ReadS JoyDeviceConnection
ReadS [JoyDeviceConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JoyDeviceConnection]
$creadListPrec :: ReadPrec [JoyDeviceConnection]
readPrec :: ReadPrec JoyDeviceConnection
$creadPrec :: ReadPrec JoyDeviceConnection
readList :: ReadS [JoyDeviceConnection]
$creadList :: ReadS [JoyDeviceConnection]
readsPrec :: Int -> ReadS JoyDeviceConnection
$creadsPrec :: Int -> ReadS JoyDeviceConnection
Read, Int -> JoyDeviceConnection -> ShowS
[JoyDeviceConnection] -> ShowS
JoyDeviceConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoyDeviceConnection] -> ShowS
$cshowList :: [JoyDeviceConnection] -> ShowS
show :: JoyDeviceConnection -> String
$cshow :: JoyDeviceConnection -> String
showsPrec :: Int -> JoyDeviceConnection -> ShowS
$cshowsPrec :: Int -> JoyDeviceConnection -> ShowS
Show, Typeable)
instance FromNumber JoyDeviceConnection Word32 where
fromNumber :: Word32 -> JoyDeviceConnection
fromNumber Word32
n = case Word32
n of
Word32
Raw.SDL_JOYDEVICEADDED -> JoyDeviceConnection
JoyDeviceAdded
Word32
Raw.SDL_JOYDEVICEREMOVED -> JoyDeviceConnection
JoyDeviceRemoved
Word32
_ -> JoyDeviceConnection
JoyDeviceAdded