{-# LANGUAGE DeriveAnyClass #-}
module KMonad.Keyboard.IO
(
KeySink
, mkKeySink
, emitKey
, KeySource
, mkKeySource
, awaitKey
)
where
import KMonad.Prelude
import KMonad.Keyboard
import KMonad.Util
import qualified RIO.Text as T
newtype KeySink = KeySink { emitKeyWith :: KeyEvent -> IO () }
mkKeySink :: HasLogFunc e
=> RIO e snk
-> (snk -> RIO e ())
-> (snk -> KeyEvent -> RIO e ())
-> RIO e (Acquire KeySink)
mkKeySink o c w = do
u <- askUnliftIO
let open = unliftIO u $ logInfo "Opening KeySink" >> o
let close snk = unliftIO u $ logInfo "Closing KeySink" >> c snk
let write snk a = unliftIO u $ w snk a
`catch` logRethrow "Encountered error in KeySink"
pure $ KeySink . write <$> mkAcquire open close
emitKey :: (HasLogFunc e) => KeySink -> KeyEvent -> RIO e ()
emitKey snk e = do
logDebug $ "Emitting: " <> display e
liftIO $ emitKeyWith snk e
newtype KeySource = KeySource { awaitKeyWith :: IO KeyEvent}
mkKeySource :: HasLogFunc e
=> RIO e src
-> (src -> RIO e ())
-> (src -> RIO e KeyEvent)
-> RIO e (Acquire KeySource)
mkKeySource o c r = do
u <- askUnliftIO
let open = unliftIO u $ logInfo "Opening KeySource" >> o
let close src = unliftIO u $ logInfo "Closing KeySource" >> c src
let read src = unliftIO u $ r src
`catch` logRethrow "Encountered error in KeySource"
pure $ KeySource . read <$> mkAcquire open close
awaitKey :: (HasLogFunc e) => KeySource -> RIO e KeyEvent
awaitKey src = do
e <- liftIO . awaitKeyWith $ src
logDebug $ "\n" <> display (T.replicate 80 "-")
<> "\nReceived event: " <> display e
pure e