116 lines
3.4 KiB
Haskell
116 lines
3.4 KiB
Haskell
import XMonad
|
|
|
|
import XMonad.Hooks.DynamicLog
|
|
import XMonad.Hooks.ManageDocks
|
|
import XMonad.Hooks.ManageHelpers
|
|
import XMonad.Hooks.StatusBar
|
|
import XMonad.Hooks.StatusBar.PP
|
|
|
|
import XMonad.StackSet as W -- float purposes
|
|
import XMonad.Actions.MouseResize
|
|
|
|
|
|
import XMonad.Util.EZConfig
|
|
import XMonad.Util.Loggers
|
|
import XMonad.Util.Ungrab
|
|
|
|
import XMonad.Layout.Magnifier
|
|
import XMonad.Layout.ThreeColumns
|
|
import XMonad.Layout.Spacing
|
|
|
|
import XMonad.Hooks.EwmhDesktops
|
|
import XMonad.Util.SpawnOnce (spawnOnce)
|
|
|
|
-- run or raise
|
|
import XMonad.Actions.WindowGo (runOrRaise)
|
|
import XMonad.ManageHook (className)
|
|
import XMonad.StackSet (RationalRect(..))
|
|
--
|
|
|
|
import XMonad.Layout.Decoration (decoration, DefaultShrinker(..), Theme(..), shrinkText)
|
|
import XMonad.Layout.Simplest
|
|
import XMonad.Layout.SimplestFloat
|
|
import XMonad.Layout.Spacing
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
main :: IO ()
|
|
main = xmonad
|
|
. ewmhFullscreen
|
|
. ewmh
|
|
. withEasySB (statusBarProp "xmobar" (pure myXmobarPP)) defToggleStrutsKey
|
|
$ myConfig
|
|
|
|
myConfig = def
|
|
{ modMask = mod4Mask -- Rebind Mod to the Super key
|
|
, layoutHook = myLayout -- Use custom layouts
|
|
, terminal = "alacritty"
|
|
, manageHook = myManageHook -- Match on certain windows
|
|
, startupHook = do
|
|
-- other startup commands
|
|
spawnOnce "xrandr --output HDMI-A-0 --mode 1366x768"
|
|
spawnOnce "xrdb /home/hashirama/.Xresources"
|
|
spawnOnce "feh --bg-fill /home/hashirama/wallpaper.jpg"
|
|
spawnOnce "compton -b"
|
|
}
|
|
`additionalKeysP`
|
|
[ ("M-d", spawn "rofi -show run")
|
|
, ("M-s", spawn "bash -c dictpopup")
|
|
, ("M-C-s", unGrab *> spawn "scrot -s" )
|
|
, ("M-e", runOrRaise "goldendict" (className =? "GoldenDict-ng"))
|
|
, ("M-p", runOrRaise "nyxt" (className =? "Nyxt"))
|
|
, ("M-t", withFocused $ windows . W.sink) -- Toggle float for the focused window
|
|
]
|
|
|
|
|
|
myManageHook :: ManageHook
|
|
myManageHook = composeAll
|
|
[ className =? "Gimp" --> doFloat
|
|
, isDialog --> doFloat
|
|
]
|
|
|
|
|
|
myTheme :: Theme
|
|
myTheme = def
|
|
{ decoHeight = 20 -- Adjust the height of the title bar as needed
|
|
-- Add other theme properties as needed
|
|
}
|
|
|
|
myLayout = mouseResize $ spacingRaw True (Border 10 10 10 10) True (Border 10 10 10 10) True $
|
|
Tall 1 (3/100) (1/2) ||| Full
|
|
|
|
|
|
|
|
|
|
myXmobarPP :: PP
|
|
myXmobarPP = def
|
|
{ ppSep = magenta " • "
|
|
, ppTitleSanitize = xmobarStrip
|
|
, ppCurrent = wrap " " "" . xmobarBorder "Top" "#8be9fd" 2
|
|
, ppHidden = white . wrap " " ""
|
|
, ppHiddenNoWindows = lowWhite . wrap " " ""
|
|
, 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" ""
|