move config to library dunno why, just for lulz i guess.
la-ninpre leobrekalini@gmail.com
Mon, 27 Jun 2022 01:46:08 +0300
2 files changed,
296 insertions(+),
421 deletions(-)
M
lib/XMonad/Config/LaNinpre.hs
→
lib/XMonad/Config/LaNinpre.hs
@@ -1,105 +1,56 @@
-{-# OPTIONS_HADDOCK prune #-} ---------------------------------------------------------------------- -- | -- Module : XMonad.Config.LaNinpre --- Description : personal stuff for xmonad +-- Description : xmonad config of la ninpre -- Maintainer : la-ninpre -- License : ISC -- Copyright : la-ninpre <aaoth AT aaoth DOT xyz> -- --- this module exists because i find it more convenient to manage some things --- from here instead of doing it right in xmonad config --- ---------------------------------------------------------------------- -module XMonad.Config.LaNinpre ( - -- $global +module XMonad.Config.LaNinpre where - -- * fonts - -- $fonts - myFonts, +import Data.List(intercalate) +import System.Exit - -- * colors - -- $colors - MyColorTheme(..), - def, - myNormColor, - myFocusColor, +import XMonad +import qualified XMonad.StackSet as W - -- * software constants - -- $software - myTerminal, - myBrowser, - myGeminiClient, - myFileMgr, - myMocp, - myEditor, +import XMonad.Actions.GridSelect +import XMonad.Actions.WithAll(sinkAll) - -- * hooks - -- $hooks - myManageHook, - myStartupHook, +import XMonad.Hooks.EwmhDesktops +import XMonad.Hooks.ManageDocks +import XMonad.Hooks.ManageHelpers +import XMonad.Hooks.SetWMName +import XMonad.Hooks.StatusBar +import XMonad.Hooks.StatusBar.PP - -- * scratchpads - -- $scratchpads - myScratchPads, - - -- * workspaces - -- $workspaces - myWorkspaces, - - -- * misc - -- $misc - myModMask, - myBorderWidth, - myAppGrid, - ) where +import XMonad.Layout.BoringWindows hiding (Replace) +import XMonad.Layout.NoBorders +import XMonad.Layout.Renamed +import XMonad.Layout.ResizableThreeColumns +import XMonad.Layout.ResizableTile +import XMonad.Layout.Simplest +import XMonad.Layout.Spacing +import XMonad.Layout.SubLayouts +import XMonad.Layout.Tabbed +import XMonad.Layout.ToggleLayouts +import XMonad.Layout.WindowNavigation -import Data.List -import Data.Map as M -import Data.Maybe -import Data.Monoid - -import XMonad -import qualified XMonad.StackSet as W -import XMonad.Hooks.ManageHelpers -import XMonad.Hooks.SetWMName +import XMonad.Util.ClickableWorkspaces +import XMonad.Util.EZConfig import XMonad.Util.NamedScratchpad import XMonad.Util.SpawnOnce --- $global --- --- constants and functions starting with \'my\' are exported and used in --- xmonad config. - --- $fonts +-- * fonts -- --- default fonts and helper functions for them. +-- default font and helper for fonts. -- | default lato font -fontLatoDef :: String -fontLatoDef = fontXft "Lato" "regular" 14 - --- | font for @ShowWMName@ --- --- normal variant --- --- > fontSWN = fontXft "Press Start 2P" "regular" 60 --- --- sitelen pona pona variant --- --- > fontSWN = fontXft "sitelen\\-pona" "regular" 80 -fontSWN :: String -fontSWN = fontXft "linja pona" "regular" 80 - --- | fonts list -myFonts :: [String] -myFonts = [ fontLatoDef - , fontSWN - ] +fontDef :: String +fontDef = fontXft "Lato" "regular" 14 --- ** helper functions --- -- | font constructor -- -- it is just a helper function to simplify the process of specifying font@@ -108,7 +59,6 @@ fontXft :: String -- ^ font family
-> String -- ^ font style -> Int -- ^ font size -> String - fontXft font style size = intercalate ":" [ "xft" , font , style@@ -117,95 +67,63 @@ , "antialias=true"
, "hinting=true" ] --- $colors +-- * colors -- -- color theme and stuff -myColorTheme :: MyColorTheme -myColorTheme = MyColorTheme "#111111" "#ccbbcc" "#223333" "#ffaaaa" - --- | unfocused window border colour -myNormColor :: String -myNormColor = col_bg def - --- | focused window border colour -myFocusColor :: String -myFocusColor = col_bg_alt def +-- | default color scheme +colorTheme :: ColorTheme +colorTheme = ColorTheme "#111111" "#ccbbcc" "#223333" "#ffaaaa" -- | color theme datatype -- -- 'Default' instance gives simple four-color colorscheme -data MyColorTheme = MyColorTheme { - col_bg :: String, - col_fg :: String, - col_bg_alt :: String, - col_fg_alt :: String +data ColorTheme = ColorTheme { + col_bg :: String, + col_fg :: String, + col_bg_alt :: String, + col_fg_alt :: String } -instance Default MyColorTheme where - def = myColorTheme +instance Default ColorTheme where + def = colorTheme --- $software +-- * software -- -- these are just contstants -- | set terminal emulator -myTerminal :: String -myTerminal = "alacritty" +terminalEmulator :: String +terminalEmulator = "alacritty" --- | set default browser -myBrowser :: String -myBrowser = "firefox" +-- | set web browser +webBrowser :: String +webBrowser = "firefox" -- | set gemini client -myGeminiClient :: String -myGeminiClient = "amfora" +geminiBrowser :: String +geminiBrowser = "lagrange" -- | set file manager -myFileMgr :: String -myFileMgr = "thunar" +fileManager :: String +fileManager = "thunar" -- | music on console -- -- this is to avoid spamming strings everywhere. @moc@ doesn't comply with -- XDG_CONFIG_HOME, so we force it to do so. -myMocp :: String -myMocp = "mocp -M '~/.config/moc'" +mocpString :: String +mocpString = "mocp -M '~/.config/moc'" -- | set editor -myEditor :: String -myEditor = myTerminal ++ " -e vim" +editor :: String +editor = terminalEmulator ++ " -e vi" --- $hooks +-- * hooks -- -- hooks for xmonad config --- ** startup hook --- --- start things at login. - --- | actual instance -myStartupHook :: X () -myStartupHook = do - --spawnOnce "dunst &" - --spawnOnce "lxsession &" - --spawnOnce "picom &" - --spawnOnce "nm-applet &" - --spawnOnce "volumeicon &" - spawnOnce "setxkbmap -layout us,ru -option 'grp:alt_shift_toggle'" - spawnOnce "kbdd" - {-spawnOnce ("trayer --edge top " - ++ "--align right " - ++ "--widthtype request " - ++ "--SetDockType true --SetPartialStrut true --expand false " - ++ "--monitor 0 --transparent true --alpha 0 " - ++ "--tint 0x19191a --height 24 &" - ) - -} - spawnOnce "~/.fehbg &" - setWMName "LG3D" - -- ** manage hook -- -- @doFloat@ forces a window to float. useful for dialog boxes and such.@@ -214,52 +132,45 @@ -- i'm doing it this way because otherwise i would have to write out the full
-- name of my workspaces and the names would be very long if using clickable workspaces. -- | manage hook -myManageHook :: Query (Endo WindowSet) -myManageHook = composeAll +localManageHook :: ManageHook +localManageHook = composeAll [ className =? "confirm" --> doFloat , className =? "file_progress" --> doFloat , className =? "dialog" --> doFloat , className =? "download" --> doFloat , className =? "error" --> doFloat , className =? "notification" --> doFloat - , className =? "pinentry-gtk-2" --> doFloat , className =? "splash" --> doFloat , className =? "toolbar" --> doFloat - , className =? "Gimp" --> doFloat - , className =? "Cadence" --> doFloat - , className =? "Steam" --> doFloat , className =? "Image Lounge" --> doFloat - , title =? "Oracle VM VirtualBox Manager" --> doFloat -- web workspace - , title =? "Mozilla Firefox" --> doShift ( myWorkspaces !! 1 ) - , className =? "Brave-browser" --> doShift ( myWorkspaces !! 1 ) - , className =? "amfora" --> doShift ( myWorkspaces !! 1 ) - , className =? "qutebrowser" --> doShift ( myWorkspaces !! 1 ) + , title =? "Mozilla Firefox" --> doShift ( workspacesTP !! 1 ) + , className =? "Brave-browser" --> doShift ( workspacesTP !! 1 ) + , className =? "amfora" --> doShift ( workspacesTP !! 1 ) + , className =? "qutebrowser" --> doShift ( workspacesTP !! 1 ) -- doc workspace - , className =? "Geary" --> doShift ( myWorkspaces !! 3 ) - , className =? "libreoffice" --> doShift ( myWorkspaces !! 3 ) - -- , className =? "libreoffice-impress" --> doShift ( myWorkspaces !! 3 ) + , className =? "Geary" --> doShift ( workspacesTP !! 3 ) + , className =? "libreoffice" --> doShift ( workspacesTP !! 3 ) -- vm workspace - , className =? "VirtualBox Manager" --> doShift ( myWorkspaces !! 4 ) -- chat workspace - , className =? "discord" --> doShift ( myWorkspaces !! 5 ) - , className =? "TelegramDesktop" --> doShift ( myWorkspaces !! 5 ) - , className =? "Element" --> doShift ( myWorkspaces !! 5 ) - , className =? "Steam" --> doShift ( myWorkspaces !! 5 ) + , className =? "discord" --> doShift ( workspacesTP !! 5 ) + , className =? "TelegramDesktop" --> doShift ( workspacesTP !! 5 ) + , className =? "Element" --> doShift ( workspacesTP !! 5 ) + , className =? "Steam" --> doShift ( workspacesTP !! 5 ) -- full workspace - , isFullscreen --> doShift ( myWorkspaces !! 6 ) + , isFullscreen --> doShift ( workspacesTP !! 6 ) -- vid workspace - , className =? "Deadbeef" --> doShift ( myWorkspaces !! 7 ) - , appName =? "mpv" --> doShift ( myWorkspaces !! 7 ) - , className =? "vlc" --> doShift ( myWorkspaces !! 7 ) + , className =? "Deadbeef" --> doShift ( workspacesTP !! 7 ) + , appName =? "mpv" --> doShift ( workspacesTP !! 7 ) + , className =? "vlc" --> doShift ( workspacesTP !! 7 ) -- gfx workspace - , className =? "Gimp" --> doShift ( myWorkspaces !! 8 ) - , className =? "Blender" --> doShift ( myWorkspaces !! 8 ) - , className =? "obs" --> doShift ( myWorkspaces !! 8 ) + , className =? "Gimp" --> doShift ( workspacesTP !! 8 ) + , className =? "Blender" --> doShift ( workspacesTP !! 8 ) + , className =? "obs" --> doShift ( workspacesTP !! 8 ) , isFullscreen --> doFullFloat - ] <+> namedScratchpadManageHook myScratchPads + ] <+> namedScratchpadManageHook scratchPads --- $scratchpads +-- * scratchpads -- -- currently i have: --@@ -272,15 +183,15 @@ --
-- * mpv instance that plays playlist in @~\/Video\/sp_playlist.m3u@ -- | scratchpad list -myScratchPads :: [NamedScratchpad] -myScratchPads = [ NS "terminal" spawnTerm findTerm manageTerm - , NS "mocp" spawnMocp findMocp manageMocp - , NS "calculator" spawnCalc findCalc manageCalc - , NS "mpvfloat" spawnMpv findMpv manageMpv - ] +scratchPads :: [NamedScratchpad] +scratchPads = [ NS "terminal" spawnTerm findTerm manageTerm + , NS "mocp" spawnMocp findMocp manageMocp + , NS "calculator" spawnCalc findCalc manageCalc + , NS "mpvfloat" spawnMpv findMpv manageMpv + ] where -- terminal - spawnTerm = myTerminal ++ " -t scratchpad" + spawnTerm = terminalEmulator ++ " -t scratchpad" findTerm = title =? "scratchpad" manageTerm = customFloating $ W.RationalRect l t w h where@@ -289,7 +200,7 @@ w = 0.9
t = 0.95 - h l = 0.95 - w -- music on console - spawnMocp = myTerminal ++ " -t mocp -e " ++ myMocp + spawnMocp = terminalEmulator ++ " -t mocp -e " ++ mocpString findMocp = title =? "mocp" manageMocp = customFloating $ W.RationalRect l t w h where@@ -316,65 +227,36 @@ h = mpvPercentage
w = mpvPercentage t = 0.03 l = 0.996 - w + mpvPercentage = 1/4 + mpvGeometry h w = " --geometry=" ++ show pw ++ "x" ++ show ph + where + pw = ceiling (1920 * w) + ph = ceiling (1080 * h) --- ** helper functions +-- * workspaces -- --- | percentage of mpv scratchpad at start -mpvPercentage :: Rational -mpvPercentage = 1/4 - --- | mpv needs geometry of window at start, so it won't resize itself, when --- playing next video on a playlist -mpvGeometry :: RealFrac a - => a -- ^ relative height of window - -> a -- ^ relative width of window - -> String +-- i've got two ways of specifying them. first one is pretty close to the +-- original dt's config and second one is using linja pona font by jan same +-- (check it out [here](http://musilili.net/linja-pona/)). -mpvGeometry h w = " --geometry=" ++ show pw ++ "x" ++ show ph - where - pw = ceiling (1920 * w) - ph = ceiling (1080 * h) +-- | normal english workspace names +workspacesNorm :: [String] +workspacesNorm = [ "dev" + , "www" + , "term" + , "doc" + , "vm" + , "chat" + , "full" + , "vid" + , "misc" + ] --- $workspaces +-- | toki pona workspace names -- --- i've got three ways of specifying them. first one is pretty close to the --- original dt's config. second is using sitelen pona pona font by jackhumbert --- (check it out [here](https://jackhumbert.github.io/sitelen-pona-pona/)). --- and third one is using linja pona font by jan same --- (check it out [here](http://musilili.net/linja-pona/)). --- --- * normal variant --- --- > myWorkspaces = [ "dev" --- > , "www" --- > , "sys" --- > , "doc" --- > , "vm" --- > , "chat" --- > , "full" --- > , "vid" --- > , "gfx" --- > ] --- --- * one using sitelen pona pona by jackhumbert --- --- this is specified with actual glyph codes because xmobar --- don't allow for ligatures and otf features. --- --- > myWorkspaces = [ "\xee3d" -- nanpa --- > , "\xee3b" -- musi --- > , "\xee49" -- pali --- > , "\xee2a" -- lipu --- > , "\xee53" -- poki --- > , "\xee6c" -- toki --- > , "\xee63" -- suli --- > , "\xee60" -- sitelen --- > , "\xee1e" -- kule --- > ] - --- | workspaces container -myWorkspaces :: [String] -myWorkspaces = [ "\xe661\xe921" -- sona nanpa +-- uses sitelen-pona font. +workspacesTP :: [String] +workspacesTP = [ "\xe661\xe921" -- sona nanpa , "\xe63b" -- musi , "\xe649" -- pali , "\xe62a\xf105" -- lipu ale@@ -385,28 +267,192 @@ , "\xf010\xe915" -- sitelen tawa
, "\xf010\xf107" -- sitelen ante ] --- $misc +-- * grid select +-- +-- stuff for 'GridSelect' + +-- | app grid for 'GridSelect' layout +appGrid :: [(String,String)] +appGrid = [ ("files" ,"thunar" ) + , ("mail" ,"thunderbird") + , ("blender" ,"blender-3.1") + , ("inkscape" ,"inkscape" ) + , ("discord" ,"discord" ) + , ("steam" ,"steam" ) + , ("obs" ,"obs" ) + , ("gimp" ,"gimp" ) + , ("ardour" ,"ardour6" ) + , ("kdenlive" ,"kdenlive" ) + ] + +-- | uses colors from 'ColorTheme' +boringColorizer :: a -> Bool -> X (String, String) +boringColorizer _ active = if active + then return (col_bg_alt def, col_fg_alt def) + else return (col_bg def, col_fg def) + +-- | 'GridSelect' config +gridSelectConfig :: GSConfig a +gridSelectConfig = (buildDefaultGSConfig boringColorizer) + { gs_font = fontDef + , gs_bordercolor = col_bg_alt def + } + +-- | allows to add aliases for commands unlike original 'spawnSelected' +spawnSelected' :: GSConfig String -> [(String, String)] -> X () +spawnSelected' conf lst = gridselect conf lst >>= flip whenJust spawn + +-- * keybindings +-- +-- list of keybindings. it supposed to override the default keybindings. + +-- | keybindings in 'EZConfig' format +keybinds :: [(String, X ())] +keybinds = [ ("M-<Return>", spawn terminalEmulator) + , ("M-w", spawn webBrowser) + , ("M-p", spawn "dmenu_run") + , ("M-<Delete>", spawn "slock") + , ("<Print>", spawn "scrot_cmd -f") + , ("C-<Print>", spawn "scrot_cmd -a") + , ("M1-<Print>", spawn "scrot_cmd -w") + + , ("M-s t", namedScratchpadAction scratchPads "terminal") + , ("M-s c", namedScratchpadAction scratchPads "calculator") + , ("M-s m", namedScratchpadAction scratchPads "mocp") + , ("M-s v", namedScratchpadAction scratchPads "mpvfloat") + + , ("M-g t", goToSelected gridSelectConfig) + , ("M-g b", bringSelected gridSelectConfig) + , ("M-g g", spawnSelected' gridSelectConfig appGrid) + + , ("M-S-c", kill) + , ("M-<Space>", sendMessage NextLayout) + , ("M-f", sendMessage ToggleLayout >> sendMessage ToggleStruts) + , ("M-h", sendMessage Shrink) + , ("M-l", sendMessage Expand) + , ("M-C-j", sendMessage MirrorShrink) + , ("M-C-k", sendMessage MirrorExpand) + , ("M-M1-h", sendMessage $ pullGroup L) + , ("M-M1-j", sendMessage $ pullGroup D) + , ("M-M1-k", sendMessage $ pullGroup U) + , ("M-M1-l", sendMessage $ pullGroup R) + , ("M-M1-u", withFocused $ sendMessage . UnMerge) + , ("M-M1-m", withFocused $ sendMessage . UnMergeAll) + , ("M-M1-,", onGroup W.focusDown') + , ("M-M1-.", onGroup W.focusUp') + , ("M-j", focusDown) + , ("M-k", focusUp) + , ("M-S-j", swapDown) + , ("M-S-k", swapUp) + , ("M-m", focusMaster) + , ("M-S-m", windows W.swapMaster) + , ("M-t", withFocused $ windows . W.sink) + , ("M-S-t", sinkAll) + , ("M-<Tab>", toggleWindowSpacingEnabled >> toggleScreenSpacingEnabled) + + , ("M-S-q", io exitSuccess) + , ("M-S-r", spawn "xmonad --recompile && xmonad --restart") + + , ("<XF86AudioPlay>", spawn $ mocpString ++ " -G") + , ("<XF86AudioRaiseVolume>", spawn $ mocpString ++ " -v +5") + , ("<XF86AudioLowerVolume>", spawn $ mocpString ++ " -v -5") + , ("<XF86AudioMute>", spawn $ mocpString ++ " -v 0") + , ("<XF86AudioPrev>", spawn $ mocpString ++ " --previous") + , ("<XF86AudioNext>", spawn $ mocpString ++ " --next") + ] + ++ + [("M-" ++ m ++ show k, windows $ f i) + | (i, k) <- zip workspacesTP [1..9] + , (f, m) <- [(W.greedyView, ""), (W.shift, "S-")] + ] + +-- * xmobar -- --- misc constants +-- stuff for xmobar --- | set windows key as modkey -myModMask :: KeyMask -myModMask = mod4Mask +-- | xmobar pretty printer +localXmobarPP :: PP +localXmobarPP = def + { ppSep = xmobarColor (col_bg_alt def) "" " | " + , ppCurrent = xmobarColor (col_fg_alt def) "" . sitelen + , ppHidden = xmobarColor (col_fg def) "" . sitelen + , ppHiddenNoWindows = xmobarColor (col_bg_alt def) "" . sitelen + , ppLayout = sitelen + } where + sitelen = xmobarFont 3 --- | specify border width -myBorderWidth :: Dimension -myBorderWidth = 1 +-- | status bar config +statusBarConfig :: StatusBarConfig +statusBarConfig = statusBarProp "xmobar" + $ clickablePP $ filterOutWsPP [scratchpadWorkspaceTag] localXmobarPP --- | app grid for 'GridSelect' layout -myAppGrid :: [(String,String)] -myAppGrid = [ ("files" ,"thunar" ) - , ("mail" ,"thunderbird") - , ("blender" ,"blender-3.1") - , ("inkscape" ,"inkscape" ) - , ("discord" ,"discord" ) - , ("steam" ,"steam" ) - , ("obs" ,"obs" ) - , ("gimp" ,"gimp" ) - , ("ardour" ,"ardour6" ) - , ("kdenlive" ,"kdenlive" ) - ] +-- * layouts +-- +-- stuff for layouts + +-- | theme for 'Tabbed' layout +tabTheme :: Theme +tabTheme = def + { fontName = fontDef + , activeTextColor = col_fg_alt def + , activeColor = col_bg_alt def + , activeBorderWidth = 0 + , inactiveTextColor = col_fg def + , inactiveColor = col_bg def + , inactiveBorderWidth = 0 + , urgentTextColor = col_bg_alt def + , urgentColor = col_fg_alt def + , urgentBorderWidth = 0 + } + +-- | layout hook +-- +-- __NOTE__: it uses sitelen-pona font to name layouts. +localLayoutHook = windowNavigation + $ boringWindows + $ toggleLayouts full + $ smartBorders + $ tiled ||| threeCol + where + tiled = renamed [Replace "\xe624"] -- lawa + $ addTabs shrinkText tabTheme + $ subLayout [] Simplest + $ spacingWithEdge space + $ ResizableTall nmaster delta ratio [] + threeCol = renamed [Replace "\xe665"] -- supa + $ addTabs shrinkText tabTheme + $ subLayout [] Simplest + $ spacingWithEdge space + $ ResizableThreeColMid nmaster delta ratio [] + full = renamed [Replace "\xe663"] -- suli + $ noBorders Full + nmaster = 1 + ratio = 1/2 + delta = 3/100 + space = 4 + +-- | main config +-- +-- you can override things like that: +-- +-- > myConfig = laNinpreConfig { workspaces = workspacesNorm } +-- > main = xmonad myConfig +laNinpreConfig = def + { terminal = terminalEmulator + , modMask = mod4Mask + , layoutHook = localLayoutHook + , manageHook = localManageHook + , workspaces = workspacesTP + , borderWidth = 1 + , keys = (`mkKeymap` keybinds) + , normalBorderColor = col_bg_alt def + , focusedBorderColor = col_fg_alt def + } + +main :: IO () +main = xmonad + . ewmhFullscreen + . ewmh + . withEasySB statusBarConfig defToggleStrutsKey + $ laNinpreConfig +
M
xmonad.hs
→
xmonad.hs
@@ -1,172 +1,1 @@
-import System.Exit - -import XMonad -import qualified XMonad.StackSet as W - -import XMonad.Actions.GridSelect -import XMonad.Actions.WithAll - -import XMonad.Hooks.DynamicLog -import XMonad.Hooks.EwmhDesktops -import XMonad.Hooks.ManageDocks -import XMonad.Hooks.StatusBar -import XMonad.Hooks.StatusBar.PP - -import XMonad.Util.ClickableWorkspaces -import XMonad.Util.EZConfig -import XMonad.Util.NamedScratchpad - -import XMonad.Layout.BoringWindows hiding (Replace) -import XMonad.Layout.NoBorders -import XMonad.Layout.Renamed -import XMonad.Layout.ResizableTile -import XMonad.Layout.ResizableThreeColumns -import XMonad.Layout.Simplest -import XMonad.Layout.Spacing -import XMonad.Layout.SubLayouts -import XMonad.Layout.Tabbed -import XMonad.Layout.ToggleLayouts -import XMonad.Layout.WindowNavigation - import XMonad.Config.LaNinpre - -myKeys :: [(String, X ())] -myKeys = [ ("M-<Return>", spawn myTerminal) - , ("M-w", spawn myBrowser) - , ("M-p", spawn "dmenu_run") - , ("M-<Delete>", spawn "slock") - , ("<Print>", spawn "scrot_cmd -f") - , ("C-<Print>", spawn "scrot_cmd -a") - , ("M1-<Print>", spawn "scrot_cmd -w") - - , ("M-s t", namedScratchpadAction myScratchPads "terminal") - , ("M-s c", namedScratchpadAction myScratchPads "calculator") - , ("M-s m", namedScratchpadAction myScratchPads "mocp") - , ("M-s v", namedScratchpadAction myScratchPads "mpvfloat") - - , ("M-g t", goToSelected myGsConfig) - , ("M-g b", bringSelected myGsConfig) - , ("M-g g", mySpawnSelected myGsConfig myAppGrid) - - , ("M-S-c", kill) - , ("M-<Space>", sendMessage NextLayout) - , ("M-f", sendMessage ToggleLayout >> sendMessage ToggleStruts) - , ("M-h", sendMessage Shrink) - , ("M-l", sendMessage Expand) - , ("M-C-j", sendMessage MirrorShrink) - , ("M-C-k", sendMessage MirrorExpand) - , ("M-M1-h", sendMessage $ pullGroup L) - , ("M-M1-j", sendMessage $ pullGroup D) - , ("M-M1-k", sendMessage $ pullGroup U) - , ("M-M1-l", sendMessage $ pullGroup R) - , ("M-M1-u", withFocused $ sendMessage . UnMerge) - , ("M-M1-m", withFocused $ sendMessage . UnMergeAll) - , ("M-M1-,", onGroup W.focusDown') - , ("M-M1-.", onGroup W.focusUp') - , ("M-j", focusDown) - , ("M-k", focusUp) - , ("M-S-j", swapDown) - , ("M-S-k", swapUp) - , ("M-m", focusMaster) - , ("M-S-m", windows W.swapMaster) - , ("M-t", withFocused $ windows . W.sink) - , ("M-S-t", sinkAll) - , ("M-<Tab>", toggleWindowSpacingEnabled >> toggleScreenSpacingEnabled) - - , ("M-S-q", io exitSuccess) - , ("M-S-r", spawn "xmonad --recompile && xmonad --restart") - - , ("<XF86AudioPlay>", spawn $ myMocp ++ " -G") - , ("<XF86AudioRaiseVolume>", spawn $ myMocp ++ " -v +5") - , ("<XF86AudioLowerVolume>", spawn $ myMocp ++ " -v -5") - , ("<XF86AudioMute>", spawn $ myMocp ++ " -v 0") - , ("<XF86AudioPrev>", spawn $ myMocp ++ " --previous") - , ("<XF86AudioNext>", spawn $ myMocp ++ " --next") - ] - ++ - [("M-" ++ m ++ show k, windows $ f i) - | (i, k) <- zip myWorkspaces [1..9] - , (f, m) <- [(W.greedyView, ""), (W.shift, "S-")] - ] - -myColorizer :: a -> Bool -> X (String, String) -myColorizer _ active = if active then return (col_bg_alt def, col_fg_alt def) - else return (col_bg def, col_fg def) - -myGsConfig :: GSConfig a -myGsConfig = (buildDefaultGSConfig myColorizer) - { gs_font = head myFonts - , gs_bordercolor = col_bg_alt def - } - -mySpawnSelected :: GSConfig String -> [(String, String)] -> X () -mySpawnSelected conf lst = gridselect conf lst >>= flip whenJust spawn - -myXmobarPP :: PP -myXmobarPP = def - { ppSep = xmobarColor (col_bg_alt def) "" " | " - , ppCurrent = xmobarColor (col_fg_alt def) "" . sitelen - , ppHidden = xmobarColor (col_fg def) "" . sitelen - , ppHiddenNoWindows = xmobarColor (col_bg_alt def) "" . sitelen - , ppLayout = sitelen - } where - sitelen = xmobarFont 3 - -mySB :: StatusBarConfig -mySB = statusBarProp "xmobar" - $ clickablePP $ filterOutWsPP [scratchpadWorkspaceTag] myXmobarPP - -myTabTheme :: Theme -myTabTheme = def - { fontName = head myFonts - , activeTextColor = col_fg_alt def - , activeColor = col_bg_alt def - , activeBorderWidth = 0 - , inactiveTextColor = col_fg def - , inactiveColor = col_bg def - , inactiveBorderWidth = 0 - , urgentTextColor = col_bg_alt def - , urgentColor = col_fg_alt def - , urgentBorderWidth = 0 - } - -myLayout = windowNavigation - $ boringWindows - $ toggleLayouts full - $ smartBorders - $ tiled ||| threeCol - where - tiled = renamed [Replace "\xe624"] -- lawa - $ addTabs shrinkText myTabTheme - $ subLayout [] Simplest - $ spacingWithEdge space $ ResizableTall nmaster delta ratio [] - threeCol = renamed [Replace "\xe665"] -- supa - $ addTabs shrinkText myTabTheme - $ subLayout [] Simplest - $ spacingWithEdge space $ ResizableThreeColMid nmaster delta ratio [] - full = renamed [Replace "\xe663"] -- suli - $ noBorders Full - nmaster = 1 - ratio = 1/2 - delta = 3/100 - space = 4 - -myConfig = def - { terminal = myTerminal - , modMask = myModMask - , layoutHook = myLayout - , manageHook = myManageHook - , workspaces = myWorkspaces - , borderWidth = myBorderWidth - , keys = (`mkKeymap` myKeys) - , normalBorderColor = col_bg_alt def - , focusedBorderColor = col_fg_alt def - , startupHook = return () >> checkKeymap myConfig myKeys - } - -main :: IO () -main = xmonad - . ewmhFullscreen - . ewmh - . withEasySB mySB defToggleStrutsKey - $ myConfig