xmonad: add XMonad.Prompt.Window
[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.Prompt.Window
50 --import XMonad.Operations (unGrab) -- TODO: needs xmonad 0.18
51 import XMonad.Util.SpawnOnce
52 import qualified XMonad.StackSet as W
53
54 main = xmonad $
55 withUrgencyHook NoUrgencyHook $
56 -- dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] } $
57 --addAfterRescreenHook myAfterRescreenHook $
58 addRandrChangeHook (spawnExec "autorandr --change") $
59 dynamicSBs barSpawner $
60 docks $
61 setEwmhActivateHook doAskUrgent $
62 ewmhFullscreen $
63 ewmh $
64 azertyConfig
65 { borderWidth = 1
66 , focusFollowsMouse = True
67 , focusedBorderColor = "#00b10b"
68 , handleEventHook = handleEventHook def
69 , keys = \conf@XConfig{XMonad.modMask} ->
70 Map.fromList $
71 let xK_XF86Backward = 0x1008ff26
72 xK_XF86Forward = 0x1008ff27 in
73 [
74 -- Start a terminal
75 ((modMask, xK_Return), spawnExec $ XMonad.terminal conf)
76 -- Launch a program
77 , ((modMask, xK_Menu), spawnCommand)
78 , ((modMask, xK_a), spawnCommand)
79 -- Browse the filesystem
80 , ((modMask, xK_BackSpace), spawnExec "systemd-run --user --unit=app-org.rofi.caja@$RANDOM -p CollectMode=inactive-or-failed caja")
81
82 -- Lock the screen
83 , ((0, xK_Pause), {-unGrab >>-} spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
84 , ((modMask, xK_Delete), {-unGrab >>-} spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
85
86 -- Take a full screenshot
87 , ((0, xK_Print), spawn "mkdir -p ~/Images/screenshots && scrot --quality 42 ~/Images/screenshots/'%Y-%m-%d_%H-%M-%S.png' && caja ~/Images/screenshots")
88 -- Take a selective screenshot
89 , ((modMask, xK_Print), spawn "select-screenshot")
90
91 -- Volume control
92 , ((0, 0x1008FF12), spawnExec "pactl -- set-sink-mute @DEFAULT_SINK@ toggle") -- XF88AudioMute
93 , ((0, 0x1008FF11), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ -5%") -- XF86AudioLowerVolume
94 , ((0, 0x1008FF13), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ +5%") -- XF86AudioRaiseVolume
95 -- Audio previous
96 -- , ((0, 0x1008FF16), spawnExec "")
97 -- Play/pause
98 -- , ((0, 0x1008FF14), spawnExec "")
99 -- Audio next
100 -- , ((0, 0x1008FF17), spawnExec "")
101 -- Eject CD tray
102 -- , ((0, 0x1008FF2C), spawnExec "eject -T")
103
104 -- Close focused window.
105 , ((modMask, xK_Escape), 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 promptConfig)
162 , ((modMask .|. controlMask, xK_p), passGeneratePrompt promptConfig)
163 , ((modMask .|. controlMask .|. shiftMask, xK_p), passRemovePrompt promptConfig)
164 , ((modMask, xK_Tab), windowMultiPrompt promptConfig [(Goto, allWindows), (Goto, wsWindows)])
165
166 -- Workspace management
167 -- XF86Back: Switch to previous workspace
168 , ((0, xK_XF86Backward), prevWS)
169 , ((modMask, xK_j), prevWS)
170 , ((modMask, xK_Page_Up), prevWS)
171 -- Switch to next workspace
172 , ((0, xK_XF86Forward), nextWS)
173 , ((modMask, xK_l), nextWS)
174 , ((modMask, xK_Page_Down), nextWS)
175 -- XF86Back: Move the current client to the previous workspace and go there
176 , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
177 , ((modMask .|. shiftMask, xK_j), shiftToPrev >> prevWS)
178 -- Move the current client to the next workspace and go there
179 , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
180 , ((modMask .|. shiftMask, xK_l), shiftToNext >> nextWS)
181 -- Switch to previous workspace
182 -- Switch to next workspace
183 {-
184 -- Move the current client to the previous workspace
185 , ((0 .|. shiftMask , xK_XF86Backward), shiftToPrev )
186 -- Move the current client to the next workspace
187 , ((0 .|. shiftMask , xK_XF86Forward), shiftToNext )
188 -}
189
190 -- Toggle copying window on all workspaces (sticky window)
191 , ((modMask, xK_s), do
192 copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
193 case copies of
194 [] -> windows copyToAll
195 _ -> killAllOtherCopies
196 )
197
198 -- Resize the master area
199 , ((modMask, xK_Left), sendMessage Shrink)
200 , ((modMask, xK_Right), sendMessage Expand)
201 -- Resize windows in ResizableTall mode
202 , ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
203 , ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
204 ] ++
205
206 -- mod-[F1..F9], Switch to workspace N
207 -- mod-shift-[F1..F9], Move client to workspace N
208 [ ((m .|. modMask, k), windows $ f i)
209 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
210 zip (workspaces conf) [xK_1 ..]
211 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
212 ] ++
213 {- NOTE: with Xinerama
214 [((m .|. modMask, k), windows $ onCurrentScreen f i)
215 | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
216 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
217 -}
218
219 -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
220 -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
221 [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
222 | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
223 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
224 ] ++
225
226 -- mod-shift-[F1..F9], Swap workspace with workspace N
227 -- mod-shift-[1..9], Swap workspace with workspace N
228 [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
229 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
230 zip (workspaces conf) [xK_1 ..]
231 ]
232 {- NOTE: with Xinerama
233 [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
234 | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
235 -}
236 , layoutHook = smartBorders $
237 mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
238 avoidStruts $ -- prevents windows from overlapping dock windows
239 let tall = ResizableTall 1 (1%200) (8%13) [] in
240 tabbed shrinkText tabConfig
241 ||| tall
242 ||| Mirror tall
243 ||| magnifiercz (13%10) Grid
244 ||| spiral (6%7)
245 ||| noBorders (fullscreenFull Full)
246 ||| ThreeColMid 1 (1%200) (1%2)
247 -- ||| Tall 1 (3/100) (1/2)
248 , manageHook = composeAll
249 -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
250 [ isFullscreen --> doFullFloat
251 , manageHook def
252 , manageDocks -- NOTE: do not tile dock windows
253 , resource =? "desktop_window" --> doIgnore
254 , className =? "Gimp" --> doFloat
255 , resource =? "gpicview" --> doSink
256 , className =? "mpv" --> doFloat
257 --, className =? "MPlayer" --> doShift "3:media" -- <+> doFloat
258 --, className =? "vlc" --> doShift "3:media"
259 , className =? "trayer" --> doIgnore
260 ]
261 , modMask = mod4Mask
262 , mouseBindings = \XConfig{XMonad.modMask} ->
263 Map.fromList
264 [
265 -- mod-button1, Set the window to floating mode and move by dragging
266 ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
267
268 -- mod-button2, Raise the window to the top of the stack
269 , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
270
271 -- mod-button3, Set the window to floating mode and resize by dragging
272 , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
273
274 , ((modMask, button4), \_ -> windows W.focusUp)
275 , ((modMask, button5), \_ -> windows W.focusDown)
276
277 -- Cycle through workspaces
278 , ((controlMask .|. modMask, button5), nextNonEmptyWS)
279 , ((controlMask .|. modMask, button4), prevNonEmptyWS)
280 ]
281 , normalBorderColor = "#7C7C7C"
282 , startupHook = setWMName "XMonad"
283 <+> spawnExec "wmname XMonad"
284 <+> spawnExec "xrdb -all .Xresources"
285 <+> spawn "sleep 1 && xmodmap .Xmodmap"
286 <+> spawnExec "xset r rate 250 25"
287 <+> spawnExec "xset b off"
288 <+> spawnExec "xhost local:root"
289 <+> spawnExec "setxkbmap -option keypad:pointerkeys"
290 -- Useful for programs launched by rofi
291 <+> spawnExec (unwords [ "systemctl --user import-environment"
292 , "DBUS_SESSION_BUS_ADDRESS"
293 , "GDK_PIXBUF_MODULE_FILE"
294 , "GIO_EXTRA_MODULES"
295 , "GLFW_IM_MODULE"
296 , "GNUPGHOME"
297 , "GTK2_RC_FILES"
298 , "GTK_A11Y"
299 , "GTK_IM_MODULE"
300 , "GTK_PATH"
301 , "LANG"
302 , "LD_LIBRARY_PATH" -- For sane and pipewire
303 , "LIBEXEC_PATH"
304 , "NIX_PROFILES" -- fcitx5 does not work without it…
305 , "PASSWORD_STORE_DIR"
306 , "PATH"
307 , "QTWEBKIT_PLUGIN_PATH"
308 , "QT_IM_MODULE"
309 , "QT_PLUGIN_PATH"
310 , "SPEECHD_CMD"
311 , "SSH_ASKPASS"
312 , "XCURSOR_PATH"
313 , "XMODIFIERS"
314 ])
315 -- <+> spawnOnce "exec arbtt-capture -r 60"
316 -- <+> spawnOnce "exec parcellite"
317 -- <+> spawnOnce "exec xautolock"
318 -- <+> spawnOnce "exec redshift-gtk -l -45.7800:1.9700 -t 6500:3700"
319 <+> spawnOnce "exec nm-applet"
320 , terminal = "urxvtc"
321 , workspaces = {- withScreens nScreens $ -}
322 {-["1:work","2:web","3:media"] ++-}
323 map show [1::Int .. 9]
324 , logHook = updatePointer (0.5, 0.5) (0, 0)
325 -- >> updatePointer (Relative 0.5 0.5)
326 }
327 where
328 tabConfig = def
329 { activeBorderColor = "#7C7C7C"
330 , activeColor = "#000000"
331 , activeTextColor = "#00FF00"
332 , inactiveBorderColor = "#7C7C7C"
333 , inactiveColor = "#000000"
334 , inactiveTextColor = "#EEEEEE"
335 , fontName = "Hack 7"
336 }
337
338 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}'\""
339
340 barSpawner :: ScreenId -> IO StatusBarConfig
341 barSpawner 0 = pure $ topXmobar <> traySB
342 --barSpawner 1 = pure $ xmobar1
343 barSpawner _ = pure $ topXmobar -- nothing on the rest of the screens
344
345 -- Display properties of the root window:
346 -- xprop -display $DISPLAY -root
347 topXmobar = statusBarPropTo "_XMONAD_XMOBAR0" "xmobar -x 0 ~/.config/xmonad/xmobar0.hs" (pure topPP)
348 where
349 topPP =
350 xmobarPP
351 { ppCurrent = xmobarColor "black" "#CCCCCC"
352 , ppHidden = xmobarColor "#CCCCCC" "black"
353 , ppHiddenNoWindows = xmobarColor "#606060" "black"
354 , ppLayout = \s -> xmobarColor "black" "#606060" $
355 case s of
356 "ResizableTall" -> " | "
357 "Mirror ResizableTall" -> " - "
358 "Tabbed Simplest" -> " + "
359 "Magnifier Grid" -> " ~ "
360 "Spiral" -> " @ "
361 "Full" -> " O "
362 "ThreeCol" -> " # "
363 _ -> s
364 , ppSep = " "
365 , ppTitle = xmobarColor "white" "black" . shorten 50
366 , ppUrgent = xmobarColor "yellow" "black"
367 , ppWsSep = " "
368 }
369
370 traySB :: StatusBarConfig
371 traySB =
372 statusBarGeneric
373 ( List.unwords
374 [ "trayer"
375 , "--align right"
376 , "--distance 0,0"
377 , "--distancefrom top,right"
378 , "--edge top"
379 , "--expand true"
380 , "--height 16"
381 , "--monitor primary"
382 , "--tint 0x000000"
383 , "--iconspacing 0"
384 , "--transparent true"
385 , "--widthtype request"
386 , "-l"
387 ]
388 )
389 mempty
390
391 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
392 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
393
394 isWindowSpaceVisible :: X (WindowSpace -> Bool)
395 isWindowSpaceVisible = do
396 vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
397 return (\w -> W.tag w `elem` vs)
398
399 spawnExec s = spawn $ List.unwords $ [ "exec" ] <> systemdCat <> [ s ]
400 systemdCat = [ "systemd-cat" , "--priority=info", "--stderr-priority=warning", "--level-prefix=false" , "--" ]
401
402 promptConfig :: XPConfig
403 promptConfig = def
404 { font = "xft:monospace-"<>show fontSize
405 , bgColor = "black"
406 , fgColor = "grey"
407 , bgHLight = "green"
408 , fgHLight = "#000000"
409 , borderColor = "darkgreen"
410 , promptBorderWidth = 1
411 , promptKeymap = promptKeyMap
412 , position = CenteredAt { xpCenterY = 0.3, xpWidth = 0.5 }
413 , height = fontSize + 11
414 , historySize = 16
415 , historyFilter = id
416 , defaultText = ""
417 , autoComplete = Nothing -- Just 500000 -- nanoseconds
418 , showCompletionOnTab = False
419 , completionKey = (0, xK_Down)
420 , prevCompletionKey = (0, xK_Up)
421 , searchPredicate = fuzzyMatch -- isPrefixOf
422 , sorter = fuzzySort
423 , defaultPrompter = const ""
424 , alwaysHighlight = True
425 , maxComplRows = Just 10
426 , maxComplColumns = Just 1
427 , changeModeKey = xK_twosuperior
428 }
429 where
430 fontSize = 11
431
432 promptKeyMap :: Map.Map (KeyMask,KeySym) (XP ())
433 promptKeyMap = Map.fromList $
434 List.map (first $ (,) controlMask) -- control + <key>
435 [ (xK_z, killBefore) -- kill line backwards
436 , (xK_k, killAfter) -- kill line forwards
437 , (xK_u, killBefore) -- kill line backwards
438 , (xK_a, startOfLine) -- move to the beginning of the line
439 , (xK_e, endOfLine) -- move to the end of the line
440 , (xK_m, deleteString Next) -- delete a character foward
441 , (xK_b, moveCursor Prev) -- move cursor forward
442 , (xK_f, moveCursor Next) -- move cursor backward
443 , (xK_BackSpace, killWord Prev) -- kill the previous word
444 , (xK_y, pasteString) -- paste a string
445 , (xK_g, quit) -- quit out of prompt
446 , (xK_bracketleft, quit)
447 ]
448 ++
449 List.map (first $ (,) altMask) -- meta key + <key>
450 [ (xK_BackSpace, killWord Prev) -- kill the prev word
451 , (xK_f, moveWord Next) -- move a word forward
452 , (xK_b, moveWord Prev) -- move a word backward
453 , (xK_d, killWord Next) -- kill the next word
454 , (xK_n, moveHistory W.focusUp') -- move up through history
455 , (xK_p, moveHistory W.focusDown') -- move down through history
456 ]
457 ++
458 List.map (first $ (,) 0) -- <key>
459 [ (xK_Return, setSuccess True >> setDone True)
460 , (xK_KP_Enter, setSuccess True >> setDone True)
461 , (xK_BackSpace, deleteString Prev)
462 , (xK_Delete, deleteString Next)
463 , (xK_Left, moveCursor Prev)
464 , (xK_Right, moveCursor Next)
465 , (xK_Home, startOfLine)
466 , (xK_End, endOfLine)
467 , (xK_Down, moveHistory W.focusUp')
468 , (xK_Up, moveHistory W.focusDown')
469 , (xK_Escape, quit)
470 ]
471
472 altMask :: KeyMask
473 altMask = mod1Mask