rewrite config from scratch and remove xmobar config xmobar config is now written in haskell instead of it's own weird config format and it will be available on my dotfiles repo.
la-ninpre leobrekalini@gmail.com
Fri, 17 Jun 2022 10:31:51 +0300
9 files changed,
545 insertions(+),
613 deletions(-)
A
example/xmonad.hs.bak
@@ -0,0 +1,455 @@
+{-# OPTIONS_HADDOCK prune #-} + +---------------------------------------------------------------------- +-- | +-- Description : la-ninpre xmonad config +-- Maintainer : la-ninpre +-- License : ISC +-- Copyright : la-ninpre <aaoth AT aaoth DOT xyz> +-- +-- personal xmonad config. based heavily on distrotube's config. +-- i've added some stuff and toki pona fonts +-- +---------------------------------------------------------------------- + +module Main where + +import System.Directory +import System.IO (hPutStrLn) +import System.Exit (exitSuccess) + +import Data.Char (isSpace, toUpper) +import Data.Maybe (fromJust, isJust) +import Data.Monoid +import Data.Tree +import Data.List +import qualified Data.Map as M + +import XMonad +import qualified XMonad.StackSet as W + +import XMonad.Actions.CopyWindow (kill1) +import XMonad.Actions.CycleWS ( Direction1D(..) + , moveTo + , shiftTo + , WSType(..) + , nextScreen + , prevScreen + ) +import XMonad.Actions.GridSelect +import XMonad.Actions.MouseResize +import XMonad.Actions.Promote +import XMonad.Actions.RotSlaves (rotSlavesDown, rotAllDown) +import XMonad.Actions.WindowGo (runOrRaise) +import XMonad.Actions.WithAll (sinkAll, killAll) +import qualified XMonad.Actions.Search as S + +import XMonad.Hooks.DynamicLog +import XMonad.Hooks.EwmhDesktops +import XMonad.Hooks.ManageDocks ( avoidStruts + , docks + , manageDocks + , ToggleStruts(..)) +import XMonad.Hooks.ManageHelpers (isFullscreen, doFullFloat) +import XMonad.Hooks.ServerMode +import XMonad.Hooks.SetWMName +import XMonad.Hooks.StatusBar.PP (filterOutWsPP) +import XMonad.Hooks.WorkspaceHistory + +import XMonad.Layout.SimplestFloat +import XMonad.Layout.ResizableTile +import XMonad.Layout.Tabbed +import XMonad.Layout.ThreeColumns +import XMonad.Layout.Accordion +import XMonad.Layout.LayoutModifier +import XMonad.Layout.LimitWindows (limitWindows, increaseLimit, decreaseLimit) +import XMonad.Layout.Magnifier +import XMonad.Layout.MultiToggle (mkToggle, single, EOT(EOT), (??)) +import XMonad.Layout.MultiToggle.Instances (StdTransformers( NBFULL + , MIRROR + , NOBORDERS + )) +import XMonad.Layout.NoBorders +import XMonad.Layout.Renamed +import XMonad.Layout.ShowWName +import XMonad.Layout.Simplest +import XMonad.Layout.Spacing +import XMonad.Layout.SubLayouts +import XMonad.Layout.WindowNavigation +import qualified XMonad.Layout.BoringWindows as BW +import XMonad.Layout.WindowArranger (windowArrange, WindowArrangerMsg(..)) +import qualified XMonad.Layout.ToggleLayouts as T ( toggleLayouts + , ToggleLayout(Toggle) + ) +import qualified XMonad.Layout.MultiToggle as MT (Toggle(..)) + +import XMonad.Util.Dmenu +import XMonad.Util.Loggers +import XMonad.Util.EZConfig (additionalKeysP) +import XMonad.Util.NamedScratchpad +import XMonad.Util.Run (runProcessWithInput, safeSpawn, spawnPipe) +import XMonad.Util.SpawnOnce +import XMonad.Util.WorkspaceCompare + +import LaNinpreConfig + +-- * misc functions +-- +-- | hides workspaces that have no windows +myHiddenNoWindows :: WorkspaceId -> String +myHiddenNoWindows = const "" + +mySuperscript :: Int -> String +mySuperscript n = map ss $ show n + where ss c | c == '0' = '⁰' + | c == '1' = '¹' + | c == '2' = '²' + | c == '3' = '³' + | c == '4' = '⁴' + | c == '5' = '⁵' + | c == '6' = '⁶' + | c == '7' = '⁷' + | c == '8' = '⁸' + | c == '9' = '⁹' + | otherwise = c + + +-- | window count logger +-- +-- gets number of windows on current workspace +myWindowCountLogger :: Logger +myWindowCountLogger = gets $ Just . show . length . W.integrate' . W.stack + . W.workspace . W.current . windowset + +-- * grid select +-- +-- $gridSelect +-- +-- this section provides theming of 'GridSelect' stuff. +-- +-- here, 'GridSelect' is used for following things: +-- +-- * spawning some frequently used programs +-- +-- * moving to desired window +-- +-- * bringing the desired window to the current workspace + +-- | custom colorizer for 'gridselect' +-- +-- essentially, it is just plain theme +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) + +-- | custom 'GSConfig' +myGridConfig :: GSConfig a +myGridConfig = (buildDefaultGSConfig myColorizer) + { gs_cellheight = 40 + , gs_cellwidth = 200 + , gs_cellpadding = 6 + , gs_originFractX = 0.5 + , gs_originFractY = 0.5 + , gs_bordercolor = col_bg_alt def + , gs_font = head myFonts + } + +-- | spawn selected programs with grid select +-- +-- it is esentially the same as 'spawnSelected' but allows to specify program aliases +mySpawnSelected :: [(String, String)] -> X () +mySpawnSelected lst = gridselect myGridConfig lst >>= flip whenJust spawn + +-- * layouts +-- +-- ** spacing raw helper functions +-- +-- $spacingHelpers +-- +-- these make calls to 'spacingRaw' simpler to write + +-- | for many windows +mySpacing :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a +mySpacing i = spacingRaw False (Border i i i i) True (Border i i i i) True + +-- | for fewer than two windows +mySpacing' :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a +mySpacing' i = spacingRaw True (Border i i i i) True (Border i i i i) True + +-- ** actually layouts +-- +-- $layouts +-- +-- currently there are: +-- +-- * tall +-- +-- * floats +-- +-- * threeCol + +tall = renamed [Replace "tall"] + $ smartBorders + $ addTabs shrinkText myTabTheme + $ subLayout [] (smartBorders Simplest ||| Accordion) + $ limitWindows 12 + $ mySpacing 4 + $ ResizableTall 1 (5/100) (1/2) [] + +floats = renamed [Replace "floats"] + $ smartBorders + $ limitWindows 20 + simplestFloat + +threeCol = renamed [Replace "threeCol"] + $ smartBorders + $ addTabs shrinkText myTabTheme + $ subLayout [] (smartBorders Simplest ||| Accordion) + $ limitWindows 7 + $ mySpacing 4 + $ ThreeColMid 1 (3/100) (1/2) + +-- | setting colors for tabs layout and tabs sublayout. +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 + } + +-- ** layout hook + +-- $layoutHook +-- +-- putting it all together with some stuff +myLayoutHook = avoidStruts + $ mouseResize + $ BW.boringWindows + $ windowNavigation + $ windowArrange + $ T.toggleLayouts floats + $ mkToggle (NBFULL ?? NOBORDERS ?? EOT) myDefaultLayout + where + myDefaultLayout = withBorder myBorderWidth tall + ||| withBorder myBorderWidth threeCol + +-- * show wm name hook + +-- | theme for showWName which prints current workspace +-- when you change workspaces. +myShowWNameTheme :: SWNConfig +myShowWNameTheme = def + { swn_font = myFonts !! 1 + , swn_fade = 0.7 + , swn_bgcolor = col_bg def + , swn_color = col_fg def + } + +-- * workspaces +-- +-- $workspaces +-- +-- here are some helper functions to deal with workspaces. +-- +-- actual workspace list is in "LaNinpreConfig". + +-- | workspace indices to use with hotkeys +myWorkspaceIndices = M.fromList $ zip myWorkspaces [1..] + +-- ** clickable workspace wrapper +-- +-- $clickable +-- +-- normal variant +-- +-- > clickable ws = "<action=xdotool key super+"++show i++">"++ws++"</action>" +-- > where i = fromJust $ M.lookup ws myWorkspaceIndices + +-- | provides option to click workspaces to switch to them. +-- this is handled by @UnsafeStdinReader@ in xmobar config. +clickable ws = "<fn=3><action=xdotool key super+"++show i++">"++ws++"</action></fn>" + where i = fromJust $ M.lookup ws myWorkspaceIndices + +-- * keybindings + +-- | keybindings list +-- +-- there's no way to document it using haddock, i guess... +myKeys :: [(String, X ())] +myKeys = + [ ("M-C-r", spawn "xmonad --recompile") -- Recompiles xmonad + , ("M-S-r", spawn "xmonad --restart") -- Restarts xmonad + , ("M-S-q", io exitSuccess) -- Quits xmonad + + -- Run Prompt + , ("M-p", spawn "dmenu_run -i -p \"Run: \"") -- Dmenu + + -- Useful programs to have a keybinding for launch + , ("M-<Return>", spawn myTerminal) + , ("M-e", spawn myFileMgr) + , ("M-w", spawn myBrowser) + , ("M-i", spawn (myTerminal + ++ " --class alacritty,amfora -e " + ++ myGeminiClient)) + , ("M-S-e", spawn "emacsclient -c") + -- Kill windows + , ("M-S-c", kill1) -- Kill the currently focused client + , ("M-S-a", killAll) -- Kill all windows on current workspace + + -- Workspaces + , ("M-.", nextScreen) -- Switch focus to next monitor + , ("M-,", prevScreen) -- Switch focus to prev monitor + -- Shifts focused window to next ws + , ("M-S-<KP_Add>", shiftTo Next nonNSP >> moveTo Next nonNSP) + -- Shifts focused window to prev ws + , ("M-S-<KP_Subtract>", shiftTo Prev nonNSP >> moveTo Prev nonNSP) + + -- Floating windows + , ("M-f", sendMessage (T.Toggle "floats")) -- Toggles my 'floats' layout + , ("M-t", withFocused $ windows . W.sink) -- Push floating window back to tile + , ("M-S-t", sinkAll) -- Push ALL floating windows to tile + + -- Increase/decrease spacing (gaps) + , ("C-M1-j", decWindowSpacing 4) -- Decrease window spacing + , ("C-M1-k", incWindowSpacing 4) -- Increase window spacing + , ("C-M1-h", decScreenSpacing 4) -- Decrease screen spacing + , ("C-M1-l", incScreenSpacing 4) -- Increase screen spacing + + -- Grid Select (MOD-g followed by a key) + , ("M-g g", mySpawnSelected myAppGrid) -- grid select favorite apps + , ("M-g t", goToSelected myGridConfig) -- goto selected window + , ("M-g b", bringSelected myGridConfig) -- bring selected window + + -- Windows navigation + , ("M-m", windows W.focusMaster) -- Move focus to the master window + , ("M-j", BW.focusDown) -- Move focus to the next window + , ("M1-<Tab>", BW.focusDown) -- legacy keybinding + , ("M-k", BW.focusUp) -- Move focus to the prev window + , ("M-S-m", windows W.swapMaster) -- Swap the focused window and the master window + , ("M-S-j", windows W.swapDown) -- Swap focused window with next window + , ("M-S-k", windows W.swapUp) -- Swap focused window with prev window + , ("M-<Backspace>", promote) -- Moves focused window to master, others maintain order + , ("M-S-<Tab>", rotSlavesDown) -- Rotate all windows except master and keep focus in place + , ("M-C-<Tab>", rotAllDown) -- Rotate all the windows in the current stack + + -- Layouts + , ("M-<Tab>", sendMessage NextLayout) -- Switch to next layout + , ("M-b", sendMessage (MT.Toggle NBFULL)) + , ("M-<Space>", sendMessage (MT.Toggle NBFULL) >> sendMessage ToggleStruts) -- Toggles noborder/full + + -- Increase/decrease windows in the master pane or the stack + , ("M-S-<Up>", sendMessage (IncMasterN 1)) -- Increase # of clients master pane + , ("M-S-<Down>", sendMessage (IncMasterN (-1))) -- Decrease # of clients master pane + , ("M-C-<Up>", increaseLimit) -- Increase # of windows + , ("M-C-<Down>", decreaseLimit) -- Decrease # of windows + + -- Window resizing + , ("M-h", sendMessage Shrink) -- Shrink horiz window width + , ("M-l", sendMessage Expand) -- Expand horiz window width + , ("M-M1-j", sendMessage MirrorShrink) -- Shrink vert window width + , ("M-M1-k", sendMessage MirrorExpand) -- Expand vert window width + + -- Sublayouts + -- This is used to push windows to tabbed sublayouts, or pull them out of it. + , ("M-C-h", sendMessage $ pullGroup L) + , ("M-C-l", sendMessage $ pullGroup R) + , ("M-C-k", sendMessage $ pullGroup U) + , ("M-C-j", sendMessage $ pullGroup D) + , ("M-C-m", withFocused (sendMessage . MergeAll)) + , ("M-C-u", withFocused (sendMessage . UnMerge)) + , ("M-C-/", withFocused (sendMessage . UnMergeAll)) + , ("M-C-<Space>", toSubl NextLayout) + , ("M-C-.", onGroup W.focusUp') -- Switch focus to next tab + , ("M-C-,", onGroup W.focusDown') -- Switch focus to prev tab + + -- Scratchpads + -- Toggle show/hide these programs. They run on a hidden workspace. + -- When you toggle them to show, it brings them to your current workspace. + -- Toggle them to hide and it sends them back to hidden workspace (NSP). + , ("M-s t", namedScratchpadAction myScratchPads "terminal") + , ("M-s m", namedScratchpadAction myScratchPads "mocp") + , ("M-s c", namedScratchpadAction myScratchPads "calculator") + , ("M-s v", namedScratchpadAction myScratchPads "mpvfloat" ) + + -- Set wallpaper with 'feh'. Type 'SUPER+F1' to launch sxiv in the wallpapers directory. + -- Then in sxiv, type 'C-x w' to set the wallpaper that you choose. + , ("M-<F1>", spawn "sxiv -r -q -t -o ~/Pictures/wallpapers/*") + , ("M-<F2>", spawn "/bin/ls ~/Pictures/wallpapers | shuf -n 1 \ + \| xargs xwallpaper --stretch") + + -- pana e nimi sewi + , ("M-<F7>", spawn "nimi_sewi") + + -- Controls for mocp music player (SUPER-u followed by a key) + , ("M-u p", spawn (myMocp ++ " --play")) + , ("M-u l", spawn (myMocp ++ " --next")) + , ("M-u h", spawn (myMocp ++ " --previous")) + , ("M-u <Space>", spawn (myMocp ++ " --toggle-pause")) + + -- screenshots + , ("<Print>", spawn "scrot_cmd -f") + , ("C-<Print>", spawn "scrot_cmd -a") + , ("M1-<Print>", spawn "scrot_cmd -w") + + -- Multimedia Keys + , ("<XF86AudioPlay>", spawn (myMocp ++ " --toggle-pause")) + , ("<XF86AudioPrev>", spawn (myMocp ++ " --previous")) + , ("<XF86AudioNext>", spawn (myMocp ++ " --next")) + , ("<XF86AudioMute>", spawn (myMocp ++ " -v 0")) + , ("<XF86AudioLowerVolume>", spawn (myMocp ++ " -v -5")) + , ("<XF86AudioRaiseVolume>", spawn (myMocp ++ " -v +5")) + , ("<XF86HomePage>", spawn "firefox https://aaoth.xyz") + , ("<XF86Mail>", runOrRaise "thunderbird" (resource =? "thunderbird")) + , ("<XF86Calculator>", namedScratchpadAction myScratchPads "calculator") + , ("<XF86Sleep>", spawn "dm-logout") + ] + -- the following lines are needed for named scratchpads. + where nonNSP = WSIs (return (\ws -> W.tag ws /= "NSP")) + nonEmptyNonNSP = WSIs (return (\ws -> isJust (W.stack ws) + && W.tag ws /= "NSP")) + + +main :: IO () +main = do + xmproc <- spawnPipe "xmobar ~/.config/xmonad/xmobar/xmobarrc" + -- the xmonad, ya know...what the wm is named after! + xmonad $ docks . ewmh $ def + { manageHook = myManageHook <+> manageDocks + --, handleEventHook = docksEventHook + , modMask = myModMask + , terminal = myTerminal + , startupHook = myStartupHook + , layoutHook = showWName' myShowWNameTheme myLayoutHook + , workspaces = myWorkspaces + , borderWidth = myBorderWidth + , normalBorderColor = myNormColor + , focusedBorderColor = myFocusColor + , logHook = dynamicLogWithPP + $ filterOutWsPP ["NSP"] + $ xmobarPP + { ppOutput = hPutStrLn xmproc + , ppCurrent = xmobarColor (col_fg_alt def) "" + . wrap "<fn=3>" "</fn>" -- toki pona + . wrap "[" "]" + -- . wrap " " " " -- normal + , ppVisible = xmobarColor (col_fg_alt def) "" . clickable + , ppHidden = xmobarColor (col_fg def) "" + . wrap "" "'" + . clickable + , ppHiddenNoWindows = xmobarColor (col_bg_alt def) "" . clickable + --, ppHiddenNoWindows = myHiddenNoWindows + , ppTitle = xmobarColor (col_fg def) "" . shorten 60 + , ppSep = xmobarColor (col_bg_alt def) "" " | " + , ppWsSep = " " + , ppUrgent = xmobarColor (col_fg_alt def) "" . wrap "!" "!" + , ppExtras = [myWindowCountLogger] + , ppOrder = \(ws:l:t:ex) -> [ws,l]++ex++[t] + } + } `additionalKeysP` myKeys +
D
xmobar/trayer-padding-icon.sh
@@ -1,48 +0,0 @@
-#!/bin/sh -# Copied from https://github.com/jaor/xmobar/issues/239#issuecomment-233206552 -# Detects the width of running trayer-srg window (xprop name 'panel') -# and creates an XPM icon of that width, 1px height, and transparent. -# Outputs an <icon>-tag for use in xmobar to display the generated -# XPM icon. -# -# Run script from xmobar: -# `Run Com "/where/ever/trayer-padding-icon.sh" [] "trayerpad" 10` -# and use `%trayerpad%` in your template. - - -# Function to create a transparent Wx1 px XPM icon -create_xpm_icon () { - timestamp=$(date) - pixels=$(for i in `seq $1`; do echo -n "."; done) - - cat << EOF > "$2" -/* XPM * -static char * trayer_pad_xpm[] = { -/* This XPM icon is used for padding in xmobar to */ -/* leave room for trayer-srg. It is dynamically */ -/* updated by by trayer-padding-icon.sh which is run */ -/* by xmobar. */ -/* Created: ${timestamp} */ -/* <w/cols> <h/rows> <colors> <chars per pixel> */ -"$1 1 1 1", -/* Colors (none: transparent) */ -". c none", -/* Pixels */ -"$pixels" -}; -EOF -} - -# Width of the trayer window -width=$(xprop -name panel | grep 'program specified minimum size' | cut -d ' ' -f 5) - -# Icon file name -iconfile="$HOME/.xmonad/xpm/tmp/trayer-padding-${width}px.xpm" - -# If the desired icon does not exist create it -if [ ! -f $iconfile ]; then - create_xpm_icon $width $iconfile -fi - -# Output the icon tag for xmobar -echo "<icon=${iconfile}/>"
D
xmobar/xmobarrc
@@ -1,107 +0,0 @@
--- https://projects.haskell.org/xmobar/ --- uses font awesome --- vim:se syntax=haskell: - -Config { font = "xft:Lato:weight=bold:pixelsize=12:antialias=true:hinting=true" - , additionalFonts = [ "xft:Font Awesome 5 Free Solid:pixelsize=12" - , "xft:Font Awesome 5 Brands:pixelsize=14" - -- sitelen pona pona by jackhumbert - --, "xft:sitelen\-pona:pixelsize=20:antialias=true:hinting=true" - -- linja pona - , "xft:linja pona:pixelsize=22:antialias=true:hinting=true" - ] - , bgColor = "#111111" - , fgColor = "#ccbbcc" - , position = TopSize C 100 24 - , lowerOnStart = True - , hideOnStart = False - , persistent = True - , iconRoot = ".config/xmonad/xpm/" - , commands = [ Run UnsafeStdinReader - , Run Com "uname" ["-r"] "" 0 - , Run Uptime - ["-t" - -- normie - --, "<fc=#7f9848><fn=1>\xf017</fn> uptime: <days>d</fc>" - -- sitelen pona pona by jackhumbert - --, "<fc=#7f9848><fn=3>\xee6b\xee64\xee3d</fn><days></fc>" - -- linja pona - , "<fn=3>\xe66b\xe664\xe63d</fn><days>" - -- tenpo suno nanpa - ] 60 - , Run Cpu - ["-t" - -- normie - --, "<fc=#c74444><fn=1>\xf108</fn>cpu: <total>%</fc>" - -- sitelen pona pona by jackhumbert - --, "<fc=#c74444><fn=3>\xee24\xee4d\xee0e\xee3d</fn>: <total>%</fc>" - -- linja pona - , "<fn=3>\xe624\xe730\xe60e\xe63d</fn>: <total>%" - -- lawa pi ilo sona - , "-H", "50", "--high", "red" - ] 20 - , Run Memory - ["-t" - -- normie - --, "<fc=#d7a06d><fn=1>\xf538</fn> ram: <used>M (<usedratio>%)</fc>" - -- sitelen pona pona by jackhumbert - --, "<fc=#d7a06d><fn=3>\xee53\xee49</fn>: <used>M (<usedratio>%)</fc>" - -- linja pona - , "<fn=3>\xe653\xf174</fn>: <used>M (<usedratio>%)" - -- poki pali - ] 20 - , Run DiskU - [("/home" - -- normie - --, "<fc=#4e96d5><fn=1>\xf0a0</fn> hdd: <free> free</fc>") - -- sitelen pona pona by jackhumbert - --, "<fc=#4e96d5><fn=3>\xee53\xee08</fn>: <free></fc>") - -- linja pona - , "<fn=3>\xe653\xf109</fn>: <free>") - -- poki awen - ] [] 60 - , Run Kbd - -- normie - --[ ("us", "<fc=#55b795><fn=1>\xf11c</fn> EN</fc>") - --, ("ru", "<fc=#55b795><fn=1>\xf11c</fn> RU</fc>") - --] - -- sitelen pona pona by jackhumbert - --[ ("us", "<fc=#55b795><fn=3>\xee6c\xee4d\xee0e\xee60 inli</fn></fc>") - --, ("ru", "<fc=#55b795><fn=3>\xee6c\xee4d\xee0e\xee60 losi</fn></fc>") - --] - -- toki pi ilo sitelen - -- linja pona - [ ("us", "<fn=3>\xe66c\xe730\xe619\xe660 [INLI]</fn>") - , ("ru", "<fn=3>\xe66c\xe730\xe619\xe660 [LOSI]</fn>") - ] - -- toki pi ilo sitelen - , Run Date - -- normie - --"<fc=#ceced2><fn=1>\xf017</fn> %d %b %Y %R</fc>" - -- sitelen pona pona by jackhumbert - --"<fc=#ceced2><fn=3>\xee6b</fn> %d-%m-%Y %R</fc>" - -- linja pona - "<fn=3>\xe66b</fn> %d-%m-%Y %R" - -- tenpo - "date" 50 - , Run Network "wg0" - ["-t" - -- normie - --, "<fc=#ceced2><fn=1>\xf6d5</fn></fc>" - -- sitelen pona pona by jackhumbert - --, "<fc=#ceced2><fn=3>\xee01</fn></fc>" - -- linja pona - , "<fn=3>\xe601</fn>" - -- akesi - ] 20 - , Run Com ".config/xmonad/xmobar/trayer-padding-icon.sh" - ["panel"] "trayerpad" 10 - , Run Com ".config/xmonad/xmobar/separator.sh" [] "s" 0 - ] - , sepChar = "%" - , alignSep = "}{" - -- ... }{ <fc=#ceced2><fn=2></fn> ... -- normie - -- ... }{ <fc=#ceced2><fn=3> linu</fn> ... -- sitelen pona pona by jackhumbert - -- ... }{ <fc=#ceced2><fn=3> [_L_IN_U]</fn> ... -- linja pona - , template = " <action=`dm-logout`><icon=la_ninpre.xpm/></action> %s% %UnsafeStdinReader% }{ <fn=3> [LINU]</fn> <action=`alacritty --class Alacritty,splash --hold -e neofetch`>%uname%</action> %s% %uptime% %s% <action=`alacritty -e htop`>%cpu%</action> %s% <action=`alacritty -e htop`>%memory%</action> %s% <action=`alacritty --class Alacritty,splash --hold -e df -h / /timeshift /home`>%disku%</action> %s% %kbd% %s% <action=`alacritty -e calcurse`>%date%</action> %s% %wg0% %trayerpad%" -}
D
xmobar/xmobarrc.bak
@@ -1,30 +0,0 @@
-Config { font = "xft:Jet Brains Mono:pixelsize=12:antialias=true;hinting=true" - , additionalFonts = [] - , bgColor = "#2e3440" - , fgColor = "#d8dee9" - , position = Top - , lowerOnStart = True - , hideOnStart = False - , allDesktops = True - , persistent = True - , iconRoot = "/home/aaoth/.xmonad/xpm/" -- default: "." - , commands = [ - -- Time and date - Run Date "%b %d %Y %H:%M" "date" 50 - -- Network up and down - , Run Network "eno1" ["-t", "<rx>kb <tx>kb"] 20 - , Run Network "wg0" ["-t", "<rx>kb <tx>kb"] 20 - -- Cpu usage in percent - , Run Cpu ["-t", "<total>%","-H","50","--high","red"] 20 - -- Ram used number and percent - , Run Memory ["-t", "<used>M (<usedratio>%)"] 20 - -- Disk space free - , Run DiskU [("/", "<free> free")] [] 60 - -- Runs a standard shell command 'uname -r' to get kernel version - , Run Com "uname" ["-r"] "" 3600 - ] - , sepChar = "%" - , alignSep = "}{" - , template = "<icon=haskell_20.xpm/>}{%uname% <fc=#666666>|</fc> <icon=cpu_20.xpm/> %cpu% <fc=#666666>|</fc> <icon=memory-icon_20.xpm/> %memory% <fc=#666666>|</fc> <icon=harddisk-icon_20.xpm/> %disku% <fc=#666666>|</fc> %eno1% wg: %wg0% <fc=#666666>|</fc> %date% " - } -
M
xmonad.hs
→
xmonad.hs
@@ -1,455 +1,120 @@
-{-# OPTIONS_HADDOCK prune #-} - ----------------------------------------------------------------------- --- | --- Description : la-ninpre xmonad config --- Maintainer : la-ninpre --- License : ISC --- Copyright : la-ninpre <aaoth AT aaoth DOT xyz> --- --- personal xmonad config. based heavily on distrotube's config. --- i've added some stuff and toki pona fonts --- ----------------------------------------------------------------------- - -module Main where - -import System.Directory -import System.IO (hPutStrLn) -import System.Exit (exitSuccess) - -import Data.Char (isSpace, toUpper) -import Data.Maybe (fromJust, isJust) -import Data.Monoid -import Data.Tree -import Data.List import qualified Data.Map as M +import System.Exit import XMonad import qualified XMonad.StackSet as W -import XMonad.Actions.CopyWindow (kill1) -import XMonad.Actions.CycleWS ( Direction1D(..) - , moveTo - , shiftTo - , WSType(..) - , nextScreen - , prevScreen - ) import XMonad.Actions.GridSelect -import XMonad.Actions.MouseResize -import XMonad.Actions.Promote -import XMonad.Actions.RotSlaves (rotSlavesDown, rotAllDown) -import XMonad.Actions.WindowGo (runOrRaise) -import XMonad.Actions.WithAll (sinkAll, killAll) -import qualified XMonad.Actions.Search as S +import XMonad.Actions.WithAll -import XMonad.Hooks.DynamicLog +import XMonad.Hooks.DynamicLog import XMonad.Hooks.EwmhDesktops -import XMonad.Hooks.ManageDocks ( avoidStruts - , docks - , manageDocks - , ToggleStruts(..)) -import XMonad.Hooks.ManageHelpers (isFullscreen, doFullFloat) -import XMonad.Hooks.ServerMode -import XMonad.Hooks.SetWMName -import XMonad.Hooks.StatusBar.PP (filterOutWsPP) -import XMonad.Hooks.WorkspaceHistory +import XMonad.Hooks.StatusBar +import XMonad.Hooks.StatusBar.PP -import XMonad.Layout.SimplestFloat -import XMonad.Layout.ResizableTile -import XMonad.Layout.Tabbed -import XMonad.Layout.ThreeColumns -import XMonad.Layout.Accordion -import XMonad.Layout.LayoutModifier -import XMonad.Layout.LimitWindows (limitWindows, increaseLimit, decreaseLimit) -import XMonad.Layout.Magnifier -import XMonad.Layout.MultiToggle (mkToggle, single, EOT(EOT), (??)) -import XMonad.Layout.MultiToggle.Instances (StdTransformers( NBFULL - , MIRROR - , NOBORDERS - )) -import XMonad.Layout.NoBorders +import XMonad.Util.ClickableWorkspaces +import XMonad.Util.EZConfig +import XMonad.Util.NamedScratchpad + import XMonad.Layout.Renamed -import XMonad.Layout.ShowWName -import XMonad.Layout.Simplest import XMonad.Layout.Spacing -import XMonad.Layout.SubLayouts -import XMonad.Layout.WindowNavigation -import qualified XMonad.Layout.BoringWindows as BW -import XMonad.Layout.WindowArranger (windowArrange, WindowArrangerMsg(..)) -import qualified XMonad.Layout.ToggleLayouts as T ( toggleLayouts - , ToggleLayout(Toggle) - ) -import qualified XMonad.Layout.MultiToggle as MT (Toggle(..)) - -import XMonad.Util.Dmenu -import XMonad.Util.Loggers -import XMonad.Util.EZConfig (additionalKeysP) -import XMonad.Util.NamedScratchpad -import XMonad.Util.Run (runProcessWithInput, safeSpawn, spawnPipe) -import XMonad.Util.SpawnOnce -import XMonad.Util.WorkspaceCompare +import XMonad.Layout.ThreeColumns import LaNinpreConfig --- * misc functions --- --- | hides workspaces that have no windows -myHiddenNoWindows :: WorkspaceId -> String -myHiddenNoWindows = const "" +myKeys :: [(String, X ())] +myKeys = [ ("M-<Return>", spawn myTerminal) + , ("M-w", spawn myBrowser) + , ("M-p", spawn "dmenu_run") + , ("<Print>", spawn "scrot_cmd -f") + , ("C-<Print>", spawn "scrot_cmd -a") + , ("M1-<Print>", spawn "scrot_cmd -w") -mySuperscript :: Int -> String -mySuperscript n = map ss $ show n - where ss c | c == '0' = '⁰' - | c == '1' = '¹' - | c == '2' = '²' - | c == '3' = '³' - | c == '4' = '⁴' - | c == '5' = '⁵' - | c == '6' = '⁶' - | c == '7' = '⁷' - | c == '8' = '⁸' - | c == '9' = '⁹' - | otherwise = c + , ("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) --- | window count logger --- --- gets number of windows on current workspace -myWindowCountLogger :: Logger -myWindowCountLogger = gets $ Just . show . length . W.integrate' . W.stack - . W.workspace . W.current . windowset + , ("M-S-c", kill) + , ("M-<Space>", sendMessage NextLayout) + , ("M-h", sendMessage Shrink) + , ("M-l", sendMessage Expand) + , ("M-j", windows W.focusDown) + , ("M-k", windows W.focusUp) + , ("M-S-j", windows W.swapDown) + , ("M-S-k", windows W.swapUp) + , ("M-m", windows W.focusMaster) + , ("M-S-m", windows W.swapMaster) + , ("M-t", withFocused $ windows . W.sink) + , ("M-S-t", sinkAll) + , ("M-<Tab>", toggleWindowSpacingEnabled >> toggleScreenSpacingEnabled) --- * grid select --- --- $gridSelect --- --- this section provides theming of 'GridSelect' stuff. --- --- here, 'GridSelect' is used for following things: --- --- * spawning some frequently used programs --- --- * moving to desired window --- --- * bringing the desired window to the current workspace + , ("M-S-q", io (exitWith ExitSuccess)) + , ("M-S-r", spawn "xmonad --recompile && xmonad --restart") + ] + ++ + [("M-" ++ m ++ show k, windows $ f i) + | (i, k) <- zip (myWorkspaces) [1..9] + , (f, m) <- [(W.greedyView, ""), (W.shift, "S-")] + ] --- | custom colorizer for 'gridselect' --- --- essentially, it is just plain theme 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) --- | custom 'GSConfig' -myGridConfig :: GSConfig a -myGridConfig = (buildDefaultGSConfig myColorizer) - { gs_cellheight = 40 - , gs_cellwidth = 200 - , gs_cellpadding = 6 - , gs_originFractX = 0.5 - , gs_originFractY = 0.5 - , gs_bordercolor = col_bg_alt def - , gs_font = head myFonts - } +myGsConfig :: GSConfig a +myGsConfig = (buildDefaultGSConfig myColorizer) + { gs_font = head myFonts + , gs_bordercolor = col_bg_alt def + } --- | spawn selected programs with grid select --- --- it is esentially the same as 'spawnSelected' but allows to specify program aliases -mySpawnSelected :: [(String, String)] -> X () -mySpawnSelected lst = gridselect myGridConfig lst >>= flip whenJust spawn +mySpawnSelected :: GSConfig String -> [(String, String)] -> X () +mySpawnSelected conf lst = gridselect conf lst >>= flip whenJust spawn --- * layouts --- --- ** spacing raw helper functions --- --- $spacingHelpers --- --- these make calls to 'spacingRaw' simpler to write - --- | for many windows -mySpacing :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a -mySpacing i = spacingRaw False (Border i i i i) True (Border i i i i) True +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 + } where + sitelen = xmobarFont 3 --- | for fewer than two windows -mySpacing' :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a -mySpacing' i = spacingRaw True (Border i i i i) True (Border i i i i) True +mySB :: StatusBarConfig +mySB = statusBarProp "xmobar" + $ clickablePP $ filterOutWsPP [scratchpadWorkspaceTag] myXmobarPP --- ** actually layouts --- --- $layouts --- --- currently there are: --- --- * tall --- --- * floats --- --- * threeCol +myLayout = tiled ||| threeCol ||| full + where + tiled = renamed [Replace "lawa"] + $ spacingWithEdge space $ Tall nmaster delta ratio + threeCol = renamed [Replace "supa"] + $ spacingWithEdge space $ ThreeColMid nmaster delta ratio + full = renamed [Replace "suli"] $ Full + nmaster = 1 + ratio = 1/2 + delta = 3/100 + space = 4 -tall = renamed [Replace "tall"] - $ smartBorders - $ addTabs shrinkText myTabTheme - $ subLayout [] (smartBorders Simplest ||| Accordion) - $ limitWindows 12 - $ mySpacing 4 - $ ResizableTall 1 (5/100) (1/2) [] - -floats = renamed [Replace "floats"] - $ smartBorders - $ limitWindows 20 - simplestFloat - -threeCol = renamed [Replace "threeCol"] - $ smartBorders - $ addTabs shrinkText myTabTheme - $ subLayout [] (smartBorders Simplest ||| Accordion) - $ limitWindows 7 - $ mySpacing 4 - $ ThreeColMid 1 (3/100) (1/2) - --- | setting colors for tabs layout and tabs sublayout. -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 - } - --- ** layout hook - --- $layoutHook --- --- putting it all together with some stuff -myLayoutHook = avoidStruts - $ mouseResize - $ BW.boringWindows - $ windowNavigation - $ windowArrange - $ T.toggleLayouts floats - $ mkToggle (NBFULL ?? NOBORDERS ?? EOT) myDefaultLayout - where - myDefaultLayout = withBorder myBorderWidth tall - ||| withBorder myBorderWidth threeCol - --- * show wm name hook - --- | theme for showWName which prints current workspace --- when you change workspaces. -myShowWNameTheme :: SWNConfig -myShowWNameTheme = def - { swn_font = myFonts !! 1 - , swn_fade = 0.7 - , swn_bgcolor = col_bg def - , swn_color = col_fg def - } - --- * workspaces --- --- $workspaces --- --- here are some helper functions to deal with workspaces. --- --- actual workspace list is in "LaNinpreConfig". - --- | workspace indices to use with hotkeys -myWorkspaceIndices = M.fromList $ zip myWorkspaces [1..] - --- ** clickable workspace wrapper --- --- $clickable --- --- normal variant --- --- > clickable ws = "<action=xdotool key super+"++show i++">"++ws++"</action>" --- > where i = fromJust $ M.lookup ws myWorkspaceIndices - --- | provides option to click workspaces to switch to them. --- this is handled by @UnsafeStdinReader@ in xmobar config. -clickable ws = "<fn=3><action=xdotool key super+"++show i++">"++ws++"</action></fn>" - where i = fromJust $ M.lookup ws myWorkspaceIndices - --- * keybindings - --- | keybindings list --- --- there's no way to document it using haddock, i guess... -myKeys :: [(String, X ())] -myKeys = - [ ("M-C-r", spawn "xmonad --recompile") -- Recompiles xmonad - , ("M-S-r", spawn "xmonad --restart") -- Restarts xmonad - , ("M-S-q", io exitSuccess) -- Quits xmonad - - -- Run Prompt - , ("M-p", spawn "dmenu_run -i -p \"Run: \"") -- Dmenu - - -- Useful programs to have a keybinding for launch - , ("M-<Return>", spawn myTerminal) - , ("M-e", spawn myFileMgr) - , ("M-w", spawn myBrowser) - , ("M-i", spawn (myTerminal - ++ " --class alacritty,amfora -e " - ++ myGeminiClient)) - , ("M-S-e", spawn "emacsclient -c") - -- Kill windows - , ("M-S-c", kill1) -- Kill the currently focused client - , ("M-S-a", killAll) -- Kill all windows on current workspace - - -- Workspaces - , ("M-.", nextScreen) -- Switch focus to next monitor - , ("M-,", prevScreen) -- Switch focus to prev monitor - -- Shifts focused window to next ws - , ("M-S-<KP_Add>", shiftTo Next nonNSP >> moveTo Next nonNSP) - -- Shifts focused window to prev ws - , ("M-S-<KP_Subtract>", shiftTo Prev nonNSP >> moveTo Prev nonNSP) - - -- Floating windows - , ("M-f", sendMessage (T.Toggle "floats")) -- Toggles my 'floats' layout - , ("M-t", withFocused $ windows . W.sink) -- Push floating window back to tile - , ("M-S-t", sinkAll) -- Push ALL floating windows to tile - - -- Increase/decrease spacing (gaps) - , ("C-M1-j", decWindowSpacing 4) -- Decrease window spacing - , ("C-M1-k", incWindowSpacing 4) -- Increase window spacing - , ("C-M1-h", decScreenSpacing 4) -- Decrease screen spacing - , ("C-M1-l", incScreenSpacing 4) -- Increase screen spacing - - -- Grid Select (MOD-g followed by a key) - , ("M-g g", mySpawnSelected myAppGrid) -- grid select favorite apps - , ("M-g t", goToSelected myGridConfig) -- goto selected window - , ("M-g b", bringSelected myGridConfig) -- bring selected window - - -- Windows navigation - , ("M-m", windows W.focusMaster) -- Move focus to the master window - , ("M-j", BW.focusDown) -- Move focus to the next window - , ("M1-<Tab>", BW.focusDown) -- legacy keybinding - , ("M-k", BW.focusUp) -- Move focus to the prev window - , ("M-S-m", windows W.swapMaster) -- Swap the focused window and the master window - , ("M-S-j", windows W.swapDown) -- Swap focused window with next window - , ("M-S-k", windows W.swapUp) -- Swap focused window with prev window - , ("M-<Backspace>", promote) -- Moves focused window to master, others maintain order - , ("M-S-<Tab>", rotSlavesDown) -- Rotate all windows except master and keep focus in place - , ("M-C-<Tab>", rotAllDown) -- Rotate all the windows in the current stack - - -- Layouts - , ("M-<Tab>", sendMessage NextLayout) -- Switch to next layout - , ("M-b", sendMessage (MT.Toggle NBFULL)) - , ("M-<Space>", sendMessage (MT.Toggle NBFULL) >> sendMessage ToggleStruts) -- Toggles noborder/full - - -- Increase/decrease windows in the master pane or the stack - , ("M-S-<Up>", sendMessage (IncMasterN 1)) -- Increase # of clients master pane - , ("M-S-<Down>", sendMessage (IncMasterN (-1))) -- Decrease # of clients master pane - , ("M-C-<Up>", increaseLimit) -- Increase # of windows - , ("M-C-<Down>", decreaseLimit) -- Decrease # of windows - - -- Window resizing - , ("M-h", sendMessage Shrink) -- Shrink horiz window width - , ("M-l", sendMessage Expand) -- Expand horiz window width - , ("M-M1-j", sendMessage MirrorShrink) -- Shrink vert window width - , ("M-M1-k", sendMessage MirrorExpand) -- Expand vert window width - - -- Sublayouts - -- This is used to push windows to tabbed sublayouts, or pull them out of it. - , ("M-C-h", sendMessage $ pullGroup L) - , ("M-C-l", sendMessage $ pullGroup R) - , ("M-C-k", sendMessage $ pullGroup U) - , ("M-C-j", sendMessage $ pullGroup D) - , ("M-C-m", withFocused (sendMessage . MergeAll)) - , ("M-C-u", withFocused (sendMessage . UnMerge)) - , ("M-C-/", withFocused (sendMessage . UnMergeAll)) - , ("M-C-<Space>", toSubl NextLayout) - , ("M-C-.", onGroup W.focusUp') -- Switch focus to next tab - , ("M-C-,", onGroup W.focusDown') -- Switch focus to prev tab - - -- Scratchpads - -- Toggle show/hide these programs. They run on a hidden workspace. - -- When you toggle them to show, it brings them to your current workspace. - -- Toggle them to hide and it sends them back to hidden workspace (NSP). - , ("M-s t", namedScratchpadAction myScratchPads "terminal") - , ("M-s m", namedScratchpadAction myScratchPads "mocp") - , ("M-s c", namedScratchpadAction myScratchPads "calculator") - , ("M-s v", namedScratchpadAction myScratchPads "mpvfloat" ) - - -- Set wallpaper with 'feh'. Type 'SUPER+F1' to launch sxiv in the wallpapers directory. - -- Then in sxiv, type 'C-x w' to set the wallpaper that you choose. - , ("M-<F1>", spawn "sxiv -r -q -t -o ~/Pictures/wallpapers/*") - , ("M-<F2>", spawn "/bin/ls ~/Pictures/wallpapers | shuf -n 1 \ - \| xargs xwallpaper --stretch") - - -- pana e nimi sewi - , ("M-<F7>", spawn "nimi_sewi") - - -- Controls for mocp music player (SUPER-u followed by a key) - , ("M-u p", spawn (myMocp ++ " --play")) - , ("M-u l", spawn (myMocp ++ " --next")) - , ("M-u h", spawn (myMocp ++ " --previous")) - , ("M-u <Space>", spawn (myMocp ++ " --toggle-pause")) - - -- screenshots - , ("<Print>", spawn "scrot_cmd -f") - , ("C-<Print>", spawn "scrot_cmd -a") - , ("M1-<Print>", spawn "scrot_cmd -w") - - -- Multimedia Keys - , ("<XF86AudioPlay>", spawn (myMocp ++ " --toggle-pause")) - , ("<XF86AudioPrev>", spawn (myMocp ++ " --previous")) - , ("<XF86AudioNext>", spawn (myMocp ++ " --next")) - , ("<XF86AudioMute>", spawn (myMocp ++ " -v 0")) - , ("<XF86AudioLowerVolume>", spawn (myMocp ++ " -v -5")) - , ("<XF86AudioRaiseVolume>", spawn (myMocp ++ " -v +5")) - , ("<XF86HomePage>", spawn "firefox https://aaoth.xyz") - , ("<XF86Mail>", runOrRaise "thunderbird" (resource =? "thunderbird")) - , ("<XF86Calculator>", namedScratchpadAction myScratchPads "calculator") - , ("<XF86Sleep>", spawn "dm-logout") - ] - -- the following lines are needed for named scratchpads. - where nonNSP = WSIs (return (\ws -> W.tag ws /= "NSP")) - nonEmptyNonNSP = WSIs (return (\ws -> isJust (W.stack ws) - && W.tag ws /= "NSP")) - +myConfig = def + { terminal = myTerminal + , modMask = myModMask + , layoutHook = myLayout + , manageHook = myManageHook <+> namedScratchpadManageHook myScratchPads + , workspaces = myWorkspaces + , borderWidth = myBorderWidth + , keys = const M.empty -- discard default keybindings + , normalBorderColor = col_bg def + , focusedBorderColor = col_bg_alt def + } `additionalKeysP` myKeys main :: IO () -main = do - xmproc <- spawnPipe "xmobar ~/.config/xmonad/xmobar/xmobarrc" - -- the xmonad, ya know...what the wm is named after! - xmonad $ docks . ewmh $ def - { manageHook = myManageHook <+> manageDocks - --, handleEventHook = docksEventHook - , modMask = myModMask - , terminal = myTerminal - , startupHook = myStartupHook - , layoutHook = showWName' myShowWNameTheme myLayoutHook - , workspaces = myWorkspaces - , borderWidth = myBorderWidth - , normalBorderColor = myNormColor - , focusedBorderColor = myFocusColor - , logHook = dynamicLogWithPP - $ filterOutWsPP ["NSP"] - $ xmobarPP - { ppOutput = hPutStrLn xmproc - , ppCurrent = xmobarColor (col_fg_alt def) "" - . wrap "<fn=3>" "</fn>" -- toki pona - . wrap "[" "]" - -- . wrap " " " " -- normal - , ppVisible = xmobarColor (col_fg_alt def) "" . clickable - , ppHidden = xmobarColor (col_fg def) "" - . wrap "" "'" - . clickable - , ppHiddenNoWindows = xmobarColor (col_bg_alt def) "" . clickable - --, ppHiddenNoWindows = myHiddenNoWindows - , ppTitle = xmobarColor (col_fg def) "" . shorten 60 - , ppSep = xmobarColor (col_bg_alt def) "" " | " - , ppWsSep = " " - , ppUrgent = xmobarColor (col_fg_alt def) "" . wrap "!" "!" - , ppExtras = [myWindowCountLogger] - , ppOrder = \(ws:l:t:ex) -> [ws,l]++ex++[t] - } - } `additionalKeysP` myKeys - +main = xmonad + . ewmhFullscreen + . ewmh + . withEasySB mySB defToggleStrutsKey + $ myConfig