1 {-# LANGUAGE NamedFieldPuns #-}
2 {-# OPTIONS_GHC -Wall #-}
3 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
5 import qualified Data.Char as Char
6 import Data.List as List
10 import qualified Data.Map as Map
11 import Control.Arrow (first)
13 -- import XMonad.Actions.DwmPromote
14 -- import XMonad.Actions.Warp
15 -- import XMonad.Layout.Maximize
16 -- import XMonad.Layout.Monitor
17 -- import XMonad.Layout.ResizableTile
18 -- import XMonad.Layout.TabBarDecoration
19 -- import XMonad.Util.EZConfig
20 -- import XMonad.Util.EZConfig(additionalKeys)
21 -- import XMonad.Util.WorkspaceCompare
22 import XMonad hiding ((|||))
23 import XMonad.Actions.CopyWindow
24 import XMonad.Actions.CycleWS
25 import XMonad.Actions.SwapWorkspaces
26 import XMonad.Actions.UpdatePointer
27 import XMonad.Config.Azerty
28 import XMonad.Hooks.DynamicLog
29 import XMonad.Hooks.EwmhDesktops
30 import XMonad.Hooks.ManageDocks
31 import XMonad.Hooks.ManageHelpers
32 import XMonad.Hooks.Rescreen
33 import XMonad.Hooks.SetWMName
34 import XMonad.Hooks.StatusBar
35 import XMonad.Hooks.UrgencyHook
36 import XMonad.Layout.Fullscreen
37 import XMonad.Layout.Grid
38 import XMonad.Layout.IndependentScreens
39 import XMonad.Layout.LayoutCombinators
40 import XMonad.Layout.Magnifier
41 import XMonad.Layout.MultiToggle
42 import XMonad.Layout.MultiToggle.Instances
43 import XMonad.Layout.NoBorders
44 import XMonad.Layout.ResizableTile
45 import XMonad.Layout.Spiral
46 import XMonad.Layout.Tabbed
47 import XMonad.Layout.ThreeColumns
49 import XMonad.Prompt.FuzzyMatch
50 import XMonad.Prompt.Pass
51 import XMonad.Util.Ungrab (unGrab)
52 --import XMonad.Operations (unGrab) -- TODO: needs xmonad 0.18
53 import XMonad.Util.SpawnOnce
54 import qualified XMonad.StackSet as W
57 withUrgencyHook NoUrgencyHook $
58 -- dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] } $
59 --addAfterRescreenHook myAfterRescreenHook $
60 addRandrChangeHook (spawnExec "autorandr --change") $
61 dynamicSBs barSpawner $
63 setEwmhActivateHook doAskUrgent $
68 , focusFollowsMouse = True
69 , focusedBorderColor = "#00b10b"
70 , handleEventHook = handleEventHook def
71 , keys = \conf@XConfig{XMonad.modMask} ->
73 let xK_XF86Backward = 0x1008ff26
74 xK_XF86Forward = 0x1008ff27 in
77 ((modMask, xK_Return), spawnExec $ XMonad.terminal conf)
79 , ((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}'\"")
80 -- Browse the filesystem
81 , ((modMask, xK_BackSpace), spawnExec "systemd-run --user --unit=app-org.rofi.caja@$RANDOM -p CollectMode=inactive-or-failed caja")
84 , ((0, xK_Pause), unGrab >> spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
86 -- Take a full screenshot
87 , ((0, xK_Print), spawn "cd ~/img/cap && scrot --quality 42 '%Y-%m-%d_%H-%M-%S.png' && caja ~/img/cap")
88 -- Take a selective screenshot
89 , ((modMask, xK_Print), spawn "select-screenshot")
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
96 -- , ((0, 0x1008FF16), spawnExec "")
98 -- , ((0, 0x1008FF14), spawnExec "")
100 -- , ((0, 0x1008FF17), spawnExec "")
102 -- , ((0, 0x1008FF2C), spawnExec "eject -T")
104 -- Close focused window.
105 , ((modMask, xK_Escape), kill)
106 , ((modMask, xK_q), kill)
109 , ((modMask, xK_c), spawnExec "clipster --select --primary")
111 -- Temporarily maximize a window
112 , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
113 -- , ((modMask, xK_f), withFocused (sendMessage . maximizeRestore))
115 -- Cycle through the available layout algorithms
116 , ((modMask, 0x13bd), sendMessage NextLayout) -- oe (²)
117 , ((modMask, xK_ampersand), sendMessage $ JumpToLayout "ResizableTall") -- & (1)
118 , ((modMask, xK_eacute), sendMessage $ JumpToLayout "Mirror ResizableTall") -- é (2)
119 , ((modMask, xK_quotedbl), sendMessage $ JumpToLayout "Tabbed Simplest") -- ' (3)
120 , ((modMask, xK_apostrophe), sendMessage $ JumpToLayout "Magnifier Grid") -- " (4)
121 , ((modMask, xK_parenleft), sendMessage $ JumpToLayout "Spiral") -- ( (5)
122 , ((modMask, xK_minus), sendMessage $ JumpToLayout "Full") -- - (6)
123 , ((modMask, xK_egrave), sendMessage $ JumpToLayout "ThreeCol") -- è (7)
125 -- Reset the layouts on the current workspace to default
126 -- , ((modMask .|. shiftMask, xK_space), setLayout $ XMonad.layoutHook conf)
128 -- Resize viewed windows to the correct size.
129 , ((modMask, xK_n), refresh)
131 -- Move focus between windows
132 , ((modMask, xK_Tab), windows W.focusDown)
133 , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp)
134 , ((modMask, xK_i), windows W.focusUp)
135 , ((modMask, xK_k), windows W.focusDown)
137 -- Move focus to the master window
138 , ((modMask, xK_m), windows W.focusMaster)
139 -- Swap the focused window and the master window
140 , ((modMask, xK_space), windows W.swapMaster)
142 -- Swap the focused window with the next window.
143 --, ((modMask, xK_o), windows W.swapDown >> windows W.focusMaster)
144 -- Swap the focused window with the previous window.
145 , ((modMask, xK_m), windows W.swapUp >> windows W.focusMaster)
147 -- Push window back into tiling.
148 , ((modMask, xK_t), withFocused $ windows . W.sink)
150 -- Change the number of windows in the master area
151 , ((modMask, xK_Up), sendMessage $ IncMasterN 1)
152 , ((modMask, xK_Down), sendMessage $ IncMasterN (-1))
154 -- Toggle the status bar gap.
155 , ((modMask, xK_b), sendMessage ToggleStruts)
158 , ((modMask .|. shiftMask, xK_End), io exitSuccess)
160 , ((modMask, xK_End), restart "xmonad" True)
162 , ((modMask, xK_p), passPrompt dtXPConfig)
163 , ((modMask .|. controlMask, xK_p), passGeneratePrompt dtXPConfig)
164 , ((modMask .|. controlMask .|. shiftMask, xK_p), passRemovePrompt dtXPConfig)
166 -- Workspace management
167 -- XF86Back: Switch to previous workspace
168 , ((0, xK_XF86Backward), prevWS)
169 , ((modMask, xK_j), prevWS)
170 -- Switch to next workspace
171 , ((0, xK_XF86Forward), nextWS)
172 , ((modMask, xK_l), nextWS)
173 -- XF86Back: Move the current client to the previous workspace and go there
174 , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
175 , ((modMask .|. shiftMask, xK_j), shiftToPrev >> prevWS)
176 -- Move the current client to the next workspace and go there
177 , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
178 , ((modMask .|. shiftMask, xK_l), shiftToNext >> nextWS)
179 -- Switch to previous workspace
180 -- Switch to next workspace
182 -- Move the current client to the previous workspace
183 , ((0 .|. shiftMask , xK_XF86Backward), shiftToPrev )
184 -- Move the current client to the next workspace
185 , ((0 .|. shiftMask , xK_XF86Forward), shiftToNext )
188 -- Toggle copying window on all workspaces (sticky window)
189 , ((modMask, xK_s), do
190 copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
192 [] -> windows copyToAll
193 _ -> killAllOtherCopies
196 -- Resize the master area
197 , ((modMask, xK_Left), sendMessage Shrink)
198 , ((modMask, xK_Right), sendMessage Expand)
199 -- Resize windows in ResizableTall mode
200 , ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
201 , ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
204 -- mod-[F1..F9], Switch to workspace N
205 -- mod-shift-[F1..F9], Move client to workspace N
206 [ ((m .|. modMask, k), windows $ f i)
207 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
208 zip (workspaces conf) [xK_1 ..]
209 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
211 {- NOTE: with Xinerama
212 [((m .|. modMask, k), windows $ onCurrentScreen f i)
213 | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
214 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
217 -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
218 -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
219 [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
220 | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
221 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
224 -- mod-shift-[F1..F9], Swap workspace with workspace N
225 -- mod-shift-[1..9], Swap workspace with workspace N
226 [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
227 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
228 zip (workspaces conf) [xK_1 ..]
230 {- NOTE: with Xinerama
231 [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
232 | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
234 , layoutHook = smartBorders $
235 mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
236 avoidStruts $ -- prevents windows from overlapping dock windows
237 let tall = ResizableTall 1 (1%200) (8%13) [] in
238 tabbed shrinkText tabConfig
241 ||| magnifiercz (13%10) Grid
243 ||| noBorders (fullscreenFull Full)
244 ||| ThreeColMid 1 (1%200) (1%2)
245 -- ||| Tall 1 (3/100) (1/2)
246 , manageHook = composeAll
247 -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
248 [ isFullscreen --> doFullFloat
250 , manageDocks -- NOTE: do not tile dock windows
251 , resource =? "desktop_window" --> doIgnore
252 , className =? "Gimp" --> doFloat
253 , resource =? "gpicview" --> doSink
254 , className =? "mpv" --> doFloat
255 --, className =? "MPlayer" --> doShift "3:media" -- <+> doFloat
256 --, className =? "vlc" --> doShift "3:media"
257 , className =? "trayer" --> doIgnore
260 , mouseBindings = \XConfig{XMonad.modMask} ->
263 -- mod-button1, Set the window to floating mode and move by dragging
264 ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
266 -- mod-button2, Raise the window to the top of the stack
267 , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
269 -- mod-button3, Set the window to floating mode and resize by dragging
270 , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
272 , ((modMask, button4), \_ -> windows W.focusUp)
273 , ((modMask, button5), \_ -> windows W.focusDown)
275 -- Cycle through workspaces
276 , ((controlMask .|. modMask, button5), nextNonEmptyWS)
277 , ((controlMask .|. modMask, button4), prevNonEmptyWS)
279 , normalBorderColor = "#7C7C7C"
280 , startupHook = setWMName "XMonad"
281 <+> spawnExec "wmname XMonad"
282 <+> spawnExec "xrdb -all .Xresources"
283 <+> spawn "sleep 1 && xmodmap .Xmodmap"
284 <+> spawnExec "xset r rate 250 25"
285 <+> spawnExec "xset b off"
286 <+> spawnExec "xhost local:root"
287 <+> spawnExec "setxkbmap -option keypad:pointerkeys"
288 -- Useful for programs launched by rofi
289 <+> spawnExec "systemctl --user import-environment GNUPGHOME PASSWORD_STORE_DIR PATH"
290 -- <+> spawnOnce "exec arbtt-capture -r 60"
291 -- <+> spawnOnce "exec parcellite"
292 -- <+> spawnOnce "exec xautolock"
293 -- <+> spawnOnce "exec redshift-gtk -l -45.7800:1.9700 -t 6500:3700"
294 <+> spawnOnce "exec nm-applet"
295 , terminal = "urxvtc"
296 , workspaces = {- withScreens nScreens $ -}
297 {-["1:work","2:web","3:media"] ++-}
298 map show [1::Int .. 9]
299 , logHook = updatePointer (0.5, 0.5) (0, 0)
300 -- >> updatePointer (Relative 0.5 0.5)
304 { activeBorderColor = "#7C7C7C"
305 , activeColor = "#000000"
306 , activeTextColor = "#00FF00"
307 , inactiveBorderColor = "#7C7C7C"
308 , inactiveColor = "#000000"
309 , inactiveTextColor = "#EEEEEE"
310 , fontName = "Hack 7"
313 barSpawner :: ScreenId -> IO StatusBarConfig
314 barSpawner 0 = pure $ topXmobar <> traySB
315 --barSpawner 1 = pure $ xmobar1
316 barSpawner _ = pure $ topXmobar -- nothing on the rest of the screens
318 -- Display properties of the root window:
319 -- xprop -display $DISPLAY -root
320 topXmobar = statusBarPropTo "_XMONAD_XMOBAR0" "xmobar -x 0 ~/.config/xmonad/xmobar0.hs" (pure topPP)
324 { ppCurrent = xmobarColor "black" "#CCCCCC"
325 , ppHidden = xmobarColor "#CCCCCC" "black"
326 , ppHiddenNoWindows = xmobarColor "#606060" "black"
327 , ppLayout = \s -> xmobarColor "black" "#606060" $
329 "ResizableTall" -> " | "
330 "Mirror ResizableTall" -> " - "
331 "Tabbed Simplest" -> " + "
332 "Magnifier Grid" -> " ~ "
338 , ppTitle = xmobarColor "white" "black" . shorten 50
339 , ppUrgent = xmobarColor "yellow" "black"
343 traySB :: StatusBarConfig
350 , "--distancefrom top,right"
354 , "--monitor primary"
357 , "--transparent true"
358 , "--widthtype request"
364 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
365 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
367 isWindowSpaceVisible :: X (WindowSpace -> Bool)
368 isWindowSpaceVisible = do
369 vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
370 return (\w -> W.tag w `elem` vs)
372 spawnExec s = spawn $ List.unwords $ [ "exec" ] <> systemdCat <> [ s ]
373 systemdCat = [ "systemd-cat" , "--priority=info", "--stderr-priority=warning", "--level-prefix=false" , "--" ]
375 dtXPConfig :: XPConfig
378 , bgColor = "#282c34"
379 , fgColor = "#bbc2cf"
380 , bgHLight = "#c792ea"
381 , fgHLight = "#000000"
382 , borderColor = "#535974"
383 , promptBorderWidth = 0
384 , promptKeymap = dtXPKeymap
386 -- , position = CenteredAt { xpCenterY = 0.3, xpWidth = 0.3 }
391 , autoComplete = Just 100000 -- set Just 100000 for .1 sec
392 , showCompletionOnTab = False
393 -- , searchPredicate = isPrefixOf
394 , searchPredicate = fuzzyMatch
395 , defaultPrompter = id $ List.map Char.toUpper -- change prompt to UPPER
396 -- , defaultPrompter = unwords . map reverse . words -- reverse the prompt
397 -- , defaultPrompter = drop 5 .id (++ "XXXX: ") -- drop first 5 chars of prompt and add XXXX:
398 , alwaysHighlight = True
399 , maxComplRows = Nothing -- set to 'Just 5' for 5 rows
402 dtXPKeymap :: Map.Map (KeyMask,KeySym) (XP ())
403 dtXPKeymap = Map.fromList $
404 List.map (first $ (,) controlMask) -- control + <key>
405 [ (xK_z, killBefore) -- kill line backwards
406 , (xK_k, killAfter) -- kill line forwards
407 , (xK_a, startOfLine) -- move to the beginning of the line
408 , (xK_e, endOfLine) -- move to the end of the line
409 , (xK_m, deleteString Next) -- delete a character foward
410 , (xK_b, moveCursor Prev) -- move cursor forward
411 , (xK_f, moveCursor Next) -- move cursor backward
412 , (xK_BackSpace, killWord Prev) -- kill the previous word
413 , (xK_y, pasteString) -- paste a string
414 , (xK_g, quit) -- quit out of prompt
415 , (xK_bracketleft, quit)
418 List.map (first $ (,) altMask) -- meta key + <key>
419 [ (xK_BackSpace, killWord Prev) -- kill the prev word
420 , (xK_f, moveWord Next) -- move a word forward
421 , (xK_b, moveWord Prev) -- move a word backward
422 , (xK_d, killWord Next) -- kill the next word
423 , (xK_n, moveHistory W.focusUp') -- move up thru history
424 , (xK_p, moveHistory W.focusDown') -- move down thru history
427 List.map (first $ (,) 0) -- <key>
428 [ (xK_Return, setSuccess True >> setDone True)
429 , (xK_KP_Enter, setSuccess True >> setDone True)
430 , (xK_BackSpace, deleteString Prev)
431 , (xK_Delete, deleteString Next)
432 , (xK_Left, moveCursor Prev)
433 , (xK_Right, moveCursor Next)
434 , (xK_Home, startOfLine)
435 , (xK_End, endOfLine)
436 , (xK_Down, moveHistory W.focusUp')
437 , (xK_Up, moveHistory W.focusDown')