172 lines
5.1 KiB
Haskell
172 lines
5.1 KiB
Haskell
{-# LANGUAGE ImportQualifiedPost #-}
|
|
|
|
import Data.Map qualified as M
|
|
import System.Exit
|
|
import XMonad
|
|
import XMonad.Actions.Navigation2D
|
|
import XMonad.Hooks.DynamicLog
|
|
import XMonad.Hooks.EwmhDesktops
|
|
import XMonad.Hooks.FloatConfigureReq
|
|
import XMonad.Hooks.ManageDocks
|
|
import XMonad.Hooks.ManageHelpers
|
|
import XMonad.Hooks.StatusBar
|
|
import XMonad.Layout.BinarySpacePartition
|
|
import XMonad.Layout.BorderResize
|
|
import XMonad.Layout.NoBorders
|
|
import XMonad.Layout.Spacing
|
|
import XMonad.Layout.ToggleLayouts
|
|
import XMonad.StackSet qualified as W
|
|
import XMonad.Util.ClickableWorkspaces
|
|
import XMonad.Util.EZConfig
|
|
import XMonad.Util.Hacks
|
|
import XMonad.Util.NamedScratchpad
|
|
import XMonad.Util.Run
|
|
import XMonad.Util.WorkspaceCompare
|
|
|
|
-- Define the color scheme using the Catppuccin palette
|
|
catppuccinColors :: (String, String, String, String, String, String, String)
|
|
catppuccinColors =
|
|
( "#89b4fa" -- blue
|
|
, "#f38ba8" -- red
|
|
, "#a6e3a1" -- green
|
|
, "#f9e2af" -- yellow
|
|
, "#f5c2e7" -- pink
|
|
, "#cdd6f4" -- white
|
|
, "#45475a" -- grey
|
|
)
|
|
|
|
-- XMobar configuration
|
|
xmobarConf :: PP
|
|
xmobarConf =
|
|
def
|
|
{ ppSep = yellowC " | "
|
|
, ppTitleSanitize = xmobarStrip
|
|
, ppCurrent = xmobarBorder "Top" blue 2 . pad
|
|
, ppHidden = whiteC . pad
|
|
, ppHiddenNoWindows = greyC . pad
|
|
, ppUrgent = redC . wrap (yellowC "!") (yellowC "!")
|
|
, ppOrder = \[ws, l, _] -> [ws, l]
|
|
}
|
|
where
|
|
(blue, red, _, yellow, _, white, grey) = catppuccinColors
|
|
xmobarColorWith :: String -> String -> String
|
|
xmobarColorWith color = xmobarColor color ""
|
|
redC = xmobarColorWith red
|
|
yellowC = xmobarColorWith yellow
|
|
whiteC = xmobarColorWith white
|
|
greyC = xmobarColorWith grey
|
|
|
|
main :: IO ()
|
|
main = do
|
|
xmproc <- spawnPipe "xmobar"
|
|
xmonad
|
|
$ javaHack
|
|
$ navigation2D
|
|
def
|
|
(xK_k, xK_h, xK_j, xK_l)
|
|
[ (mod4Mask, windowGo)
|
|
, (mod4Mask .|. shiftMask, windowSwap)
|
|
]
|
|
False
|
|
$ docks
|
|
$ addEwmhWorkspaceSort (pure (filterOutWs [scratchpadWorkspaceTag]))
|
|
$ ewmhFullscreen
|
|
$ ewmh
|
|
$ withEasySB
|
|
(statusBarProp "xmobar ~/.xmonad/xmobar/xmobar.hs" (clickablePP (filterOutWsPP [scratchpadWorkspaceTag] xmobarConf)))
|
|
defToggleStrutsKey
|
|
myConfig
|
|
|
|
myConfig =
|
|
def
|
|
{ modMask = mod4Mask
|
|
, layoutHook =
|
|
lessBorders OnlyScreenFloat $
|
|
avoidStruts $
|
|
spacingRaw False (Border 10 10 10 10) True (Border 10 10 10 10) True $
|
|
borderResize emptyBSP
|
|
, terminal = myTerminal
|
|
, keys = myKeys
|
|
, borderWidth = 2
|
|
, normalBorderColor = "#6c7086"
|
|
, focusedBorderColor = "#a6e3a1"
|
|
, handleEventHook = fixSteamFlicker
|
|
, startupHook = addExclusives [["vesktop", "telegram"]]
|
|
, manageHook =
|
|
composeAll
|
|
[ namedScratchpadManageHook scratchpads
|
|
, isFullscreen --> doFullFloat
|
|
]
|
|
}
|
|
`additionalKeysP` myAdditionalKeys
|
|
|
|
scratchpads :: [NamedScratchpad]
|
|
scratchpads =
|
|
[ NS "vesktop" "vesktop" (className =? "vesktop") (rectCentered 0.7)
|
|
, NS "telegram" "telegram-desktop" (className =? "TelegramDesktop") (rectCentered 0.7)
|
|
]
|
|
where
|
|
rectCentered percentage = customFloating $ W.RationalRect offset offset percentage percentage
|
|
where
|
|
offset = (1 - percentage) / 2
|
|
|
|
-- Application Launchers
|
|
myFileManager, myBrowser, myTerminal :: String
|
|
myFileManager = "nautilus"
|
|
myBrowser = "firefox-nightly"
|
|
myTerminal = "wezterm"
|
|
|
|
rofiMacro :: String
|
|
rofiMacro = "rofi -show"
|
|
|
|
centerRect :: W.RationalRect
|
|
centerRect = W.RationalRect 0.25 0.25 0.5 0.5
|
|
|
|
-- Functions for Floating Windows
|
|
floatOrNot :: X () -> X () -> X ()
|
|
floatOrNot float notFloat = withFocused $ \windowId -> do
|
|
floats <- gets (W.floating . windowset)
|
|
if windowId `M.member` floats then float else notFloat
|
|
|
|
centerFloat' :: Window -> X ()
|
|
centerFloat' window = windows $ W.float window centerRect
|
|
|
|
toggleFloat :: X ()
|
|
toggleFloat = floatOrNot (withFocused $ windows . W.sink) (withFocused centerFloat')
|
|
|
|
-- Keybindings
|
|
myAdditionalKeys :: [(String, X ())]
|
|
myAdditionalKeys =
|
|
[ ("M-<Return>", spawn myTerminal)
|
|
, ("M-r", spawn $ rofiMacro ++ " drun")
|
|
, ("M-w", spawn myBrowser)
|
|
, ("M-e", spawn myFileManager)
|
|
, ("M-q", kill)
|
|
, ("M-d", namedScratchpadAction scratchpads "vesktop")
|
|
, ("M-t", namedScratchpadAction scratchpads "telegram")
|
|
, ("M-S-e", resetFocusedNSP)
|
|
, ("M-S-s", spawn "screenshot --window")
|
|
, ("M-C-3", spawn "screenshot --screen")
|
|
, ("M-C-4", spawn "screenshot --area")
|
|
, ("M-C-h", sendMessage $ ExpandTowards L)
|
|
, ("M-C-j", sendMessage $ ExpandTowards D)
|
|
, ("M-C-k", sendMessage $ ExpandTowards U)
|
|
, ("M-C-l", sendMessage $ ExpandTowards R)
|
|
, ("M-<Space>", toggleFloat)
|
|
, ("M-m", withFocused hide)
|
|
, ("M-n", sendMessage $ Toggle "Full")
|
|
, ("M-S-q", io exitSuccess)
|
|
, ("M-S-r", spawn "xmonad --recompile; xmonad --restart")
|
|
, ("<XF86AudioPlay>", spawn "playerctl play-pause")
|
|
, ("<XF86AudioNext>", spawn "playerctl next")
|
|
, ("<XF86AudioPrev>", spawn "playerctl previous")
|
|
]
|
|
|
|
myKeys :: XConfig l -> M.Map (KeyMask, KeySym) (X ())
|
|
myKeys conf@XConfig {XMonad.modMask = modm} =
|
|
M.fromList $
|
|
[ ((m .|. modm, k), windows $ f i)
|
|
| (i, k) <- zip (workspaces conf) [xK_1 .. xK_9]
|
|
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
|
|
]
|