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
|
|
|
|
|
2021-11-07 13:35:08 -05:00
|
|
|
import System.Directory (XdgDirectory (..), getXdgDirectory)
|
2020-03-28 14:44:50 -04:00
|
|
|
import System.IO
|
|
|
|
|
2021-11-07 13:35:08 -05:00
|
|
|
import XMonad.Core hiding (spawn)
|
|
|
|
import XMonad.Internal.Dependency
|
2021-06-20 13:55:31 -04:00
|
|
|
import XMonad.Internal.Notify
|
2020-04-06 00:14:56 -04:00
|
|
|
import XMonad.Internal.Process
|
2021-11-21 10:26:28 -05: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
|
|
|
--------------------------------------------------------------------------------
|
2021-06-19 00:17:47 -04:00
|
|
|
-- | DMenu executables
|
2020-04-01 22:06:00 -04:00
|
|
|
|
2020-03-28 14:44:50 -04:00
|
|
|
myDmenuCmd :: String
|
|
|
|
myDmenuCmd = "rofi"
|
|
|
|
|
2021-06-19 00:17:47 -04:00
|
|
|
myDmenuDevices :: String
|
|
|
|
myDmenuDevices = "rofi-dev"
|
|
|
|
|
|
|
|
myDmenuPasswords :: String
|
|
|
|
myDmenuPasswords = "rofi-bw"
|
|
|
|
|
|
|
|
myDmenuMonitors :: String
|
|
|
|
myDmenuMonitors = "rofi-autorandr"
|
|
|
|
|
|
|
|
myDmenuNetworks :: String
|
|
|
|
myDmenuNetworks = "networkmanager_dmenu"
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- | Other internal functions
|
|
|
|
|
2021-11-20 19:35:24 -05:00
|
|
|
spawnDmenuCmd :: String -> [String] -> FeatureX
|
2021-11-21 10:26:28 -05:00
|
|
|
spawnDmenuCmd n = featureExeArgs n 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
|
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runDevMenu :: FeatureX
|
2021-11-21 10:26:28 -05:00
|
|
|
runDevMenu = featureDefault "device manager" [Executable myDmenuDevices] $ do
|
2021-06-19 00:17:47 -04:00
|
|
|
c <- io $ getXdgDirectory XdgConfig "rofi/devices.yml"
|
|
|
|
spawnCmd myDmenuDevices
|
|
|
|
$ ["-c", c]
|
|
|
|
++ "--" : themeArgs "#999933"
|
|
|
|
++ myDmenuMatchingArgs
|
2020-05-02 00:02:29 -04:00
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runBwMenu :: FeatureX
|
2021-11-21 10:26:28 -05:00
|
|
|
runBwMenu = featureDefault "password manager" [Executable myDmenuPasswords] $
|
2021-09-05 12:22:16 -04:00
|
|
|
spawnCmd myDmenuPasswords $ ["-c"] ++ themeArgs "#bb6600" ++ myDmenuMatchingArgs
|
2020-05-02 00:02:29 -04:00
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
-- TODO this is weirdly inverted
|
2020-03-28 14:44:50 -04:00
|
|
|
runShowKeys :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
|
|
|
|
runShowKeys x = addName "Show Keybindings" $ do
|
2021-11-20 01:15:04 -05:00
|
|
|
s <- io $ evalFeature $ runDMenuShowKeys x
|
2021-11-21 10:26:28 -05:00
|
|
|
ifSatisfied s
|
2021-06-20 13:55:31 -04:00
|
|
|
$ spawnNotify
|
|
|
|
$ defNoteError { body = Just $ Text "could not display keymap" }
|
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runDMenuShowKeys :: [((KeyMask, KeySym), NamedAction)] -> FeatureX
|
2021-11-20 19:35:24 -05:00
|
|
|
runDMenuShowKeys kbs =
|
2021-11-21 10:26:28 -05:00
|
|
|
featureDefault "keyboard shortcut menu" [Executable myDmenuCmd] $ io $ do
|
2021-06-20 13:55:31 -04:00
|
|
|
(h, _, _, _) <- createProcess' $ (shell' cmd) { std_in = CreatePipe }
|
|
|
|
forM_ h $ \h' -> hPutStr h' (unlines $ showKm kbs) >> hClose h'
|
|
|
|
where
|
|
|
|
cmd = fmtCmd myDmenuCmd $ ["-dmenu", "-p", "commands"]
|
2021-09-06 00:30:06 -04:00
|
|
|
++ themeArgs "#7f66ff" ++ myDmenuMatchingArgs
|
2020-03-28 14:44:50 -04:00
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runCmdMenu :: FeatureX
|
2021-11-20 19:35:24 -05:00
|
|
|
runCmdMenu = spawnDmenuCmd "command menu" ["-show", "run"]
|
2020-03-28 14:44:50 -04:00
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runAppMenu :: FeatureX
|
2021-11-20 19:35:24 -05:00
|
|
|
runAppMenu = spawnDmenuCmd "app launcher" ["-show", "drun"]
|
2020-03-28 14:44:50 -04:00
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runClipMenu :: FeatureX
|
2021-11-20 19:35:24 -05:00
|
|
|
runClipMenu =
|
2021-11-21 10:26:28 -05:00
|
|
|
featureDefault "clipboard manager" [Executable myDmenuCmd, Executable "greenclip"]
|
2021-06-22 00:01:07 -04:00
|
|
|
$ spawnCmd myDmenuCmd args
|
|
|
|
where
|
|
|
|
args = [ "-modi", "\"clipboard:greenclip print\""
|
|
|
|
, "-show", "clipboard"
|
|
|
|
, "-run-command", "'{cmd}'"
|
|
|
|
] ++ themeArgs "#00c44e"
|
2020-03-28 14:44:50 -04:00
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runWinMenu :: FeatureX
|
2021-11-20 19:35:24 -05:00
|
|
|
runWinMenu = spawnDmenuCmd "window switcher" ["-show", "window"]
|
2020-03-28 14:44:50 -04:00
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runNetMenu :: FeatureX
|
2021-11-20 19:35:24 -05:00
|
|
|
runNetMenu =
|
2021-11-21 10:26:28 -05:00
|
|
|
featureExeArgs "network control menu" myDmenuNetworks $ themeArgs "#ff3333"
|
2020-08-17 18:46:02 -04:00
|
|
|
|
2021-11-20 01:15:04 -05:00
|
|
|
runAutorandrMenu :: FeatureX
|
2021-11-20 19:35:24 -05:00
|
|
|
runAutorandrMenu =
|
2021-11-21 10:26:28 -05:00
|
|
|
featureExeArgs "autorandr menu" myDmenuMonitors $ themeArgs "#ff0066"
|