{-# LANGUAGE CPP #-}
module KMonad.Args.Joiner
( joinConfigIO
, joinConfig
)
where
import KMonad.Prelude hiding (uncons)
import KMonad.Args.Types
import KMonad.Action
import KMonad.Button
import KMonad.Keyboard
import KMonad.Keyboard.IO
#ifdef linux_HOST_OS
import KMonad.Keyboard.IO.Linux.DeviceSource
import KMonad.Keyboard.IO.Linux.UinputSink
#endif
#ifdef mingw32_HOST_OS
import KMonad.Keyboard.IO.Windows.LowLevelHookSource
import KMonad.Keyboard.IO.Windows.SendEventSink
#endif
#ifdef darwin_HOST_OS
import KMonad.Keyboard.IO.Mac.IOKitSource
import KMonad.Keyboard.IO.Mac.KextSink
#endif
import Control.Monad.Except
import RIO.List (uncons, headMaybe)
import RIO.Partial (fromJust)
import qualified Data.LayerStack as L
import qualified RIO.HashMap as M
import qualified RIO.Text as T
data JoinError
= DuplicateBlock Text
| MissingBlock Text
| DuplicateAlias Text
| DuplicateLayer Text
| MissingAlias Text
| MissingLayer Text
| MissingSetting Text
| DuplicateSetting Text
| InvalidOS Text
| NestedTrans
| InvalidComposeKey
| LengthMismatch Text Int Int
instance Show JoinError where
show e = case e of
DuplicateBlock t -> "Encountered duplicate block of type: " <> T.unpack t
MissingBlock t -> "Missing at least 1 block of type: " <> T.unpack t
DuplicateAlias t -> "Multiple aliases of the same name: " <> T.unpack t
DuplicateLayer t -> "Multiple layers of the same name: " <> T.unpack t
MissingAlias t -> "Reference to non-existent alias: " <> T.unpack t
MissingLayer t -> "Reference to non-existent layer: " <> T.unpack t
MissingSetting t -> "Missing setting in 'defcfg': " <> T.unpack t
DuplicateSetting t -> "Duplicate setting in 'defcfg': " <> T.unpack t
InvalidOS t -> "Not available under this OS: " <> T.unpack t
NestedTrans -> "Encountered 'Transparent' ouside of top-level layer"
InvalidComposeKey -> "Encountered invalid button as Compose key"
LengthMismatch t l s -> mconcat
[ "Mismatch between length of 'defsrc' and deflayer <", T.unpack t, ">\n"
, "Source length: ", show s, "\n"
, "Layer length: ", show l ]
instance Exception JoinError
data JCfg = JCfg
{ _cmpKey :: Button
, _kes :: [KExpr]
}
makeLenses ''JCfg
defJCfg :: [KExpr] ->JCfg
defJCfg = JCfg
(emitB KeyRightAlt)
newtype J a = J { unJ :: ExceptT JoinError (Reader JCfg) a }
deriving ( Functor, Applicative, Monad
, MonadError JoinError , MonadReader JCfg)
runJ :: J a -> JCfg -> Either JoinError a
runJ j = runReader (runExceptT $ unJ j)
joinConfigIO :: HasLogFunc e => [KExpr] -> RIO e CfgToken
joinConfigIO es = case runJ joinConfig $ defJCfg es of
Left e -> throwM e
Right c -> pure c
extract :: Prism' a b -> [a] -> [b]
extract p = catMaybes . map (preview p)
data SingletonError
= None
| Duplicate
onlyOne :: [a] -> Either SingletonError a
onlyOne xs = case uncons xs of
Just (x, []) -> Right x
Just _ -> Left Duplicate
Nothing -> Left None
oneBlock :: Text -> Prism' KExpr a -> J a
oneBlock t l = onlyOne . extract l <$> view kes >>= \case
Right x -> pure x
Left None -> throwError $ MissingBlock t
Left Duplicate -> throwError $ DuplicateBlock t
joinConfig :: J CfgToken
joinConfig = getOverride >>= \cfg -> (local (const cfg) joinConfig')
joinConfig' :: J CfgToken
joinConfig' = do
es <- view kes
i <- getI
o <- getO
ft <- getFT
al <- getAllow
let als = extract _KDefAlias $ es
let lys = extract _KDefLayer $ es
src <- oneBlock "defsrc" _KDefSrc
(km, fl) <- joinKeymap src als lys
pure $ CfgToken
{ _snk = o
, _src = i
, _km = km
, _fstL = fl
, _flt = ft
, _allow = al
}
getOverride :: J JCfg
getOverride = do
env <- ask
cfg <- oneBlock "defcfg" _KDefCfg
let getB = joinButton [] M.empty
let go e v = case v of
SCmpSeq b -> getB b >>= maybe (throwError InvalidComposeKey)
(\b' -> pure $ set cmpKey b' e)
_ -> pure e
foldM go env cfg
runLF :: (forall e. HasLogFunc e => RIO e a) -> LogFunc -> IO a
runLF = flip runRIO
getI :: J (LogFunc -> IO (Acquire KeySource))
getI = do
cfg <- oneBlock "defcfg" _KDefCfg
case onlyOne . extract _SIToken $ cfg of
Right i -> pickInput i
Left None -> throwError $ MissingSetting "input"
Left Duplicate -> throwError $ DuplicateSetting "input"
getO :: J (LogFunc -> IO (Acquire KeySink))
getO = do
cfg <- oneBlock "defcfg" _KDefCfg
case onlyOne . extract _SOToken $ cfg of
Right o -> pickOutput o
Left None -> throwError $ MissingSetting "input"
Left Duplicate -> throwError $ DuplicateSetting "input"
getFT :: J Bool
getFT = do
cfg <- oneBlock "defcfg" _KDefCfg
case onlyOne . extract _SFallThrough $ cfg of
Right b -> pure b
Left None -> pure False
Left Duplicate -> throwError $ DuplicateSetting "fallthrough"
getAllow :: J Bool
getAllow = do
cfg <- oneBlock "defcfg" _KDefCfg
case onlyOne . extract _SAllowCmd $ cfg of
Right b -> pure b
Left None -> pure False
Left Duplicate -> throwError $ DuplicateSetting "allow-cmd"
#ifdef linux_HOST_OS
pickInput :: IToken -> J (LogFunc -> IO (Acquire KeySource))
pickInput (KDeviceSource f) = pure $ runLF (deviceSource64 f)
pickInput KLowLevelHookSource = throwError $ InvalidOS "LowLevelHookSource"
pickInput (KIOKitSource _) = throwError $ InvalidOS "IOKitSource"
pickOutput :: OToken -> J (LogFunc -> IO (Acquire KeySink))
pickOutput (KUinputSink t init) = pure $ runLF (uinputSink cfg)
where cfg = defUinputCfg { _keyboardName = T.unpack t
, _postInit = T.unpack <$> init }
pickOutput KSendEventSink = throwError $ InvalidOS "SendEventSink"
pickOutput KKextSink = throwError $ InvalidOS "KextSink"
#endif
#ifdef mingw32_HOST_OS
pickInput :: IToken -> J (LogFunc -> IO (Acquire KeySource))
pickInput KLowLevelHookSource = pure $ runLF llHook
pickInput (KDeviceSource _) = throwError $ InvalidOS "DeviceSource"
pickInput (KIOKitSource _) = throwError $ InvalidOS "IOKitSource"
pickOutput :: OToken -> J (LogFunc -> IO (Acquire KeySink))
pickOutput KSendEventSink = pure $ runLF sendEventKeySink
pickOutput (KUinputSink _ _) = throwError $ InvalidOS "UinputSink"
pickOutput KKextSink = throwError $ InvalidOS "KextSink"
#endif
#ifdef darwin_HOST_OS
pickInput :: IToken -> J (LogFunc -> IO (Acquire KeySource))
pickInput (KIOKitSource name) = pure $ runLF (iokitSource (T.unpack <$> name))
pickInput (KDeviceSource _) = throwError $ InvalidOS "DeviceSource"
pickInput KLowLevelHookSource = throwError $ InvalidOS "LowLevelHookSource"
pickOutput :: OToken -> J (LogFunc -> IO (Acquire KeySink))
pickOutput KKextSink = pure $ runLF kextSink
pickOutput (KUinputSink _ _) = throwError $ InvalidOS "UinputSink"
pickOutput KSendEventSink = throwError $ InvalidOS "SendEventSink"
#endif
type Aliases = M.HashMap Text Button
type LNames = [Text]
joinAliases :: LNames -> [DefAlias] -> J Aliases
joinAliases ns als = foldM f M.empty $ concat als
where f mp (t, b) = if t `M.member` mp
then throwError $ DuplicateAlias t
else flip (M.insert t) mp <$> (unnest $ joinButton ns mp b)
unnest :: J (Maybe Button) -> J Button
unnest = join . fmap (maybe (throwError NestedTrans) (pure . id))
joinButton :: LNames -> Aliases -> DefButton -> J (Maybe Button)
joinButton ns als =
let ret = pure . Just
go = unnest . joinButton ns als
jst = fmap Just
fi = fromIntegral
in \case
KRef t -> case M.lookup t als of
Nothing -> throwError $ MissingAlias t
Just b -> ret b
KEmit c -> ret $ emitB c
KCommand t -> ret $ cmdButton t
KLayerToggle t -> if t `elem` ns
then ret $ layerToggle t
else throwError $ MissingLayer t
KLayerSwitch t -> if t `elem` ns
then ret $ layerSwitch t
else throwError $ MissingLayer t
KLayerAdd t -> if t `elem` ns
then ret $ layerAdd t
else throwError $ MissingLayer t
KLayerRem t -> if t `elem` ns
then ret $ layerRem t
else throwError $ MissingLayer t
KLayerDelay s t -> if t `elem` ns
then ret $ layerDelay (fi s) t
else throwError $ MissingLayer t
KLayerNext t -> if t `elem` ns
then ret $ layerNext t
else throwError $ MissingLayer t
KComposeSeq bs -> view cmpKey >>= \c -> jst $ tapMacro . (c:) <$> mapM go bs
KTapMacro bs -> jst $ tapMacro <$> mapM go bs
KAround o i -> jst $ around <$> go o <*> go i
KTapNext t h -> jst $ tapNext <$> go t <*> go h
KTapHold s t h -> jst $ tapHold (fi s) <$> go t <*> go h
KTapHoldNext s t h -> jst $ tapHoldNext (fi s) <$> go t <*> go h
KTapNextRelease t h -> jst $ tapNextRelease <$> go t <*> go h
KTapHoldNextRelease ms t h
-> jst $ tapHoldNextRelease (fi ms) <$> go t <*> go h
KAroundNext b -> jst $ aroundNext <$> go b
KPause ms -> jst . pure $ onPress (pause ms)
KMultiTap bs d -> jst $ multiTap <$> go d <*> mapM f bs
where f (ms, b) = (fi ms,) <$> go b
KTrans -> pure Nothing
KBlock -> ret pass
joinKeymap :: DefSrc -> [DefAlias] -> [DefLayer] -> J (LMap Button, LayerTag)
joinKeymap _ _ [] = throwError $ MissingBlock "deflayer"
joinKeymap src als lys = do
let f acc x = if x `elem` acc then throwError $ DuplicateLayer x else pure (x:acc)
nms <- foldM f [] $ map _layerName lys
als' <- joinAliases nms als
lys' <- mapM (joinLayer als' nms src) lys
pure $ (L.mkLayerStack lys', _layerName . fromJust . headMaybe $ lys)
joinLayer ::
Aliases
-> LNames
-> DefSrc
-> DefLayer
-> J (Text, [(Keycode, Button)])
joinLayer als ns src DefLayer{_layerName=n, _buttons=bs} = do
when (length bs /= length src) $
throwError $ LengthMismatch n (length bs) (length src)
let f acc (kc, b) = joinButton ns als b >>= \case
Nothing -> pure acc
Just b' -> pure $ (kc, b') : acc
(n,) <$> foldM f [] (zip src bs)