304 lines
		
	
	
		
			9.1 KiB
		
	
	
	
		
			Haskell
		
	
	
			
		
		
	
	
			304 lines
		
	
	
		
			9.1 KiB
		
	
	
	
		
			Haskell
		
	
	
-- {{{ Imports
 | 
						|
 | 
						|
import Control.Monad (liftM2)
 | 
						|
import Data.Map qualified as M
 | 
						|
import XMonad
 | 
						|
import XMonad.Actions.CopyWindow (copyToAll, killAllOtherCopies)
 | 
						|
import XMonad.Actions.FloatSnap
 | 
						|
import XMonad.Actions.Submap
 | 
						|
import XMonad.Hooks.EwmhDesktops
 | 
						|
import XMonad.Hooks.ManageDocks
 | 
						|
import XMonad.Hooks.ManageHelpers
 | 
						|
import XMonad.Hooks.OnPropertyChange (onXPropertyChange)
 | 
						|
import XMonad.Hooks.StatusBar
 | 
						|
import XMonad.Hooks.StatusBar.PP
 | 
						|
import XMonad.Hooks.WindowSwallowing (swallowEventHook)
 | 
						|
import XMonad.Layout.CenteredIfSingle
 | 
						|
import XMonad.Layout.IndependentScreens
 | 
						|
import XMonad.Layout.LayoutHints (hintsEventHook, layoutHints)
 | 
						|
import XMonad.Layout.PerScreen
 | 
						|
import XMonad.Layout.PerWorkspace
 | 
						|
import XMonad.Layout.Renamed
 | 
						|
import XMonad.Layout.Spacing
 | 
						|
import XMonad.Layout.Tabbed
 | 
						|
import XMonad.Layout.ThreeColumns
 | 
						|
import XMonad.StackSet qualified as W
 | 
						|
import XMonad.Util.EZConfig
 | 
						|
import XMonad.Util.Hacks qualified as Hacks
 | 
						|
import XMonad.Util.Loggers
 | 
						|
import XMonad.Util.Paste
 | 
						|
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- Statusbar {{{
 | 
						|
 | 
						|
pp :: PP
 | 
						|
pp =
 | 
						|
  def
 | 
						|
    { ppSep = tertiaryColor "  ",
 | 
						|
      ppCurrent = brackitify,
 | 
						|
      ppHidden = secondaryColor,
 | 
						|
      ppHiddenNoWindows = tertiaryColor,
 | 
						|
      ppUrgent = red . wrap (yellow "!") (yellow "!"),
 | 
						|
      ppLayout = id,
 | 
						|
      ppTitle = shorten 80,
 | 
						|
      ppTitleSanitize = xmobarStrip,
 | 
						|
      ppOrder = \[workspaces, layout, windows, _] -> [layout],
 | 
						|
      ppExtras = [logTitles formatFocused formatUnfocused]
 | 
						|
    }
 | 
						|
  where
 | 
						|
    brackitify = wrap "〈" "〉"
 | 
						|
    formatFocused = secondaryColor . ppWindow
 | 
						|
    formatUnfocused = tertiaryColor . ppWindow
 | 
						|
 | 
						|
    ppWindow = xmobarRaw . (\w -> if null w then "Untitled" else w) . shorten 16
 | 
						|
 | 
						|
    primaryColor = xmobarColor "#000000" ""
 | 
						|
    secondaryColor = xmobarColor "#333333" ""
 | 
						|
    tertiaryColor = xmobarColor "#555555" ""
 | 
						|
    yellow = xmobarColor "#ff0" ""
 | 
						|
    red = xmobarColor "#ff5555" ""
 | 
						|
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- Workspaces & screens {{{
 | 
						|
 | 
						|
-- Shift to workspace and view workspace
 | 
						|
shiftAndView = doF . liftM2 (.) W.greedyView W.shift
 | 
						|
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- Hooks {{{
 | 
						|
 | 
						|
-- startupHook {{{
 | 
						|
myStartupHook =
 | 
						|
  do
 | 
						|
    spawn "killall -q polybar; parallel ::: 'polybar -r top' 'polybar -r bottom'"
 | 
						|
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- manageHook {{{
 | 
						|
myManageHook :: ManageHook
 | 
						|
myManageHook =
 | 
						|
  composeAll
 | 
						|
    [ isDialog --> doCenterFloat,
 | 
						|
      className =? "Zathura" --> doShift "1_info",
 | 
						|
      className =? "firefox" --> shiftAndView "1_www",
 | 
						|
      className =? "firefoxdeveloperedition" --> shiftAndView "1_www",
 | 
						|
      className =? "Anki" --> shiftAndView "1_etc",
 | 
						|
      className =? "Obsidian" --> shiftAndView "1_etc",
 | 
						|
      className =? "Launcher" --> doRectFloat (W.RationalRect 0.05 0.4 0.9 0.5),
 | 
						|
      className =? "Zettelkasten" --> doRectFloat (W.RationalRect 0.05 0.4 0.9 0.5),
 | 
						|
      className =? "Calculator" --> doCenterFloat,
 | 
						|
      className =? "feh" --> doCenterFloat,
 | 
						|
      -- Center matplotlib and prevent focus stealing
 | 
						|
      -- className =? "matplotlib" --> doRectFloat (W.RationalRect 0.5 0.5 0.5 0.5),
 | 
						|
      className =? "matplotlib" --> doCenterFloat,
 | 
						|
      className =? "Matplotlib" --> doCenterFloat,
 | 
						|
      className =? "Xournalpp" --> doRectFloat (W.RationalRect 0.5 0.5 0.5 0.5),
 | 
						|
      className =? "KeePassXC" --> doRectFloat (W.RationalRect 0.1 0.1 0.8 0.8),
 | 
						|
      className =? "flameshot" --> doRectFloat (W.RationalRect 0.1 0.1 0.8 0.8)
 | 
						|
    ]
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- dynamicManageHook {{{
 | 
						|
myDynamicManageHook :: ManageHook
 | 
						|
myDynamicManageHook =
 | 
						|
 composeAll
 | 
						|
   [
 | 
						|
     title =? "Zettelkasten — Firefox Developer Edition" --> doShift "1_sh"
 | 
						|
   ]
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- layoutHook {{{
 | 
						|
myLayoutHook =
 | 
						|
  avoidStruts $
 | 
						|
    smartSpacingWithEdge 4 $
 | 
						|
      layoutHints $
 | 
						|
        onWorkspace "1_sh" (Tall nmaster delta 0.8) $
 | 
						|
          ifWider smallWidth (tWide ||| c3mWide ||| f) t
 | 
						|
  where
 | 
						|
    smallWidth = 1920
 | 
						|
 | 
						|
    -- Tall layouts
 | 
						|
    tWide =
 | 
						|
      centeredIfSingle 0.62 1 t
 | 
						|
    t =
 | 
						|
      named "[]+" $
 | 
						|
        Tall nmaster delta ratio
 | 
						|
 | 
						|
    -- Column layouts
 | 
						|
    c3mWide =
 | 
						|
      centeredIfSingle 0.62 1 c3m
 | 
						|
    c3m =
 | 
						|
      named "[|]" $
 | 
						|
        ThreeColMid nmaster delta ratio
 | 
						|
 | 
						|
    -- Fullscreen layouts
 | 
						|
    f = named "[+]" Full
 | 
						|
 | 
						|
    -- Modifiers
 | 
						|
    named n = renamed [Replace n]
 | 
						|
    nmaster = 1
 | 
						|
    ratio = 0.62
 | 
						|
    delta = 4 / 100
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- handleEventHook {{{
 | 
						|
myHandleEventHook =
 | 
						|
  handleEventHook def
 | 
						|
    -- See window swallowing (https://hackage.haskell.org/package/xmonad-contrib-0.18.0/docs/XMonad-Hooks-WindowSwallowing.html)
 | 
						|
    <> onXPropertyChange "WM_NAME" myDynamicManageHook
 | 
						|
    <> Hacks.windowedFullscreenFixEventHook
 | 
						|
    <> hintsEventHook
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- Main config {{{
 | 
						|
 | 
						|
myWorkspaces = [ "sh", "www", "dev", "info", "etc" ]
 | 
						|
myWorkspaceKeys = [ "a", "s", "d", "f", "g" ]
 | 
						|
mySharedWorkspaces = [ "shared" ]
 | 
						|
mySharedWorkspaceKeys = [ "1" ]
 | 
						|
-- Use Win key instead of Alt
 | 
						|
myModMask = mod4Mask
 | 
						|
 | 
						|
myConfig =
 | 
						|
  def
 | 
						|
    { terminal = "kitty",
 | 
						|
      modMask = myModMask,
 | 
						|
      workspaces = withScreen 1 myWorkspaces ++ withScreen 2 mySharedWorkspaces,
 | 
						|
      -- Styling
 | 
						|
      focusedBorderColor = "#000",
 | 
						|
      normalBorderColor = "#0000",
 | 
						|
      borderWidth = 4,
 | 
						|
      -- Hooks
 | 
						|
      startupHook = myStartupHook,
 | 
						|
      manageHook = myManageHook <+> manageHook def,
 | 
						|
      layoutHook = myLayoutHook,
 | 
						|
      handleEventHook = myHandleEventHook
 | 
						|
    }
 | 
						|
    `removeKeysP` myRemoveKeys
 | 
						|
    `additionalKeysP` myKeys
 | 
						|
    `additionalMouseBindings` myMouseBindings
 | 
						|
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- Keybindings {{{
 | 
						|
 | 
						|
-- Keybindings to be added/overridden
 | 
						|
myKeys :: [(String, X ())]
 | 
						|
myKeys =
 | 
						|
  [ ("M-<Space> s", unfloatFocusedW),
 | 
						|
    ("M-<Space> <Space>", nextLayout),          -- Cycle through layouts
 | 
						|
    ("M-<Space> S-<Space>", defaultLayout),     --
 | 
						|
    ("M-<Space> M-<Space>", nextLayout),        -- ..fat finger
 | 
						|
    ("M-<Space> M-S-<Space>", defaultLayout),   --
 | 
						|
    ("<F8>",  spawnKeepassXC),
 | 
						|
    ("M-p",   spawnLauncher),
 | 
						|
    ("M-w", spawnWindowSwitcher),
 | 
						|
    ("M-S-w", spawnWifiMenu),
 | 
						|
    ("<Insert>", pasteSelection),
 | 
						|
    ("<Print>", printScreen),
 | 
						|
    ("<XF86AudioRaiseVolume>", raiseVol),       -- Audio volume & playback
 | 
						|
    ("<XF86AudioLowerVolume>", lowerVol),       --
 | 
						|
    ("<XF86AudioMute>", mute),                  --
 | 
						|
    ("M-<Right>", nextTrack),                   --
 | 
						|
    ("M-<Left>", prevTrack),                    --
 | 
						|
    ("M-<Up>", play),                           --
 | 
						|
    ("M-<Down>", pause),                        --
 | 
						|
    ("<XF86MonBrightnessUp>", brighten),        -- Brightness & hue controls
 | 
						|
    ("<XF86MonBrightnessDown>", dim),           --
 | 
						|
    ("S-<XF86MonBrightnessUp>", warm),          --
 | 
						|
    ("S-<XF86MonBrightnessDown>", cool),        --
 | 
						|
    ("M-S-<XF86MonBrightnessUp>", resetTemp),   --
 | 
						|
    ("M-S-<XF86MonBrightnessDown>", resetTemp), --
 | 
						|
    ("M-S-b", fullscreenBrowser),
 | 
						|
    ("<XF86PowerOff>", spawn "systemctl suspend"), --TODO: Only enable this on laptop
 | 
						|
    ("M-c", windows copyToAll),
 | 
						|
    ("M-S-c", killAllOtherCopies),
 | 
						|
    ("M-S-<Delete>", kill)
 | 
						|
  ] ++
 | 
						|
  [ (m ++ k, windows $ f w) |
 | 
						|
    (m, f) <- zip ["M-", "M-S-"]
 | 
						|
                  [W.greedyView, W.shift],
 | 
						|
                  (k, w) <- zip myWorkspaceKeys
 | 
						|
                                (withScreen 1 myWorkspaces)
 | 
						|
                         ++ zip mySharedWorkspaceKeys
 | 
						|
                                (withScreen 2 mySharedWorkspaces)
 | 
						|
  ]
 | 
						|
 | 
						|
zipKeyPrefixes :: [String] -> [String] -> [String]
 | 
						|
zipKeyPrefixes prefixes keys = [prefix ++ key | prefix <- prefixes, key <- keys]
 | 
						|
 | 
						|
-- Keybindings to be removed
 | 
						|
myRemoveKeys :: [String]
 | 
						|
myRemoveKeys = "M-S-q" : zipKeyPrefixes ["M-", "M-S-"] (map show [ 1..5 ])
 | 
						|
 | 
						|
myMouseBindings =
 | 
						|
  [
 | 
						|
      ((mod4Mask,               button1), (\w -> focus w >> mouseMoveWindow w >> afterDrag (snapMagicMove (Just 50) (Just 50) w)))
 | 
						|
    , ((mod4Mask .|. shiftMask, button1), (\w -> focus w >> mouseMoveWindow w >> afterDrag (snapMagicResize [L,R,U,D] (Just 50) (Just 50) w)))
 | 
						|
    , ((mod4Mask,               button3), (\w -> focus w >> mouseResizeWindow w >> afterDrag (snapMagicResize [R,D] (Just 50) (Just 50) w)))
 | 
						|
  ]
 | 
						|
 | 
						|
unfloatFocusedW :: X ()
 | 
						|
unfloatFocusedW = withFocused $ windows . W.sink
 | 
						|
 | 
						|
myStartupHook :: X ()
 | 
						|
nextLayout = sendMessage NextLayout
 | 
						|
 | 
						|
defaultLayout :: X ()
 | 
						|
defaultLayout = setLayout $ Layout myLayoutHook
 | 
						|
 | 
						|
spawnKeepassXC :: X ()
 | 
						|
spawnKeepassXC = spawn "keepassxc"
 | 
						|
 | 
						|
fullscreenBrowser :: X ()
 | 
						|
fullscreenBrowser = spawn "firefox --fullscreen"
 | 
						|
 | 
						|
spawnWindowSwitcher = spawn "rofi -show window -show-icons"
 | 
						|
 | 
						|
spawnWifiMenu = spawn "rofi -show wifi -modi \"wifi:iwdrofimenu\""
 | 
						|
 | 
						|
spawnLauncher, spawnClipManager :: X ()
 | 
						|
spawnLauncher = spawn "rofi -show drun -show-icons"
 | 
						|
spawnClipManager = spawn "rofi -modi 'clipboard:greenclip print' -show clipboard -run-command '{cmd}'"
 | 
						|
 | 
						|
printScreen :: X ()
 | 
						|
printScreen = spawn "flameshot gui"
 | 
						|
 | 
						|
raiseVol, lowerVol, mute :: X ()
 | 
						|
raiseVol = spawn "pactl set-sink-volume @DEFAULT_SINK@ +5%"
 | 
						|
lowerVol = spawn "pactl set-sink-volume @DEFAULT_SINK@ -5%"
 | 
						|
mute = spawn "pactl set-sink-mute @DEFAULT_SINK@ toggle"
 | 
						|
 | 
						|
nextTrack, prevTrack, play, pause :: X ()
 | 
						|
nextTrack = spawn "playerctl next"
 | 
						|
prevTrack = spawn "playerctl previous"
 | 
						|
play = spawn "playerctl play"
 | 
						|
pause = spawn "playerctl pause"
 | 
						|
 | 
						|
brighten, dim, warm, cool, resetTemp :: X ()
 | 
						|
brighten = spawn "brightnessctl set 20+"
 | 
						|
dim = spawn "brightnessctl set 20-"
 | 
						|
warm = spawn "screen-temperature +50"
 | 
						|
cool = spawn "screen-temperature -50"
 | 
						|
resetTemp = spawn "screen-temperature 3000"
 | 
						|
 | 
						|
-- }}}
 | 
						|
 | 
						|
-- Main {{{
 | 
						|
 | 
						|
main :: IO ()
 | 
						|
main =
 | 
						|
  do xmonad
 | 
						|
    $ ewmh
 | 
						|
    $ withEasySB
 | 
						|
      (statusBarProp "polybar" $ pure pp)
 | 
						|
      defToggleStrutsKey
 | 
						|
      myConfig
 | 
						|
 | 
						|
-- }}}
 |