xmonad-config/lib/XMonad/Internal/Command/DMenu.hs

103 lines
3.1 KiB
Haskell
Raw Normal View History

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
import Control.Monad.Reader
import Graphics.X11.Types
import System.IO
import XMonad.Core hiding (spawn)
import XMonad.Internal.Process
2020-04-01 20:17:47 -04:00
import XMonad.Internal.Shell
import XMonad.Util.NamedActions
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Other internal functions
myDmenuCmd :: String
myDmenuCmd = "rofi"
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]
devSecrets = concatMap (\x -> ["-s", x])
2020-12-11 16:11:58 -05:00
[ "/tmp/media/ndwar/Roylab:user=ndwarshuis3@gatech.edu,host=outlook.office365.com"
, "/tmp/media/ndwar/MC3M:user=ndwarshuis3@gatech.edu,host=outlook.office365.com"
] ++
2020-12-14 21:01:57 -05:00
concatMap (\x -> ["-b", x])
[ "/home/ndwar/.ssh:\"Veracrypt (ssh)\""
, "/tmp/media/ndwar/accounts:\"Veracrypt (accounts)\""
, "/tmp/media/ndwar/ansible-pki:\"Veracrypt (Ansible PKI)\""
, "/tmp/media/ndwar/call-logs:\"Veracrypt (ACR)\""
] ++
concatMap (\x -> ["-v", x])
[ "/tmp/media/ndwar/accounts:/mnt/data/Documents/personal_records/financial/acnt.crypt"
, "/home/ndwar/.ssh:/mnt/data/Documents/crypt/ssh-config"
, "/tmp/media/ndwar/ansible-pki:/home/ndwar/.ansible/openvpn.vcrypt"
2020-12-14 21:01:57 -05:00
, "/tmp/media/ndwar/call-logs:/mnt/data/Documents/personal_records/call_logs"
2020-05-02 00:02:29 -04:00
]
runDevMenu :: X ()
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
runShowKeys :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
runShowKeys x = addName "Show Keybindings" $ do
(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
runCmdMenu :: X ()
runCmdMenu = spawnDmenuCmd ["-show", "run"]
runAppMenu :: X ()
runAppMenu = spawnDmenuCmd ["-show", "drun"]
runClipMenu :: X ()
2020-08-15 17:00:13 -04:00
runClipMenu = spawnDmenuCmd $
[ "-modi", "\"clipboard:greenclip print\""
, "-show", "clipboard"
, "-run-command", "'{cmd}'"
2020-08-15 17:00:13 -04:00
] ++ themeArgs "#00c44e"
runWinMenu :: X ()
runWinMenu = spawnDmenuCmd ["-show", "window"]
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"