xmonad/xmonad.hs

156 lines
6.5 KiB
Haskell

import Control.Monad (liftM2)
import qualified Data.Monoid
import XMonad
import XMonad.Actions.WindowGo
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.StatusBar
import qualified XMonad.Layout.LayoutModifier
import XMonad.Layout.Spacing
import XMonad.Layout.WindowNavigation
import XMonad.StackSet (Workspace (tag), currentTag, integrate', stack, greedyView, shift, focusWindow)
import XMonad.Util.EZConfig
import XMonad.Util.Loggers
import XMonad.Util.SpawnOnce
import XMonad.Util.Ungrab
import XMonad.Util.WorkspaceCompare (getSortByIndex)
import XMonad.Hooks.InsertPosition (insertPosition, Position(Master, End), Focus (Newer))
import XMonad.Hooks.ManageHelpers
import Data.List (isInfixOf)
main :: IO ()
main = do
colors <- getWalColors
xmonad . ewmhFullscreen . ewmh
. withEasySB (statusBarProp "xmobar ~/.config/xmobar/xmobarrc" (pure $ myXmobarPP colors)) defToggleStrutsKey
$ def
{ modMask = mod4Mask,
terminal = "st",
startupHook = myStartupHook,
borderWidth = 2,
normalBorderColor = "#000000",
focusedBorderColor = colors !! 7,
workspaces = myWorkspaces,
manageHook = myManageHook,
layoutHook = myLayout,
logHook = activateLogHook (reader focusWindow >>= doF)<+> logHook def
}
`additionalKeysP` [ ("M-S-z", spawn "xscreensaver-command -lock"),
("M-S-s", unGrab *> spawn "cast_screenshot"),
("M-f", runOrRaise "brave" (className =? "Brave-browser")),
("M-i", raise (className =? "jetbrains-idea")),
("M-<Space>", spawn "rofi -show drun") ,
("M-p", spawn "dmen") ,
-- audio settings
("<XF86AudioLowerVolume>", spawn "amixer set Master 5%- unmute"),
("<XF86AudioRaiseVolume>", spawn "amixer set Master 5%+ unmute"),
("<XF86AudioMute>", spawn "amixer set Master toggle"),
-- window navigation
("M-l", sendMessage $ Go R),
("M-h", sendMessage $ Go L),
-- layout switching
("M-<Tab>", sendMessage NextLayout),
-- dmenu stuff
("M1-<F4>", spawn "dshutdown")
]
myXmobarPP :: [String] -> PP
myXmobarPP colors =
def
{ ppSep = walXmobarColor 1 "",
ppTitleSanitize = xmobarStrip,
ppCurrent = wrap " " "" . xmobarBorder "Top" (colors!!6) 2,
ppHidden = white . wrap " " "",
ppHiddenNoWindows = white . wrap " " "",
ppUrgent = red . wrap (yellow "!") (yellow "!"),
ppOrder = \[ws, l, _, wins] -> [ws, l, wins],
ppExtras = [logTitles formatFocused formatUnfocused],
ppSort = hideWorkspaces
}
where
formatFocused = wrap (white "[") (white "]") . walXmobarColor 7. ppWindow
formatUnfocused = wrap (lowWhite "[") (lowWhite "]") .walXmobarColor 4. ppWindow
walXmobarColor index = xmobarColor (colors!!index) ""
ppWindow :: String -> String
ppWindow = xmobarRaw . (\w -> if null w then "untitled" else w) . shorten 30
lowWhite, red, white, yellow :: String -> String
white = xmobarColor "#f8f8f2" ""
yellow = xmobarColor "#f1fa8c" ""
red = xmobarColor "#ff5555" ""
lowWhite = xmobarColor "#bbbbbb" ""
hideWorkspaces = do
sortByIndex <- getSortByIndex
wsfilter <- thefilter
return (wsfilter . sortByIndex)
where
thefilter :: X ([WindowSpace] -> [WindowSpace])
--thefilter = filter ( not . isEmptyWs) . sortworkspaces
thefilter = do
currentWS <- withWindowSet (pure . currentTag)
return $ reverse . dropWhile (liftM2 (&&) ((currentWS /=) . tag) isEmptyWs) . reverse
where
isEmptyWs workspace = null $ integrate' $ stack workspace
myStartupHook :: X ()
myStartupHook = do
spawnOnce "picom &"
spawnOnce "sh $HOME/.fehbg"
getWalColors :: IO [String]
getWalColors = do
let file = "/home/qv/.cache/wal/colors"
contents <- readFile file
let colors = lines contents
return (colors ++ replicate (16 - length colors) "#000000")
mySpacing' :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
mySpacing' i = spacingRaw True (Border i 0 i i) True (Border i 0 i i) True
--myWorkspaces = [" dev ", " www ", " sys ", " doc ", " vbox ", " chat ", " mus ", " vid ", " gfx "]
myWorkspaces :: [String]
myWorkspaces = show <$> [1 .. 9]
myLayout = windowNavigation tiled ||| Mirror tiled ||| Full
where
tiled = mySpacing' 8 $ Tall nmaster delta ratio
nmaster = 1 -- Default number of windows in the master pane
ratio = 1/2 -- Default proportion of screen occupied by master pane
delta = 3/100 -- Percent of screen to increment by when resizing panes
myManageHook :: XMonad.Query (Data.Monoid.Endo WindowSet)
myManageHook =
composeAll
-- 'doFloat' forces a window to float. Useful for dialog boxes and such.
-- using 'doShift ( myWorkspaces !! 7)' sends program to workspace 8!
-- I'm doing it this way because otherwise I would have to write out the full
-- name of my workspaces and the names would be very long if using clickable workspaces.
[ 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,
title =? "Oracle VM VirtualBox Manager" --> doFloat,
title =? "Mozilla Firefox" --> viewShift (myWorkspaces !! 1),
title =? "Signal" --> viewShift (myWorkspaces !! 2),
className =? "TelegramDesktop" --> viewShift (myWorkspaces !! 2),
className =? "Gimp" --> doShift (myWorkspaces !! 8),
className =? "VirtualBox Manager" --> doShift (myWorkspaces !! 4),
(className =? "firefox" <&&> resource =? "Dialog") --> doFloat, -- Float Firefox Dialog
className =? "jetbrains-idea" --> viewShift (myWorkspaces !! 4) ,
(className =? "jetbrains-studio") <&&> (title ~=? "win") --> doIgnore
] <+> insertPosition End Newer
where viewShift = doF . liftM2 (.) greedyView shift
-- IntelliJ fix
(~=?) :: Eq a => Query [a] -> [a] -> Query Bool
q ~=? x = fmap (isInfixOf x) q