{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
module SDL.Input.GameController
  ( ControllerDevice (..)
  , availableControllers
  , openController
  , closeController
  , controllerAttached
  , getControllerID
  , controllerMapping
  , addControllerMapping
  , addControllerMappingsFromFile
  , ControllerButton (..)
  , ControllerButtonState (..)
  , controllerButton
  , ControllerAxis (..)
  , controllerAxis
  
  , ControllerDeviceConnection (..)
  ) where
import Control.Monad (filterM)
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 (withCString)
import Foreign.C.Types
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc
import Foreign.Ptr
import Foreign.Storable
import GHC.Generics (Generic)
import GHC.Int (Int32)
import SDL.Input.Joystick (numJoysticks)
import SDL.Internal.Exception
import SDL.Internal.Numbered
import SDL.Internal.Types
import SDL.Vect
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BSI
import qualified SDL.Raw as Raw
import qualified Data.Text.Encoding as Text
import qualified Data.Vector as V
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
data ControllerDevice = ControllerDevice
  { ControllerDevice -> Text
gameControllerDeviceName :: Text
  , ControllerDevice -> CInt
gameControllerDeviceId :: CInt
  }
  deriving (ControllerDevice -> ControllerDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ControllerDevice -> ControllerDevice -> Bool
$c/= :: ControllerDevice -> ControllerDevice -> Bool
== :: ControllerDevice -> ControllerDevice -> Bool
$c== :: ControllerDevice -> ControllerDevice -> Bool
Eq, forall x. Rep ControllerDevice x -> ControllerDevice
forall x. ControllerDevice -> Rep ControllerDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ControllerDevice x -> ControllerDevice
$cfrom :: forall x. ControllerDevice -> Rep ControllerDevice x
Generic, ReadPrec [ControllerDevice]
ReadPrec ControllerDevice
Int -> ReadS ControllerDevice
ReadS [ControllerDevice]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ControllerDevice]
$creadListPrec :: ReadPrec [ControllerDevice]
readPrec :: ReadPrec ControllerDevice
$creadPrec :: ReadPrec ControllerDevice
readList :: ReadS [ControllerDevice]
$creadList :: ReadS [ControllerDevice]
readsPrec :: Int -> ReadS ControllerDevice
$creadsPrec :: Int -> ReadS ControllerDevice
Read, Eq ControllerDevice
ControllerDevice -> ControllerDevice -> Bool
ControllerDevice -> ControllerDevice -> Ordering
ControllerDevice -> ControllerDevice -> ControllerDevice
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 :: ControllerDevice -> ControllerDevice -> ControllerDevice
$cmin :: ControllerDevice -> ControllerDevice -> ControllerDevice
max :: ControllerDevice -> ControllerDevice -> ControllerDevice
$cmax :: ControllerDevice -> ControllerDevice -> ControllerDevice
>= :: ControllerDevice -> ControllerDevice -> Bool
$c>= :: ControllerDevice -> ControllerDevice -> Bool
> :: ControllerDevice -> ControllerDevice -> Bool
$c> :: ControllerDevice -> ControllerDevice -> Bool
<= :: ControllerDevice -> ControllerDevice -> Bool
$c<= :: ControllerDevice -> ControllerDevice -> Bool
< :: ControllerDevice -> ControllerDevice -> Bool
$c< :: ControllerDevice -> ControllerDevice -> Bool
compare :: ControllerDevice -> ControllerDevice -> Ordering
$ccompare :: ControllerDevice -> ControllerDevice -> Ordering
Ord, Int -> ControllerDevice -> ShowS
[ControllerDevice] -> ShowS
ControllerDevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ControllerDevice] -> ShowS
$cshowList :: [ControllerDevice] -> ShowS
show :: ControllerDevice -> String
$cshow :: ControllerDevice -> String
showsPrec :: Int -> ControllerDevice -> ShowS
$cshowsPrec :: Int -> ControllerDevice -> ShowS
Show, Typeable)
availableControllers :: MonadIO m => m (V.Vector ControllerDevice)
availableControllers :: forall (m :: Type -> Type).
MonadIO m =>
m (Vector ControllerDevice)
availableControllers = 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
  [CInt]
indices <- forall (m :: Type -> Type) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM forall (m :: Type -> Type). MonadIO m => CInt -> m Bool
Raw.isGameController [CInt
0 .. (CInt
n forall a. Num a => a -> a -> a
- CInt
1)]
  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]
indices 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.Controller.availableGameControllers" Text
"SDL_GameControllerNameForIndex" forall a b. (a -> b) -> a -> b
$
        forall (m :: Type -> Type). MonadIO m => CInt -> m (Ptr CChar)
Raw.gameControllerNameForIndex 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 -> ControllerDevice
ControllerDevice Text
name CInt
i)
openController
  :: (Functor m, MonadIO m)
  => ControllerDevice
  
  -> m GameController
openController :: forall (m :: Type -> Type).
(Functor m, MonadIO m) =>
ControllerDevice -> m GameController
openController (ControllerDevice Text
_ CInt
x) =
  forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap GameController -> GameController
GameController 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.GameController.openController" Text
"SDL_GameControllerOpen" forall a b. (a -> b) -> a -> b
$
      forall (m :: Type -> Type). MonadIO m => CInt -> m GameController
Raw.gameControllerOpen CInt
x
closeController :: MonadIO m => GameController -> m ()
closeController :: forall (m :: Type -> Type). MonadIO m => GameController -> m ()
closeController (GameController GameController
j) = forall (m :: Type -> Type). MonadIO m => GameController -> m ()
Raw.gameControllerClose GameController
j
controllerAttached :: MonadIO m => GameController -> m Bool
controllerAttached :: forall (m :: Type -> Type). MonadIO m => GameController -> m Bool
controllerAttached (GameController GameController
c) = forall (m :: Type -> Type). MonadIO m => GameController -> m Bool
Raw.gameControllerGetAttached GameController
c
getControllerID :: MonadIO m => GameController -> m Int32
getControllerID :: forall (m :: Type -> Type). MonadIO m => GameController -> m Int32
getControllerID (GameController GameController
c) =
  forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Input.GameController.getControllerID" Text
"SDL_JoystickInstanceID" forall a b. (a -> b) -> a -> b
$
    forall (m :: Type -> Type). MonadIO m => GameController -> m Int32
Raw.joystickInstanceID GameController
c
controllerMapping :: MonadIO m => GameController -> m Text
controllerMapping :: forall (m :: Type -> Type). MonadIO m => GameController -> m Text
controllerMapping (GameController GameController
c) = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  Ptr CChar
mapping <-
    forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Input.GameController.getControllerMapping" Text
"SDL_GameControllerMapping" forall a b. (a -> b) -> a -> b
$
      forall (m :: Type -> Type).
MonadIO m =>
GameController -> m (Ptr CChar)
Raw.gameControllerMapping GameController
c
  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
mapping
addControllerMapping :: MonadIO m => BS.ByteString -> m ()
addControllerMapping :: forall (m :: Type -> Type). MonadIO m => ByteString -> m ()
addControllerMapping ByteString
mapping =
  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 ()
throwIfNeg_ Text
"SDL.Input.GameController.addControllerMapping" Text
"SDL_GameControllerAddMapping" forall a b. (a -> b) -> a -> b
$
      let (ForeignPtr Word8
mappingForeign, Int
_, Int
_) = ByteString -> (ForeignPtr Word8, Int, Int)
BSI.toForeignPtr ByteString
mapping
       in forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
mappingForeign forall a b. (a -> b) -> a -> b
$ \Ptr Word8
mappingPtr ->
            forall (m :: Type -> Type). MonadIO m => Ptr CChar -> m CInt
Raw.gameControllerAddMapping (forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
mappingPtr)
addControllerMappingsFromFile :: MonadIO m => FilePath -> m ()
addControllerMappingsFromFile :: forall (m :: Type -> Type). MonadIO m => String -> m ()
addControllerMappingsFromFile String
mappingFile =
  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 ()
throwIfNeg_ Text
"SDL.Input.GameController.addControllerMappingsFromFile" Text
"SDL_GameControllerAddMappingsFromFile" forall a b. (a -> b) -> a -> b
$
      forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
mappingFile forall (m :: Type -> Type). MonadIO m => Ptr CChar -> m CInt
Raw.gameControllerAddMappingsFromFile
controllerAxis :: MonadIO m => GameController -> ControllerAxis -> m Int16
controllerAxis :: forall (m :: Type -> Type).
MonadIO m =>
GameController -> ControllerAxis -> m Int16
controllerAxis (GameController GameController
c) ControllerAxis
axis =
  forall (m :: Type -> Type).
MonadIO m =>
GameController -> Int32 -> m Int16
Raw.gameControllerGetAxis GameController
c (forall a b. ToNumber a b => a -> b
toNumber ControllerAxis
axis)
controllerButton :: MonadIO m => GameController -> ControllerButton -> m ControllerButtonState
controllerButton :: forall (m :: Type -> Type).
MonadIO m =>
GameController -> ControllerButton -> m ControllerButtonState
controllerButton (GameController GameController
c) ControllerButton
button =
  forall a b. FromNumber a b => b -> a
fromNumber forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: Type -> Type).
MonadIO m =>
GameController -> Int32 -> m Word8
Raw.gameControllerGetButton GameController
c (forall a b. ToNumber a b => a -> b
toNumber ControllerButton
button)
data ControllerButton
  = ControllerButtonInvalid
  | ControllerButtonA
  | ControllerButtonB
  | ControllerButtonX
  | ControllerButtonY
  | ControllerButtonBack
  | ControllerButtonGuide
  | ControllerButtonStart
  | ControllerButtonLeftStick
  | ControllerButtonRightStick
  | ControllerButtonLeftShoulder
  | ControllerButtonRightShoulder
  | ControllerButtonDpadUp
  | ControllerButtonDpadDown
  | ControllerButtonDpadLeft
  | ControllerButtonDpadRight
  deriving (Typeable ControllerButton
ControllerButton -> DataType
ControllerButton -> Constr
(forall b. Data b => b -> b)
-> ControllerButton -> ControllerButton
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) -> ControllerButton -> u
forall u. (forall d. Data d => d -> u) -> ControllerButton -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButton -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButton -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerButton -> m ControllerButton
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButton -> m ControllerButton
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerButton
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ControllerButton -> c ControllerButton
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerButton)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerButton)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButton -> m ControllerButton
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButton -> m ControllerButton
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButton -> m ControllerButton
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButton -> m ControllerButton
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerButton -> m ControllerButton
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerButton -> m ControllerButton
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ControllerButton -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ControllerButton -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ControllerButton -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ControllerButton -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButton -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButton -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButton -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButton -> r
gmapT :: (forall b. Data b => b -> b)
-> ControllerButton -> ControllerButton
$cgmapT :: (forall b. Data b => b -> b)
-> ControllerButton -> ControllerButton
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerButton)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerButton)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerButton)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerButton)
dataTypeOf :: ControllerButton -> DataType
$cdataTypeOf :: ControllerButton -> DataType
toConstr :: ControllerButton -> Constr
$ctoConstr :: ControllerButton -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerButton
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerButton
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ControllerButton -> c ControllerButton
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ControllerButton -> c ControllerButton
Data, ControllerButton -> ControllerButton -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ControllerButton -> ControllerButton -> Bool
$c/= :: ControllerButton -> ControllerButton -> Bool
== :: ControllerButton -> ControllerButton -> Bool
$c== :: ControllerButton -> ControllerButton -> Bool
Eq, forall x. Rep ControllerButton x -> ControllerButton
forall x. ControllerButton -> Rep ControllerButton x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ControllerButton x -> ControllerButton
$cfrom :: forall x. ControllerButton -> Rep ControllerButton x
Generic, Eq ControllerButton
ControllerButton -> ControllerButton -> Bool
ControllerButton -> ControllerButton -> Ordering
ControllerButton -> ControllerButton -> ControllerButton
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 :: ControllerButton -> ControllerButton -> ControllerButton
$cmin :: ControllerButton -> ControllerButton -> ControllerButton
max :: ControllerButton -> ControllerButton -> ControllerButton
$cmax :: ControllerButton -> ControllerButton -> ControllerButton
>= :: ControllerButton -> ControllerButton -> Bool
$c>= :: ControllerButton -> ControllerButton -> Bool
> :: ControllerButton -> ControllerButton -> Bool
$c> :: ControllerButton -> ControllerButton -> Bool
<= :: ControllerButton -> ControllerButton -> Bool
$c<= :: ControllerButton -> ControllerButton -> Bool
< :: ControllerButton -> ControllerButton -> Bool
$c< :: ControllerButton -> ControllerButton -> Bool
compare :: ControllerButton -> ControllerButton -> Ordering
$ccompare :: ControllerButton -> ControllerButton -> Ordering
Ord, ReadPrec [ControllerButton]
ReadPrec ControllerButton
Int -> ReadS ControllerButton
ReadS [ControllerButton]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ControllerButton]
$creadListPrec :: ReadPrec [ControllerButton]
readPrec :: ReadPrec ControllerButton
$creadPrec :: ReadPrec ControllerButton
readList :: ReadS [ControllerButton]
$creadList :: ReadS [ControllerButton]
readsPrec :: Int -> ReadS ControllerButton
$creadsPrec :: Int -> ReadS ControllerButton
Read, Int -> ControllerButton -> ShowS
[ControllerButton] -> ShowS
ControllerButton -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ControllerButton] -> ShowS
$cshowList :: [ControllerButton] -> ShowS
show :: ControllerButton -> String
$cshow :: ControllerButton -> String
showsPrec :: Int -> ControllerButton -> ShowS
$cshowsPrec :: Int -> ControllerButton -> ShowS
Show, Typeable)
instance FromNumber ControllerButton Int32 where
  fromNumber :: Int32 -> ControllerButton
fromNumber Int32
n = case Int32
n of
    Int32
Raw.SDL_CONTROLLER_BUTTON_A -> ControllerButton
ControllerButtonA
    Int32
Raw.SDL_CONTROLLER_BUTTON_B -> ControllerButton
ControllerButtonB
    Int32
Raw.SDL_CONTROLLER_BUTTON_X -> ControllerButton
ControllerButtonX
    Int32
Raw.SDL_CONTROLLER_BUTTON_Y -> ControllerButton
ControllerButtonY
    Int32
Raw.SDL_CONTROLLER_BUTTON_BACK -> ControllerButton
ControllerButtonBack
    Int32
Raw.SDL_CONTROLLER_BUTTON_GUIDE -> ControllerButton
ControllerButtonGuide
    Int32
Raw.SDL_CONTROLLER_BUTTON_START -> ControllerButton
ControllerButtonStart
    Int32
Raw.SDL_CONTROLLER_BUTTON_LEFTSTICK -> ControllerButton
ControllerButtonLeftStick
    Int32
Raw.SDL_CONTROLLER_BUTTON_RIGHTSTICK -> ControllerButton
ControllerButtonRightStick
    Int32
Raw.SDL_CONTROLLER_BUTTON_LEFTSHOULDER -> ControllerButton
ControllerButtonLeftShoulder
    Int32
Raw.SDL_CONTROLLER_BUTTON_RIGHTSHOULDER -> ControllerButton
ControllerButtonRightShoulder
    Int32
Raw.SDL_CONTROLLER_BUTTON_DPAD_UP -> ControllerButton
ControllerButtonDpadUp
    Int32
Raw.SDL_CONTROLLER_BUTTON_DPAD_DOWN -> ControllerButton
ControllerButtonDpadDown
    Int32
Raw.SDL_CONTROLLER_BUTTON_DPAD_LEFT -> ControllerButton
ControllerButtonDpadLeft
    Int32
Raw.SDL_CONTROLLER_BUTTON_DPAD_RIGHT -> ControllerButton
ControllerButtonDpadRight
    Int32
_ -> ControllerButton
ControllerButtonInvalid
instance ToNumber ControllerButton Int32 where
  toNumber :: ControllerButton -> Int32
toNumber ControllerButton
c = case ControllerButton
c of
    ControllerButton
ControllerButtonA -> Int32
Raw.SDL_CONTROLLER_BUTTON_A
    ControllerButton
ControllerButtonB -> Int32
Raw.SDL_CONTROLLER_BUTTON_B
    ControllerButton
ControllerButtonX -> Int32
Raw.SDL_CONTROLLER_BUTTON_X
    ControllerButton
ControllerButtonY -> Int32
Raw.SDL_CONTROLLER_BUTTON_Y
    ControllerButton
ControllerButtonBack -> Int32
Raw.SDL_CONTROLLER_BUTTON_BACK
    ControllerButton
ControllerButtonGuide -> Int32
Raw.SDL_CONTROLLER_BUTTON_GUIDE
    ControllerButton
ControllerButtonStart -> Int32
Raw.SDL_CONTROLLER_BUTTON_START
    ControllerButton
ControllerButtonLeftStick -> Int32
Raw.SDL_CONTROLLER_BUTTON_LEFTSTICK
    ControllerButton
ControllerButtonRightStick -> Int32
Raw.SDL_CONTROLLER_BUTTON_RIGHTSTICK
    ControllerButton
ControllerButtonLeftShoulder -> Int32
Raw.SDL_CONTROLLER_BUTTON_LEFTSHOULDER
    ControllerButton
ControllerButtonRightShoulder -> Int32
Raw.SDL_CONTROLLER_BUTTON_RIGHTSHOULDER
    ControllerButton
ControllerButtonDpadUp -> Int32
Raw.SDL_CONTROLLER_BUTTON_DPAD_UP
    ControllerButton
ControllerButtonDpadDown -> Int32
Raw.SDL_CONTROLLER_BUTTON_DPAD_DOWN
    ControllerButton
ControllerButtonDpadLeft -> Int32
Raw.SDL_CONTROLLER_BUTTON_DPAD_LEFT
    ControllerButton
ControllerButtonDpadRight -> Int32
Raw.SDL_CONTROLLER_BUTTON_DPAD_RIGHT
    ControllerButton
ControllerButtonInvalid -> Int32
Raw.SDL_CONTROLLER_BUTTON_INVALID
data ControllerButtonState
  = ControllerButtonPressed
  | ControllerButtonReleased
  | ControllerButtonInvalidState
  deriving (Typeable ControllerButtonState
ControllerButtonState -> DataType
ControllerButtonState -> Constr
(forall b. Data b => b -> b)
-> ControllerButtonState -> ControllerButtonState
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) -> ControllerButtonState -> u
forall u.
(forall d. Data d => d -> u) -> ControllerButtonState -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButtonState -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButtonState -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerButtonState -> m ControllerButtonState
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButtonState -> m ControllerButtonState
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerButtonState
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ControllerButtonState
-> c ControllerButtonState
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerButtonState)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerButtonState)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButtonState -> m ControllerButtonState
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButtonState -> m ControllerButtonState
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButtonState -> m ControllerButtonState
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerButtonState -> m ControllerButtonState
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerButtonState -> m ControllerButtonState
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerButtonState -> m ControllerButtonState
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ControllerButtonState -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ControllerButtonState -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ControllerButtonState -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ControllerButtonState -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButtonState -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButtonState -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButtonState -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerButtonState -> r
gmapT :: (forall b. Data b => b -> b)
-> ControllerButtonState -> ControllerButtonState
$cgmapT :: (forall b. Data b => b -> b)
-> ControllerButtonState -> ControllerButtonState
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerButtonState)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerButtonState)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerButtonState)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerButtonState)
dataTypeOf :: ControllerButtonState -> DataType
$cdataTypeOf :: ControllerButtonState -> DataType
toConstr :: ControllerButtonState -> Constr
$ctoConstr :: ControllerButtonState -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerButtonState
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerButtonState
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ControllerButtonState
-> c ControllerButtonState
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ControllerButtonState
-> c ControllerButtonState
Data, ControllerButtonState -> ControllerButtonState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ControllerButtonState -> ControllerButtonState -> Bool
$c/= :: ControllerButtonState -> ControllerButtonState -> Bool
== :: ControllerButtonState -> ControllerButtonState -> Bool
$c== :: ControllerButtonState -> ControllerButtonState -> Bool
Eq, forall x. Rep ControllerButtonState x -> ControllerButtonState
forall x. ControllerButtonState -> Rep ControllerButtonState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ControllerButtonState x -> ControllerButtonState
$cfrom :: forall x. ControllerButtonState -> Rep ControllerButtonState x
Generic, Eq ControllerButtonState
ControllerButtonState -> ControllerButtonState -> Bool
ControllerButtonState -> ControllerButtonState -> Ordering
ControllerButtonState
-> ControllerButtonState -> ControllerButtonState
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 :: ControllerButtonState
-> ControllerButtonState -> ControllerButtonState
$cmin :: ControllerButtonState
-> ControllerButtonState -> ControllerButtonState
max :: ControllerButtonState
-> ControllerButtonState -> ControllerButtonState
$cmax :: ControllerButtonState
-> ControllerButtonState -> ControllerButtonState
>= :: ControllerButtonState -> ControllerButtonState -> Bool
$c>= :: ControllerButtonState -> ControllerButtonState -> Bool
> :: ControllerButtonState -> ControllerButtonState -> Bool
$c> :: ControllerButtonState -> ControllerButtonState -> Bool
<= :: ControllerButtonState -> ControllerButtonState -> Bool
$c<= :: ControllerButtonState -> ControllerButtonState -> Bool
< :: ControllerButtonState -> ControllerButtonState -> Bool
$c< :: ControllerButtonState -> ControllerButtonState -> Bool
compare :: ControllerButtonState -> ControllerButtonState -> Ordering
$ccompare :: ControllerButtonState -> ControllerButtonState -> Ordering
Ord, ReadPrec [ControllerButtonState]
ReadPrec ControllerButtonState
Int -> ReadS ControllerButtonState
ReadS [ControllerButtonState]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ControllerButtonState]
$creadListPrec :: ReadPrec [ControllerButtonState]
readPrec :: ReadPrec ControllerButtonState
$creadPrec :: ReadPrec ControllerButtonState
readList :: ReadS [ControllerButtonState]
$creadList :: ReadS [ControllerButtonState]
readsPrec :: Int -> ReadS ControllerButtonState
$creadsPrec :: Int -> ReadS ControllerButtonState
Read, Int -> ControllerButtonState -> ShowS
[ControllerButtonState] -> ShowS
ControllerButtonState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ControllerButtonState] -> ShowS
$cshowList :: [ControllerButtonState] -> ShowS
show :: ControllerButtonState -> String
$cshow :: ControllerButtonState -> String
showsPrec :: Int -> ControllerButtonState -> ShowS
$cshowsPrec :: Int -> ControllerButtonState -> ShowS
Show, Typeable)
instance FromNumber ControllerButtonState Word32 where
  fromNumber :: Word32 -> ControllerButtonState
fromNumber Word32
n = case Word32
n of
    Word32
Raw.SDL_CONTROLLERBUTTONDOWN -> ControllerButtonState
ControllerButtonPressed
    Word32
Raw.SDL_CONTROLLERBUTTONUP -> ControllerButtonState
ControllerButtonReleased
    Word32
_ -> ControllerButtonState
ControllerButtonInvalidState
data ControllerAxis
  = ControllerAxisInvalid
  | ControllerAxisLeftX
  | ControllerAxisLeftY
  | ControllerAxisRightX
  | ControllerAxisRightY
  | ControllerAxisTriggerLeft
  | ControllerAxisTriggerRight
  | ControllerAxisMax
  deriving (Typeable ControllerAxis
ControllerAxis -> DataType
ControllerAxis -> Constr
(forall b. Data b => b -> b) -> ControllerAxis -> ControllerAxis
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) -> ControllerAxis -> u
forall u. (forall d. Data d => d -> u) -> ControllerAxis -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerAxis -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerAxis -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerAxis -> m ControllerAxis
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerAxis -> m ControllerAxis
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerAxis
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ControllerAxis -> c ControllerAxis
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerAxis)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerAxis)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerAxis -> m ControllerAxis
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerAxis -> m ControllerAxis
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerAxis -> m ControllerAxis
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerAxis -> m ControllerAxis
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerAxis -> m ControllerAxis
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerAxis -> m ControllerAxis
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ControllerAxis -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ControllerAxis -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ControllerAxis -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ControllerAxis -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerAxis -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerAxis -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerAxis -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ControllerAxis -> r
gmapT :: (forall b. Data b => b -> b) -> ControllerAxis -> ControllerAxis
$cgmapT :: (forall b. Data b => b -> b) -> ControllerAxis -> ControllerAxis
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerAxis)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerAxis)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerAxis)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ControllerAxis)
dataTypeOf :: ControllerAxis -> DataType
$cdataTypeOf :: ControllerAxis -> DataType
toConstr :: ControllerAxis -> Constr
$ctoConstr :: ControllerAxis -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerAxis
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerAxis
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ControllerAxis -> c ControllerAxis
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ControllerAxis -> c ControllerAxis
Data, ControllerAxis -> ControllerAxis -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ControllerAxis -> ControllerAxis -> Bool
$c/= :: ControllerAxis -> ControllerAxis -> Bool
== :: ControllerAxis -> ControllerAxis -> Bool
$c== :: ControllerAxis -> ControllerAxis -> Bool
Eq, forall x. Rep ControllerAxis x -> ControllerAxis
forall x. ControllerAxis -> Rep ControllerAxis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ControllerAxis x -> ControllerAxis
$cfrom :: forall x. ControllerAxis -> Rep ControllerAxis x
Generic, Eq ControllerAxis
ControllerAxis -> ControllerAxis -> Bool
ControllerAxis -> ControllerAxis -> Ordering
ControllerAxis -> ControllerAxis -> ControllerAxis
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 :: ControllerAxis -> ControllerAxis -> ControllerAxis
$cmin :: ControllerAxis -> ControllerAxis -> ControllerAxis
max :: ControllerAxis -> ControllerAxis -> ControllerAxis
$cmax :: ControllerAxis -> ControllerAxis -> ControllerAxis
>= :: ControllerAxis -> ControllerAxis -> Bool
$c>= :: ControllerAxis -> ControllerAxis -> Bool
> :: ControllerAxis -> ControllerAxis -> Bool
$c> :: ControllerAxis -> ControllerAxis -> Bool
<= :: ControllerAxis -> ControllerAxis -> Bool
$c<= :: ControllerAxis -> ControllerAxis -> Bool
< :: ControllerAxis -> ControllerAxis -> Bool
$c< :: ControllerAxis -> ControllerAxis -> Bool
compare :: ControllerAxis -> ControllerAxis -> Ordering
$ccompare :: ControllerAxis -> ControllerAxis -> Ordering
Ord, ReadPrec [ControllerAxis]
ReadPrec ControllerAxis
Int -> ReadS ControllerAxis
ReadS [ControllerAxis]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ControllerAxis]
$creadListPrec :: ReadPrec [ControllerAxis]
readPrec :: ReadPrec ControllerAxis
$creadPrec :: ReadPrec ControllerAxis
readList :: ReadS [ControllerAxis]
$creadList :: ReadS [ControllerAxis]
readsPrec :: Int -> ReadS ControllerAxis
$creadsPrec :: Int -> ReadS ControllerAxis
Read, Int -> ControllerAxis -> ShowS
[ControllerAxis] -> ShowS
ControllerAxis -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ControllerAxis] -> ShowS
$cshowList :: [ControllerAxis] -> ShowS
show :: ControllerAxis -> String
$cshow :: ControllerAxis -> String
showsPrec :: Int -> ControllerAxis -> ShowS
$cshowsPrec :: Int -> ControllerAxis -> ShowS
Show, Typeable)
instance ToNumber ControllerAxis Int32 where
  toNumber :: ControllerAxis -> Int32
toNumber ControllerAxis
a = case ControllerAxis
a of
    ControllerAxis
ControllerAxisLeftX -> Int32
Raw.SDL_CONTROLLER_AXIS_LEFTX
    ControllerAxis
ControllerAxisLeftY -> Int32
Raw.SDL_CONTROLLER_AXIS_LEFTY
    ControllerAxis
ControllerAxisRightX -> Int32
Raw.SDL_CONTROLLER_AXIS_RIGHTX
    ControllerAxis
ControllerAxisRightY -> Int32
Raw.SDL_CONTROLLER_AXIS_RIGHTY
    ControllerAxis
ControllerAxisTriggerLeft -> Int32
Raw.SDL_CONTROLLER_AXIS_TRIGGERLEFT
    ControllerAxis
ControllerAxisTriggerRight -> Int32
Raw.SDL_CONTROLLER_AXIS_TRIGGERRIGHT
    ControllerAxis
ControllerAxisMax -> Int32
Raw.SDL_CONTROLLER_AXIS_MAX
    ControllerAxis
ControllerAxisInvalid -> Int32
Raw.SDL_CONTROLLER_AXIS_INVALID
instance FromNumber ControllerAxis Int32 where
  fromNumber :: Int32 -> ControllerAxis
fromNumber Int32
n = case Int32
n of
    Int32
Raw.SDL_CONTROLLER_AXIS_LEFTX -> ControllerAxis
ControllerAxisLeftX
    Int32
Raw.SDL_CONTROLLER_AXIS_LEFTY -> ControllerAxis
ControllerAxisLeftY
    Int32
Raw.SDL_CONTROLLER_AXIS_RIGHTX -> ControllerAxis
ControllerAxisRightX
    Int32
Raw.SDL_CONTROLLER_AXIS_RIGHTY -> ControllerAxis
ControllerAxisRightY
    Int32
Raw.SDL_CONTROLLER_AXIS_TRIGGERLEFT -> ControllerAxis
ControllerAxisTriggerLeft
    Int32
Raw.SDL_CONTROLLER_AXIS_TRIGGERRIGHT -> ControllerAxis
ControllerAxisTriggerRight
    Int32
Raw.SDL_CONTROLLER_AXIS_MAX -> ControllerAxis
ControllerAxisMax
    Int32
_ -> ControllerAxis
ControllerAxisInvalid
data ControllerDeviceConnection
  = ControllerDeviceAdded
  | ControllerDeviceRemoved
  | ControllerDeviceRemapped
  deriving (Typeable ControllerDeviceConnection
ControllerDeviceConnection -> DataType
ControllerDeviceConnection -> Constr
(forall b. Data b => b -> b)
-> ControllerDeviceConnection -> ControllerDeviceConnection
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) -> ControllerDeviceConnection -> u
forall u.
(forall d. Data d => d -> u) -> ControllerDeviceConnection -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ControllerDeviceConnection
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ControllerDeviceConnection
-> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerDeviceConnection -> m ControllerDeviceConnection
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerDeviceConnection -> m ControllerDeviceConnection
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerDeviceConnection
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ControllerDeviceConnection
-> c ControllerDeviceConnection
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ControllerDeviceConnection)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerDeviceConnection)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerDeviceConnection -> m ControllerDeviceConnection
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerDeviceConnection -> m ControllerDeviceConnection
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerDeviceConnection -> m ControllerDeviceConnection
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ControllerDeviceConnection -> m ControllerDeviceConnection
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerDeviceConnection -> m ControllerDeviceConnection
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> ControllerDeviceConnection -> m ControllerDeviceConnection
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ControllerDeviceConnection -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ControllerDeviceConnection -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ControllerDeviceConnection -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ControllerDeviceConnection -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ControllerDeviceConnection
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ControllerDeviceConnection
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ControllerDeviceConnection
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ControllerDeviceConnection
-> r
gmapT :: (forall b. Data b => b -> b)
-> ControllerDeviceConnection -> ControllerDeviceConnection
$cgmapT :: (forall b. Data b => b -> b)
-> ControllerDeviceConnection -> ControllerDeviceConnection
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerDeviceConnection)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ControllerDeviceConnection)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ControllerDeviceConnection)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ControllerDeviceConnection)
dataTypeOf :: ControllerDeviceConnection -> DataType
$cdataTypeOf :: ControllerDeviceConnection -> DataType
toConstr :: ControllerDeviceConnection -> Constr
$ctoConstr :: ControllerDeviceConnection -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerDeviceConnection
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ControllerDeviceConnection
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ControllerDeviceConnection
-> c ControllerDeviceConnection
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ControllerDeviceConnection
-> c ControllerDeviceConnection
Data, ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
$c/= :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
== :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
$c== :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
Eq, forall x.
Rep ControllerDeviceConnection x -> ControllerDeviceConnection
forall x.
ControllerDeviceConnection -> Rep ControllerDeviceConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ControllerDeviceConnection x -> ControllerDeviceConnection
$cfrom :: forall x.
ControllerDeviceConnection -> Rep ControllerDeviceConnection x
Generic, Eq ControllerDeviceConnection
ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
ControllerDeviceConnection
-> ControllerDeviceConnection -> Ordering
ControllerDeviceConnection
-> ControllerDeviceConnection -> ControllerDeviceConnection
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 :: ControllerDeviceConnection
-> ControllerDeviceConnection -> ControllerDeviceConnection
$cmin :: ControllerDeviceConnection
-> ControllerDeviceConnection -> ControllerDeviceConnection
max :: ControllerDeviceConnection
-> ControllerDeviceConnection -> ControllerDeviceConnection
$cmax :: ControllerDeviceConnection
-> ControllerDeviceConnection -> ControllerDeviceConnection
>= :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
$c>= :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
> :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
$c> :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
<= :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
$c<= :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
< :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
$c< :: ControllerDeviceConnection -> ControllerDeviceConnection -> Bool
compare :: ControllerDeviceConnection
-> ControllerDeviceConnection -> Ordering
$ccompare :: ControllerDeviceConnection
-> ControllerDeviceConnection -> Ordering
Ord, ReadPrec [ControllerDeviceConnection]
ReadPrec ControllerDeviceConnection
Int -> ReadS ControllerDeviceConnection
ReadS [ControllerDeviceConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ControllerDeviceConnection]
$creadListPrec :: ReadPrec [ControllerDeviceConnection]
readPrec :: ReadPrec ControllerDeviceConnection
$creadPrec :: ReadPrec ControllerDeviceConnection
readList :: ReadS [ControllerDeviceConnection]
$creadList :: ReadS [ControllerDeviceConnection]
readsPrec :: Int -> ReadS ControllerDeviceConnection
$creadsPrec :: Int -> ReadS ControllerDeviceConnection
Read, Int -> ControllerDeviceConnection -> ShowS
[ControllerDeviceConnection] -> ShowS
ControllerDeviceConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ControllerDeviceConnection] -> ShowS
$cshowList :: [ControllerDeviceConnection] -> ShowS
show :: ControllerDeviceConnection -> String
$cshow :: ControllerDeviceConnection -> String
showsPrec :: Int -> ControllerDeviceConnection -> ShowS
$cshowsPrec :: Int -> ControllerDeviceConnection -> ShowS
Show, Typeable)
instance FromNumber ControllerDeviceConnection Word32 where
  fromNumber :: Word32 -> ControllerDeviceConnection
fromNumber Word32
n = case Word32
n of
    Word32
Raw.SDL_CONTROLLERDEVICEADDED -> ControllerDeviceConnection
ControllerDeviceAdded
    Word32
Raw.SDL_CONTROLLERDEVICEREMOVED -> ControllerDeviceConnection
ControllerDeviceRemoved
    Word32
_ -> ControllerDeviceConnection
ControllerDeviceRemapped