gentoo-dots/.config/xmonad/xmonad.hs

306 lines
13 KiB
Haskell
Raw Normal View History

2023-04-30 17:36:12 +02:00
-- Base
import XMonad
import System.Exit
import qualified XMonad.StackSet as W
-- Actions
import XMonad.Actions.CycleWS (toggleWS')
import XMonad.Actions.MouseResize
2024-02-07 22:18:21 +01:00
import XMonad.Actions.SinkAll (sinkAll)
2023-04-30 17:36:12 +02:00
-- Data
import qualified Data.Map as M
import Data.Maybe (isJust)
-- Hooks
import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.StatusBar
import XMonad.Hooks.StatusBar.PP
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.SetWMName
import XMonad.Hooks.InsertPosition
-- Layout modifiers
import XMonad.Layout.Renamed
import XMonad.Layout.Spacing
import XMonad.Layout.NoBorders
import XMonad.Layout.SimplestFloat
import XMonad.Layout.LayoutModifier
import XMonad.Layout.ResizableTile
import XMonad.Layout.PerWorkspace
import XMonad.Layout.WindowArranger (windowArrange, WindowArrangerMsg(..))
-- Utils
import XMonad.Util.Loggers
import XMonad.Util.NamedScratchpad
import XMonad.Util.SpawnOnce
import XMonad.Util.EZConfig
import XMonad.Util.Hacks
-- main loop
main :: IO ()
main = xmonad
. ewmhFullscreen
. ewmh
. withEasySB (statusBarProp "xmobar ~/.config/xmobar/xmobarrc" (pure myXmobarPP)) toggleStrutsKey
$ myConfig
where
toggleStrutsKey :: XConfig Layout -> (KeyMask, KeySym)
toggleStrutsKey XConfig{ modMask = m } = (m, xK_F11)
-- My config
myConfig = def
{ modMask = myModMask
, layoutHook = myLayoutHook
2023-08-23 19:51:32 +02:00
, manageHook = insertPosition End Newer <+> myManageHook
2023-04-30 17:36:12 +02:00
, handleEventHook = trayerAboveXmobarEventHook
, focusFollowsMouse = myFocusFollowsMouse
, terminal = myTerminal
, borderWidth = myBorderWidth
, normalBorderColor = myNormalBorderColor
, focusedBorderColor = myFocusedBorderColor
, keys = myKeys
, workspaces = myWorkspaces
, startupHook = myStartupHook
}
-- My variables
myModMask = mod4Mask
myTerminal = "alacritty"
myBorderWidth = 2
myFocusFollowsMouse :: Bool
myFocusFollowsMouse = False
myNormalBorderColor = "#737994"
myFocusedBorderColor = "#c6d0f5"
myWorkspaces = ["","","","","","","","",""]
-- My startup hook
myStartupHook :: X ()
myStartupHook = do
spawn "killall trayer-srg" -- kill current trayer on each restart
spawnOnce "sxhkd -c $HOME/.config/sxhkd/general"
spawnOnce "gentoo-pipewire-launcher"
2023-08-23 19:51:32 +02:00
spawnOnce "transmission-daemon"
2023-04-30 17:36:12 +02:00
spawnOnce "syncthing"
2023-08-23 19:51:32 +02:00
spawnOnce "picom"
spawnOnce "clipmenud"
2023-04-30 17:36:12 +02:00
spawnOnce "dunst"
spawnOnce "keepassxc"
2023-08-23 19:51:32 +02:00
spawnOnce "/usr/libexec/polkit-gnome-authentication-agent-1"
2024-01-08 16:14:01 +01:00
spawn ("sleep 2 && trayer-srg --edge top --align right --widthtype request --padding 6 --iconspacing 7 --SetDockType true --SetPartialStrut true --expand true --monitor 1 --transparent true --alpha 0 --tint 0x303446 --height 24 -l")
2023-04-30 17:36:12 +02:00
setWMName "LG3D" -- Fix java programs
-- My scratchpads
myScratchPads :: [NamedScratchpad]
myScratchPads = [ NS "terminal" spawnTerm findTerm manageTerm
, NS "wiki" spawnWiki findWiki manageWiki
, NS "notes" spawnNotes findNotes manageNotes
2023-08-23 19:51:32 +02:00
, NS "profanity" spawnProfanity findProfanity manageProfanity
2024-02-07 22:18:21 +01:00
, NS "godot" spawnGodot findGodot manageGodot
2023-04-30 17:36:12 +02:00
]
where
spawnTerm = myTerminal ++ " --class scratchpad,scratchpad"
findTerm = className =? "scratchpad"
manageTerm = customFloating $ W.RationalRect l t w h
where
h = 0.8
w = 0.8
t = 0.9 -h
l = 0.9 -w
2023-08-23 19:51:32 +02:00
spawnWiki = myTerminal ++ " --class wiki,wiki -e wiki"
2023-04-30 17:36:12 +02:00
findWiki = className =? "wiki"
manageWiki = customFloating $ W.RationalRect l t w h
where
h = 0.8
w = 0.8
t = 0.9 -h
l = 0.9 -w
2023-08-23 19:51:32 +02:00
spawnNotes = myTerminal ++ " --class wiki,wiki -e notes"
2023-04-30 17:36:12 +02:00
findNotes = className =? "notes"
manageNotes = customFloating $ W.RationalRect l t w h
where
h = 0.8
w = 0.8
t = 0.9 -h
l = 0.9 -w
2023-08-23 19:51:32 +02:00
spawnProfanity = myTerminal ++ " --class profanity,profanity -e profanity"
findProfanity = className =? "profanity"
manageProfanity = customFloating $ W.RationalRect l t w h
where
h = 0.8
w = 0.8
t = 0.9 -h
l = 0.9 -w
2024-02-07 22:18:21 +01:00
spawnGodot = myTerminal ++ " --class godot,godot -e nvim --listen /tmp/godot.pipe"
findGodot = className =? "godot"
manageGodot = customFloating $ W.RationalRect l t w h
where
h = 0.8
w = 0.8
t = 0.9 -h
l = 0.9 -w
2023-08-23 19:51:32 +02:00
2023-04-30 17:36:12 +02:00
--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
-- Below is a variation of the above except no borders are applied
-- if fewer than two windows. So a single window has no gaps.
mySpacing' :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
mySpacing' i = spacingRaw True (Border i i i i) True (Border i i i i) True
-- My layouts
tall = renamed [Replace "tall"]
$ withBorder myBorderWidth
2024-01-08 16:14:01 +01:00
$ mySpacing 4
2023-04-30 17:36:12 +02:00
$ ResizableTall 1 (3/100) (1/2) []
monocle = renamed [Replace "monocle"]
$ withBorder myBorderWidth
2024-01-08 16:14:01 +01:00
$ mySpacing 4
2023-04-30 17:36:12 +02:00
$ Full
floats = renamed [Replace "floats"]
$ withBorder myBorderWidth
$ simplestFloat
myLayoutHook = lessBorders OnlyScreenFloat
$ mouseResize
$ windowArrange
$ myDefaultLayout
where
myDefaultLayout = onWorkspaces [(myWorkspaces !! 0), (myWorkspaces !! 3), (myWorkspaces !! 4)] (monocle ||| floats ||| tall)
$ onWorkspace (myWorkspaces !! 5) (floats ||| tall ||| monocle)
$ tall
||| monocle
||| floats
-- My manage hook
myManageHook :: ManageHook
myManageHook = composeAll
2024-01-08 16:14:01 +01:00
[ className =? "qutebrowser" --> doShiftAndGo ( myWorkspaces !! 0)
2023-04-30 17:36:12 +02:00
, className =? "newsboat" --> doShiftAndGo ( myWorkspaces !! 3)
, className =? "videos" --> doShiftAndGo ( myWorkspaces !! 3)
, className =? "ytfzf" --> doShiftAndGo ( myWorkspaces !! 3)
, className =? "lf" --> doShiftAndGo ( myWorkspaces !! 3)
, className =? "thunderbird" --> doShiftAndGo ( myWorkspaces !! 4)
, className =? "Ferdium" --> doShiftAndGo ( myWorkspaces !! 4)
, className =? "discord" --> doShiftAndGo ( myWorkspaces !! 4)
, className =? "tutanota-desktop" --> doShiftAndGo ( myWorkspaces !! 4)
2023-08-23 19:51:32 +02:00
, className =? "Lutris" --> doShiftAndGo ( myWorkspaces !! 5)
, className =? "steam" --> doShiftAndGo ( myWorkspaces !! 5)
2023-04-30 17:36:12 +02:00
, className =? "heroic" --> doShiftAndGo ( myWorkspaces !! 5)
2023-08-23 19:51:32 +02:00
, className =? "cartridges" --> doShiftAndGo ( myWorkspaces !! 5)
2023-11-07 18:43:12 +01:00
, className =? "Cemu" --> doShiftAndGo ( myWorkspaces !! 5)
, className =? "xemu" --> doShiftAndGo ( myWorkspaces !! 5)
2024-01-08 16:14:01 +01:00
, className =? "librewolf" --> doShiftAndGo ( myWorkspaces !! 8)
2023-04-30 17:36:12 +02:00
, isDialog --> doCenterFloat <+> doF W.swapUp
2023-08-23 19:51:32 +02:00
, className =? "Gimp" --> doFloat <+> doF W.swapUp
, className =? "confirm" --> doFloat <+> doF W.swapUp
, className =? "file_progress" --> doFloat <+> doF W.swapUp
, className =? "dialog" --> doFloat <+> doF W.swapUp
, className =? "download" --> doFloat <+> doF W.swapUp
, className =? "error" --> doFloat <+> doF W.swapUp
, className =? "notification" --> doFloat <+> doF W.swapUp
, className =? "splash" --> doFloat <+> doF W.swapUp
, className =? "toolbar" --> doFloat <+> doF W.swapUp
, className =? "pinentry-gtk-2" --> doFloat <+> doF W.swapUp
, className =? "Yad" --> doCenterFloat <+> doF W.swapUp
, className =? "badd" --> doCenterFloat <+> doF W.swapUp
2023-11-07 18:43:12 +01:00
, className =? "filepicker" --> doRectFloat (W.RationalRect (1/12) (1/12) (5/6) (5/6)) <+> doF W.swapUp
2024-02-08 18:05:52 +01:00
, isFullscreen --> doFullFloat
2023-04-30 17:36:12 +02:00
, namedScratchpadManageHook myScratchPads
]
where
doShiftAndGo ws = doF (W.greedyView ws) <+> doShift ws
-- My keybindings in a nice readable format
myKeys = \c -> mkKeymap c $
[ ("M-S-q", kill) -- kill active window
, ("M-<Space>", sendMessage NextLayout) -- cycle layout
, ("M-S-<Space>", withFocused toggleFloat) -- toggle floating state of a window
, ("M-j", windows W.focusDown) -- Move focus down
, ("M-k", windows W.focusUp) -- Move focus up
, ("M-S-<Return>", windows W.swapMaster) -- Move Focused window to master
, ("M-S-j", windows W.swapDown) --Move window down the stack
, ("M-S-k", windows W.swapUp) -- Move window up the stack
, ("M-h", sendMessage Shrink) -- Shrink master
, ("M-l", sendMessage Expand) -- Expand master
, ("M-,", sendMessage (IncMasterN 1)) -- Increase master count
, ("M-.", sendMessage (IncMasterN (-1))) -- Decrease msaster count
, ("M-C-e", io (exitWith ExitSuccess)) -- Quit xmonad
, ("M-S-r", spawn "xmonad --recompile && xmonad --restart") -- Restart xmonad
, ("M-<Tab>", toggleWS' ["NSP"]) -- Toogle last used workspace, ignoring named scratchpad
, ("M-s t", namedScratchpadAction myScratchPads "terminal") -- Toggle scratchpad
, ("M-s w", namedScratchpadAction myScratchPads "wiki") -- Toggle scratchpad
, ("M-s n", namedScratchpadAction myScratchPads "notes") -- Toggle scratchpad
2023-08-23 19:51:32 +02:00
, ("M-s p", namedScratchpadAction myScratchPads "profanity") -- Toggle scratchpad
2024-02-07 22:18:21 +01:00
, ("M-s g", namedScratchpadAction myScratchPads "godot") -- Toggle scratchpad
2023-04-30 17:36:12 +02:00
, ("M-1", viewDesktop 0) -- Check workspace 1
, ("M-2", viewDesktop 1) -- Check workspace 2
, ("M-3", viewDesktop 2) -- Check workspace 3
, ("M-4", viewDesktop 3) -- Check workspace 4
, ("M-5", viewDesktop 4) -- Check workspace 5
, ("M-6", viewDesktop 5) -- Check workspace 6
, ("M-7", viewDesktop 6) -- Check workspace 7
, ("M-8", viewDesktop 7) -- Check workspace 8
, ("M-9", viewDesktop 8) -- Check workspace 9
, ("M-S-1", shiftWindow 0) -- Send window to workspace 1
, ("M-S-2", shiftWindow 1) -- Send window to workspace 2
, ("M-S-3", shiftWindow 2) -- Send window to workspace 3
, ("M-S-4", shiftWindow 3) -- Send window to workspace 4
, ("M-S-5", shiftWindow 4) -- Send window to workspace 5
, ("M-S-6", shiftWindow 5) -- Send window to workspace 6
, ("M-S-7", shiftWindow 6) -- Send window to workspace 7
, ("M-S-8", shiftWindow 7) -- Send window to workspace 8
, ("M-S-9", shiftWindow 8) -- Send window to workspace 9
, ("M-C-1", shiftAndView 0) -- Send window and check workspace 1
, ("M-C-2", shiftAndView 1) -- Send window and check workspace 2
, ("M-C-3", shiftAndView 2) -- Send window and check workspace 3
, ("M-C-4", shiftAndView 3) -- Send window and check workspace 4
, ("M-C-5", shiftAndView 4) -- Send window and check workspace 5
, ("M-C-6", shiftAndView 5) -- Send window and check workspace 6
, ("M-C-7", shiftAndView 6) -- Send window and check workspace 7
, ("M-C-8", shiftAndView 7) -- Send window and check workspace 8
, ("M-C-9", shiftAndView 8) -- Send window and check workspace 9
2024-02-07 22:18:21 +01:00
, ("M-f", sinkAll) -- Nuke solution for simplestFloat layout
2023-04-30 17:36:12 +02:00
]
where
toggleFloat w = windows (\s -> if M.member w (W.floating s)
then W.sink w s
else (W.float w (W.RationalRect (1/6) (1/6) (2/3) (2/3)) s))
viewDesktop d = windows $ W.greedyView $ myWorkspaces !! d
shiftWindow w = windows $ W.shift $ myWorkspaces !! w
shiftAndView w = windows $ W.greedyView (myWorkspaces !! w) . W.shift (myWorkspaces !! w)
-- My xmobar workspace and other things config
myXmobarPP :: PP
myXmobarPP = filterOutWsPP ["NSP"]
$ def
{ ppSep = magenta ""
, ppWsSep = " "
, ppTitleSanitize = xmobarStrip
, ppCurrent = xmobarBorder "Bottom" "#89b4fa" 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
ppWindow :: String -> String
ppWindow = xmobarRaw . (\w -> if null w then "untitled" else w) . shorten 25
blue, lowWhite, magenta, red, white, yellow :: String -> String
magenta = xmobarColor "#eba0ac" ""
blue = xmobarColor "#cba6f7" ""
white = xmobarColor "#cdd6f4" ""
yellow = xmobarColor "#f9e2af" ""
red = xmobarColor "#f38ba8" ""
lowWhite = xmobarColor "#585b70" ""