{-# LANGUAGE NegativeLiterals #-} {-# LANGUAGE LambdaCase #-} import XMonad import XMonad.Actions.SwapWorkspaces(swapWithCurrent) import XMonad.Actions.Submap (submap) import XMonad.Util.EZConfig (additionalKeys, removeKeys) import XMonad.Util.NamedScratchpad (NamedScratchpad (NS), customFloating, namedScratchpadAction, namedScratchpadManageHook, scratchpadWorkspaceTag) import XMonad.Util.SpawnOnce (spawnOnce) import XMonad.Layout.NoBorders (smartBorders) import XMonad.Layout.Reflect (reflectHoriz) import XMonad.Layout.Spacing (smartSpacingWithEdge) import XMonad.Layout.ResizableTile (ResizableTall(ResizableTall), MirrorResize (MirrorShrink, MirrorExpand)) import XMonad.Hooks.ManageHelpers (isFullscreen, (~?), composeOne, (-?>)) import XMonad.Hooks.FadeWindows (fadeWindowsLogHook, opaque, isUnfocused, transparency, isFloating) import XMonad.Hooks.EwmhDesktops (ewmh, ewmhFullscreen) import XMonad.Hooks.InsertPosition (insertPosition, Focus(Newer, Older), Position(Below, Above)) import XMonad.Hooks.RefocusLast (refocusLastLogHook) import XMonad.Hooks.StatusBar (StatusBarConfig, statusBarProp, dynamicEasySBs) import XMonad.Hooks.DynamicLog (PP(ppHiddenNoWindows, ppCurrent, ppSep), xmobarColor, filterOutWsPP, wrap) import XMonad.Util.Hacks (javaHack) import XMonad.StackSet qualified as W import Data.Map.Strict qualified as M import Graphics.X11.ExtraTypes.XF86 import System.Posix.Env (putEnv) import Data.Char (chr, ord, toUpper) import System.Exit (exitSuccess) -- Note: `xmonad --restart` will make Firefox's fullscreen work duck the xmobar stop working -- You need restart Firefox main :: IO () main = do xmonad . javaHack . dynamicEasySBs xmobar . ewmhFullscreen . ewmh $ def { modMask = superMask , focusFollowsMouse = True , workspaces = myWorkspaces , terminal = myTerm , startupHook = do spawn "xterm" , layoutHook = let tallr = reflectHoriz $ ResizableTall 1 (1/10) (3/7) [] in smartBorders ( smartSpacingWithEdge 5 tallr ||| Full ) } -- Only remove mappings that needs pass through (it's a map). `removeKeys` [ (superMask, xK_h) , (superMask, xK_l) , (superMask, xK_p) -- It has been more than once that I actidently killed xmonad >:( , (superMask .|. shiftMask, xK_q) ] ++ [ (superMask , n) | n <- [xK_1 .. xK_9] ] ++ [ (superMask .|. shiftMask, n) | n <- [xK_1 .. xK_9] ] `additionalKeys` [ -- Toggle fullscreen ((superMask, xK_Escape), sendMessage NextLayout) -- Resize windows , ((superMask, xK_equal ), sendMessage $ IncMasterN 1) , ((superMask, xK_minus ), sendMessage $ IncMasterN -1) , ((superMask, xK_comma ), sendMessage Shrink ) , ((superMask, xK_period ), sendMessage Expand ) , ((superMask .|. shiftMask, xK_comma ), sendMessage MirrorShrink ) , ((superMask .|. shiftMask, xK_period), sendMessage MirrorExpand ) ] -- Yeet ++ (let workspaceKeys = [xK_h, xK_t, xK_n, xK_s, xK_m, xK_w, xK_v, xK_z] in [ ((superMask, k), windows $ W.greedyView space) | (k, space) <- zip workspaceKeys myWorkspaces ] ++ [ ((superMask .|. altMask, k), windows $ W.greedyView space . W.shift space) | (k, space) <- zip workspaceKeys myWorkspaces ] ++ [ ((superMask .|. controlMask, k), windows $ swapWithCurrent space) | (k, space) <- zip workspaceKeys myWorkspaces ]) -- Launcher ++ (let launchFirefox = "if type firefox; then firefox; else firefox-esr; fi" launchDmenu = "dmenu_run -i -fn \"Iosevka Extended-17\" -nb \"#36363a\" -nf \"#e2e2e4\" -sb \"#f7f7f8\" -sf \"#36363a\" -l 10" lock = "xscreensaver-command -lock" in [ ((controlMask .|. altMask, xK_b), spawn launchFirefox) , ((superMask, xK_o), spawn launchDmenu ) , ((superMask, xK_l), spawn lock ) ]) myTerm :: String myTerm = "kitty" superMask, altMask :: KeyMask superMask = mod4Mask altMask = mod1Mask myWorkspaces :: [String] myWorkspaces = map pure ['a', 'b', 'c', 'd', 'e', 'f', 'g', 'h'] xmobar :: ScreenId -> X StatusBarConfig xmobar = \case 0 -> pure $ statusBarProp "xmobar -x 0" (pure myPrettyPrinter) 1 -> pure $ statusBarProp "xmobar -x 1" (pure myPrettyPrinter) _ -> mempty where myPrettyPrinter = filterOutWsPP [scratchpadWorkspaceTag] $ def { ppCurrent = xmobarColor "#000000" "#ffffff" . wrap " " " " . fmap toUpper , ppHiddenNoWindows = xmobarColor "#9c9c9c" "" . const "⋅" , ppSep = " | " } isFirefoxPIP :: Query Bool isFirefoxPIP = className =? "firefox" <&&> title =? "Picture-in-Picture" isFirefoxFullscreen :: Query Bool isFirefoxFullscreen = className =? "firefox" <&&> isFullscreen -- Firefox having multimedia content isFirefoxVideo :: Query Bool isFirefoxVideo = className =? "firefox" <&&> title ~? "YouTube"