module Affection.MessageBus.Message.JoystickMessage
( JoystickMessage(..)
, Linear.V2
, SDL.JoyHatPosition
, SDL.JoyButtonState
, SDL.JoyDeviceConnection
, Word8
, Int16
, Int32
) where
import Affection.MessageBus.Message.Class
import Data.Word (Word8)
import Data.Int (Int32, Int16)
import qualified SDL
import Linear (V2(..))
data JoystickMessage
= MsgJoystickAxis
{ msgJAWhen :: Double
, msgJAWhich :: Int32
, msgJAAxis :: Word8
, msgJAValue :: Int16
}
| MsgJoystickBall
{ msgJBWhen :: Double
, msgJBWhich :: Int32
, msgJBBall :: Word8
, msgJBRelMotion :: V2 Int16
}
| MsgJoystickHat
{ msgJHWhen :: Double
, msgJHWhich :: Int32
, msgJHHat :: Word8
, msgJHPosition :: SDL.JoyHatPosition
}
| MsgJoystickButton
{ msgJBWhen :: Double
, msgJBWhich :: Int32
, msgJBButton :: Word8
, msgJBState :: SDL.JoyButtonState
}
| MsgJoystickDevice
{ msgJDWhen :: Double
, msgJDWhich :: Int32
, msgJDConnection :: SDL.JoyDeviceConnection
}
deriving (Show)
instance Message JoystickMessage where
msgTime (MsgJoystickAxis t _ _ _) = t
msgTime (MsgJoystickBall t _ _ _) = t
msgTime (MsgJoystickHat t _ _ _) = t
msgTime (MsgJoystickButton t _ _ _) = t
msgTime (MsgJoystickDevice t _ _) = t