all repos — xmonad-config @ e00093fb569b5b66f657228e9bcdc463b727bd4b

personal xmonad config

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