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