nix-config/home/modules/desktop-xmonad/xmonad/xmonad.hs

93 lines
2.5 KiB
Haskell

import XMonad ( xmonad )
import XMonad.Core
( ScreenId (S)
, terminal
, modMask
, borderWidth
, normalBorderColor
, focusedBorderColor
, workspaces
, keys
, mouseBindings
, layoutHook
, manageHook
, XConfig
( logHook
, focusFollowsMouse
, startupHook
, handleEventHook
)
)
import XMonad.Config ( def )
import XMonad.Hooks.ServerMode ( serverModeEventHook )
import XMonad.Hooks.EwmhDesktops ( ewmh )
import XMonad.Hooks.ManageDocks ( docks )
import XMonad.Hooks.SetWMName ( setWMName )
import XMonad.Layout.IndependentScreens ( countScreens , withScreens )
import XMonad.Util.Replace ( replace )
import XMonad.Actions.UpdatePointer ( updatePointer )
import XMonad.Actions.Navigation2D
( withNavigation2DConfig
, Navigation2DConfig
, centerNavigation
, singleWindowRect
, defaultTiledNavigation
, layoutNavigation
, unmappedWindowRect
)
import Graphics.X11.Types ( mod4Mask )
import HostConfig
( colorConfig
, selColor
, inactiveBorderColor
)
import ManageHook ( myManageHook )
import Xmobar ( mkBars )
import Bindings ( keybinds, mousebinds )
import Layouts ( myLayoutHook )
main :: IO ()
main = do
replace
nscreens <- countScreens
let
myScreens = [0 .. nscreens-1]
wsLs = withScreens (S nscreens) myWorkspaces
bars <- mkBars myScreens
xmonad $ opts def
{ terminal = "alacritty"
, modMask = mod4Mask
, borderWidth = 4
, normalBorderColor = inactiveBorderColor colorConfig
, focusedBorderColor = selColor colorConfig
, workspaces = wsLs
, keys = keybinds
, mouseBindings = mousebinds
, layoutHook = myLayoutHook
, manageHook = myManageHook
, logHook = bars >> updatePtr
, focusFollowsMouse = True
, handleEventHook = serverModeEventHook
, startupHook = setWMName "LG3D"
}
where
opts = docks . ewmh . withNavigation2DConfig myNav2DConf
updatePtr = updatePointer (0.9, 0.9) (0, 0)
myNav2DConf :: Navigation2DConfig
myNav2DConf = def
{ defaultTiledNavigation = centerNavigation
, layoutNavigation = [("Full", centerNavigation)]
, unmappedWindowRect = [("Full", singleWindowRect)]
}
myWorkspaces :: [String]
myWorkspaces = map show ids
where ids :: [Int]
ids = [1..9]