{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
module System.Hardware.Linux.Joystick (
Joystick(..)
, minValue
, maxValue
, byteLength
, interpretJoystick
, readJoystick
) where
import Data.Aeson.Types (FromJSON, ToJSON)
import Data.Binary (Binary(..), decode, encode)
import Data.Binary.Get (getWord16host, getWord32host)
import Data.Binary.Put (putWord16host, putWord32host)
import Data.Bits ((.&.), complement, shift)
import Data.ByteString.Lazy.Char8 as BS (ByteString, length, readFile, splitAt)
import Data.Serialize (Serialize)
import Data.Word (Word8, Word16, Word32)
import GHC.Generics (Generic)
minValue :: Int
minValue = - maxValue
maxValue :: Int
maxValue = 1 `shift` 15 - 1
byteLength :: Integral a => a
byteLength =
fromIntegral
. BS.length
. encode
$ RawJoystick 0 0 0 0
data RawJoystick =
RawJoystick
{
rawTime :: Word32
, rawValue :: Word16
, rawType :: Word8
, rawNumber :: Word8
}
deriving (Eq, Ord, Read, Show)
instance Binary RawJoystick where
get =
do
rawTime <- getWord32host
rawValue <- getWord16host
rawType <- get
rawNumber <- get
return RawJoystick{..}
put RawJoystick{..} =
do
putWord32host rawTime
putWord16host rawValue
put rawType
put rawNumber
data Joystick =
Joystick
{
timestamp :: Int
, value :: Int
, number :: Int
, button :: Bool
, axis :: Bool
, initial :: Bool
}
deriving (Eq, Generic, Ord, Read, Show)
instance FromJSON Joystick
instance ToJSON Joystick
instance Binary Joystick
instance Serialize Joystick
interpretJoystick :: ByteString
-> Joystick
interpretJoystick x =
let
RawJoystick{..} = decode x
timestamp = fromIntegral rawTime
value = twosComplement rawValue
number = fromIntegral rawNumber
typ = fromIntegral rawType :: Int
button = 0x01 .&. typ /= 0
axis = 0x02 .&. typ /= 0
initial = 0x80 .&. typ /= 0
in
Joystick{..}
twosComplement :: Word16
-> Int
twosComplement x =
fromIntegral (x' .&. complement mask) - fromIntegral (x' .&. mask)
where
x' = fromIntegral x :: Int
mask = 1 `shift` 15
readJoystick :: FilePath
-> IO [Joystick]
readJoystick path =
let
chunks :: ByteString -> [ByteString]
chunks x =
let
(y, ys) = BS.splitAt 8 x
in
y : chunks ys
in
map interpretJoystick
. chunks
<$> BS.readFile path