xmonad-config/bin/xmonad.hs

693 lines
22 KiB
Haskell
Raw Normal View History

{-# LANGUAGE LambdaCase #-}
2020-03-20 01:12:20 -04:00
{-# LANGUAGE MultiWayIf #-}
module Main (main) where
2020-03-22 23:23:02 -04:00
import ACPI
import DBus.Common
import DBus.IntelBacklight
import DBus.Screensaver
import Notify
import Process
import SendXMsg
import Shell
2020-03-22 23:23:02 -04:00
import qualified Theme as T
import WorkspaceMon
import Control.Arrow (first)
2020-03-22 23:23:02 -04:00
import Control.Concurrent
import Control.Monad
( forM
, forM_
, liftM2
2020-03-22 23:23:02 -04:00
, mapM_
, void
, when
)
import Data.List
( find
, isPrefixOf
, sortBy
, sortOn
)
2020-03-22 23:23:02 -04:00
import qualified Data.Map.Lazy as M
import Data.Maybe (catMaybes, isJust)
import Data.Monoid (All (..))
import DBus.Client (Client)
2020-03-22 23:23:02 -04:00
import Graphics.X11.Types
import Graphics.X11.Xlib.Atom
import Graphics.X11.Xlib.Extras
import Graphics.X11.Xrandr
2020-03-22 23:23:02 -04:00
import System.Directory
import System.Exit
import System.IO
import System.Posix.IO
import System.Posix.Process
import System.Posix.Types
2020-03-22 23:23:02 -04:00
import Text.Read (readMaybe)
2020-03-25 18:55:52 -04:00
import Xmobar.Common
2020-03-22 23:23:02 -04:00
import XMonad
import XMonad.Actions.CopyWindow
import XMonad.Actions.CycleWS
import XMonad.Actions.DynamicWorkspaces
import XMonad.Actions.PhysicalScreens
import XMonad.Actions.Volume
2020-03-27 21:09:40 -04:00
import XMonad.Actions.Warp
2020-03-22 23:23:02 -04:00
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
-- import XMonad.Layout.LayoutCombinators hiding ((|||))
-- import XMonad.Layout.Master
2020-03-22 23:23:02 -04:00
import XMonad.Layout.NoBorders
import XMonad.Layout.NoFrillsDecoration
import XMonad.Layout.PerWorkspace
import XMonad.Layout.Renamed
-- import XMonad.Layout.Simplest
2020-03-22 23:23:02 -04:00
import XMonad.Layout.Tabbed
import XMonad.Prompt
import XMonad.Prompt.ConfirmPrompt
import qualified XMonad.StackSet as W
2020-03-22 23:23:02 -04:00
import XMonad.Util.EZConfig
import XMonad.Util.NamedActions
import XMonad.Util.Run
2020-03-20 01:15:22 -04:00
main :: IO ()
main = do
2020-03-20 00:51:36 -04:00
dbClient <- startXMonadService
(barPID, h) <- spawnPipe' "xmobar"
2020-03-22 23:20:10 -04:00
_ <- forkIO runPowermon
2020-03-25 14:45:21 -04:00
_ <- forkIO runWorkspaceMon'
launch
$ ewmh
2020-03-26 09:48:02 -04:00
$ addDescrKeys' ((myModMask, xK_F1), showKeybindings) (mkKeys [barPID] dbClient)
$ def { terminal = myTerm
, modMask = myModMask
, layoutHook = myLayouts
, manageHook = myManageHook <+> manageDocks <+> manageHook def
, handleEventHook = myEventHook <+> docksEventHook <+> handleEventHook def
, startupHook = docksStartupHook <+> startupHook def
, workspaces = myWorkspaces
, logHook = myLoghook h
, clickJustFocuses = False
, focusFollowsMouse = False
2020-03-22 17:59:49 -04:00
, normalBorderColor = T.bordersColor
, focusedBorderColor = T.selectedBordersColor
}
2020-03-25 14:45:21 -04:00
runWorkspaceMon' :: IO ()
runWorkspaceMon' = runWorkspaceMon
$ fromList [ (myGimpClass, myGimpWorkspace)
, (myVMClass, myVMWorkspace)
, (myXSaneClass, myXSaneWorkspace)
2020-03-25 14:45:21 -04:00
]
spawnPipe' :: MonadIO m => String -> m (ProcessID, Handle)
spawnPipe' x = io $ do
2020-03-20 01:12:20 -04:00
(rd, wr) <- createPipe
setFdOption wr CloseOnExec True
h <- fdToHandle wr
hSetBuffering h LineBuffering
p <- xfork $ do
_ <- dupTo rd stdInput
executeFile "/bin/sh" False ["-c", x] Nothing
closeFd rd
return (p, h)
2020-03-20 01:15:22 -04:00
myWorkspaces :: [String]
myWorkspaces = map show [1..10 :: Int]
myLayouts = onWorkspace myVMWorkspace vmLayout
$ onWorkspace myGimpWorkspace gimpLayout
$ tall ||| single ||| full
where
addTopBar = noFrillsDeco shrinkText T.tabbedTheme
tall = renamed [Replace "Tall"]
$ avoidStruts
$ addTopBar
$ noBorders
$ Tall 1 0.03 0.5
single = renamed [Replace "Tabbed"]
$ avoidStruts
$ noBorders
$ tabbedAlways shrinkText T.tabbedTheme
full = renamed [Replace "Full"]
$ noBorders Full
vmLayout = noBorders Full
-- TODO use a tabbed layout for multiple master windows
gimpLayout = renamed [Replace "Gimp Layout"]
$ avoidStruts
$ noBorders
$ addTopBar
$ Tall 1 0.025 0.8
-- | Format workspace and layout in loghook
-- The format will be like "[<1> 2 3] 4 5 | LAYOUT" where each digit
-- is the workspace and LAYOUT is the current layout. Each workspace
-- in the brackets is currently visible and the order reflects the
-- physical location of each screen. The "<>" is the workspace
-- that currently has focus
2020-03-20 01:15:22 -04:00
myLoghook :: Handle -> X ()
myLoghook h = withWindowSet $ io . hPutStrLn h . myWindowSetXinerama
2020-03-20 01:15:22 -04:00
myWindowSetXinerama
:: LayoutClass layout a1 =>
W.StackSet String (layout a1) a2 ScreenId ScreenDetail -> String
myWindowSetXinerama ws = wsString ++ sep ++ layout
where
2020-03-25 18:55:52 -04:00
wsString = wrapColorBg T.backdropFgColor "" $ onscreen ++ offscreen'
offscreen' = if null offscreen then "" else " " ++ offscreen
2020-03-25 18:55:52 -04:00
sep = wrapColorBg T.backdropFgColor "" " : "
onscreen = wrapColorBg hilightFgColor hilightBgColor
$ (\s -> " " ++ s ++ " ")
$ unwords
$ map (fmtTags . W.tag . W.workspace)
. sortBy compareXCoord
$ W.current ws : W.visible ws
fmtTags t = if t == W.currentTag ws
2020-03-25 18:55:52 -04:00
then wrapColorBg T.fgColor hilightBgColor t
else t
offscreen = unwords
$ map W.tag
. filter (isJust . W.stack)
. sortOn W.tag
$ W.hidden ws
hilightBgColor = "#8fc7ff"
hilightFgColor = T.blend' 0.5 hilightBgColor T.fgColor
layout = description . W.layout . W.workspace . W.current $ ws
compareXCoord s0 s1 = compare x0 x1
where
(_, Rectangle x0 _ _ _) = getScreenIdAndRectangle s0
(_, Rectangle x1 _ _ _) = getScreenIdAndRectangle s1
viewShift = doF . liftM2 (.) W.view W.shift
appendViewShift tag = liftX (appendWorkspace tag) >> viewShift tag
($?) :: Query a -> (a -> Bool) -> Query Bool
($?) q f = f <$> q
2020-03-27 20:02:27 -04:00
matchGimpRole :: String -> Query Bool
matchGimpRole role = stringProperty "WM_WINDOW_ROLE" $? isPrefixOf role
<&&> className =? myGimpClass
moveBottom :: W.StackSet i l a s sd -> W.StackSet i l a s sd
moveBottom = W.modify' $ \(W.Stack f t b) -> W.Stack f (reverse b ++ t) []
2020-03-20 01:15:22 -04:00
myManageHook :: ManageHook
myManageHook = composeOne
[ isDialog -?> doCenterFloat
-- VM window
, className =? myVMClass -?> appendViewShift myVMWorkspace
-- GIMP
2020-03-27 20:02:27 -04:00
, matchGimpRole "gimp-image-window" -?> appendViewShift myGimpWorkspace
, matchGimpRole "gimp-dock" -?> doF (moveBottom . W.focusMaster)
, matchGimpRole "gimp-toolbox" -?> doF (moveBottom . W.focusMaster)
, className =? myGimpClass -?> appendViewShift myGimpWorkspace
-- XSane
, className =? myXSaneClass -?> appendViewShift myXSaneWorkspace >> doFloat
-- the seafile applet
, className =? "Seafile Client" -?> doFloat
-- gnucash
, (className =? "Gnucash" <&&> title =? "Transaction Import Assistant") -?> doFloat
-- plots and graphics created by R
, className =? "R_x11" -?> doFloat
, className =? "mpv" -?> doFloat
-- the floating windows created by the brave browser
, stringProperty "WM_NAME" =? "Brave" -?> doFloat
, (stringProperty "WM_WINDOW_ROLE" =? "pop-up"
<&&> className =? "Brave-browser") -?> doFloat
-- the dialog windows created by the zotero addon in Google Docs
, (className =? "Zotero" <&&> resource =? "Toplevel") -?> doFloat
]
2020-03-20 01:15:22 -04:00
myEventHook :: Event -> X All
myEventHook ClientMessageEvent { ev_message_type = t, ev_data = d }
| t == bITMAP = do
2020-03-25 14:45:21 -04:00
let (xtype, tag) = splitXMsg d
case xtype of
Workspace -> removeEmptyWorkspaceByTag tag
ACPI -> do
2020-03-22 23:20:10 -04:00
let acpiTag = toEnum <$> readMaybe tag :: Maybe ACPIEvent
forM_ acpiTag $ \case
Power -> runPowerPrompt
Sleep -> confirmPrompt T.promptTheme "suspend?" runSuspend
LidClose -> do
status <- io isDischarging
forM_ status $ \s -> runScreenLock >> when s runSuspend
return (All True)
myEventHook _ = return (All True)
data PowerPrompt = PowerPrompt
instance XPrompt PowerPrompt where
2020-03-16 19:34:13 -04:00
showXPrompt PowerPrompt = "(P)oweroff (S)uspend (H)ibernate (R)eboot:"
runScreenLock :: X ()
runScreenLock = spawn "screenlock"
runPowerOff :: X ()
runPowerOff = spawn "systemctl poweroff"
runSuspend :: X ()
runSuspend = spawn "systemctl suspend"
runHibernate :: X ()
runHibernate = spawn "systemctl hibernate"
runReboot :: X ()
runReboot = spawn "systemctl reboot"
2020-03-22 23:46:56 -04:00
data PowerAction = Poweroff
| Shutdown
| Hibernate
| Reboot
deriving (Eq)
instance Enum PowerAction where
toEnum 0 = Poweroff
toEnum 1 = Shutdown
toEnum 2 = Hibernate
toEnum 3 = Reboot
toEnum _ = errorWithoutStackTrace "Main.Enum.PowerAction.toEnum: bad argument"
fromEnum Poweroff = 0
fromEnum Shutdown = 1
fromEnum Hibernate = 2
fromEnum Reboot = 3
runPowerPrompt :: X ()
runPowerPrompt = mkXPrompt PowerPrompt theme comp executeAction
where
2020-03-16 19:34:13 -04:00
comp = mkComplFunFromList []
theme = T.promptTheme { promptKeymap = keymap }
keymap = M.fromList
2020-03-16 19:36:12 -04:00
$ ((controlMask, xK_g), quit) :
2020-03-16 19:34:13 -04:00
map (first $ (,) 0)
2020-03-22 23:46:56 -04:00
[ (xK_p, sendAction Poweroff)
, (xK_s, sendAction Shutdown)
, (xK_h, sendAction Hibernate)
, (xK_r, sendAction Reboot)
2020-03-16 19:34:13 -04:00
, (xK_Return, quit)
, (xK_Escape, quit)
]
2020-03-22 23:46:56 -04:00
sendAction a = setInput (show $ fromEnum a) >> setSuccess True >> setDone True
executeAction a = case toEnum $ read a of
Poweroff -> runPowerOff
Shutdown -> runScreenLock >> runSuspend
Hibernate -> runScreenLock >> runHibernate
Reboot -> runReboot
runQuitPrompt :: X ()
runQuitPrompt = confirmPrompt T.promptTheme "quit?" $ io exitSuccess
-- TODO for some reason the screen never wakes up after suspend when
-- the nvidia card is up, so block suspend if nvidia card is running
-- and warn user
2020-03-16 20:16:53 -04:00
isUsingNvidia :: IO Bool
isUsingNvidia = doesDirectoryExist "/sys/module/nvidia"
runOptimusPrompt :: X ()
runOptimusPrompt = do
nvidiaOn <- io isUsingNvidia
switch $ if nvidiaOn then "intel" else "nvidia"
where
switch mode = confirmPrompt T.promptTheme (prompt mode) (cmd mode)
prompt mode = "gpu switch to " ++ mode ++ "?"
cmd mode = spawnCmd "optimus-manager"
["--switch", mode, "--no-confirm"]
>> io exitSuccess
-- shell commands
myTerm :: String
myTerm = "urxvt"
runTerm :: X ()
runTerm = spawn myTerm
runCalc :: X ()
runCalc = spawnCmd myTerm ["-e", "R"]
myDmenuCmd :: String
myDmenuCmd = "rofi"
2020-03-17 23:40:09 -04:00
-- | Focus rofi on the current workspace always
-- Apparently xrandr and xinerama order monitors differently, which
-- means they have different indices. Since rofi uses the former and
-- xmonad uses the latter, this function is to figure out the xrandr
-- screen name based on the xinerama screen that is currently in
-- focus. The steps to do this:
-- 1) get the coordinates of the currently focuses xinerama screen
-- 2) get list of Xrandr outputs and filter which ones are connected
-- 3) match the coordinates of the xinerama screen with the xrandr
-- output and return the latter's name (eg "DP-0") which can be
-- fed to Rofi
getMonitorName :: X (Maybe String)
getMonitorName = do
dpy <- asks display
root <- asks theRoot
-- these are the focused screen coordinates according to xinerama
(sx, sy) <- getCoords
io $ do
res <- xrrGetScreenResourcesCurrent dpy root
outputs <- forM res $ \res' ->
forM (xrr_sr_outputs res') $ \output -> do
oi <- xrrGetOutputInfo dpy res' output
case oi of
-- connection: 0 == connected, 1 == disconnected
Just XRROutputInfo { xrr_oi_connection = 0
, xrr_oi_name = name
, xrr_oi_crtc = crtc
} -> do
ci <- xrrGetCrtcInfo dpy res' crtc
return $ (\ci' -> Just (name, xrr_ci_x ci', xrr_ci_y ci'))
=<< ci
_ -> return Nothing
return $ (\(name, _, _) -> Just name)
=<< find (\(_, x, y) -> x == sx && y == sy) . catMaybes
=<< outputs
where
getCoords = do
(Rectangle x y _ _) <- getFocusedScreen
return (fromIntegral x, fromIntegral y)
getFocusedScreen :: X Rectangle
getFocusedScreen = withWindowSet $ return . screenRect . W.screenDetail . W.current
2020-03-17 23:40:09 -04:00
spawnDmenuCmd :: String -> [String] -> X ()
spawnDmenuCmd cmd args = do
name <- getMonitorName
case name of
2020-03-20 01:12:20 -04:00
Just n -> spawnCmd cmd $ ["-m", n] ++ args
Nothing -> io $ putStrLn "fail"
2020-03-17 23:40:09 -04:00
spawnDmenuCmd' :: [String] -> X ()
spawnDmenuCmd' = spawnDmenuCmd myDmenuCmd
runCmdMenu :: X ()
2020-03-17 23:40:09 -04:00
runCmdMenu = spawnDmenuCmd' ["-show", "run"]
runAppMenu :: X ()
2020-03-17 23:40:09 -04:00
runAppMenu = spawnDmenuCmd' ["-show", "drun"]
runClipMenu :: X ()
2020-03-20 01:12:20 -04:00
runClipMenu = spawnDmenuCmd'
[ "-modi", "\"clipboard:greenclip print\""
, "-show", "clipboard"
, "-run-command", "'{cmd}'"
, "-theme-str", "'#element.selected.normal { background-color: #00c44e; }'"
]
runWinMenu :: X ()
2020-03-17 23:40:09 -04:00
runWinMenu = spawnDmenuCmd' ["-show", "window"]
runNetMenu :: X ()
2020-03-17 23:40:09 -04:00
runNetMenu = spawnDmenuCmd "networkmanager_dmenu" []
runDevMenu :: X ()
2020-03-17 23:40:09 -04:00
runDevMenu = spawnDmenuCmd "rofi-devices" []
runBrowser :: X ()
runBrowser = spawn "brave"
runEditor :: X ()
runEditor = spawnCmd "emacsclient"
["-c", "-e", "\"(select-frame-set-input-focus (selected-frame))\""]
runFileManager :: X ()
runFileManager = spawn "pcmanfm"
getScreenshotDir :: IO FilePath
getScreenshotDir = do
h <- getHomeDirectory
return $ h ++ "/Pictures/screenshots"
runFlameshot :: String -> X ()
runFlameshot mode = do
ssDir <- io getScreenshotDir
spawnCmd "flameshot" $ mode : ["-p", ssDir]
-- TODO this will steal focus from the current window (and puts it
-- in the root window?) ...need to fix
runAreaCapture :: X ()
runAreaCapture = runFlameshot "gui"
-- myWindowCap = "screencap -w" --external script
runScreenCapture :: X ()
runScreenCapture = runFlameshot "screen"
runDesktopCapture :: X ()
runDesktopCapture = runFlameshot "full"
2020-03-20 00:51:36 -04:00
runCleanup :: [ProcessID] -> Client -> X ()
runCleanup ps client = io $ do
mapM_ killPID ps
stopXMonadService client
runRestart :: X ()
runRestart = restart "xmonad" True
runRecompile :: X ()
runRecompile = do
-- assume that the conf directory contains a valid stack project
-- TODO this is hacky AF
confDir <- getXMonadDir
spawn $ cmd confDir
where
cmd c = fmtCmd "cd" [c]
#!&& fmtCmd "stack" ["install", ":xmonad"]
2020-03-18 12:17:39 -04:00
#!&& fmtNotifyCmd defNoteInfo { body = Just $ Text "compilation succeeded" }
#!|| fmtNotifyCmd defNoteError { body = Just $ Text "compilation failed" }
myMultimediaCtl :: String
myMultimediaCtl = "playerctl"
runTogglePlay :: X ()
runTogglePlay = spawnCmd myMultimediaCtl ["play-pause"]
runPrevTrack :: X ()
runPrevTrack = spawnCmd myMultimediaCtl ["previous"]
runNextTrack :: X ()
runNextTrack = spawnCmd myMultimediaCtl ["next"]
runStopPlay :: X ()
runStopPlay = spawnCmd myMultimediaCtl ["stop"]
runVolumeDown :: X ()
runVolumeDown = void (lowerVolume 2)
runVolumeUp :: X ()
runVolumeUp = void (raiseVolume 2)
runVolumeMute :: X ()
runVolumeMute = void toggleMute
runToggleBluetooth :: X ()
2020-03-16 16:01:04 -04:00
runToggleBluetooth = spawn
$ "bluetoothctl show | grep -q \"Powered: no\""
#!&& "a=on"
#!|| "a=off"
#!>> fmtCmd "bluetoothctl" ["power", "$a", ">", "/dev/null"]
2020-03-18 12:17:39 -04:00
#!&& fmtNotifyCmd defNoteInfo { body = Just $ Text "bluetooth powered $a" }
runIncBacklight :: X ()
runIncBacklight = io $ void callIncBrightness
runDecBacklight :: X ()
runDecBacklight = io $ void callDecBrightness
runMinBacklight :: X ()
runMinBacklight = io $ void callMinBrightness
runMaxBacklight :: X ()
runMaxBacklight = io $ void callMaxBrightness
2020-03-26 22:06:38 -04:00
runToggleDPMS :: X ()
runToggleDPMS = io $ void callToggle
-- keybindings
showKeybindings :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
showKeybindings x = addName "Show Keybindings" $ do
name <- getMonitorName
case name of
Just n -> do
h <- spawnPipe $ cmd n
io $ hPutStr h (unlines $ showKm x)
io $ hClose h
return ()
Nothing -> io $ putStrLn "fail"
where cmd name = fmtCmd myDmenuCmd
[ "-dmenu"
, "-m"
, name
, "-p"
, "commands"
, "-theme-str"
, "'#element.selected.normal { background-color: #a200ff; }'"
]
myVMWorkspace :: String
myVMWorkspace = "VM"
myVMClass :: String
myVMClass = "VirtualBoxVM"
myGimpWorkspace :: String
myGimpWorkspace = "GIMP"
-- TODO I don't feel like changing the version long term
myGimpClass :: String
myGimpClass = "Gimp-2.10"
myXSaneWorkspace :: String
myXSaneWorkspace = "XSANE"
myXSaneClass :: String
myXSaneClass = "Xsane"
wsOccupied :: Eq a1 => a1 -> W.StackSet a1 l a2 sid sd -> Bool
2020-03-27 15:35:37 -04:00
wsOccupied tag ws = elem tag $ map W.tag $ filter (isJust . W.stack)
-- list of all workspaces with windows on them
-- TODO is there not a better way to do this?
$ W.workspace (W.current ws) : W.hidden ws ++ map W.workspace (W.visible ws)
spawnOrSwitch :: WorkspaceId -> X () -> X ()
spawnOrSwitch tag cmd = do
occupied <- withWindowSet $ return . wsOccupied tag
if occupied then windows $ W.view tag else cmd
runVBox :: X ()
runVBox = spawnOrSwitch myVMWorkspace $ spawnCmd "vbox-start" ["win8raw"]
runGimp :: X ()
runGimp = spawnOrSwitch myGimpWorkspace $ spawnCmd "gimp-2.10" []
runXSane :: X ()
runXSane = spawnOrSwitch myXSaneWorkspace $ spawnCmd "xsane" []
myModMask :: KeyMask
myModMask = mod4Mask
mkNamedSubmap
:: XConfig l
-> String
2020-03-26 09:48:02 -04:00
-> [(String, String, X ())]
-> [((KeyMask, KeySym), NamedAction)]
2020-03-20 01:12:20 -04:00
mkNamedSubmap c sectionName bindings =
2020-03-26 09:48:02 -04:00
(subtitle sectionName:) $ mkNamedKeymap c
$ map (\(key, name, cmd) -> (key, addName name cmd)) bindings
2020-03-26 09:48:02 -04:00
mkKeys :: [ProcessID] -> Client -> XConfig Layout -> [((KeyMask, KeySym), NamedAction)]
mkKeys hs client c =
mkNamedSubmap c "Window Layouts"
2020-03-26 21:03:34 -04:00
[ ("M-j", "focus down", windows W.focusDown)
, ("M-k", "focus up", windows W.focusUp)
, ("M-m", "focus master", windows W.focusMaster)
, ("M-S-j", "swap down", windows W.swapDown)
, ("M-S-k", "swap up", windows W.swapUp)
, ("M-S-m", "swap master", windows W.swapMaster)
, ("M-<Return>", "next layout", sendMessage NextLayout)
2020-03-26 21:06:38 -04:00
, ("M-S-<Return>", "reset layout", setLayout $ layoutHook c)
2020-03-26 21:03:34 -04:00
, ("M-t", "sink tiling", withFocused $ windows . W.sink)
, ("M--", "shrink", sendMessage Shrink)
, ("M-=", "expand", sendMessage Expand)
2020-03-26 21:06:38 -04:00
, ("M-S--", "remove master window", sendMessage $ IncMasterN (-1))
, ("M-S-=", "add master window", sendMessage $ IncMasterN 1)
] ++
mkNamedSubmap c "Workspaces"
2020-03-26 21:06:38 -04:00
-- ASSUME standard workspaces only use numbers 0-9 (otherwise we won't get
2020-03-26 21:03:34 -04:00
-- valid keysyms)
2020-03-26 21:41:56 -04:00
([ (mods ++ n, msg ++ n, f n) | n <- myWorkspaces
, (mods, msg, f) <-
[ ("M-", "switch to workspace ", windows . W.view)
, ("M-S-", "move client to workspace ", windows . W.shift)
, ("M-C-", "follow client to workspace ", \n' -> do
windows $ W.shift n'
windows $ W.view n')
]
] ++
[ ("M-M1-l", "move up workspace", moveTo Next HiddenNonEmptyWS)
, ("M-M1-h", "move down workspace", moveTo Prev HiddenNonEmptyWS)
]) ++
mkNamedSubmap c "Screens"
2020-03-26 09:48:02 -04:00
[ ("M-l", "move up screen", nextScreen)
, ("M-h", "move down screen", prevScreen)
2020-03-26 21:41:56 -04:00
, ("M-C-l", "follow client up screen", shiftNextScreen >> nextScreen)
, ("M-C-h", "follow client down screen", shiftPrevScreen >> prevScreen)
, ("M-S-l", "shift workspace up screen", swapNextScreen >> nextScreen)
, ("M-S-h", "shift workspace down screen", swapPrevScreen >> prevScreen)
] ++
mkNamedSubmap c "Actions"
2020-03-26 09:48:02 -04:00
[ ("M-q", "close window", kill1)
, ("M-r", "run program", runCmdMenu)
2020-03-27 21:09:40 -04:00
, ("M-<Space>", "warp pointer", warpToWindow 0.5 0.5)
2020-03-26 09:48:02 -04:00
, ("M-C-s", "capture area", runAreaCapture)
, ("M-C-S-s", "capture screen", runScreenCapture)
, ("M-C-d", "capture desktop", runDesktopCapture)
-- , ("M-C-S-s", "capture focused window", spawn myWindowCap)
] ++
mkNamedSubmap c "Launchers"
2020-03-26 09:48:02 -04:00
[ ("<XF86Search>", "select/launch app", runAppMenu)
, ("M-g", "launch clipboard manager", runClipMenu)
, ("M-a", "launch network selector", runNetMenu)
, ("M-w", "launch window selector", runWinMenu)
, ("M-u", "launch device selector", runDevMenu)
, ("M-C-e", "launch editor", runEditor)
, ("M-C-w", "launch browser", runBrowser)
, ("M-C-t", "launch terminal", runTerm)
, ("M-C-q", "launch calc", runCalc)
, ("M-C-f", "launch file manager", runFileManager)
, ("M-C-v", "launch windows VM", runVBox)
, ("M-C-g", "launch GIMP", runGimp)
, ("M-C-x", "launch XSane", runXSane)
] ++
mkNamedSubmap c "Multimedia"
2020-03-26 09:48:02 -04:00
[ ("<XF86AudioPlay>", "toggle play/pause", runTogglePlay)
, ("<XF86AudioPrev>", "previous track", runPrevTrack)
, ("<XF86AudioNext>", "next track", runNextTrack)
, ("<XF86AudioStop>", "stop", runStopPlay)
, ("<XF86AudioLowerVolume>", "volume down", runVolumeDown)
, ("<XF86AudioRaiseVolume>", "volume up", runVolumeUp)
, ("<XF86AudioMute>", "volume mute", runVolumeMute)
] ++
2020-03-26 22:02:20 -04:00
-- dummy map for dunst commands (defined separately but this makes them show
-- up in the help menu)
mkNamedSubmap c "Dunst"
[ ("M-`", "dunst history", return ())
, ("M-S-`", "dunst close", return ())
, ("M-M1-`", "dunst context menu", return ())
, ("M-C-`", "dunst close all", return ())
] ++
mkNamedSubmap c "System"
2020-03-26 09:48:02 -04:00
[ ("M-.", "backlight up", runIncBacklight)
, ("M-,", "backlight down", runDecBacklight)
, ("M-M1-,", "backlight min", runMinBacklight)
, ("M-M1-.", "backlight max", runMaxBacklight)
, ("M-<End>", "power menu", runPowerPrompt)
, ("M-<Home>", "quit xmonad", runQuitPrompt)
, ("M-<Delete>", "lock screen", runScreenLock)
-- M-<F1> reserved for showing the keymap
, ("M-<F2>", "restart xmonad", runCleanup hs client >> runRestart)
, ("M-<F3>", "recompile xmonad", runRecompile)
, ("M-<F10>", "toggle bluetooth", runToggleBluetooth)
2020-03-26 22:06:38 -04:00
, ("M-<F11>", "toggle screensaver", runToggleDPMS)
, ("M-<F12>", "switch gpu", runOptimusPrompt)
]