2020-04-01 22:06:00 -04:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- | Dmenu (Rofi) Commands
|
|
|
|
|
2020-04-01 20:17:47 -04:00
|
|
|
module XMonad.Internal.Command.DMenu
|
|
|
|
( runCmdMenu
|
|
|
|
, runAppMenu
|
|
|
|
, runClipMenu
|
|
|
|
, runWinMenu
|
|
|
|
, runNetMenu
|
|
|
|
, runDevMenu
|
2020-05-02 00:02:29 -04:00
|
|
|
, runBwMenu
|
2020-04-01 20:17:47 -04:00
|
|
|
, runShowKeys
|
2020-08-17 18:46:02 -04:00
|
|
|
, runAutorandrMenu
|
2020-04-01 20:17:47 -04:00
|
|
|
) where
|
2020-03-28 14:44:50 -04:00
|
|
|
|
|
|
|
import Control.Monad.Reader
|
|
|
|
|
|
|
|
import Graphics.X11.Types
|
|
|
|
|
|
|
|
import System.IO
|
|
|
|
|
2020-04-06 00:14:56 -04:00
|
|
|
import XMonad.Core hiding (spawn)
|
|
|
|
import XMonad.Internal.Process
|
2020-04-01 20:17:47 -04:00
|
|
|
import XMonad.Internal.Shell
|
2020-03-28 14:44:50 -04:00
|
|
|
import XMonad.Util.NamedActions
|
|
|
|
|
2020-04-01 22:06:00 -04:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- | Other internal functions
|
|
|
|
|
2020-03-28 14:44:50 -04:00
|
|
|
myDmenuCmd :: String
|
|
|
|
myDmenuCmd = "rofi"
|
|
|
|
|
2020-07-06 03:06:44 -04:00
|
|
|
spawnDmenuCmd :: [String] -> X ()
|
|
|
|
spawnDmenuCmd = spawnCmd myDmenuCmd
|
2020-04-01 22:06:00 -04:00
|
|
|
|
2020-08-15 17:00:13 -04:00
|
|
|
themeArgs :: String -> [String]
|
|
|
|
themeArgs hexColor =
|
|
|
|
[ "-theme-str"
|
|
|
|
, "'#element.selected.normal { background-color: " ++ hexColor ++ "; }'"
|
|
|
|
]
|
|
|
|
|
|
|
|
myDmenuMatchingArgs :: [String]
|
|
|
|
myDmenuMatchingArgs = ["-i"] -- case insensitivity
|
|
|
|
|
2020-04-01 22:06:00 -04:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- | Exported Commands
|
|
|
|
|
2020-05-02 00:02:29 -04:00
|
|
|
devSecrets :: [String]
|
2021-03-17 22:44:25 -04:00
|
|
|
devSecrets = ["-c", "/home/ndwar/.config/rofi/devices.yml"]
|
2020-05-02 00:02:29 -04:00
|
|
|
|
|
|
|
runDevMenu :: X ()
|
2020-07-06 03:06:44 -04:00
|
|
|
runDevMenu = spawnCmd "rofi-dev" $ devSecrets ++ rofiArgs
|
2020-05-02 00:25:57 -04:00
|
|
|
where
|
2020-08-15 17:00:13 -04:00
|
|
|
rofiArgs = "--" : themeArgs "#999933" ++ myDmenuMatchingArgs
|
2020-05-02 00:02:29 -04:00
|
|
|
|
|
|
|
runBwMenu :: X ()
|
2020-08-15 17:00:13 -04:00
|
|
|
runBwMenu = spawnCmd "rofi-bw" $ ["-c", "--"] ++ themeArgs "#bb6600"
|
|
|
|
++ myDmenuMatchingArgs
|
2020-05-02 00:02:29 -04:00
|
|
|
|
2020-03-28 14:44:50 -04:00
|
|
|
runShowKeys :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
|
|
|
|
runShowKeys x = addName "Show Keybindings" $ do
|
2020-07-06 03:06:44 -04:00
|
|
|
(h, _, _, _) <- io $ createProcess' $ (shell' cmd) { std_in = CreatePipe }
|
|
|
|
io $ forM_ h $ \h' -> hPutStr h' (unlines $ showKm x) >> hClose h'
|
2020-08-15 17:00:13 -04:00
|
|
|
where cmd = fmtCmd myDmenuCmd $ ["-dmenu", "-p", "commands"]
|
|
|
|
++ themeArgs "#a200ff" ++ myDmenuMatchingArgs
|
2020-03-28 14:44:50 -04:00
|
|
|
|
|
|
|
runCmdMenu :: X ()
|
2020-07-06 03:06:44 -04:00
|
|
|
runCmdMenu = spawnDmenuCmd ["-show", "run"]
|
2020-03-28 14:44:50 -04:00
|
|
|
|
|
|
|
runAppMenu :: X ()
|
2020-07-06 03:06:44 -04:00
|
|
|
runAppMenu = spawnDmenuCmd ["-show", "drun"]
|
2020-03-28 14:44:50 -04:00
|
|
|
|
|
|
|
runClipMenu :: X ()
|
2020-08-15 17:00:13 -04:00
|
|
|
runClipMenu = spawnDmenuCmd $
|
2020-03-28 14:44:50 -04:00
|
|
|
[ "-modi", "\"clipboard:greenclip print\""
|
|
|
|
, "-show", "clipboard"
|
|
|
|
, "-run-command", "'{cmd}'"
|
2020-08-15 17:00:13 -04:00
|
|
|
] ++ themeArgs "#00c44e"
|
2020-03-28 14:44:50 -04:00
|
|
|
|
|
|
|
runWinMenu :: X ()
|
2020-07-06 03:06:44 -04:00
|
|
|
runWinMenu = spawnDmenuCmd ["-show", "window"]
|
2020-03-28 14:44:50 -04:00
|
|
|
|
|
|
|
runNetMenu :: X ()
|
2020-08-15 17:00:13 -04:00
|
|
|
runNetMenu = spawnCmd "networkmanager_dmenu" $ themeArgs "#ff3333"
|
2020-08-17 18:46:02 -04:00
|
|
|
|
|
|
|
runAutorandrMenu :: X ()
|
|
|
|
runAutorandrMenu = spawnCmd "rofi-autorandr" $ themeArgs "#ff0066"
|