all repos — xmonad-config @ e99ef8a9fb81980c2e487d445de4e6c53754299c

personal xmonad config

lib/XMonad/Config/LaNinpre.hs (view raw)

  1----------------------------------------------------------------------
  2-- |
  3-- Module       :   XMonad.Config.LaNinpre
  4-- Description  :   xmonad config of la ninpre
  5-- Maintainer   :   la-ninpre
  6-- License      :   ISC
  7-- Copyright    :   la-ninpre <aaoth AT aaoth DOT xyz>
  8--
  9----------------------------------------------------------------------
 10
 11module XMonad.Config.LaNinpre where
 12
 13import Data.List(intercalate)
 14import System.Exit
 15
 16import XMonad
 17import qualified XMonad.StackSet as W
 18
 19import XMonad.Actions.GridSelect
 20import XMonad.Actions.WithAll(sinkAll)
 21
 22import XMonad.Hooks.EwmhDesktops
 23import XMonad.Hooks.ManageDocks
 24import XMonad.Hooks.ManageHelpers
 25import XMonad.Hooks.SetWMName
 26import XMonad.Hooks.StatusBar
 27import XMonad.Hooks.StatusBar.PP
 28
 29import XMonad.Layout.BoringWindows hiding (Replace)
 30import XMonad.Layout.NoBorders
 31import XMonad.Layout.Renamed
 32import XMonad.Layout.ResizableThreeColumns
 33import XMonad.Layout.ResizableTile
 34import XMonad.Layout.Simplest
 35import XMonad.Layout.Spacing
 36import XMonad.Layout.SubLayouts
 37import XMonad.Layout.Tabbed
 38import XMonad.Layout.ToggleLayouts
 39import XMonad.Layout.WindowNavigation
 40
 41import XMonad.Util.ClickableWorkspaces
 42import XMonad.Util.EZConfig
 43import XMonad.Util.NamedScratchpad
 44import XMonad.Util.SpawnOnce
 45
 46-- * fonts
 47-- 
 48-- $fonts
 49--
 50-- default font and helper for fonts.
 51
 52-- | default font
 53fontDef :: String
 54fontDef = fontXft "Lato" "regular" 14
 55
 56-- | font constructor
 57--
 58-- it is just a helper function to simplify the process of specifying font
 59-- with xft.
 60fontXft :: String   -- ^ font family
 61        -> String   -- ^ font style
 62        -> Int      -- ^ font size
 63        -> String
 64fontXft font style size = intercalate ":" [ "xft"
 65                                , font
 66                                , style
 67                                , "size=" ++ show size
 68                                , "antialias=true"
 69                                , "hinting=true"
 70                                ]
 71
 72-- * colors
 73--
 74-- $colors
 75--
 76-- color theme and stuff
 77
 78-- | default color theme
 79colorTheme :: ColorTheme
 80colorTheme = ColorTheme "#111111" "#ccbbcc" "#223333" "#ffaaaa"
 81
 82-- | color theme datatype
 83--
 84-- 'Default' instance gives simple four-color colorscheme
 85data ColorTheme = ColorTheme {
 86  col_bg     :: String,
 87  col_fg     :: String,
 88  col_bg_alt :: String,
 89  col_fg_alt :: String
 90}
 91
 92instance Default ColorTheme where
 93    def = colorTheme
 94
 95
 96-- * software
 97--
 98-- $software
 99--
100-- these are just contstants
101
102-- | set terminal emulator
103terminalEmulator :: String
104terminalEmulator = "alacritty"
105
106-- | set web browser
107webBrowser :: String
108webBrowser = "firefox"
109
110-- | set gemini client
111geminiBrowser :: String
112geminiBrowser = "lagrange"
113
114-- | set file manager
115fileManager :: String
116fileManager = "thunar"
117
118-- | music on console
119--
120-- this is to avoid spamming strings everywhere. @moc@ doesn't comply with
121-- XDG_CONFIG_HOME, so we force it to do so.
122mocpString :: String
123mocpString = "mocp -M '~/.config/moc'"
124
125-- | set editor
126editor :: String
127editor = terminalEmulator ++ " -e vi"
128
129-- * manage hook
130--
131-- $managehook
132--
133-- send some windows here and there.
134
135-- | manage hook
136localManageHook :: ManageHook
137localManageHook = composeAll
138     [ className =? "confirm"         --> doFloat
139     , className =? "file_progress"   --> doFloat
140     , className =? "dialog"          --> doFloat
141     , className =? "download"        --> doFloat
142     , className =? "error"           --> doFloat
143     , className =? "notification"    --> doFloat
144     , className =? "splash"          --> doFloat
145     , className =? "toolbar"         --> doFloat
146     , className =? "Image Lounge"    --> doFloat
147     -- web workspace
148     , title =? "Mozilla Firefox"     --> doShift ( workspacesTP !! 1 )
149     , className =? "Brave-browser"   --> doShift ( workspacesTP !! 1 )
150     , className =? "amfora"          --> doShift ( workspacesTP !! 1 )
151     , className =? "qutebrowser"     --> doShift ( workspacesTP !! 1 )
152     -- doc workspace
153     , className =? "Geary"           --> doShift ( workspacesTP !! 3 )
154     , className =? "libreoffice"     --> doShift ( workspacesTP !! 3 )
155     -- vm workspace
156     -- chat workspace
157     , className =? "discord"         --> doShift ( workspacesTP !! 5 )
158     , className =? "TelegramDesktop" --> doShift ( workspacesTP !! 5 )
159     , className =? "Element"         --> doShift ( workspacesTP !! 5 )
160     , className =? "Steam"           --> doShift ( workspacesTP !! 5 )
161     -- full workspace
162     , isFullscreen                   --> doShift ( workspacesTP !! 6 )
163     -- vid workspace
164     , className =? "Deadbeef"        --> doShift ( workspacesTP !! 7 )
165     , appName   =? "mpv"             --> doShift ( workspacesTP !! 7 )
166     , className =? "vlc"             --> doShift ( workspacesTP !! 7 )
167     -- gfx workspace
168     , className =? "Gimp"            --> doShift ( workspacesTP !! 8 )
169     , className =? "Blender"         --> doShift ( workspacesTP !! 8 )
170     , className =? "obs"             --> doShift ( workspacesTP !! 8 )
171     , isFullscreen -->  doFullFloat
172     ] <+> namedScratchpadManageHook scratchPads
173
174-- * scratchpads
175--
176-- $scratchpads
177--
178-- currently i have:
179--
180--     *   plain terminal scratchpad
181--
182--     *   music on console
183--     
184--     *   calculator (qalculate-gtk)
185--
186--     *   mpv instance that plays playlist in @~\/Video\/sp_playlist.m3u@
187
188-- | scratchpad list
189scratchPads :: [NamedScratchpad]
190scratchPads = [ NS "terminal" spawnTerm findTerm manageTerm
191              , NS "mocp" spawnMocp findMocp manageMocp
192              , NS "calculator" spawnCalc findCalc manageCalc
193              , NS "mpvfloat" spawnMpv findMpv manageMpv
194              ]
195  where
196    -- terminal
197    spawnTerm  = terminalEmulator ++ " -t scratchpad"
198    findTerm   = title =? "scratchpad"
199    manageTerm = customFloating $ W.RationalRect l t w h
200               where
201                 h = 0.9
202                 w = 0.9
203                 t = 0.95 - h
204                 l = 0.95 - w
205    -- music on console
206    spawnMocp  = terminalEmulator ++ " -t mocp -e " ++ mocpString
207    findMocp   = title =? "mocp"
208    manageMocp = customFloating $ W.RationalRect l t w h
209               where
210                 h = 0.9
211                 w = 0.9
212                 t = 0.95 - h
213                 l = 0.95 - w 
214    -- calculator
215    spawnCalc  = "qalculate-gtk"
216    findCalc   = className =? "Qalculate-gtk"
217    manageCalc = customFloating $ W.RationalRect l t w h
218               where
219                 h = 0.5
220                 w = 0.4
221                 t = 0.75 - h
222                 l = 0.70 - w
223    -- mpv scratchpad to watch some stuff listed in ~/Video/sp_playlist.m3u
224    spawnMpv  = "mpv --pause -x11-name mpv-sp ~/Video/sp_playlist.m3u"
225                ++ mpvGeometry mpvPercentage mpvPercentage
226    findMpv   = appName =? "mpv-sp"
227    manageMpv = customFloating $ W.RationalRect l t w h
228               where
229                 h = mpvPercentage
230                 w = mpvPercentage
231                 t = 0.03
232                 l = 0.996 - w
233    mpvPercentage = 1/4
234    mpvGeometry h w = " --geometry=" ++ show pw ++ "x" ++ show ph
235       where
236         pw = ceiling (1920 * w)
237         ph = ceiling (1080 * h)
238
239-- * workspaces
240--
241-- $workspaces
242--
243-- i've got two ways of specifying them. first one is pretty close to the
244-- original dt's config and second one is using linja pona font by jan same
245-- (check it out [here](http://musilili.net/linja-pona/)).
246
247-- | normal english workspace names
248workspacesNorm :: [String]
249workspacesNorm = [ "dev"
250                 , "www"
251                 , "term"
252                 , "doc"
253                 , "vm"
254                 , "chat"
255                 , "full"
256                 , "vid"
257                 , "misc"
258                 ]
259
260-- | toki pona workspace names
261--
262-- uses sitelen-pona font.
263workspacesTP :: [String]
264workspacesTP = [ "\xe661\xe921" -- sona nanpa
265               , "\xe63b"       -- musi
266               , "\xe649"       -- pali
267               , "\xe62a\xf105" -- lipu ale
268               , "\xe653\xf115" -- poki ilo
269               , "\xe66c"       -- toki
270               , "\xe62a\xf200" -- lipu suli
271               , "\xf010\xe915" -- sitelen tawa
272               , "\xf010\xf107" -- sitelen ante
273               ]
274
275-- * grid select
276--
277-- $gridselect
278--
279-- stuff for 'GridSelect'
280
281-- | app grid for 'GridSelect' layout
282appGrid :: [(String,String)]
283appGrid = [ ("files"     ,"thunar"     )
284          , ("mail"      ,"thunderbird")
285          , ("blender"   ,"blender-3.1")
286          , ("inkscape"  ,"inkscape"   )
287          , ("discord"   ,"discord"    )
288          , ("steam"     ,"steam"      )
289          , ("obs"       ,"obs"        )
290          , ("gimp"      ,"gimp"       )
291          , ("ardour"    ,"ardour6"    )
292          , ("kdenlive"  ,"kdenlive"   )
293          ]
294
295-- | uses colors from 'ColorTheme'
296boringColorizer :: a -> Bool -> X (String, String)
297boringColorizer _ active = if active
298                           then return (col_bg_alt def, col_fg_alt def)
299                           else return (col_bg     def, col_fg     def)
300
301-- | 'GridSelect' config
302gridSelectConfig :: GSConfig a
303gridSelectConfig = (buildDefaultGSConfig boringColorizer)
304           { gs_font        = fontDef
305           , gs_bordercolor = col_bg_alt def
306           }
307
308-- | allows to add aliases for commands unlike original 'spawnSelected'
309spawnSelected' :: GSConfig String -> [(String, String)] -> X ()
310spawnSelected' conf lst = gridselect conf lst >>= flip whenJust spawn
311
312-- * keybindings
313--
314-- $keybindings
315--
316-- list of keybindings. it supposed to override the default keybindings.
317
318-- | keybindings in 'EZConfig' format
319keybinds :: [(String, X ())]
320keybinds = [ ("M-<Return>", spawn terminalEmulator)
321           , ("M-w",        spawn webBrowser)
322           , ("M-p",        spawn "dmenu_run")
323           , ("M-<Delete>", spawn "slock")
324           , ("<Print>",    spawn "scrot_cmd -f")
325           , ("C-<Print>",  spawn "scrot_cmd -a")
326           , ("M1-<Print>", spawn "scrot_cmd -w")
327
328           , ("M-s t",      namedScratchpadAction scratchPads "terminal")
329           , ("M-s c",      namedScratchpadAction scratchPads "calculator")
330           , ("M-s m",      namedScratchpadAction scratchPads "mocp")
331           , ("M-s v",      namedScratchpadAction scratchPads "mpvfloat")
332
333           , ("M-g t",      goToSelected gridSelectConfig)
334           , ("M-g b",      bringSelected gridSelectConfig)
335           , ("M-g g",      spawnSelected' gridSelectConfig appGrid)
336
337           , ("M-S-c",      kill)
338           , ("M-<Space>",  sendMessage NextLayout)
339           , ("M-f",        sendMessage ToggleLayout >> sendMessage ToggleStruts)
340           , ("M-h",        sendMessage Shrink)
341           , ("M-l",        sendMessage Expand)
342           , ("M-C-j",      sendMessage MirrorShrink)
343           , ("M-C-k",      sendMessage MirrorExpand)
344           , ("M-M1-h",     sendMessage $ pullGroup L)
345           , ("M-M1-j",     sendMessage $ pullGroup D)
346           , ("M-M1-k",     sendMessage $ pullGroup U)
347           , ("M-M1-l",     sendMessage $ pullGroup R)
348           , ("M-M1-u",     withFocused $ sendMessage . UnMerge)
349           , ("M-M1-m",     withFocused $ sendMessage . UnMergeAll)
350           , ("M-M1-,",     onGroup W.focusDown')
351           , ("M-M1-.",     onGroup W.focusUp')
352           , ("M-j",        focusDown)
353           , ("M-k",        focusUp)
354           , ("M-S-j",      swapDown)
355           , ("M-S-k",      swapUp)
356           , ("M-m",        focusMaster)
357           , ("M-S-m",      windows W.swapMaster)
358           , ("M-t",        withFocused $ windows . W.sink)
359           , ("M-S-t",      sinkAll)
360           , ("M-<Tab>",    toggleWindowSpacingEnabled >> toggleScreenSpacingEnabled)
361
362           , ("M-S-q",      io exitSuccess)
363           , ("M-S-r",      spawn "xmonad --recompile && xmonad --restart")
364
365           , ("<XF86AudioPlay>",        spawn $ mocpString ++ " -G")
366           , ("<XF86AudioRaiseVolume>", spawn $ mocpString ++ " -v +5")
367           , ("<XF86AudioLowerVolume>", spawn $ mocpString ++ " -v -5")
368           , ("<XF86AudioMute>",        spawn $ mocpString ++ " -v 0")
369           , ("<XF86AudioPrev>",        spawn $ mocpString ++ " --previous")
370           , ("<XF86AudioNext>",        spawn $ mocpString ++ " --next")
371           ]
372           ++
373           [("M-" ++ m ++ show k, windows $ f i)
374               | (i, k) <- zip workspacesTP [1..9]
375               , (f, m) <- [(W.greedyView, ""), (W.shift, "S-")]
376           ]
377
378-- * xmobar
379--
380-- $xmobar
381--
382-- stuff for xmobar
383
384-- | xmobar pretty printer
385localXmobarPP :: PP
386localXmobarPP = def
387           { ppSep             = xmobarColor (col_bg_alt def) "" " | "
388           , ppCurrent         = xmobarColor (col_fg_alt def) "" . sitelen
389           , ppHidden          = xmobarColor (col_fg     def) "" . sitelen
390           , ppHiddenNoWindows = xmobarColor (col_bg_alt def) "" . sitelen
391           , ppLayout          = sitelen
392           } where
393               sitelen = xmobarFont 3
394
395-- | status bar config
396statusBarConfig :: StatusBarConfig
397statusBarConfig = statusBarProp "xmobar"
398     $ clickablePP $ filterOutWsPP [scratchpadWorkspaceTag] localXmobarPP
399
400-- * layouts 
401--
402-- $layouts
403--
404-- stuff for layouts
405
406-- | theme for 'Tabbed' layout
407tabTheme :: Theme
408tabTheme = def
409           { fontName            = fontDef
410           , activeTextColor     = col_fg_alt def
411           , activeColor         = col_bg_alt def
412           , activeBorderWidth   = 0
413           , inactiveTextColor   = col_fg def
414           , inactiveColor       = col_bg def
415           , inactiveBorderWidth = 0
416           , urgentTextColor     = col_bg_alt def
417           , urgentColor         = col_fg_alt def
418           , urgentBorderWidth   = 0
419           }
420
421-- * misc
422
423-- | layout hook 
424--
425-- __NOTE__: it uses sitelen-pona font to name layouts.
426localLayoutHook = windowNavigation
427         $ boringWindows
428         $ toggleLayouts full
429         $ smartBorders
430         $ tiled ||| threeCol
431         where
432            tiled    = renamed [Replace "\xe624"] -- lawa
433                     $ addTabs shrinkText tabTheme
434                     $ subLayout [] Simplest
435                     $ spacingWithEdge space
436                     $ ResizableTall nmaster delta ratio []
437            threeCol = renamed [Replace "\xe665"] -- supa
438                     $ addTabs shrinkText tabTheme
439                     $ subLayout [] Simplest
440                     $ spacingWithEdge space
441                     $ ResizableThreeColMid nmaster delta ratio []
442            full     = renamed [Replace "\xe663"] -- suli
443                     $ noBorders Full
444            nmaster  = 1
445            ratio    = 1/2
446            delta    = 3/100
447            space    = 4
448
449-- | main config 
450--
451-- you can override things like that:
452--
453-- @
454--     myConfig = laNinpreConfig { workspaces = 'workspacesNorm' }
455--     main = xmonad myConfig
456-- @
457laNinpreConfig = def
458         { terminal           = terminalEmulator
459         , modMask            = mod4Mask
460         , layoutHook         = localLayoutHook
461         , manageHook         = localManageHook
462         , workspaces         = workspacesTP
463         , borderWidth        = 1
464         , keys               = (`mkKeymap` keybinds)
465         , normalBorderColor  = col_bg_alt def
466         , focusedBorderColor = col_fg_alt def
467         }
468
469main :: IO ()
470main = xmonad
471     . ewmhFullscreen
472     . ewmh
473     . withEasySB statusBarConfig defToggleStrutsKey
474     $ laNinpreConfig
475