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.SetWMName
31 import XMonad.Hooks.UrgencyHook
32 import XMonad.Layout.Fullscreen
33 import XMonad.Layout.Grid
34 import XMonad.Layout.IndependentScreens
35 import XMonad.Layout.LayoutCombinators
36 import XMonad.Layout.Magnifier
37 import XMonad.Layout.MultiToggle
38 import XMonad.Layout.MultiToggle.Instances
39 import XMonad.Layout.NoBorders
40 import XMonad.Layout.ResizableTile
41 import XMonad.Layout.Spiral
42 import XMonad.Layout.Tabbed
43 import XMonad.Layout.ThreeColumns
44 import XMonad.Util.Run(spawnPipe)
45 import XMonad.Util.SpawnOnce
46 import qualified XMonad.StackSet as W
49 conf@XConfig{XMonad.modMask} =
51 let xK_XF86Backward = 0x1008ff26
52 xK_XF86Forward = 0x1008ff27 in
55 ((modMask, xK_Return), spawn $ XMonad.terminal conf)
57 , ((modMask, xK_Menu), spawn "exec rofi -show run -no-disable-history -run-command \"bash -c 'systemd-run --user -E PATH=\\\"\\$PATH\\\" --unit=app-org.rofi.\\$(systemd-escape \\\"{cmd}\\\")@\\$RANDOM -p CollectMode=inactive-or-failed {cmd}'\"")
58 -- Browse the filesystem
59 , ((modMask, xK_BackSpace), spawn "systemd-run --user -E PATH=\"$PATH\" --unit=app-org.rofi.caja@$RANDOM -p CollectMode=inactive-or-failed caja")
62 , ((0, xK_Pause), spawn "systemctl --user start xss-lock.service; xset s activate dpms force off")
64 -- Take a full screenshot
65 , ((0, xK_Print), spawn "cd ~/img/cap && scrot --quality 42 '%Y-%m-%d_%H-%M-%S.png' && caja ~/img/cap")
66 -- Take a selective screenshot
67 , ((modMask, xK_Print), spawn "select-screenshot")
70 , ((0, 0x1008FF12), spawn "pactl -- set-sink-mute @DEFAULT_SINK@ toggle") -- XF88AudioMute
71 , ((0, 0x1008FF11), spawn "pactl -- set-sink-volume @DEFAULT_SINK@ -5%") -- XF86AudioLowerVolume
72 , ((0, 0x1008FF13), spawn "pactl -- set-sink-volume @DEFAULT_SINK@ +5%") -- XF86AudioRaiseVolume
74 -- , ((0, 0x1008FF16), spawn "")
76 -- , ((0, 0x1008FF14), spawn "")
78 -- , ((0, 0x1008FF17), spawn "")
80 -- , ((0, 0x1008FF2C), spawn "eject -T")
82 -- Close focused window.
83 , ((modMask, xK_Escape), kill)
84 , ((modMask, xK_q), kill)
86 -- Temporarily maximize a window
87 , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
88 -- , ((modMask, xK_f), withFocused (sendMessage . maximizeRestore))
90 -- Cycle through the available layout algorithms
91 , ((modMask, 0x13bd), sendMessage NextLayout) -- oe (²)
92 , ((modMask, xK_ampersand), sendMessage $ JumpToLayout "ResizableTall") -- & (1)
93 , ((modMask, xK_eacute), sendMessage $ JumpToLayout "Mirror ResizableTall") -- é (2)
94 , ((modMask, xK_quotedbl), sendMessage $ JumpToLayout "Tabbed Simplest") -- ' (3)
95 , ((modMask, xK_apostrophe), sendMessage $ JumpToLayout "Magnifier Grid") -- " (4)
96 , ((modMask, xK_parenleft), sendMessage $ JumpToLayout "Spiral") -- ( (5)
97 , ((modMask, xK_minus), sendMessage $ JumpToLayout "Full") -- - (6)
98 , ((modMask, xK_egrave), sendMessage $ JumpToLayout "ThreeCol") -- è (7)
100 -- Reset the layouts on the current workspace to default
101 -- , ((modMask .|. shiftMask, xK_space), setLayout $ XMonad.layoutHook conf)
103 -- Resize viewed windows to the correct size.
104 , ((modMask, xK_n), refresh)
106 -- Move focus between windows
107 , ((modMask, xK_Tab), windows W.focusDown)
108 , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp)
109 , ((modMask, xK_i), windows W.focusUp)
110 , ((modMask, xK_k), windows W.focusDown)
112 -- Move focus to the master window
113 , ((modMask, xK_m), windows W.focusMaster)
114 -- Swap the focused window and the master window
115 , ((modMask, xK_space), windows W.swapMaster)
117 -- Swap the focused window with the next window.
118 --, ((modMask, xK_o), windows W.swapDown >> windows W.focusMaster)
119 -- Swap the focused window with the previous window.
120 , ((modMask, xK_m), windows W.swapUp >> windows W.focusMaster)
122 -- Push window back into tiling.
123 , ((modMask, xK_t), withFocused $ windows . W.sink)
125 -- Change the number of windows in the master area
126 , ((modMask, xK_Up), sendMessage $ IncMasterN 1)
127 , ((modMask, xK_Down), sendMessage $ IncMasterN (-1))
129 -- Toggle the status bar gap.
130 , ((modMask, xK_b), sendMessage ToggleStruts)
133 , ((modMask .|. shiftMask, xK_End), io exitSuccess)
135 , ((modMask, xK_End), restart "xmonad" True)
137 -- Workspace management
138 -- XF86Back: Switch to previous workspace
139 , ((0, xK_XF86Backward), prevWS)
140 , ((modMask, xK_j), prevWS)
141 -- Switch to next workspace
142 , ((0, xK_XF86Forward), nextWS)
143 , ((modMask, xK_l), nextWS)
144 -- XF86Back: Move the current client to the previous workspace and go there
145 , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
146 , ((modMask .|. shiftMask, xK_j), shiftToPrev >> prevWS)
147 -- Move the current client to the next workspace and go there
148 , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
149 , ((modMask .|. shiftMask, xK_l), shiftToNext >> nextWS)
150 -- Switch to previous workspace
151 -- Switch to next workspace
153 -- Move the current client to the previous workspace
154 , ((0 .|. shiftMask , xK_XF86Backward), shiftToPrev )
155 -- Move the current client to the next workspace
156 , ((0 .|. shiftMask , xK_XF86Forward), shiftToNext )
159 -- Toggle copying window on all workspaces (sticky window)
160 , ((modMask, xK_s), do
161 copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
163 [] -> windows copyToAll
164 _ -> killAllOtherCopies
167 -- Resize the master area
168 , ((modMask, xK_Left), sendMessage Shrink)
169 , ((modMask, xK_Right), sendMessage Expand)
170 -- Resize windows in ResizableTall mode
171 , ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
172 , ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
175 -- mod-[F1..F9], Switch to workspace N
176 -- mod-shift-[F1..F9], Move client to workspace N
177 [ ((m .|. modMask, k), windows $ f i)
178 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
179 zip (workspaces conf) [xK_1 ..]
180 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
182 {- NOTE: with Xinerama
183 [((m .|. modMask, k), windows $ onCurrentScreen f i)
184 | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
185 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
188 -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
189 -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
190 [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
191 | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
192 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
195 -- mod-shift-[F1..F9], Swap workspace with workspace N
196 -- mod-shift-[1..9], Swap workspace with workspace N
197 [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
198 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
199 zip (workspaces conf) [xK_1 ..]
201 {- NOTE: with Xinerama
202 [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
203 | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
208 XConfig{XMonad.modMask} =
211 -- mod-button1, Set the window to floating mode and move by dragging
212 ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
214 -- mod-button2, Raise the window to the top of the stack
215 , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
217 -- mod-button3, Set the window to floating mode and resize by dragging
218 , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
220 , ((modMask, button4), \_ -> windows W.focusUp)
221 , ((modMask, button5), \_ -> windows W.focusDown)
223 -- Cycle through workspaces
224 , ((controlMask .|. modMask, button5), nextNonEmptyWS)
225 , ((controlMask .|. modMask, button4), prevNonEmptyWS)
228 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
229 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
231 isWindowSpaceVisible :: X (WindowSpace -> Bool)
232 isWindowSpaceVisible = do
233 vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
234 return (\w -> W.tag w `elem` vs)
236 defaults xmproc _nScreens = docks $ ewmhFullscreen $ ewmh $
239 , focusFollowsMouse = True
240 , focusedBorderColor = "#00b10b"
241 , handleEventHook = handleEventHook def
243 , layoutHook = smartBorders $
244 mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
245 avoidStruts $ -- prevents windows from overlapping dock windows
246 let tall = ResizableTall 1 (1%200) (8%13) [] in tall
248 ||| tabbed shrinkText tabConfig
249 ||| magnifiercz (13%10) Grid
251 ||| noBorders (fullscreenFull Full)
252 ||| ThreeColMid 1 (1%200) (1%2)
253 -- ||| Tall 1 (3/100) (1/2)
254 , manageHook = composeAll
255 -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
256 [ isFullscreen --> doFullFloat
258 , manageDocks -- NOTE: do not tile dock windows
259 , resource =? "desktop_window" --> doIgnore
260 , className =? "Gimp" --> doFloat
261 , resource =? "gpicview" --> doSink
262 , className =? "mpv" --> doFloat
263 --, className =? "MPlayer" --> doShift "3:media" -- <+> doFloat
264 --, className =? "vlc" --> doShift "3:media"
265 , className =? "stalonetray" --> doIgnore
268 , mouseBindings = myMouseBindings
269 , normalBorderColor = "#7C7C7C"
270 , startupHook = setWMName "XMonad"
271 <+> spawn "wmname XMonad"
272 <+> spawn "xrdb -all .Xresources"
273 <+> spawn "sleep 1 && xmodmap .Xmodmap"
274 <+> spawn "xset r rate 250 25"
275 <+> spawn "xset b off"
276 <+> spawn "xhost local:root"
277 <+> spawn "setxkbmap -option keypad:pointerkeys"
278 -- <+> spawnOnce "exec arbtt-capture -r 60"
279 -- <+> spawnOnce "exec parcellite"
280 -- <+> spawnOnce "exec urxvtd -o -q"
281 -- <+> spawnOnce "exec xautolock"
282 -- <+> spawnOnce "exec redshift-gtk -l -45.7800:1.9700 -t 6500:3700"
283 <+> spawnOnce "exec nm-applet"
284 <+> spawnOnce (List.unwords
286 , "--background '#000000'"
287 , "--geometry 5x1-0+0"
290 , "--kludges force_icons_size"
291 , "--max-geometry 0x1+0+0"
293 , "--window-strut none"
295 , terminal = "urxvtc"
296 , workspaces = {- withScreens nScreens $ -}
297 {-["1:work","2:web","3:media"] ++-}
298 map show [1::Int .. 9]
300 dynamicLogWithPP xmobarPP
301 { ppCurrent = xmobarColor "black" "#CCCCCC"
302 , ppHidden = xmobarColor "#CCCCCC" "black"
303 , ppHiddenNoWindows = xmobarColor "#606060" "black"
304 , ppLayout = \s -> xmobarColor "black" "#606060" $
306 "ResizableTall" -> " | "
307 "Mirror ResizableTall" -> " - "
308 "Tabbed Simplest" -> " + "
309 "Magnifier Grid" -> " ~ "
314 , ppOutput = hPutStrLn xmproc
316 , ppTitle = xmobarColor "white" "black" . shorten 100
317 , ppUrgent = xmobarColor "yellow" "black"
320 >> updatePointer (0.5, 0.5) (0, 0)
321 -- >> updatePointer (Relative 0.5 0.5)
325 { activeBorderColor = "#7C7C7C"
326 , activeColor = "#000000"
327 , activeTextColor = "#00FF00"
328 , inactiveBorderColor = "#7C7C7C"
329 , inactiveColor = "#000000"
330 , inactiveTextColor = "#EEEEEE"
331 , fontName = "xft:DejaVu Sans Mono:pixelsize=9:antialias=true"
338 nScreens <- countScreens
339 xmproc <- spawnPipe "exec xmobar ~/.xmonad/xmobar.hs"
341 withUrgencyHook NoUrgencyHook $ -- dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] }
342 defaults xmproc (nScreens::Integer)