#+title: Phil's xmonad config #+author: Phil Bajsicki #+PROPERTY: header-args :tangle xmonad.hs * Table of Contents :toc: - [[#info][Info]] - [[#imports][Imports]] - [[#base][Base]] - [[#actions][Actions]] - [[#data][Data]] - [[#hooks][Hooks]] - [[#layouts][Layouts]] - [[#layout-modifiers][Layout Modifiers]] - [[#xmonadprompt][XMonad.Prompt]] - [[#utilities][Utilities]] - [[#colorschemes][Colorschemes]] - [[#window-management-and-layouts][Window Management and Layouts]] - [[#border-width-and-spacing][Border Width and Spacing]] - [[#layouts-1][Layouts]] - [[#theming-for-tabs-sublayout][Theming for tabs (sub)layout]] - [[#workspace-definitions][Workspace definitions]] - [[#manage-hook][Manage Hook]] - [[#startup-hook][Startup Hook]] - [[#pretty-print-for-xmobar][Pretty Print for XMobar]] - [[#main-xmonad-loop][Main XMonad loop]] - [[#xmobar][XMobar]] - [[#xmonad--managehook][XMonad & manageHook]] - [[#keybinds][Keybinds]] - [[#workspaces][Workspaces]] - [[#window-focus-and-movement][Window focus and movement]] - [[#sublayouts][Sublayouts]] - [[#xmonad-and-apps][XMonad and apps]] * Info This is my XMonad config. It's heavily based on Derek Taylor's config from DTOS. The notable things I changed are noted in their specific sections. * Imports ** Base #+begin_src haskell import XMonad import System.Directory import System.IO (hClose, hPutStr, hPutStrLn) import System.Exit (exitSuccess) import qualified XMonad.StackSet as W #+end_src ** Actions #+begin_src haskell import XMonad.Actions.CopyWindow (kill1) import XMonad.Actions.CycleWS import XMonad.Actions.GridSelect import XMonad.Actions.MouseResize import XMonad.Actions.Promote import XMonad.Actions.RotSlaves (rotSlavesDown, rotAllDown) import XMonad.Actions.SpawnOn import XMonad.Actions.UpdatePointer import XMonad.Actions.WindowGo (runOrRaise) import XMonad.Actions.WithAll (sinkAll, killAll) import qualified XMonad.Actions.Search as S #+end_src ** Data #+begin_src haskell import Data.Char (isSpace, toUpper) import Data.Maybe (fromJust) import Data.Monoid import Data.Maybe (isJust) import Data.Tree import qualified Data.Map as M #+end_src ** Hooks #+begin_src haskell import XMonad.Hooks.DynamicLog (dynamicLogWithPP, wrap, xmobarPP, xmobarColor, shorten, PP(..)) import XMonad.Hooks.EwmhDesktops -- for some fullscreen events, also for xcomposite in obs. import XMonad.Hooks.ManageDocks (avoidStruts, docks, manageDocks, ToggleStruts(..)) import XMonad.Hooks.ManageHelpers (isFullscreen, doFullFloat, doCenterFloat) import XMonad.Hooks.ServerMode import XMonad.Hooks.SetWMName import XMonad.Hooks.StatusBar import XMonad.Hooks.StatusBar.PP import XMonad.Hooks.WindowSwallowing import XMonad.Hooks.WorkspaceHistory #+end_src ** Layouts #+begin_src haskell import XMonad.Layout.Accordion import XMonad.Layout.GridVariants (Grid(Grid)) import XMonad.Layout.SimplestFloat import XMonad.Layout.Spiral import XMonad.Layout.ResizableTile import XMonad.Layout.Tabbed import XMonad.Layout.ThreeColumns #+end_src ** Layout Modifiers #+begin_src haskell import XMonad.Layout.LayoutModifier import XMonad.Layout.LimitWindows (limitWindows, increaseLimit, decreaseLimit) import XMonad.Layout.MultiToggle (mkToggle, single, EOT(EOT), (??)) import XMonad.Layout.MultiToggle.Instances (StdTransformers(NBFULL, MIRROR, NOBORDERS)) import XMonad.Layout.NoBorders import XMonad.Layout.Renamed import XMonad.Layout.ShowWName import XMonad.Layout.Simplest import XMonad.Layout.Spacing import XMonad.Layout.SubLayouts import XMonad.Layout.WindowArranger (windowArrange, WindowArrangerMsg(..)) import XMonad.Layout.WindowNavigation import qualified XMonad.Layout.ToggleLayouts as T (toggleLayouts, ToggleLayout(Toggle)) import qualified XMonad.Layout.MultiToggle as MT (Toggle(..)) #+end_src ** XMonad.Prompt #+begin_src haskell import XMonad.Prompt import XMonad.Prompt.OrgMode #+end_src ** Utilities #+begin_src haskell import XMonad.Util.Dmenu import XMonad.Util.EZConfig import XMonad.Util.Loggers import XMonad.Util.NamedActions import XMonad.Util.NamedScratchpad import XMonad.Util.Run (runProcessWithInput, safeSpawn, spawnPipe) import XMonad.Util.SpawnOnce import XMonad.Util.ClickableWorkspaces #+end_src ** Colorschemes DT's ColorScheme module. Possible choice are: - DoomOne - Dracula - GruvboxDark - MonokaiPro - Nord - OceanicNext - Palenight - SolarizedDark - SolarizedLight - TomorrowNight #+begin_src haskell import Colors.DoomOne #+end_src * Window Management and Layouts ** Border Width and Spacing #+begin_src haskell myBorderWidth :: Dimension myBorderWidth = 2 windowCount :: X (Maybe String) windowCount = gets $ Just . show . length . W.integrate' . W.stack . W.workspace . W.current . windowset --Makes setting the spacingRaw simpler to write. The spacingRaw module adds a configurable amount of space around windows. mySpacing :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a mySpacing i = spacingRaw False (Border i i i i) True (Border i i i i) True #+end_src ** Layouts - limitWindows n sets maximum number of windows displayed for layout. - mySpacing n sets the gap size around the windows. #+begin_src haskell tall = renamed [Replace "tall"] $ smartBorders -- $ windowNavigation $ addTabs shrinkText myTabTheme $ subLayout [] (smartBorders Simplest) $ mySpacing 8 $ ResizableTall 1 (3/100) (1/2) [] monocle = renamed [Replace "monocle"] $ smartBorders $ windowNavigation $ mySpacing 8 $ addTabs shrinkText myTabTheme $ subLayout [] (smartBorders Simplest) $ Full tabs = renamed [Replace "tabs"] -- I cannot add spacing to this layout because it will -- add spacing between window and tabs which looks bad. $ tabbed shrinkText myTabTheme #+end_src ** Theming for tabs (sub)layout #+begin_src haskell myTabTheme = def { fontName = "xft:Iosevka-9" , activeColor = color15 , inactiveColor = colorBack , activeBorderColor = color15 , inactiveBorderColor = colorFore , activeTextColor = colorBack , inactiveTextColor = colorFore } #+end_src ** Workspace definitions #+begin_src haskell myWorkspaces = ["1", "2", "3", "4", "5", "6", "7", "8", "9", "e", "w", "g", "d", "b", "j", "f", "o", "u", "r", "s", "t", "h", "v", "y", "n", "a", "i", "l", "x", "c", "m", "k", "q", "z", "p"] #+end_src ** Manage Hook #+begin_src haskell myManageHook = manageSpawn <> composeAll [ className =? "confirm" --> doFloat , className =? "file_progress" --> doFloat , className =? "dialog" --> doFloat , className =? "download" --> doFloat , className =? "error" --> doFloat , className =? "Gimp" --> doFloat , className =? "notification" --> doFloat , className =? "pinentry-gtk-2" --> doFloat , className =? "splash" --> doFloat , className =? "toolbar" --> doFloat , className =? "zoom" --> doFloat , className =? "Yad" --> doCenterFloat , (className =? "firefox" <&&> resource =? "Dialog") --> doFloat -- Float Firefox Dialog , isFullscreen --> doFullFloat ] #+end_src ** Startup Hook Set the WMName and session type so applications which check for it don't bug out. *** Settings applied on login #+begin_src haskell myStartupHook = do setWMName "LG3D" spawnOnce "lxsession" #+end_src **** Keyboard layout I'm Polish, so I type on a Polish layout. I also extensively use the compose key, so I have it handy. #+begin_src haskell spawnOnce "setxkbmap -model pc104 -layout pl -option compose:rctrl" #+end_src **** Mount encrypted container #+begin_src haskell spawnOnce "gocryptfs ~/.bajsicki enc --extpass lxqt-openssh-askpass" #+end_src **** Wallpaper Randomize wallpaper. Requires /feh/. You can change the path to any directory with wallpapers for consistent variety. #+begin_src haskell spawnOnce "feh --recursive --randomize --bg-fill /mnt/ext1/media/Images/Wallpapers/*" #+end_src #+RESULTS: **** Trayer Trayer is a system tray, which works well with XMobar. This restarts it every time XMonad is reinitialized to avoid weirdness. #+begin_src haskell spawn "killall trayer" -- kill current trayer on each spawn ("sleep 2 && trayer --edge top --align right --widthtype request --padding 6 --SetDockType true --SetPartialStrut true --expand true --monitor 1 --transparent true --alpha 0 " ++ colorTrayer ++ " --height 20") #+end_src **** Daemons ***** Dunst Dunst for notifications. #+begin_src haskell spawnOnce "dunst" #+end_src ***** Compositing - picom #+begin_src haskell spawnOnce "picom -b" #+end_src ***** Activity Watch I like looking back on the way I spend my time every once in a while. Local time tracking is really helpful, so I run AW in the background. #+begin_src haskell spawnOnce "aw-server" spawnOnce "aw-watcher-afk" spawnOnce "aw-watcher-window" spawnOnce "poetry run aw-watcher-spotify" #+end_src ***** Emacs Emacs daemon for emacsclient. #+begin_src haskell spawnOnce "/usr/bin/emacs --daemon" #+end_src *** Startup applications #+begin_src haskell spawnOn "1" "firefox-developer-edition" spawnOn "2" "evolution" spawnOn "9" "steam" spawnOn "3" "discord" spawnOn "6" "google-chrome-stable" spawnOn "e" "/usr/bin/emacsclient" spawnOn "j" "keepassxc" #+end_src ** Pretty Print for XMobar #+begin_src haskell myXmobarPP :: PP myXmobarPP = def { ppSep = magenta " " , ppTitleSanitize = xmobarStrip , ppCurrent = xmobarBorder "Top" "#8be9fd" 2 , ppHidden = white , ppHiddenNoWindows = lowWhite , ppUrgent = red . wrap (yellow "!") (yellow "!") , ppOrder = \[ws, l, _, wins] -> [ws, l, wins] , ppExtras = [logTitles formatFocused formatUnfocused] } where formatFocused = wrap (white "[") (white "]") . magenta . ppWindow formatUnfocused = wrap (lowWhite "[") (lowWhite "]") . blue . ppWindow -- | Windows should have *some* title, which should not not exceed a -- sane length. ppWindow :: String -> String ppWindow = xmobarRaw . (\w -> if null w then "untitled" else w) . shorten 30 blue, lowWhite, magenta, red, white, yellow :: String -> String magenta = xmobarColor "#ff79c6" "" blue = xmobarColor "#bd93f9" "" white = xmobarColor "#f8f8f2" "" yellow = xmobarColor "#f1fa8c" "" red = xmobarColor "#ff5555" "" lowWhite = xmobarColor "#bbbbbb" "" #+end_src #+begin_src haskell xmobar0 = statusBarProp "xmobar -x 0 ~/.config/xmobar/xmobarrc" (pure myXmobarPP) xmobar1 = statusBarProp "xmobar -x 1 ~/.config/xmobar/xmobarrc-no-trayer" (pure myXmobarPP) xmobar2 = statusBarProp "xmobar -x 2 ~/.config/xmobar/xmobarrc-no-trayer" (pure myXmobarPP) xmobar3 = statusBarProp "xmobar -x 3 ~/.config/xmobar/xmobarrc-no-trayer" (pure myXmobarPP) #+end_src * Main XMonad loop #+begin_src haskell main :: IO () main = do #+end_src ** XMobar Launching four instances of xmobar on their monitors. #+begin_src haskell :tangle no xmproc0 <- spawnPipe ("xmobar -x 0 $HOME/.config/xmobar/xmobarrc") xmproc1 <- spawnPipe ("xmobar -x 1 $HOME/.config/xmobar/xmobarrc-no-trayer") xmproc2 <- spawnPipe ("xmobar -x 2 $HOME/.config/xmobar/xmobarrc-no-trayer") xmproc3 <- spawnPipe ("xmobar -x 3 $HOME/.config/xmobar/xmobarrc-no-trayer") #+end_src ** XMonad & manageHook #+begin_src haskell xmonad $ ewmh $ docks $ withSB (xmobar0 <> xmobar1 <> xmobar2) $ def { manageHook = myManageHook <+> manageDocks #+end_src *** handleEventHook This lets alacritty be swallowed when it opens a GUI application. #+begin_src haskell , handleEventHook = swallowEventHook (className =? "Alacritty" <||> className =? "st-256color" <||> className =? "XTerm") (return True) #+end_src *** Pulling settings together #+begin_src haskell , modMask = mod4Mask , terminal = "alacritty" , startupHook = myStartupHook , layoutHook = avoidStruts $ windowNavigation $ subTabbed $ windowArrange $ mkToggle (NBFULL ?? NOBORDERS ?? EOT) $ withBorder myBorderWidth tall ||| noBorders monocle ||| noBorders tabs , workspaces = myWorkspaces , borderWidth = myBorderWidth , normalBorderColor = colorBack , focusedBorderColor = color15 , logHook = updatePointer (0.5, 0.5) (0, 0) } #+end_src *** logHook Define logHook. ppOutput streams into the three instances of XMobar. #+begin_src haskell :tangle no , logHook = dynamicLogWithPP { ppOutput = \x -> hPutStrLn xmproc0 x >> hPutStrLn xmproc1 x >> hPutStrLn xmproc2 x } #+end_src **** Colors/ clicks #+begin_src haskell :tangle no , ppCurrent = xmobarColor color06 "" . wrap ("") "" , ppVisible = xmobarColor color06 "" , ppHidden = xmobarColor color05 "" . wrap ("") "" , ppHiddenNoWindows = xmobarColor color05 "" #+end_src **** Window Title, Separators, etc. #+begin_src haskell :tangle no -- Title of active window , ppTitle = xmobarColor colorFore "" . shorten 48 -- Separator character , ppSep = " | " -- Urgent workspace , ppUrgent = xmobarColor color02 "" . wrap "!" "!" -- Adding # of windows on current workspace to the bar , ppExtras = [windowCount] -- order of things in xmobar , ppOrder = \(ws:l:t:ex) -> [ws,l]++ex++[t] } >> updatePointer (0.5, 0.5) (0.0, 0.0) } #+end_src * Keybinds ** Workspaces This is the bulk of my changes. I use /a lot/ of workspaces. They're all under two chords. M-s /shows/ a workspace, and M-t /throws/ a window to a workspace. Easy mnemonics, yay. #+begin_src haskell `additionalKeysP` [ ("M-s 1", (windows $ W.greedyView $ myWorkspaces !! 0)) , ("M-s 2", (windows $ W.greedyView $ myWorkspaces !! 1)) , ("M-s 3", (windows $ W.greedyView $ myWorkspaces !! 2)) , ("M-s 4", (windows $ W.greedyView $ myWorkspaces !! 3)) , ("M-s 5", (windows $ W.greedyView $ myWorkspaces !! 4)) , ("M-s 6", (windows $ W.greedyView $ myWorkspaces !! 5)) , ("M-s 7", (windows $ W.greedyView $ myWorkspaces !! 6)) , ("M-s 8", (windows $ W.greedyView $ myWorkspaces !! 7)) , ("M-s 9", (windows $ W.greedyView $ myWorkspaces !! 8)) , ("M-s e", (windows $ W.greedyView $ myWorkspaces !! 9)) , ("M-s w", (windows $ W.greedyView $ myWorkspaces !! 10)) , ("M-s g", (windows $ W.greedyView $ myWorkspaces !! 11)) , ("M-s d", (windows $ W.greedyView $ myWorkspaces !! 12)) , ("M-s b", (windows $ W.greedyView $ myWorkspaces !! 13)) , ("M-s j", (windows $ W.greedyView $ myWorkspaces !! 14)) , ("M-s f", (windows $ W.greedyView $ myWorkspaces !! 15)) , ("M-s o", (windows $ W.greedyView $ myWorkspaces !! 16)) , ("M-s u", (windows $ W.greedyView $ myWorkspaces !! 17)) , ("M-s r", (windows $ W.greedyView $ myWorkspaces !! 18)) , ("M-s s", (windows $ W.greedyView $ myWorkspaces !! 19)) , ("M-s t", (windows $ W.greedyView $ myWorkspaces !! 20)) , ("M-s h", (windows $ W.greedyView $ myWorkspaces !! 21)) , ("M-s v", (windows $ W.greedyView $ myWorkspaces !! 22)) , ("M-s y", (windows $ W.greedyView $ myWorkspaces !! 23)) , ("M-s n", (windows $ W.greedyView $ myWorkspaces !! 24)) , ("M-s a", (windows $ W.greedyView $ myWorkspaces !! 25)) , ("M-s i", (windows $ W.greedyView $ myWorkspaces !! 26)) , ("M-s l", (windows $ W.greedyView $ myWorkspaces !! 27)) , ("M-s x", (windows $ W.greedyView $ myWorkspaces !! 28)) , ("M-s c", (windows $ W.greedyView $ myWorkspaces !! 29)) , ("M-s m", (windows $ W.greedyView $ myWorkspaces !! 30)) , ("M-s k", (windows $ W.greedyView $ myWorkspaces !! 31)) , ("M-s q", (windows $ W.greedyView $ myWorkspaces !! 32)) , ("M-s z", (windows $ W.greedyView $ myWorkspaces !! 33)) , ("M-s p", (windows $ W.greedyView $ myWorkspaces !! 34)) , ("M-t 1", (windows $ W.shift $ myWorkspaces !! 0)) , ("M-t 2", (windows $ W.shift $ myWorkspaces !! 1)) , ("M-t 3", (windows $ W.shift $ myWorkspaces !! 2)) , ("M-t 4", (windows $ W.shift $ myWorkspaces !! 3)) , ("M-t 5", (windows $ W.shift $ myWorkspaces !! 4)) , ("M-t 6", (windows $ W.shift $ myWorkspaces !! 5)) , ("M-t 7", (windows $ W.shift $ myWorkspaces !! 6)) , ("M-t 8", (windows $ W.shift $ myWorkspaces !! 7)) , ("M-t 9", (windows $ W.shift $ myWorkspaces !! 8)) , ("M-t e", (windows $ W.shift $ myWorkspaces !! 9)) , ("M-t w", (windows $ W.shift $ myWorkspaces !! 10)) , ("M-t g", (windows $ W.shift $ myWorkspaces !! 11)) , ("M-t d", (windows $ W.shift $ myWorkspaces !! 12)) , ("M-t b", (windows $ W.shift $ myWorkspaces !! 13)) , ("M-t j", (windows $ W.shift $ myWorkspaces !! 14)) , ("M-t f", (windows $ W.shift $ myWorkspaces !! 15)) , ("M-t o", (windows $ W.shift $ myWorkspaces !! 16)) , ("M-t u", (windows $ W.shift $ myWorkspaces !! 17)) , ("M-t r", (windows $ W.shift $ myWorkspaces !! 18)) , ("M-t s", (windows $ W.shift $ myWorkspaces !! 19)) , ("M-t t", (windows $ W.shift $ myWorkspaces !! 20)) , ("M-t h", (windows $ W.shift $ myWorkspaces !! 21)) , ("M-t v", (windows $ W.shift $ myWorkspaces !! 22)) , ("M-t y", (windows $ W.shift $ myWorkspaces !! 23)) , ("M-t n", (windows $ W.shift $ myWorkspaces !! 24)) , ("M-t a", (windows $ W.shift $ myWorkspaces !! 25)) , ("M-t i", (windows $ W.shift $ myWorkspaces !! 26)) , ("M-t l", (windows $ W.shift $ myWorkspaces !! 27)) , ("M-t x", (windows $ W.shift $ myWorkspaces !! 28)) , ("M-t c", (windows $ W.shift $ myWorkspaces !! 29)) , ("M-t m", (windows $ W.shift $ myWorkspaces !! 30)) , ("M-t k", (windows $ W.shift $ myWorkspaces !! 31)) , ("M-t q", (windows $ W.shift $ myWorkspaces !! 32)) , ("M-t z", (windows $ W.shift $ myWorkspaces !! 33)) , ("M-t p", (windows $ W.shift $ myWorkspaces !! 34)) #+end_src ** Window focus and movement Pretty self-explanatory. /ToggleStruts/ is fullscreen. /sinkAll/ tiles floating windows. #+begin_src haskell , ("M-o", windows W.focusUp) , ("M-a", windows W.focusDown) , ("M-S-o", windows W.swapUp) , ("M-S-a", windows W.swapDown) , ("M-S-y", windows W.swapMaster) , ("M-", promote) , ("M-S-,", rotSlavesDown) , ("M-S-.", rotAllDown) , ("M-.", nextScreen) , ("M-,", prevScreen) , ("M-", sendMessage NextLayout) , ("M-f", sendMessage (MT.Toggle NBFULL) >> sendMessage ToggleStruts) , ("M-y", sendMessage Shrink) , ("M-l", sendMessage Expand) , ("M-b", sinkAll) #+end_src ** Sublayouts This lets me 'collect' windows into a tiled group if it starts getting crowded on the screen. #+begin_src haskell -- Sublayouts -- This is used to push windows to tabbed sublayouts, or pull them out of it. , ("C-S-M1-n",sendMessage $ pullGroup L) , ("C-S-M1-i",sendMessage $ pullGroup R) , ("C-S-M1-o",sendMessage $ pullGroup U) , ("C-S-M1-a",sendMessage $ pullGroup D) , ("C-S-M1-f",withFocused (sendMessage . MergeAll)) -- , ("M-C-u",withFocused (sendMessage . UnMerge)) , ("C-S-M1-u", withFocused (sendMessage . UnMergeAll)) , ("C-S-M1-j", onGroup W.focusUp') , ("C-S-M1-y", onGroup W.focusDown') #+end_src ** XMonad and apps Notes: I use a ZSA Moonlander so a lot of the 4-5 key sequences are actually just two keys. *** XMonad #+begin_src haskell , ("C-M1-S-0", sequence_ [spawn "xmonad --restart", spawn "xmonad --recompile"]) , ("M-S-M1-C-0", io exitSuccess) , ("S-C-M1-q", kill1) , ("M-S-C-M1-q", killAll) , ("M-d", spawn "rofi -show drun") #+end_src *** Some common keybinds: #+begin_src haskell , ("M-e", spawn "emacsclient -c -a 'emacs'") , ("M-", spawn "alacritty") , ("M-S-", spawn "feh --randomize --bg-fill /usr/share/backgrounds/archlinux/*") , ("M-", spawn "dm-maim") , ("", spawn "flameshot gui") #+end_src *** Keybindings for keyboard layout changes #+begin_src haskell , ("M-j p", spawn "setxkbmap -model pc104 -layout pl -option compose:rctrl") , ("M-j g", spawn "setxkbmap -model pc104 -layout gr -option compose:rctrl") #+end_src *** XMonad.Prompt.OrgMode #+begin_src haskell , ("M-c i", orgPrompt def "TODO" "~/enc/org/inbox.org") , ("M-c l", orgPromptPrimary def "LINK" "~/enc/org/inbox.org") , ("M-c n", orgPrompt def "NOTE" "~/enc/org/inbox.org") , ("M-c p", orgPromptRefile def "TODO" "~/enc/org/phil.org") #+end_src *** Timestamp chords For local time, EST, and PST. #+begin_src haskell -- Time! Timestamps! , ("M-w l", spawn "sleep 0.5 && xdotool type \"$(date +'%Y.%m.%d %H:%M:%S %Z')\"") , ("M-w e", spawn "sleep 0.5 && xdotool type \"$(TZ=America/New_York date +'%Y.%m.%d %H:%M:%S %Z')\"") , ("M-w m", spawn "sleep 0.5 && xdotool type \"$(TZ=America/Denver date +'%Y.%m.%d %H:%M:%S %Z')\"") #+end_src *** Multimedia keys #+begin_src haskell , ("", spawn "mpc toggle") , ("", spawn "mpc prev") , ("", spawn "mpc next") , ("", spawn "amixer set Master toggle") , ("", spawn "pactl set-sink-volume \"bluez_output.E8_EE_CC_02_F6_8A.1\" -5%") , ("", spawn "pactl set-sink-volume \"bluez_output.E8_EE_CC_02_F6_8A.1\" +5%") ] #+end_src *** Mouse wheel to switch workspaces. #+begin_src haskell `additionalMouseBindings` [ ((mod4Mask, button4), \w -> focus w >> prevWS) , ((mod4Mask, button5), \w -> focus w >> nextWS)] #+end_src