{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
module System.Hardware.Linux.SpaceNav (
SpaceNav(..)
, byteLength
, interpretSpaceNav
, readSpaceNav
) where
import Data.Aeson.Types (FromJSON, ToJSON)
import Data.Binary (Binary(..), decode)
import Data.Bits ((.&.), complement, shift)
import Data.ByteString.Lazy.Char8 as BS (ByteString, readFile, splitAt)
import Data.Serialize (Serialize)
import Data.Word (Word32)
import GHC.Generics (Generic)
import System.Hardware.Linux.Input (InputEvent(..), byteLength)
data SpaceNav =
SpaceNavButton
{
timestamp :: Integer
, number :: Int
, pressed :: Bool
}
| SpaceNavAnalog
{
timestamp :: Integer
, number :: Int
, setting :: Double
}
| SpaceNavNull
deriving (Eq, Generic, Ord, Read, Show)
instance FromJSON SpaceNav
instance ToJSON SpaceNav
instance Binary SpaceNav
instance Serialize SpaceNav
interpretSpaceNav :: ByteString
-> SpaceNav
interpretSpaceNav x =
let
InputEvent{..} = decode x
(seconds, microseconds) = timeval
seconds' = fromIntegral seconds :: Integer
microseconds' = fromIntegral microseconds :: Integer
timestamp = (10^(6 :: Int) * seconds' + microseconds') * 10^(6 :: Int)
in
case typ of
0x01 -> let
number = fromIntegral $ code .&. 0x00ff
pressed = value /= 0
in
SpaceNavButton{..}
0x02 -> let
number = fromIntegral code
setting = fromIntegral (twosComplement value) / 400
in
SpaceNavAnalog{..}
_ -> SpaceNavNull
twosComplement :: Word32
-> Int
twosComplement x =
fromIntegral (x' .&. complement mask) - fromIntegral (x' .&. mask)
where
x' = fromIntegral x :: Int
mask = 1 `shift` 31
readSpaceNav :: FilePath
-> IO [SpaceNav]
readSpaceNav path =
let
chunks :: ByteString -> [ByteString]
chunks x =
let
(y, ys) = BS.splitAt 8 x
in
y : chunks ys
in
map interpretSpaceNav
. chunks
<$> BS.readFile path