1 {-# LANGUAGE NamedFieldPuns #-}
2 {-# OPTIONS_GHC -Wall #-}
3 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
5 import Data.List as List
9 import qualified Data.Map as Map
11 -- import XMonad.Actions.DwmPromote
12 -- import XMonad.Actions.Warp
13 -- import XMonad.Layout.Maximize
14 -- import XMonad.Layout.Monitor
15 -- import XMonad.Layout.ResizableTile
16 -- import XMonad.Layout.TabBarDecoration
17 -- import XMonad.Util.EZConfig
18 -- import XMonad.Util.EZConfig(additionalKeys)
19 -- import XMonad.Util.WorkspaceCompare
20 import XMonad hiding ((|||))
21 import XMonad.Actions.CopyWindow
22 import XMonad.Actions.CycleWS
23 import XMonad.Actions.SwapWorkspaces
24 import XMonad.Actions.UpdatePointer
25 import XMonad.Config.Azerty
26 import XMonad.Hooks.DynamicLog
27 import XMonad.Hooks.EwmhDesktops
28 import XMonad.Hooks.ManageDocks
29 import XMonad.Hooks.ManageHelpers
30 import XMonad.Hooks.Rescreen
31 import XMonad.Hooks.SetWMName
32 import XMonad.Hooks.StatusBar
33 import XMonad.Hooks.UrgencyHook
34 import XMonad.Layout.Fullscreen
35 import XMonad.Layout.Grid
36 import XMonad.Layout.IndependentScreens
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.Util.Ungrab (unGrab)
47 --import XMonad.Operations (unGrab) -- TODO: needs xmonad 0.18
48 import XMonad.Util.SpawnOnce
49 import qualified XMonad.StackSet as W
52 withUrgencyHook NoUrgencyHook $
53 -- dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] } $
54 --addAfterRescreenHook myAfterRescreenHook $
55 addRandrChangeHook (spawnExec "autorandr --change") $
56 dynamicSBs barSpawner $
58 setEwmhActivateHook doAskUrgent $
63 , focusFollowsMouse = True
64 , focusedBorderColor = "#00b10b"
65 , handleEventHook = handleEventHook def
66 , keys = \conf@XConfig{XMonad.modMask} ->
68 let xK_XF86Backward = 0x1008ff26
69 xK_XF86Forward = 0x1008ff27 in
72 ((modMask, xK_Return), spawnExec $ XMonad.terminal conf)
74 , ((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}'\"")
75 -- Browse the filesystem
76 , ((modMask, xK_BackSpace), spawnExec "systemd-run --user --unit=app-org.rofi.caja@$RANDOM -p CollectMode=inactive-or-failed caja")
79 , ((0, xK_Pause), unGrab >> spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
81 -- Take a full screenshot
82 , ((0, xK_Print), spawn "cd ~/img/cap && scrot --quality 42 '%Y-%m-%d_%H-%M-%S.png' && caja ~/img/cap")
83 -- Take a selective screenshot
84 , ((modMask, xK_Print), spawn "select-screenshot")
87 , ((0, 0x1008FF12), spawnExec "pactl -- set-sink-mute @DEFAULT_SINK@ toggle") -- XF88AudioMute
88 , ((0, 0x1008FF11), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ -5%") -- XF86AudioLowerVolume
89 , ((0, 0x1008FF13), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ +5%") -- XF86AudioRaiseVolume
91 -- , ((0, 0x1008FF16), spawnExec "")
93 -- , ((0, 0x1008FF14), spawnExec "")
95 -- , ((0, 0x1008FF17), spawnExec "")
97 -- , ((0, 0x1008FF2C), spawnExec "eject -T")
99 -- Close focused window.
100 , ((modMask, xK_Escape), kill)
101 , ((modMask, xK_q), kill)
104 , ((modMask, xK_c), spawnExec "clipster --select --primary")
106 -- Temporarily maximize a window
107 , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
108 -- , ((modMask, xK_f), withFocused (sendMessage . maximizeRestore))
110 -- Cycle through the available layout algorithms
111 , ((modMask, 0x13bd), sendMessage NextLayout) -- oe (²)
112 , ((modMask, xK_ampersand), sendMessage $ JumpToLayout "ResizableTall") -- & (1)
113 , ((modMask, xK_eacute), sendMessage $ JumpToLayout "Mirror ResizableTall") -- é (2)
114 , ((modMask, xK_quotedbl), sendMessage $ JumpToLayout "Tabbed Simplest") -- ' (3)
115 , ((modMask, xK_apostrophe), sendMessage $ JumpToLayout "Magnifier Grid") -- " (4)
116 , ((modMask, xK_parenleft), sendMessage $ JumpToLayout "Spiral") -- ( (5)
117 , ((modMask, xK_minus), sendMessage $ JumpToLayout "Full") -- - (6)
118 , ((modMask, xK_egrave), sendMessage $ JumpToLayout "ThreeCol") -- è (7)
120 -- Reset the layouts on the current workspace to default
121 -- , ((modMask .|. shiftMask, xK_space), setLayout $ XMonad.layoutHook conf)
123 -- Resize viewed windows to the correct size.
124 , ((modMask, xK_n), refresh)
126 -- Move focus between windows
127 , ((modMask, xK_Tab), windows W.focusDown)
128 , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp)
129 , ((modMask, xK_i), windows W.focusUp)
130 , ((modMask, xK_k), windows W.focusDown)
132 -- Move focus to the master window
133 , ((modMask, xK_m), windows W.focusMaster)
134 -- Swap the focused window and the master window
135 , ((modMask, xK_space), windows W.swapMaster)
137 -- Swap the focused window with the next window.
138 --, ((modMask, xK_o), windows W.swapDown >> windows W.focusMaster)
139 -- Swap the focused window with the previous window.
140 , ((modMask, xK_m), windows W.swapUp >> windows W.focusMaster)
142 -- Push window back into tiling.
143 , ((modMask, xK_t), withFocused $ windows . W.sink)
145 -- Change the number of windows in the master area
146 , ((modMask, xK_Up), sendMessage $ IncMasterN 1)
147 , ((modMask, xK_Down), sendMessage $ IncMasterN (-1))
149 -- Toggle the status bar gap.
150 , ((modMask, xK_b), sendMessage ToggleStruts)
153 , ((modMask .|. shiftMask, xK_End), io exitSuccess)
155 , ((modMask, xK_End), restart "xmonad" True)
157 -- Workspace management
158 -- XF86Back: Switch to previous workspace
159 , ((0, xK_XF86Backward), prevWS)
160 , ((modMask, xK_j), prevWS)
161 -- Switch to next workspace
162 , ((0, xK_XF86Forward), nextWS)
163 , ((modMask, xK_l), nextWS)
164 -- XF86Back: Move the current client to the previous workspace and go there
165 , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
166 , ((modMask .|. shiftMask, xK_j), shiftToPrev >> prevWS)
167 -- Move the current client to the next workspace and go there
168 , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
169 , ((modMask .|. shiftMask, xK_l), shiftToNext >> nextWS)
170 -- Switch to previous workspace
171 -- Switch to next workspace
173 -- Move the current client to the previous workspace
174 , ((0 .|. shiftMask , xK_XF86Backward), shiftToPrev )
175 -- Move the current client to the next workspace
176 , ((0 .|. shiftMask , xK_XF86Forward), shiftToNext )
179 -- Toggle copying window on all workspaces (sticky window)
180 , ((modMask, xK_s), do
181 copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
183 [] -> windows copyToAll
184 _ -> killAllOtherCopies
187 -- Resize the master area
188 , ((modMask, xK_Left), sendMessage Shrink)
189 , ((modMask, xK_Right), sendMessage Expand)
190 -- Resize windows in ResizableTall mode
191 , ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
192 , ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
195 -- mod-[F1..F9], Switch to workspace N
196 -- mod-shift-[F1..F9], Move client to workspace N
197 [ ((m .|. modMask, k), windows $ f i)
198 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
199 zip (workspaces conf) [xK_1 ..]
200 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
202 {- NOTE: with Xinerama
203 [((m .|. modMask, k), windows $ onCurrentScreen f i)
204 | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
205 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
208 -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
209 -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
210 [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
211 | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
212 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
215 -- mod-shift-[F1..F9], Swap workspace with workspace N
216 -- mod-shift-[1..9], Swap workspace with workspace N
217 [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
218 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
219 zip (workspaces conf) [xK_1 ..]
221 {- NOTE: with Xinerama
222 [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
223 | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
225 , layoutHook = smartBorders $
226 mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
227 avoidStruts $ -- prevents windows from overlapping dock windows
228 let tall = ResizableTall 1 (1%200) (8%13) [] in
229 tabbed shrinkText tabConfig
232 ||| magnifiercz (13%10) Grid
234 ||| noBorders (fullscreenFull Full)
235 ||| ThreeColMid 1 (1%200) (1%2)
236 -- ||| Tall 1 (3/100) (1/2)
237 , manageHook = composeAll
238 -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
239 [ isFullscreen --> doFullFloat
241 , manageDocks -- NOTE: do not tile dock windows
242 , resource =? "desktop_window" --> doIgnore
243 , className =? "Gimp" --> doFloat
244 , resource =? "gpicview" --> doSink
245 , className =? "mpv" --> doFloat
246 --, className =? "MPlayer" --> doShift "3:media" -- <+> doFloat
247 --, className =? "vlc" --> doShift "3:media"
248 , className =? "trayer" --> doIgnore
251 , mouseBindings = \XConfig{XMonad.modMask} ->
254 -- mod-button1, Set the window to floating mode and move by dragging
255 ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
257 -- mod-button2, Raise the window to the top of the stack
258 , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
260 -- mod-button3, Set the window to floating mode and resize by dragging
261 , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
263 , ((modMask, button4), \_ -> windows W.focusUp)
264 , ((modMask, button5), \_ -> windows W.focusDown)
266 -- Cycle through workspaces
267 , ((controlMask .|. modMask, button5), nextNonEmptyWS)
268 , ((controlMask .|. modMask, button4), prevNonEmptyWS)
270 , normalBorderColor = "#7C7C7C"
271 , startupHook = setWMName "XMonad"
272 <+> spawnExec "wmname XMonad"
273 <+> spawnExec "xrdb -all .Xresources"
274 <+> spawn "sleep 1 && xmodmap .Xmodmap"
275 <+> spawnExec "xset r rate 250 25"
276 <+> spawnExec "xset b off"
277 <+> spawnExec "xhost local:root"
278 <+> spawnExec "setxkbmap -option keypad:pointerkeys"
279 -- Useful for programs launched by rofi
280 <+> spawnExec "systemctl --user import-environment GNUPGHOME PASSWORD_STORE_DIR PATH"
281 -- <+> spawnOnce "exec arbtt-capture -r 60"
282 -- <+> spawnOnce "exec parcellite"
283 -- <+> spawnOnce "exec xautolock"
284 -- <+> spawnOnce "exec redshift-gtk -l -45.7800:1.9700 -t 6500:3700"
285 <+> spawnOnce "exec nm-applet"
286 , terminal = "urxvtc"
287 , workspaces = {- withScreens nScreens $ -}
288 {-["1:work","2:web","3:media"] ++-}
289 map show [1::Int .. 9]
290 , logHook = updatePointer (0.5, 0.5) (0, 0)
291 -- >> updatePointer (Relative 0.5 0.5)
295 { activeBorderColor = "#7C7C7C"
296 , activeColor = "#000000"
297 , activeTextColor = "#00FF00"
298 , inactiveBorderColor = "#7C7C7C"
299 , inactiveColor = "#000000"
300 , inactiveTextColor = "#EEEEEE"
301 , fontName = "Hack 7"
304 barSpawner :: ScreenId -> IO StatusBarConfig
305 barSpawner 0 = pure $ topXmobar <> traySB
306 --barSpawner 1 = pure $ xmobar1
307 barSpawner _ = pure $ topXmobar -- nothing on the rest of the screens
309 -- Display properties of the root window:
310 -- xprop -display $DISPLAY -root
311 topXmobar = statusBarPropTo "_XMONAD_XMOBAR0" "xmobar -x 0 ~/.config/xmonad/xmobar0.hs" (pure topPP)
315 { ppCurrent = xmobarColor "black" "#CCCCCC"
316 , ppHidden = xmobarColor "#CCCCCC" "black"
317 , ppHiddenNoWindows = xmobarColor "#606060" "black"
318 , ppLayout = \s -> xmobarColor "black" "#606060" $
320 "ResizableTall" -> " | "
321 "Mirror ResizableTall" -> " - "
322 "Tabbed Simplest" -> " + "
323 "Magnifier Grid" -> " ~ "
329 , ppTitle = xmobarColor "white" "black" . shorten 50
330 , ppUrgent = xmobarColor "yellow" "black"
334 traySB :: StatusBarConfig
341 , "--distancefrom top,right"
345 , "--monitor primary"
348 , "--transparent true"
349 , "--widthtype request"
355 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
356 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
358 isWindowSpaceVisible :: X (WindowSpace -> Bool)
359 isWindowSpaceVisible = do
360 vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
361 return (\w -> W.tag w `elem` vs)
363 spawnExec s = spawn $ List.unwords $ [ "exec" ] <> systemdCat <> [ s ]
364 systemdCat = [ "systemd-cat" , "--priority=info", "--stderr-priority=warning", "--level-prefix=false" , "--" ]