ENH make showkeys use dep framework
This commit is contained in:
parent
ec957c1dbf
commit
53a537960e
|
@ -95,11 +95,12 @@ run = do
|
||||||
lockRes <- evalSometimes runScreenLock
|
lockRes <- evalSometimes runScreenLock
|
||||||
let lock = fromMaybe skip lockRes
|
let lock = fromMaybe skip lockRes
|
||||||
ext <- evalExternal $ externalBindings ts db lock
|
ext <- evalExternal $ externalBindings ts db lock
|
||||||
|
sk <- evalAlways runShowKeys
|
||||||
-- IDK why this is necessary; nothing prior to this line will print if missing
|
-- IDK why this is necessary; nothing prior to this line will print if missing
|
||||||
hFlush stdout
|
hFlush stdout
|
||||||
ds <- getDirectories
|
ds <- getDirectories
|
||||||
let conf = ewmh
|
let conf = ewmh
|
||||||
$ addKeymap (filterExternal ext)
|
$ addKeymap sk (filterExternal ext)
|
||||||
$ docks
|
$ docks
|
||||||
$ def { terminal = myTerm
|
$ def { terminal = myTerm
|
||||||
, modMask = myModMask
|
, modMask = myModMask
|
||||||
|
@ -462,8 +463,9 @@ xMsgEventHook _ _ = return (All True)
|
||||||
myModMask :: KeyMask
|
myModMask :: KeyMask
|
||||||
myModMask = mod4Mask
|
myModMask = mod4Mask
|
||||||
|
|
||||||
addKeymap :: [KeyGroup (X ())] -> XConfig l -> XConfig l
|
addKeymap :: ([((KeyMask, KeySym), NamedAction)] -> X ())
|
||||||
addKeymap external = addDescrKeys' ((myModMask, xK_F1), runShowKeys)
|
-> [KeyGroup (X ())] -> XConfig l -> XConfig l
|
||||||
|
addKeymap showKeys external = addDescrKeys' ((myModMask, xK_F1), showKeys)
|
||||||
(\c -> concatMap (mkNamedSubmap c) $ internalBindings c ++ external)
|
(\c -> concatMap (mkNamedSubmap c) $ internalBindings c ++ external)
|
||||||
|
|
||||||
internalBindings :: XConfig Layout -> [KeyGroup (X ())]
|
internalBindings :: XConfig Layout -> [KeyGroup (X ())]
|
||||||
|
|
|
@ -15,17 +15,17 @@ module XMonad.Internal.Command.DMenu
|
||||||
, runAutorandrMenu
|
, runAutorandrMenu
|
||||||
) where
|
) where
|
||||||
|
|
||||||
-- import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
|
|
||||||
import Graphics.X11.Types
|
import Graphics.X11.Types
|
||||||
|
|
||||||
import System.Directory (XdgDirectory (..), getXdgDirectory)
|
import System.Directory (XdgDirectory (..), getXdgDirectory)
|
||||||
-- import System.IO
|
import System.IO
|
||||||
|
|
||||||
import XMonad.Core hiding (spawn)
|
import XMonad.Core hiding (spawn)
|
||||||
import XMonad.Internal.Dependency
|
import XMonad.Internal.Dependency
|
||||||
-- import XMonad.Internal.Notify
|
import XMonad.Internal.Notify
|
||||||
-- import XMonad.Internal.Process
|
import XMonad.Internal.Process
|
||||||
import XMonad.Internal.Shell
|
import XMonad.Internal.Shell
|
||||||
import XMonad.Util.NamedActions
|
import XMonad.Util.NamedActions
|
||||||
|
|
||||||
|
@ -91,39 +91,27 @@ runVPNMenu :: SometimesX
|
||||||
runVPNMenu = sometimesIO "VPN selector" (Only_ $ localExe myDmenuVPN) $
|
runVPNMenu = sometimesIO "VPN selector" (Only_ $ localExe myDmenuVPN) $
|
||||||
spawnCmd myDmenuVPN $ ["-c"] ++ themeArgs "#007766" ++ myDmenuMatchingArgs
|
spawnCmd myDmenuVPN $ ["-c"] ++ themeArgs "#007766" ++ myDmenuMatchingArgs
|
||||||
|
|
||||||
-- runShowKeys :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
|
runShowKeys :: Always ([((KeyMask, KeySym), NamedAction)] -> X ())
|
||||||
-- runShowKeys x = addName "Show Keybindings" $ do
|
runShowKeys = Option showKeysDMenu (Always fallback)
|
||||||
-- s <- io $ evalFeature $ runDMenuShowKeys x
|
where
|
||||||
-- ifSatisfied s
|
-- TODO this should technically depend on dunst
|
||||||
-- $ spawnNotify
|
fallback = const $ spawnNotify
|
||||||
-- $ defNoteError { body = Just $ Text "could not display keymap" }
|
$ defNoteError { body = Just $ Text "could not display keymap" }
|
||||||
|
|
||||||
-- TODO not sure what to do with this yet
|
showKeysDMenu :: SubfeatureRoot ([((KeyMask, KeySym), NamedAction)] -> X ())
|
||||||
runShowKeys :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
|
showKeysDMenu = Subfeature
|
||||||
runShowKeys _ = NamedAction (skip :: (X ()))
|
{ sfName = "keyboard shortcut menu"
|
||||||
-- addName "Show Keybindings" $ evalAlways $ runDMenuShowKeys x
|
, sfData = IORoot_ showKeys $ Only_ $ sysExe myDmenuCmd
|
||||||
|
, sfLevel = Warn
|
||||||
|
}
|
||||||
|
|
||||||
-- runDMenuShowKeys :: [((KeyMask, KeySym), NamedAction)] -> AlwaysX
|
showKeys :: [((KeyMask, KeySym), NamedAction)] -> X ()
|
||||||
-- runDMenuShowKeys kbs =
|
showKeys kbs = io $ do
|
||||||
-- Option (runDMenuShowKeys' kbs) (Always runNotifyShowKeys)
|
(h, _, _, _) <- createProcess' $ (shell' cmd) { std_in = CreatePipe }
|
||||||
|
forM_ h $ \h' -> hPutStr h' (unlines $ showKm kbs) >> hClose h'
|
||||||
-- runNotifyShowKeys :: X ()
|
where
|
||||||
-- runNotifyShowKeys = spawnNotify
|
cmd = fmtCmd myDmenuCmd $ ["-dmenu", "-p", "commands"]
|
||||||
-- $ defNoteError { body = Just $ Text "could not display keymap" }
|
++ themeArgs "#7f66ff" ++ myDmenuMatchingArgs
|
||||||
|
|
||||||
-- runDMenuShowKeys' :: [((KeyMask, KeySym), NamedAction)] -> Subfeature (X ()) Tree
|
|
||||||
-- runDMenuShowKeys' kbs = Subfeature
|
|
||||||
-- { sfName = "keyboard shortcut menu"
|
|
||||||
-- , sfTree = IOTree (Standalone act) deps
|
|
||||||
-- , sfLevel = Warn
|
|
||||||
-- }
|
|
||||||
-- where
|
|
||||||
-- deps = Only $ Executable True myDmenuCmd
|
|
||||||
-- act = io $ do
|
|
||||||
-- (h, _, _, _) <- createProcess' $ (shell' cmd) { std_in = CreatePipe }
|
|
||||||
-- forM_ h $ \h' -> hPutStr h' (unlines $ showKm kbs) >> hClose h'
|
|
||||||
-- cmd = fmtCmd myDmenuCmd $ ["-dmenu", "-p", "commands"]
|
|
||||||
-- ++ themeArgs "#7f66ff" ++ myDmenuMatchingArgs
|
|
||||||
|
|
||||||
runCmdMenu :: SometimesX
|
runCmdMenu :: SometimesX
|
||||||
runCmdMenu = spawnDmenuCmd "command menu" ["-show", "run"]
|
runCmdMenu = spawnDmenuCmd "command menu" ["-show", "run"]
|
||||||
|
|
|
@ -15,6 +15,7 @@ module XMonad.Internal.Dependency
|
||||||
, SometimesIO
|
, SometimesIO
|
||||||
, PostPass(..)
|
, PostPass(..)
|
||||||
, Subfeature(..)
|
, Subfeature(..)
|
||||||
|
, SubfeatureRoot
|
||||||
, LogLevel(..)
|
, LogLevel(..)
|
||||||
|
|
||||||
-- dependency tree types
|
-- dependency tree types
|
||||||
|
@ -176,7 +177,8 @@ data LogLevel = Silent | Error | Warn | Debug deriving (Eq, Show, Ord)
|
||||||
-- needed
|
-- needed
|
||||||
data Root a = forall p. IORoot (p -> a) (Tree IODependency IODependency_ p)
|
data Root a = forall p. IORoot (p -> a) (Tree IODependency IODependency_ p)
|
||||||
| IORoot_ a (Tree_ IODependency_)
|
| IORoot_ a (Tree_ IODependency_)
|
||||||
| forall p. DBusRoot (p -> Client -> a) (Tree IODependency DBusDependency_ p) (Maybe Client)
|
| forall p. DBusRoot (p -> Client -> a)
|
||||||
|
(Tree IODependency DBusDependency_ p) (Maybe Client)
|
||||||
| DBusRoot_ (Client -> a) (Tree_ DBusDependency_) (Maybe Client)
|
| DBusRoot_ (Client -> a) (Tree_ DBusDependency_) (Maybe Client)
|
||||||
|
|
||||||
-- | The dependency tree with rules to merge results
|
-- | The dependency tree with rules to merge results
|
||||||
|
@ -210,7 +212,8 @@ data DBusDependency_ = Bus BusName
|
||||||
| DBusIO IODependency_
|
| DBusIO IODependency_
|
||||||
|
|
||||||
-- | A dependency that only requires IO to evaluate (no payload)
|
-- | A dependency that only requires IO to evaluate (no payload)
|
||||||
data IODependency_ = IOSystem_ SystemDependency | forall a. IOSometimes_ (Sometimes a)
|
data IODependency_ = IOSystem_ SystemDependency
|
||||||
|
| forall a. IOSometimes_ (Sometimes a)
|
||||||
|
|
||||||
data SystemDependency = Executable Bool FilePath
|
data SystemDependency = Executable Bool FilePath
|
||||||
| AccessiblePath FilePath Bool Bool
|
| AccessiblePath FilePath Bool Bool
|
||||||
|
|
Loading…
Reference in New Issue