{-# LANGUAGE DeriveAnyClass #-}
module KMonad.Keyboard.IO.Linux.DeviceSource
( deviceSource
, deviceSource64
, KeyEventParser
, decode64
)
where
import KMonad.Prelude
import Foreign.C.Types
import System.Posix
import KMonad.Keyboard.IO.Linux.Types
import KMonad.Util
import qualified Data.Serialize as B (decode)
import qualified RIO.ByteString as B
data DeviceSourceError
= IOCtlGrabError FilePath
| IOCtlReleaseError FilePath
| KeyIODecodeError String
deriving Exception
instance Show DeviceSourceError where
show (IOCtlGrabError pth) = "Could not perform IOCTL grab on: " <> pth
show (IOCtlReleaseError pth) = "Could not perform IOCTL release on: " <> pth
show (KeyIODecodeError msg) = "KeyEvent decode failed with msg: " <> msg
makeClassyPrisms ''DeviceSourceError
foreign import ccall "ioctl_keyboard"
c_ioctl_keyboard :: CInt -> CInt -> IO CInt
ioctl_keyboard :: MonadIO m
=> Fd
-> Bool
-> m Int
ioctl_keyboard (Fd h) b = fromIntegral <$>
liftIO (c_ioctl_keyboard h (if b then 1 else 0))
data KeyEventParser = KeyEventParser
{ _nbytes :: !Int
, _prs :: !(B.ByteString -> Either String LinuxKeyEvent)
}
makeClassy ''KeyEventParser
defEventParser :: KeyEventParser
defEventParser = KeyEventParser 24 decode64
decode64 :: B.ByteString -> Either String LinuxKeyEvent
decode64 bs = (linuxKeyEvent . fliptup) <$> result
where
result :: Either String (Int32, Word16, Word16, Word64, Word64)
result = B.decode . B.reverse $ bs
fliptup (a, b, c, d, e) = (e, d, c, b, a)
data DeviceSourceCfg = DeviceSourceCfg
{ _pth :: !FilePath
, _parser :: !KeyEventParser
}
makeClassy ''DeviceSourceCfg
data DeviceFile = DeviceFile
{ _cfg :: !DeviceSourceCfg
, _fd :: !Fd
, _hdl :: !Handle
}
makeClassy ''DeviceFile
instance HasDeviceSourceCfg DeviceFile where deviceSourceCfg = cfg
instance HasKeyEventParser DeviceFile where keyEventParser = cfg.parser
deviceSource :: HasLogFunc e
=> KeyEventParser
-> FilePath
-> RIO e (Acquire KeySource)
deviceSource pr pt = mkKeySource (lsOpen pr pt) lsClose lsRead
deviceSource64 :: HasLogFunc e
=> FilePath
-> RIO e (Acquire KeySource)
deviceSource64 = deviceSource defEventParser
lsOpen :: (HasLogFunc e)
=> KeyEventParser
-> FilePath
-> RIO e DeviceFile
lsOpen pr pt = do
h <- liftIO . openFd pt ReadOnly Nothing $
OpenFileFlags False False False False False
hd <- liftIO $ fdToHandle h
logInfo $ "Initiating ioctl grab"
ioctl_keyboard h True `onErr` IOCtlGrabError pt
return $ DeviceFile (DeviceSourceCfg pt pr) h hd
lsClose :: (HasLogFunc e) => DeviceFile -> RIO e ()
lsClose src = do
logInfo $ "Releasing ioctl grab"
ioctl_keyboard (src^.fd) False `onErr` IOCtlReleaseError (src^.pth)
liftIO . closeFd $ src^.fd
lsRead :: (HasLogFunc e) => DeviceFile -> RIO e KeyEvent
lsRead src = do
bts <- B.hGet (src^.hdl) (src^.nbytes)
case (src^.prs $ bts) of
Right p -> case fromLinuxKeyEvent p of
Just e -> return e
Nothing -> lsRead src
Left s -> throwIO $ KeyIODecodeError s