dotfiles/dotfiles/xmonad/xmonad.hs

121 lines
4.5 KiB
Haskell
Raw Normal View History

import Graphics.X11.ExtraTypes.XF86
import System.Taffybar.Hooks.PagerHints (pagerHints)
import Text.Printf
import XMonad hiding ( (|||) )
2016-10-05 02:30:30 -06:00
import XMonad.Actions.CycleWS
import XMonad.Actions.WindowBringer
import XMonad.Actions.WorkspaceNames
import XMonad.Config ()
import XMonad.Hooks.EwmhDesktops
2016-09-13 13:51:06 -06:00
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.FadeInactive
2016-10-03 15:57:58 -06:00
import XMonad.Layout.BoringWindows
import XMonad.Layout.LayoutCombinators
2016-10-03 15:57:58 -06:00
import XMonad.Layout.Minimize
2016-09-27 18:27:03 -06:00
import XMonad.Layout.MultiColumns
2016-09-15 02:49:15 -06:00
import XMonad.Layout.MultiToggle
import XMonad.Layout.MultiToggle.Instances
import XMonad.Layout.NoBorders
import XMonad.Layout.Spacing
import qualified XMonad.StackSet as W
import XMonad.Util.CustomKeys
import XMonad.Util.NamedWindows (getName)
getClass :: Window -> X String
getClass w = do
classHint <- withDisplay $ \d -> io $ getClassHint d w
return $ resClass classHint
myDecorateName ws w = do
name <- show <$> getName w
classTitle <- getClass w
workspaceToName <- getWorkspaceNames
return $ printf "%-20s%-50s %+40s" classTitle name $ "in " ++ workspaceToName (W.tag ws)
myWindowBringerConfig = WindowBringerConfig { menuCommand = "rofi"
, menuArgs = ["-dmenu", "-i"]
, windowTitler = myDecorateName
}
main = xmonad $ ewmh $ pagerHints def
{ modMask = mod4Mask
2016-09-13 13:51:06 -06:00
, terminal = "urxvt"
2016-09-13 18:51:12 -06:00
, manageHook = manageDocks <+> manageHook def
, layoutHook = myLayoutHook
, logHook = myLogHook
2016-09-16 15:33:37 -06:00
, handleEventHook = docksEventHook <+> fullscreenEventHook
2016-09-13 13:51:06 -06:00
, startupHook = myStartup
2016-10-13 14:28:44 -06:00
, keys = customKeys (const []) addKeys
}
2016-09-09 18:48:28 -06:00
myLogHook = fadeInactiveLogHook 0.9
setWorkspaceNameToFocusedWindow workspace = do
namedWindows <- mapM getName $ take 2 $ W.integrate' $ W.stack workspace
setWorkspaceName (W.tag workspace) (concatMap show namedWindows)
automaticallySetWorkspaceNames = do
ws <- gets windowset
mapM_ setWorkspaceNameToFocusedWindow (W.workspaces ws)
shiftThenView i = W.greedyView i . W.shift i
2016-10-13 01:10:53 -06:00
layouts = multiCol [1, 1] 2 0.01 (-0.5) ||| Full ||| Tall 1 (3/100) (1/2)
myLayoutHook = avoidStruts . smartSpacing 10 . noBorders . minimize
. boringWindows . mkToggle (MIRROR ?? EOT) $ layouts
myStartup = spawn "systemctl --user start wm.target"
addKeys conf@XConfig {modMask = modm} =
[ ((modm, xK_p), spawn "rofi -show drun")
2016-09-19 12:07:03 -06:00
, ((modm .|. shiftMask, xK_p), spawn "rofi -show run")
, ((modm, xK_g), gotoMenuConfig myWindowBringerConfig)
, ((modm, xK_b), bringMenuConfig myWindowBringerConfig)
2016-10-05 03:20:35 -06:00
, ((modm .|. controlMask, xK_t), spawn
"systemctl --user restart taffybar.service")
2016-10-03 18:49:44 -06:00
, ((modm, xK_v), spawn "copyq paste")
2016-10-05 02:30:30 -06:00
, ((modm, xK_s), swapNextScreen)
, ((modm .|. controlMask, xK_space), sendMessage $ JumpToLayout "Full")
, ((modm, xK_slash), sendMessage $ Toggle MIRROR)
2016-10-03 15:57:58 -06:00
, ((modm, xK_m), withFocused minimizeWindow)
, ((modm .|. shiftMask, xK_m), sendMessage RestoreNextMinimizedWin)
2016-10-05 03:20:35 -06:00
-- Hyper bindings
, ((mod3Mask, xK_e), moveTo Next EmptyWS)
, ((mod3Mask .|. shiftMask, xK_e), shiftTo Next EmptyWS)
, ((mod3Mask, xK_v), spawn "copyq_rofi.sh")
, ((mod3Mask, xK_p), spawn "system_password.sh")
, ((mod3Mask, xK_s), spawn "screenshot.sh")
, ((mod3Mask, xK_c), spawn "shell_command.sh")
2016-10-05 03:20:35 -06:00
-- playerctl
, ((mod3Mask, xK_f), spawn "playerctl play-pause")
, ((0, xF86XK_AudioPause), spawn "playerctl play-pause")
2016-10-05 03:20:35 -06:00
, ((mod3Mask, xK_d), spawn "playerctl next")
, ((0, xF86XK_AudioNext), spawn "playerctl next")
, ((mod3Mask, xK_a), spawn "playerctl previous")
, ((0, xF86XK_AudioPrev), spawn "playerctl previous")
-- volume control
2016-10-05 17:32:53 -06:00
, ((0, xF86XK_AudioRaiseVolume), spawn "pactl set-sink-volume 0 +05%")
, ((0, xF86XK_AudioLowerVolume), spawn "pactl set-sink-volume 0 -05%")
, ((0, xF86XK_AudioMute), spawn "pactl set-sink-mute 0 toggle")
2016-10-05 17:32:53 -06:00
, ((mod3Mask, xK_w), spawn "pactl set-sink-volume 0 +05%")
, ((mod3Mask, xK_s), spawn "pactl set-sink-volume 0 -05%")
2016-10-13 01:09:35 -06:00
] ++
2016-10-13 01:09:35 -06:00
-- Replace original moving stuff around + greedy view bindings
[((additionalMask .|. modm, key), windows $ function workspace)
| (workspace, key) <- zip (workspaces conf) [xK_1 .. xK_9]
, (function, additionalMask) <-
[ (W.greedyView, 0)
, (W.shift, shiftMask)
, (shiftThenView, controlMask)]]
-- Local Variables:
-- flycheck-ghc-args: ("-Wno-missing-signatures")
-- End: