all repos — xmonad-config @ 3da3ace194a06ff8867257a38e57decb8a12358a

personal xmonad config

xmonad.hs (view raw)

  1{-# OPTIONS_HADDOCK prune #-}
  2
  3----------------------------------------------------------------------
  4-- |
  5-- Description  :   la-ninpre xmonad config
  6-- Maintainer   :   la-ninpre
  7-- License      :   ISC
  8-- Copyright    :   la-ninpre <aaoth AT aaoth DOT xyz>
  9--
 10-- personal xmonad config. based heavily on distrotube's config.
 11-- i've added some stuff and toki pona fonts
 12--
 13----------------------------------------------------------------------
 14
 15module Main where
 16
 17import System.Directory
 18import System.IO (hPutStrLn)
 19import System.Exit (exitSuccess)
 20
 21import Data.Char (isSpace, toUpper)
 22import Data.Maybe (fromJust, isJust)
 23import Data.Monoid
 24import Data.Tree
 25import Data.List
 26import qualified Data.Map as M
 27
 28import XMonad
 29import qualified XMonad.StackSet as W
 30
 31import XMonad.Actions.CopyWindow (kill1)
 32import XMonad.Actions.CycleWS ( Direction1D(..)
 33                              , moveTo
 34                              , shiftTo
 35                              , WSType(..)
 36                              , nextScreen
 37                              , prevScreen
 38                              )
 39import XMonad.Actions.GridSelect
 40import XMonad.Actions.MouseResize
 41import XMonad.Actions.Promote
 42import XMonad.Actions.RotSlaves (rotSlavesDown, rotAllDown)
 43import XMonad.Actions.WindowGo (runOrRaise)
 44import XMonad.Actions.WithAll (sinkAll, killAll)
 45import qualified XMonad.Actions.Search as S
 46
 47import XMonad.Hooks.DynamicLog 
 48import XMonad.Hooks.EwmhDesktops
 49import XMonad.Hooks.ManageDocks ( avoidStruts
 50                                , docksEventHook
 51                                , manageDocks
 52                                , ToggleStruts(..))
 53import XMonad.Hooks.ManageHelpers (isFullscreen, doFullFloat)
 54import XMonad.Hooks.ServerMode
 55import XMonad.Hooks.SetWMName
 56import XMonad.Hooks.WorkspaceHistory
 57
 58import XMonad.Layout.SimplestFloat
 59import XMonad.Layout.ResizableTile
 60import XMonad.Layout.Tabbed
 61import XMonad.Layout.ThreeColumns
 62import XMonad.Layout.Accordion
 63import XMonad.Layout.LayoutModifier
 64import XMonad.Layout.LimitWindows (limitWindows, increaseLimit, decreaseLimit)
 65import XMonad.Layout.Magnifier
 66import XMonad.Layout.MultiToggle (mkToggle, single, EOT(EOT), (??))
 67import XMonad.Layout.MultiToggle.Instances (StdTransformers( NBFULL
 68                                                           , MIRROR
 69                                                           , NOBORDERS
 70                                                           ))
 71import XMonad.Layout.NoBorders
 72import XMonad.Layout.Renamed
 73import XMonad.Layout.ShowWName
 74import XMonad.Layout.Simplest
 75import XMonad.Layout.Spacing
 76import XMonad.Layout.SubLayouts
 77import XMonad.Layout.WindowNavigation
 78import qualified XMonad.Layout.BoringWindows as BW
 79import XMonad.Layout.WindowArranger (windowArrange, WindowArrangerMsg(..))
 80import qualified XMonad.Layout.ToggleLayouts as T ( toggleLayouts
 81                                                  , ToggleLayout(Toggle)
 82                                                  )
 83import qualified XMonad.Layout.MultiToggle as MT (Toggle(..))
 84
 85import XMonad.Util.Dmenu
 86import XMonad.Util.Loggers
 87import XMonad.Util.EZConfig (additionalKeysP)
 88import XMonad.Util.NamedScratchpad
 89import XMonad.Util.Run (runProcessWithInput, safeSpawn, spawnPipe)
 90import XMonad.Util.SpawnOnce
 91import XMonad.Util.WorkspaceCompare
 92
 93import LaNinpreConfig
 94
 95-- * misc functions
 96--
 97-- | hides workspaces that have no windows
 98myHiddenNoWindows :: WorkspaceId -> String
 99myHiddenNoWindows = const ""
100
101mySuperscript :: Int -> String
102mySuperscript n = map ss $ show n
103                where ss c | c == '0' = '⁰'
104                           | c == '1' = '¹'
105                           | c == '2' = '²'
106                           | c == '3' = '³'
107                           | c == '4' = '⁴'
108                           | c == '5' = '⁵'
109                           | c == '6' = '⁶'
110                           | c == '7' = '⁷'
111                           | c == '8' = '⁸'
112                           | c == '9' = '⁹'
113                           | otherwise = c
114
115
116-- | window count logger
117-- 
118--   gets number of windows on current workspace
119myWindowCountLogger :: Logger
120myWindowCountLogger = gets $ Just . show . length . W.integrate' . W.stack
121                           . W.workspace . W.current . windowset
122
123-- * grid select
124--
125-- $gridSelect
126--
127-- this section provides theming of 'GridSelect' stuff.
128--
129-- here, 'GridSelect' is used for following things:
130--
131--      * spawning some frequently used programs
132--
133--      * moving to desired window
134--
135--      * bringing the desired window to the current workspace
136
137-- | custom colorizer for 'gridselect'
138--
139-- essentially, it is just plain theme
140myColorizer :: a -> Bool -> X (String, String)
141myColorizer _ active = if active then return (col_bg_alt def, col_fg_alt def)
142                                 else return (col_bg     def, col_fg     def)
143
144-- | custom 'GSConfig'
145myGridConfig :: GSConfig a
146myGridConfig = (buildDefaultGSConfig myColorizer)
147    { gs_cellheight   = 40
148    , gs_cellwidth    = 200
149    , gs_cellpadding  = 6
150    , gs_originFractX = 0.5
151    , gs_originFractY = 0.5
152    , gs_bordercolor  = col_bg_alt def
153    , gs_font         = head myFonts
154    }
155
156-- | spawn selected programs with grid select
157--
158-- it is esentially the same as 'spawnSelected' but allows to specify program aliases
159mySpawnSelected :: [(String, String)] -> X ()
160mySpawnSelected lst = gridselect myGridConfig lst >>= flip whenJust spawn
161
162-- * layouts
163--
164-- ** spacing raw helper functions
165--
166-- $spacingHelpers
167--
168-- these make calls to 'spacingRaw' simpler to write
169
170-- | for many windows
171mySpacing :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
172mySpacing i = spacingRaw False (Border i i i i) True (Border i i i i) True
173
174-- | for fewer than two windows
175mySpacing' :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
176mySpacing' i = spacingRaw True (Border i i i i) True (Border i i i i) True
177
178-- ** actually layouts
179--
180-- $layouts
181--
182-- currently there are:
183--
184--      *   tall
185--
186--      *   floats
187--
188--      *   threeCol
189
190tall     = renamed [Replace "tall"]
191           $ smartBorders
192           $ addTabs shrinkText myTabTheme
193           $ subLayout [] (smartBorders Simplest ||| Accordion)
194           $ limitWindows 12
195           $ mySpacing 4
196           $ ResizableTall 1 (5/100) (1/2) []
197
198floats   = renamed [Replace "floats"]
199           $ smartBorders
200           $ limitWindows 20
201             simplestFloat
202
203threeCol = renamed [Replace "threeCol"]
204           $ smartBorders
205           $ addTabs shrinkText myTabTheme
206           $ subLayout [] (smartBorders Simplest ||| Accordion)
207           $ limitWindows 7
208           $ mySpacing 4
209           $ ThreeColMid 1 (3/100) (1/2)
210
211-- | setting colors for tabs layout and tabs sublayout.
212myTabTheme :: Theme
213myTabTheme = def { fontName            = head myFonts
214                 , activeTextColor     = col_fg_alt def
215                 , activeColor         = col_bg_alt def
216                 , activeBorderWidth   = 0
217                 , inactiveTextColor   = col_fg def
218                 , inactiveColor       = col_bg def
219                 , inactiveBorderWidth = 0
220                 , urgentTextColor     = col_bg_alt def
221                 , urgentColor         = col_fg_alt def
222                 , urgentBorderWidth   = 0
223                 }
224
225-- ** layout hook
226
227-- $layoutHook
228--
229-- putting it all together with some stuff
230myLayoutHook = avoidStruts
231               $ mouseResize
232               $ BW.boringWindows
233               $ windowNavigation
234               $ windowArrange
235               $ T.toggleLayouts floats
236               $ mkToggle (NBFULL ?? NOBORDERS ?? EOT) myDefaultLayout
237               where
238               myDefaultLayout = withBorder myBorderWidth tall
239                                 ||| withBorder myBorderWidth threeCol
240
241-- * show wm name hook
242
243-- | theme for showWName which prints current workspace
244--   when you change workspaces.
245myShowWNameTheme :: SWNConfig
246myShowWNameTheme = def
247    { swn_font    = myFonts !! 1
248    , swn_fade    = 0.7
249    , swn_bgcolor = col_bg def
250    , swn_color   = col_fg def
251    }
252
253-- * workspaces
254--
255-- $workspaces
256--
257-- here are some helper functions to deal with workspaces.
258--
259-- actual workspace list is in "LaNinpreConfig".
260
261-- | workspace indices to use with hotkeys
262myWorkspaceIndices = M.fromList $ zip myWorkspaces [1..]
263
264-- ** clickable workspace wrapper
265--
266-- $clickable
267--
268-- normal variant
269--
270-- > clickable ws = "<action=xdotool key super+"++show i++">"++ws++"</action>"
271-- >     where i = fromJust $ M.lookup ws myWorkspaceIndices
272
273-- | provides option to click workspaces to switch to them.
274--   this is handled by @UnsafeStdinReader@ in xmobar config.
275clickable ws = "<fn=3><action=xdotool key super+"++show i++">"++ws++"</action></fn>"
276    where i = fromJust $ M.lookup ws myWorkspaceIndices
277
278-- * keybindings
279
280-- | keybindings list
281--
282--   there's no way to document it using haddock, i guess...
283myKeys :: [(String, X ())]
284myKeys =
285        [ ("M-C-r", spawn "xmonad --recompile") -- Recompiles xmonad
286        , ("M-S-r", spawn "xmonad --restart")   -- Restarts xmonad
287        , ("M-S-q", io exitSuccess)             -- Quits xmonad
288
289    -- Run Prompt
290        , ("M-r", spawn "dmenu_run -i -p \"Run: \"") -- Dmenu
291
292    -- Other Dmenu Prompts
293    -- In Xmonad and many tiling window managers, M-p is the default keybinding to
294    -- launch dmenu_run, so I've decided to use M-p plus KEY for these dmenu scripts.
295        , ("M-p p", spawn "passmenu")     -- passmenu
296        , ("M-p c", spawn "dm-colpick")   -- pick color from our scheme
297        , ("M-p e", spawn "dm-confedit")  -- edit config files
298        , ("M-p i", spawn "dm-maim")      -- screenshots (images)
299        , ("M-p k", spawn "dm-kill")      -- kill processes
300        , ("M-p m", spawn "dm-man")       -- manpages
301        , ("M-p q", spawn "dm-logout")    -- logout menu
302        , ("M-p s", spawn "dm-websearch") -- search various search engines
303        , ("M-p h", spawn "dm-hub")       -- hub of all scripts to choose one
304
305    -- Useful programs to have a keybinding for launch
306        , ("M-<Return>", spawn myTerminal)
307        , ("M-e", spawn myFileMgr)
308        , ("M-w", spawn myBrowser)
309        , ("M-i", spawn (myTerminal
310                         ++ " --class alacritty,amfora -e "
311                         ++ myGeminiClient))
312        , ("M-S-e", spawn "emacsclient -c")
313    -- Kill windows
314        , ("M-S-c", kill1)    -- Kill the currently focused client
315        , ("M-S-a", killAll)  -- Kill all windows on current workspace
316
317    -- Workspaces
318        , ("M-.", nextScreen) -- Switch focus to next monitor
319        , ("M-,", prevScreen) -- Switch focus to prev monitor
320        -- Shifts focused window to next ws
321        , ("M-S-<KP_Add>", shiftTo Next nonNSP >> moveTo Next nonNSP)
322        -- Shifts focused window to prev ws
323        , ("M-S-<KP_Subtract>", shiftTo Prev nonNSP >> moveTo Prev nonNSP)
324
325    -- Floating windows
326        , ("M-f", sendMessage (T.Toggle "floats")) -- Toggles my 'floats' layout
327        , ("M-t", withFocused $ windows . W.sink)  -- Push floating window back to tile
328        , ("M-S-t", sinkAll)                       -- Push ALL floating windows to tile
329
330    -- Increase/decrease spacing (gaps)
331        , ("C-M1-j", decWindowSpacing 4) -- Decrease window spacing
332        , ("C-M1-k", incWindowSpacing 4) -- Increase window spacing
333        , ("C-M1-h", decScreenSpacing 4) -- Decrease screen spacing
334        , ("C-M1-l", incScreenSpacing 4) -- Increase screen spacing
335
336    -- Grid Select (MOD-g followed by a key)
337        , ("M-g g", mySpawnSelected myAppGrid)  -- grid select favorite apps
338        , ("M-g t", goToSelected myGridConfig)  -- goto selected window
339        , ("M-g b", bringSelected myGridConfig) -- bring selected window
340
341    -- Windows navigation
342        , ("M-m", windows W.focusMaster)  -- Move focus to the master window
343        , ("M-j", BW.focusDown)           -- Move focus to the next window
344        , ("M1-<Tab>", BW.focusDown)      -- legacy keybinding
345        , ("M-k", BW.focusUp)             -- Move focus to the prev window
346        , ("M-S-m", windows W.swapMaster) -- Swap the focused window and the master window
347        , ("M-S-j", windows W.swapDown)   -- Swap focused window with next window
348        , ("M-S-k", windows W.swapUp)     -- Swap focused window with prev window
349        , ("M-<Backspace>", promote)      -- Moves focused window to master, others maintain order
350        , ("M-S-<Tab>", rotSlavesDown)    -- Rotate all windows except master and keep focus in place
351        , ("M-C-<Tab>", rotAllDown)       -- Rotate all the windows in the current stack
352
353    -- Layouts
354        , ("M-<Tab>", sendMessage NextLayout)           -- Switch to next layout
355        , ("M-b", sendMessage (MT.Toggle NBFULL))
356        , ("M-<Space>", sendMessage (MT.Toggle NBFULL) >> sendMessage ToggleStruts) -- Toggles noborder/full
357
358    -- Increase/decrease windows in the master pane or the stack
359        , ("M-S-<Up>", sendMessage (IncMasterN 1))      -- Increase # of clients master pane
360        , ("M-S-<Down>", sendMessage (IncMasterN (-1))) -- Decrease # of clients master pane
361        , ("M-C-<Up>", increaseLimit)                   -- Increase # of windows
362        , ("M-C-<Down>", decreaseLimit)                 -- Decrease # of windows
363
364    -- Window resizing
365        , ("M-h", sendMessage Shrink)                   -- Shrink horiz window width
366        , ("M-l", sendMessage Expand)                   -- Expand horiz window width
367        , ("M-M1-j", sendMessage MirrorShrink)          -- Shrink vert window width
368        , ("M-M1-k", sendMessage MirrorExpand)          -- Expand vert window width
369
370    -- Sublayouts
371    -- This is used to push windows to tabbed sublayouts, or pull them out of it.
372        , ("M-C-h", sendMessage $ pullGroup L)
373        , ("M-C-l", sendMessage $ pullGroup R)
374        , ("M-C-k", sendMessage $ pullGroup U)
375        , ("M-C-j", sendMessage $ pullGroup D)
376        , ("M-C-m", withFocused (sendMessage . MergeAll))
377        , ("M-C-u", withFocused (sendMessage . UnMerge))
378        , ("M-C-/", withFocused (sendMessage . UnMergeAll))
379        , ("M-C-<Space>", toSubl NextLayout)
380        , ("M-C-.", onGroup W.focusUp')   -- Switch focus to next tab
381        , ("M-C-,", onGroup W.focusDown') -- Switch focus to prev tab
382
383    -- Scratchpads
384    -- Toggle show/hide these programs.  They run on a hidden workspace.
385    -- When you toggle them to show, it brings them to your current workspace.
386    -- Toggle them to hide and it sends them back to hidden workspace (NSP).
387        , ("M-s t", namedScratchpadAction myScratchPads "terminal")
388        , ("M-s m", namedScratchpadAction myScratchPads "mocp")
389        , ("M-s c", namedScratchpadAction myScratchPads "calculator")
390        , ("M-s v", namedScratchpadAction myScratchPads "mpvfloat" )
391
392    -- Set wallpaper with 'feh'. Type 'SUPER+F1' to launch sxiv in the wallpapers directory.
393    -- Then in sxiv, type 'C-x w' to set the wallpaper that you choose.
394        , ("M-<F1>", spawn "sxiv -r -q -t -o ~/Pictures/wallpapers/*")
395        , ("M-<F2>", spawn "/bin/ls ~/Pictures/wallpapers | shuf -n 1 \
396            \| xargs xwallpaper --stretch")
397
398    -- pana e nimi sewi
399         , ("M-<F7>", spawn "nimi_sewi")
400
401    -- Controls for mocp music player (SUPER-u followed by a key)
402        , ("M-u p", spawn (myMocp ++ " --play"))
403        , ("M-u l", spawn (myMocp ++ " --next"))
404        , ("M-u h", spawn (myMocp ++ " --previous"))
405        , ("M-u <Space>", spawn (myMocp ++ " --toggle-pause"))
406
407    -- Multimedia Keys
408        , ("<XF86AudioPlay>", spawn (myMocp ++ " --toggle-pause"))
409        , ("<XF86AudioPrev>", spawn (myMocp ++ " --previous"))
410        , ("<XF86AudioNext>", spawn (myMocp ++ " --next"))
411        , ("<XF86AudioMute>", spawn (myMocp ++ " -v 0"))
412        , ("<XF86AudioLowerVolume>", spawn (myMocp ++ " -v -5"))
413        , ("<XF86AudioRaiseVolume>", spawn (myMocp ++ " -v +5"))
414        , ("<XF86HomePage>", spawn "firefox https://aaoth.xyz")
415        , ("<XF86Mail>", runOrRaise "thunderbird" (resource =? "thunderbird"))
416        , ("<XF86Calculator>", namedScratchpadAction myScratchPads "calculator")
417        , ("<XF86Sleep>", spawn "dm-logout")
418        ]
419    -- the following lines are needed for named scratchpads.
420        where nonNSP          = WSIs (return (\ws -> W.tag ws /= "NSP"))
421              nonEmptyNonNSP  = WSIs (return (\ws -> isJust (W.stack ws)
422                                      && W.tag ws /= "NSP"))
423
424
425main :: IO ()
426main = do
427    xmproc <- spawnPipe "xmobar ~/.xmonad/xmobar/xmobarrc"
428    -- the xmonad, ya know...what the wm is named after!
429    xmonad $ ewmh def
430        { manageHook         = myManageHook <+> manageDocks
431        , handleEventHook    = docksEventHook
432        , modMask            = myModMask
433        , terminal           = myTerminal
434        , startupHook        = myStartupHook
435        , layoutHook         = showWName' myShowWNameTheme myLayoutHook
436        , workspaces         = myWorkspaces
437        , borderWidth        = myBorderWidth
438        , normalBorderColor  = myNormColor
439        , focusedBorderColor = myFocusColor
440        , logHook = dynamicLogWithPP
441                    $ namedScratchpadFilterOutWorkspacePP
442                    $ xmobarPP
443              { ppOutput  = hPutStrLn xmproc
444              , ppCurrent = xmobarColor (col_fg_alt def) ""
445                            . wrap "<fn=3>" "</fn>" -- toki pona
446                            . wrap "[" "]"
447                            -- . wrap " " " " -- normal
448              , ppVisible = xmobarColor (col_fg_alt def) "" . clickable
449              , ppHidden  = xmobarColor (col_fg def) ""
450                            . wrap "" "'"
451                            . clickable
452              , ppHiddenNoWindows = xmobarColor (col_bg_alt def) "" . clickable
453              --, ppHiddenNoWindows = myHiddenNoWindows
454              , ppTitle   = xmobarColor (col_fg def) "" . shorten 60
455              , ppSep     = xmobarColor (col_bg_alt def) "" " | "
456              , ppWsSep   = "  "
457              , ppUrgent  = xmobarColor (col_fg_alt def) "" . wrap "!" "!"
458              , ppExtras  = [myWindowCountLogger]
459              , ppOrder   = \(ws:l:t:ex) -> [ws,l]++ex++[t]
460              }
461        } `additionalKeysP` myKeys
462