]> Git — Sourcephile - julm/julm-nix.git/blob - home-manager/profiles/xmonad/xmonad.hs
home-manager: update
[julm/julm-nix.git] / home-manager / profiles / xmonad / xmonad.hs
1 {-# LANGUAGE NamedFieldPuns #-}
2 {-# OPTIONS_GHC -Wall #-}
3 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
4 import Data.Default
5 import qualified Data.Char as Char
6 import Data.List as List
7 import Data.Ratio
8 import System.Exit
9 import qualified Data.Map as Map
10 import Control.Arrow (first)
11
12 -- import XMonad.Actions.DwmPromote
13 -- import XMonad.Actions.Warp
14 -- import XMonad.Layout.Maximize
15 -- import XMonad.Layout.Monitor
16 -- import XMonad.Layout.ResizableTile
17 -- import XMonad.Layout.TabBarDecoration
18 -- import XMonad.Util.EZConfig
19 -- import XMonad.Util.EZConfig(additionalKeys)
20 -- import XMonad.Util.WorkspaceCompare
21 import XMonad hiding ((|||))
22 import XMonad.Actions.CopyWindow
23 import XMonad.Actions.CycleWS
24 import XMonad.Actions.SwapWorkspaces
25 import XMonad.Actions.UpdatePointer
26 import XMonad.Config.Azerty
27 import XMonad.Hooks.DynamicLog
28 import XMonad.Hooks.EwmhDesktops
29 import XMonad.Hooks.ManageDocks
30 import XMonad.Hooks.ManageHelpers
31 import XMonad.Hooks.Rescreen
32 import XMonad.Hooks.SetWMName
33 import XMonad.Hooks.StatusBar
34 import XMonad.Hooks.UrgencyHook
35 import XMonad.Layout.Fullscreen
36 import XMonad.Layout.Grid
37 import XMonad.Layout.LayoutCombinators
38 import XMonad.Layout.Magnifier
39 import XMonad.Layout.MultiToggle
40 import XMonad.Layout.MultiToggle.Instances
41 import XMonad.Layout.NoBorders
42 import XMonad.Layout.ResizableTile
43 import XMonad.Layout.Spiral
44 import XMonad.Layout.Tabbed
45 import XMonad.Layout.ThreeColumns
46 import XMonad.Prompt
47 import XMonad.Prompt.FuzzyMatch
48 import XMonad.Prompt.Pass
49 --import XMonad.Operations (unGrab) -- TODO: needs xmonad 0.18
50 import XMonad.Util.SpawnOnce
51 import qualified XMonad.StackSet as W
52
53 main = xmonad $
54 withUrgencyHook NoUrgencyHook $
55 -- dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] } $
56 --addAfterRescreenHook myAfterRescreenHook $
57 addRandrChangeHook (spawnExec "autorandr --change") $
58 dynamicSBs barSpawner $
59 docks $
60 setEwmhActivateHook doAskUrgent $
61 ewmhFullscreen $
62 ewmh $
63 azertyConfig
64 { borderWidth = 1
65 , focusFollowsMouse = True
66 , focusedBorderColor = "#00b10b"
67 , handleEventHook = handleEventHook def
68 , keys = \conf@XConfig{XMonad.modMask} ->
69 Map.fromList $
70 let xK_XF86Backward = 0x1008ff26
71 xK_XF86Forward = 0x1008ff27 in
72 [
73 -- Start a terminal
74 ((modMask, xK_Return), spawnExec $ XMonad.terminal conf)
75 -- Launch a program
76 , ((modMask, xK_Menu), spawnCommand)
77 , ((modMask, xK_a), spawnCommand)
78 -- Browse the filesystem
79 , ((modMask, xK_BackSpace), spawnExec "systemd-run --user --unit=app-org.rofi.caja@$RANDOM -p CollectMode=inactive-or-failed caja")
80
81 -- Lock the screen
82 , ((0, xK_Pause), {-unGrab >>-} spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
83 , ((modMask, xK_Delete), {-unGrab >>-} spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
84
85 -- Take a full screenshot
86 , ((0, xK_Print), spawn "mkdir -p ~/Images/screenshots && scrot --quality 42 ~/Images/screenshots/'%Y-%m-%d_%H-%M-%S.png' && caja ~/Images/screenshots")
87 -- Take a selective screenshot
88 , ((modMask, xK_Print), spawn "select-screenshot")
89
90 -- Volume control
91 , ((0, 0x1008FF12), spawnExec "pactl -- set-sink-mute @DEFAULT_SINK@ toggle") -- XF88AudioMute
92 , ((0, 0x1008FF11), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ -5%") -- XF86AudioLowerVolume
93 , ((0, 0x1008FF13), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ +5%") -- XF86AudioRaiseVolume
94 -- Audio previous
95 -- , ((0, 0x1008FF16), spawnExec "")
96 -- Play/pause
97 -- , ((0, 0x1008FF14), spawnExec "")
98 -- Audio next
99 -- , ((0, 0x1008FF17), spawnExec "")
100 -- Eject CD tray
101 -- , ((0, 0x1008FF2C), spawnExec "eject -T")
102
103 -- Close focused window.
104 , ((modMask, xK_Escape), kill)
105 , ((modMask, xK_q), kill)
106
107 -- Clipboard
108 , ((modMask, xK_c), spawnExec "clipster --select --primary")
109
110 -- Temporarily maximize a window
111 , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
112 -- , ((modMask, xK_f), withFocused (sendMessage . maximizeRestore))
113
114 -- Cycle through the available layout algorithms
115 , ((modMask, 0x13bd), sendMessage NextLayout) -- oe (²)
116 , ((modMask, xK_ampersand), sendMessage $ JumpToLayout "ResizableTall") -- & (1)
117 , ((modMask, xK_eacute), sendMessage $ JumpToLayout "Mirror ResizableTall") -- é (2)
118 , ((modMask, xK_quotedbl), sendMessage $ JumpToLayout "Tabbed Simplest") -- ' (3)
119 , ((modMask, xK_apostrophe), sendMessage $ JumpToLayout "Magnifier Grid") -- " (4)
120 , ((modMask, xK_parenleft), sendMessage $ JumpToLayout "Spiral") -- ( (5)
121 , ((modMask, xK_minus), sendMessage $ JumpToLayout "Full") -- - (6)
122 , ((modMask, xK_egrave), sendMessage $ JumpToLayout "ThreeCol") -- è (7)
123
124 -- Reset the layouts on the current workspace to default
125 -- , ((modMask .|. shiftMask, xK_space), setLayout $ XMonad.layoutHook conf)
126
127 -- Resize viewed windows to the correct size.
128 , ((modMask, xK_n), refresh)
129
130 -- Move focus between windows
131 , ((modMask, xK_Tab), windows W.focusDown)
132 , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp)
133 , ((modMask, xK_i), windows W.focusUp)
134 , ((modMask, xK_k), windows W.focusDown)
135
136 -- Move focus to the master window
137 , ((modMask, xK_m), windows W.focusMaster)
138 -- Swap the focused window and the master window
139 , ((modMask, xK_space), windows W.swapMaster)
140
141 -- Swap the focused window with the next window.
142 --, ((modMask, xK_o), windows W.swapDown >> windows W.focusMaster)
143 -- Swap the focused window with the previous window.
144 , ((modMask, xK_m), windows W.swapUp >> windows W.focusMaster)
145
146 -- Push window back into tiling.
147 , ((modMask, xK_t), withFocused $ windows . W.sink)
148
149 -- Change the number of windows in the master area
150 , ((modMask, xK_Up), sendMessage $ IncMasterN 1)
151 , ((modMask, xK_Down), sendMessage $ IncMasterN (-1))
152
153 -- Toggle the status bar gap.
154 , ((modMask, xK_b), sendMessage ToggleStruts)
155
156 -- Quit xmonad
157 , ((modMask .|. shiftMask, xK_End), io exitSuccess)
158 -- Restart xmonad
159 , ((modMask, xK_End), restart "xmonad" True)
160
161 , ((modMask, xK_p), passPrompt dtXPConfig)
162 , ((modMask .|. controlMask, xK_p), passGeneratePrompt dtXPConfig)
163 , ((modMask .|. controlMask .|. shiftMask, xK_p), passRemovePrompt dtXPConfig)
164
165 -- Workspace management
166 -- XF86Back: Switch to previous workspace
167 , ((0, xK_XF86Backward), prevWS)
168 , ((modMask, xK_j), prevWS)
169 , ((modMask, xK_Page_Up), prevWS)
170 -- Switch to next workspace
171 , ((0, xK_XF86Forward), nextWS)
172 , ((modMask, xK_l), nextWS)
173 , ((modMask, xK_Page_Down), nextWS)
174 -- XF86Back: Move the current client to the previous workspace and go there
175 , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
176 , ((modMask .|. shiftMask, xK_j), shiftToPrev >> prevWS)
177 -- Move the current client to the next workspace and go there
178 , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
179 , ((modMask .|. shiftMask, xK_l), shiftToNext >> nextWS)
180 -- Switch to previous workspace
181 -- Switch to next workspace
182 {-
183 -- Move the current client to the previous workspace
184 , ((0 .|. shiftMask , xK_XF86Backward), shiftToPrev )
185 -- Move the current client to the next workspace
186 , ((0 .|. shiftMask , xK_XF86Forward), shiftToNext )
187 -}
188
189 -- Toggle copying window on all workspaces (sticky window)
190 , ((modMask, xK_s), do
191 copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
192 case copies of
193 [] -> windows copyToAll
194 _ -> killAllOtherCopies
195 )
196
197 -- Resize the master area
198 , ((modMask, xK_Left), sendMessage Shrink)
199 , ((modMask, xK_Right), sendMessage Expand)
200 -- Resize windows in ResizableTall mode
201 , ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
202 , ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
203 ] ++
204
205 -- mod-[F1..F9], Switch to workspace N
206 -- mod-shift-[F1..F9], Move client to workspace N
207 [ ((m .|. modMask, k), windows $ f i)
208 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
209 zip (workspaces conf) [xK_1 ..]
210 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
211 ] ++
212 {- NOTE: with Xinerama
213 [((m .|. modMask, k), windows $ onCurrentScreen f i)
214 | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
215 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
216 -}
217
218 -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
219 -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
220 [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
221 | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
222 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
223 ] ++
224
225 -- mod-shift-[F1..F9], Swap workspace with workspace N
226 -- mod-shift-[1..9], Swap workspace with workspace N
227 [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
228 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
229 zip (workspaces conf) [xK_1 ..]
230 ]
231 {- NOTE: with Xinerama
232 [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
233 | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
234 -}
235 , layoutHook = smartBorders $
236 mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
237 avoidStruts $ -- prevents windows from overlapping dock windows
238 let tall = ResizableTall 1 (1%200) (8%13) [] in
239 tabbed shrinkText tabConfig
240 ||| tall
241 ||| Mirror tall
242 ||| magnifiercz (13%10) Grid
243 ||| spiral (6%7)
244 ||| noBorders (fullscreenFull Full)
245 ||| ThreeColMid 1 (1%200) (1%2)
246 -- ||| Tall 1 (3/100) (1/2)
247 , manageHook = composeAll
248 -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
249 [ isFullscreen --> doFullFloat
250 , manageHook def
251 , manageDocks -- NOTE: do not tile dock windows
252 , resource =? "desktop_window" --> doIgnore
253 , className =? "Gimp" --> doFloat
254 , resource =? "gpicview" --> doSink
255 , className =? "mpv" --> doFloat
256 --, className =? "MPlayer" --> doShift "3:media" -- <+> doFloat
257 --, className =? "vlc" --> doShift "3:media"
258 , className =? "trayer" --> doIgnore
259 ]
260 , modMask = mod4Mask
261 , mouseBindings = \XConfig{XMonad.modMask} ->
262 Map.fromList
263 [
264 -- mod-button1, Set the window to floating mode and move by dragging
265 ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
266
267 -- mod-button2, Raise the window to the top of the stack
268 , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
269
270 -- mod-button3, Set the window to floating mode and resize by dragging
271 , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
272
273 , ((modMask, button4), \_ -> windows W.focusUp)
274 , ((modMask, button5), \_ -> windows W.focusDown)
275
276 -- Cycle through workspaces
277 , ((controlMask .|. modMask, button5), nextNonEmptyWS)
278 , ((controlMask .|. modMask, button4), prevNonEmptyWS)
279 ]
280 , normalBorderColor = "#7C7C7C"
281 , startupHook = setWMName "XMonad"
282 <+> spawnExec "wmname XMonad"
283 <+> spawnExec "xrdb -all .Xresources"
284 <+> spawn "sleep 1 && xmodmap .Xmodmap"
285 <+> spawnExec "xset r rate 250 25"
286 <+> spawnExec "xset b off"
287 <+> spawnExec "xhost local:root"
288 <+> spawnExec "setxkbmap -option keypad:pointerkeys"
289 -- Useful for programs launched by rofi
290 <+> spawnExec (unwords [ "systemctl --user import-environment"
291 , "DBUS_SESSION_BUS_ADDRESS"
292 , "GDK_PIXBUF_MODULE_FILE"
293 , "GIO_EXTRA_MODULES"
294 , "GLFW_IM_MODULE"
295 , "GNUPGHOME"
296 , "GTK2_RC_FILES"
297 , "GTK_A11Y"
298 , "GTK_IM_MODULE"
299 , "GTK_PATH"
300 , "LANG"
301 , "LD_LIBRARY_PATH" -- For sane and pipewire
302 , "LIBEXEC_PATH"
303 , "NIX_PROFILES" -- fcitx5 does not work without it…
304 , "PASSWORD_STORE_DIR"
305 , "PATH"
306 , "QTWEBKIT_PLUGIN_PATH"
307 , "QT_IM_MODULE"
308 , "QT_PLUGIN_PATH"
309 , "SPEECHD_CMD"
310 , "SSH_ASKPASS"
311 , "XCURSOR_PATH"
312 , "XMODIFIERS"
313 ])
314 -- <+> spawnOnce "exec arbtt-capture -r 60"
315 -- <+> spawnOnce "exec parcellite"
316 -- <+> spawnOnce "exec xautolock"
317 -- <+> spawnOnce "exec redshift-gtk -l -45.7800:1.9700 -t 6500:3700"
318 <+> spawnOnce "exec nm-applet"
319 , terminal = "urxvtc"
320 , workspaces = {- withScreens nScreens $ -}
321 {-["1:work","2:web","3:media"] ++-}
322 map show [1::Int .. 9]
323 , logHook = updatePointer (0.5, 0.5) (0, 0)
324 -- >> updatePointer (Relative 0.5 0.5)
325 }
326 where
327 tabConfig = def
328 { activeBorderColor = "#7C7C7C"
329 , activeColor = "#000000"
330 , activeTextColor = "#00FF00"
331 , inactiveBorderColor = "#7C7C7C"
332 , inactiveColor = "#000000"
333 , inactiveTextColor = "#EEEEEE"
334 , fontName = "Hack 7"
335 }
336
337 spawnCommand = spawnExec "rofi -show run -no-disable-history -run-command \"bash -c 'systemd-run --user --unit=app-org.rofi.\\$(systemd-escape \\\"{cmd}\\\")@\\$RANDOM -p CollectMode=inactive-or-failed {cmd}'\""
338
339 barSpawner :: ScreenId -> IO StatusBarConfig
340 barSpawner 0 = pure $ topXmobar <> traySB
341 --barSpawner 1 = pure $ xmobar1
342 barSpawner _ = pure $ topXmobar -- nothing on the rest of the screens
343
344 -- Display properties of the root window:
345 -- xprop -display $DISPLAY -root
346 topXmobar = statusBarPropTo "_XMONAD_XMOBAR0" "xmobar -x 0 ~/.config/xmonad/xmobar0.hs" (pure topPP)
347 where
348 topPP =
349 xmobarPP
350 { ppCurrent = xmobarColor "black" "#CCCCCC"
351 , ppHidden = xmobarColor "#CCCCCC" "black"
352 , ppHiddenNoWindows = xmobarColor "#606060" "black"
353 , ppLayout = \s -> xmobarColor "black" "#606060" $
354 case s of
355 "ResizableTall" -> " | "
356 "Mirror ResizableTall" -> " - "
357 "Tabbed Simplest" -> " + "
358 "Magnifier Grid" -> " ~ "
359 "Spiral" -> " @ "
360 "Full" -> " O "
361 "ThreeCol" -> " # "
362 _ -> s
363 , ppSep = " "
364 , ppTitle = xmobarColor "white" "black" . shorten 50
365 , ppUrgent = xmobarColor "yellow" "black"
366 , ppWsSep = " "
367 }
368
369 traySB :: StatusBarConfig
370 traySB =
371 statusBarGeneric
372 ( List.unwords
373 [ "trayer"
374 , "--align right"
375 , "--distance 0,0"
376 , "--distancefrom top,right"
377 , "--edge top"
378 , "--expand true"
379 , "--height 16"
380 , "--monitor primary"
381 , "--tint 0x000000"
382 , "--iconspacing 0"
383 , "--transparent true"
384 , "--widthtype request"
385 , "-l"
386 ]
387 )
388 mempty
389
390 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
391 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
392
393 isWindowSpaceVisible :: X (WindowSpace -> Bool)
394 isWindowSpaceVisible = do
395 vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
396 return (\w -> W.tag w `elem` vs)
397
398 spawnExec s = spawn $ List.unwords $ [ "exec" ] <> systemdCat <> [ s ]
399 systemdCat = [ "systemd-cat" , "--priority=info", "--stderr-priority=warning", "--level-prefix=false" , "--" ]
400
401 dtXPConfig :: XPConfig
402 dtXPConfig = def
403 { font = "Hack 7"
404 , bgColor = "#282c34"
405 , fgColor = "#bbc2cf"
406 , bgHLight = "#c792ea"
407 , fgHLight = "#000000"
408 , borderColor = "#535974"
409 , promptBorderWidth = 0
410 , promptKeymap = dtXPKeymap
411 , position = Top
412 -- , position = CenteredAt { xpCenterY = 0.3, xpWidth = 0.3 }
413 , height = 23
414 , historySize = 256
415 , historyFilter = id
416 , defaultText = []
417 , autoComplete = Just 100000 -- set Just 100000 for .1 sec
418 , showCompletionOnTab = False
419 -- , searchPredicate = isPrefixOf
420 , searchPredicate = fuzzyMatch
421 , defaultPrompter = id $ List.map Char.toUpper -- change prompt to UPPER
422 -- , defaultPrompter = unwords . map reverse . words -- reverse the prompt
423 -- , defaultPrompter = drop 5 .id (++ "XXXX: ") -- drop first 5 chars of prompt and add XXXX:
424 , alwaysHighlight = True
425 , maxComplRows = Nothing -- set to 'Just 5' for 5 rows
426 }
427
428 dtXPKeymap :: Map.Map (KeyMask,KeySym) (XP ())
429 dtXPKeymap = Map.fromList $
430 List.map (first $ (,) controlMask) -- control + <key>
431 [ (xK_z, killBefore) -- kill line backwards
432 , (xK_k, killAfter) -- kill line forwards
433 , (xK_a, startOfLine) -- move to the beginning of the line
434 , (xK_e, endOfLine) -- move to the end of the line
435 , (xK_m, deleteString Next) -- delete a character foward
436 , (xK_b, moveCursor Prev) -- move cursor forward
437 , (xK_f, moveCursor Next) -- move cursor backward
438 , (xK_BackSpace, killWord Prev) -- kill the previous word
439 , (xK_y, pasteString) -- paste a string
440 , (xK_g, quit) -- quit out of prompt
441 , (xK_bracketleft, quit)
442 ]
443 ++
444 List.map (first $ (,) altMask) -- meta key + <key>
445 [ (xK_BackSpace, killWord Prev) -- kill the prev word
446 , (xK_f, moveWord Next) -- move a word forward
447 , (xK_b, moveWord Prev) -- move a word backward
448 , (xK_d, killWord Next) -- kill the next word
449 , (xK_n, moveHistory W.focusUp') -- move up thru history
450 , (xK_p, moveHistory W.focusDown') -- move down thru history
451 ]
452 ++
453 List.map (first $ (,) 0) -- <key>
454 [ (xK_Return, setSuccess True >> setDone True)
455 , (xK_KP_Enter, setSuccess True >> setDone True)
456 , (xK_BackSpace, deleteString Prev)
457 , (xK_Delete, deleteString Next)
458 , (xK_Left, moveCursor Prev)
459 , (xK_Right, moveCursor Next)
460 , (xK_Home, startOfLine)
461 , (xK_End, endOfLine)
462 , (xK_Down, moveHistory W.focusUp')
463 , (xK_Up, moveHistory W.focusDown')
464 , (xK_Escape, quit)
465 ]
466
467 altMask :: KeyMask
468 altMask = mod1Mask