{-# LANGUAGE DeriveAnyClass #-}
module KMonad.Keyboard.IO.Linux.UinputSink
( UinputSink
, UinputCfg(..)
, keyboardName
, vendorCode
, productCode
, productVersion
, postInit
, uinputSink
, defUinputCfg
)
where
import KMonad.Prelude
import Data.Time.Clock.System (getSystemTime)
import Foreign.C.String
import Foreign.C.Types
import System.Posix
import UnliftIO.Async (async)
import UnliftIO.Process (callCommand)
import KMonad.Keyboard.IO.Linux.Types
import KMonad.Util
type SinkId = String
data UinputSinkError
= UinputRegistrationError SinkId
| UinputReleaseError SinkId
| SinkEncodeError SinkId LinuxKeyEvent
deriving Exception
instance Show UinputSinkError where
show (UinputRegistrationError snk) = "Could not register sink with OS: " <> snk
show (UinputReleaseError snk) = "Could not unregister sink with OS: " <> snk
show (SinkEncodeError snk a) = unwords
[ "Could not encode Keyaction"
, show a
, "to bytes for writing to"
, snk
]
makeClassyPrisms ''UinputSinkError
data UinputCfg = UinputCfg
{ _vendorCode :: !CInt
, _productCode :: !CInt
, _productVersion :: !CInt
, _keyboardName :: !String
, _postInit :: !(Maybe String)
} deriving (Eq, Show)
makeClassy ''UinputCfg
defUinputCfg :: UinputCfg
defUinputCfg = UinputCfg
{ _vendorCode = 0x1235
, _productCode = 0x5679
, _productVersion = 0x0000
, _keyboardName = "KMonad simulated keyboard"
, _postInit = Nothing
}
data UinputSink = UinputSink
{ _cfg :: UinputCfg
, _st :: MVar Fd
}
makeLenses ''UinputSink
uinputSink :: HasLogFunc e => UinputCfg -> RIO e (Acquire KeySink)
uinputSink c = mkKeySink (usOpen c) usClose usWrite
foreign import ccall "acquire_uinput_keysink"
c_acquire_uinput_keysink
:: CInt
-> CString
-> CInt
-> CInt
-> CInt
-> IO Int
foreign import ccall "release_uinput_keysink"
c_release_uinput_keysink :: CInt -> IO Int
foreign import ccall "send_event"
c_send_event :: CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO Int
acquire_uinput_keysink :: MonadIO m => Fd -> UinputCfg -> m Int
acquire_uinput_keysink (Fd h) c = liftIO $ do
cstr <- newCString $ c^.keyboardName
c_acquire_uinput_keysink h cstr
(c^.vendorCode) (c^.productCode) (c^.productVersion)
release_uinput_keysink :: MonadIO m => Fd -> m Int
release_uinput_keysink (Fd h) = liftIO $ c_release_uinput_keysink h
send_event :: ()
=> UinputSink
-> Fd
-> LinuxKeyEvent
-> RIO e ()
send_event u (Fd h) e@(LinuxKeyEvent (s', ns', typ, c, val)) = do
(liftIO $ c_send_event h typ c val s' ns')
`onErr` SinkEncodeError (u^.cfg.keyboardName) e
usOpen :: HasLogFunc e => UinputCfg -> RIO e UinputSink
usOpen c = do
fd <- liftIO . openFd "/dev/uinput" WriteOnly Nothing $
OpenFileFlags False False False True False
logInfo "Registering Uinput device"
acquire_uinput_keysink fd c `onErr` UinputRegistrationError (c ^. keyboardName)
flip (maybe $ pure ()) (c^.postInit) $ \cmd -> do
logInfo $ "Running UinputSink command: " <> displayShow cmd
void . async . callCommand $ cmd
UinputSink c <$> newMVar fd
usClose :: HasLogFunc e => UinputSink -> RIO e ()
usClose snk = withMVar (snk^.st) $ \h -> finally (release h) (close h)
where
release h = do
logInfo $ "Unregistering Uinput device"
release_uinput_keysink h
`onErr` UinputReleaseError (snk^.cfg.keyboardName)
close h = do
logInfo $ "Closing Uinput device file"
liftIO $ closeFd h
usWrite :: HasLogFunc e => UinputSink -> KeyEvent -> RIO e ()
usWrite u e = withMVar (u^.st) $ \fd -> do
now <- liftIO $ getSystemTime
send_event u fd . toLinuxKeyEvent e $ now
send_event u fd . sync $ now