]> Git — Sourcephile - julm/julm-nix.git/blob - home-manager/profiles/xmonad/xmonad.hs
xmonad: use pactl instead of amixer (which no longer works)
[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 Data.List as List
6 import Data.Ratio
7 import System.Exit
8 import System.IO
9 import qualified Data.Map as Map
10
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
47
48 doSink = doF . W.sink =<< ask
49
50 myKeys
51 conf@XConfig{XMonad.modMask} =
52 Map.fromList $
53 let xK_XF86Backward = 0x1008ff26
54 xK_XF86Forward = 0x1008ff27 in
55 [
56 -- Start a terminal
57 ((modMask, xK_Return), spawn $ XMonad.terminal conf)
58 -- Launch a program
59 , ((modMask, xK_Menu), spawn "exec gmrun")
60 -- Browse the filesystem
61 , ((modMask, xK_BackSpace), spawn "caja")
62
63 -- Lock the screen
64 , ((0, xK_Pause), spawn "xset s activate dpms force off")
65
66 -- Take a full screenshot
67 , ((0, xK_Print), spawn "cd ~/img/cap && scrot --quality 42 '%Y-%m-%d_%H-%M-%S.png' && caja ~/img/cap")
68 -- Take a selective screenshot
69 , ((modMask, xK_Print), spawn "select-screenshot")
70
71 -- Volume control
72 , ((0, 0x1008FF12), spawn "pactl -- set-sink-mute 0 toggle") -- XF88AudioMute
73 , ((0, 0x1008FF11), spawn "pactl -- set-sink-volume 0 -5%") -- XF86AudioLowerVolume
74 , ((0, 0x1008FF13), spawn "pactl -- set-sink-volume 0 +5%") -- XF86AudioRaiseVolume
75 -- Audio previous
76 -- , ((0, 0x1008FF16), spawn "")
77 -- Play/pause
78 -- , ((0, 0x1008FF14), spawn "")
79 -- Audio next
80 -- , ((0, 0x1008FF17), spawn "")
81 -- Eject CD tray
82 -- , ((0, 0x1008FF2C), spawn "eject -T")
83
84 -- Close focused window.
85 , ((modMask, xK_Escape), kill)
86 , ((modMask, xK_q), kill)
87
88 -- Temporarily maximize a window
89 , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
90 -- , ((modMask, xK_f), withFocused (sendMessage . maximizeRestore))
91
92 -- Cycle through the available layout algorithms
93 , ((modMask, 0x13bd), sendMessage NextLayout) -- oe (²)
94 , ((modMask, xK_ampersand), sendMessage $ JumpToLayout "ResizableTall") -- & (1)
95 , ((modMask, xK_eacute), sendMessage $ JumpToLayout "Mirror ResizableTall") -- é (2)
96 , ((modMask, xK_quotedbl), sendMessage $ JumpToLayout "Tabbed Simplest") -- ' (3)
97 , ((modMask, xK_apostrophe), sendMessage $ JumpToLayout "Magnifier Grid") -- " (4)
98 , ((modMask, xK_parenleft), sendMessage $ JumpToLayout "Spiral") -- ( (5)
99 , ((modMask, xK_minus), sendMessage $ JumpToLayout "Full") -- - (6)
100 , ((modMask, xK_egrave), sendMessage $ JumpToLayout "ThreeCol") -- è (7)
101
102 -- Reset the layouts on the current workspace to default
103 -- , ((modMask .|. shiftMask, xK_space), setLayout $ XMonad.layoutHook conf)
104
105 -- Resize viewed windows to the correct size.
106 , ((modMask, xK_n), refresh)
107
108 -- Move focus between windows
109 , ((modMask, xK_Tab), windows W.focusDown)
110 , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp)
111 , ((modMask, xK_i), windows W.focusUp)
112 , ((modMask, xK_k), windows W.focusDown)
113
114 -- Move focus to the master window
115 , ((modMask, xK_m), windows W.focusMaster)
116 -- Swap the focused window and the master window
117 , ((modMask, xK_space), windows W.swapMaster)
118
119 -- Swap the focused window with the next window.
120 --, ((modMask, xK_o), windows W.swapDown >> windows W.focusMaster)
121 -- Swap the focused window with the previous window.
122 , ((modMask, xK_m), windows W.swapUp >> windows W.focusMaster)
123
124 -- Push window back into tiling.
125 , ((modMask, xK_t), withFocused $ windows . W.sink)
126
127 -- Change the number of windows in the master area
128 , ((modMask, xK_Up), sendMessage $ IncMasterN 1)
129 , ((modMask, xK_Down), sendMessage $ IncMasterN (-1))
130
131 -- Toggle the status bar gap.
132 , ((modMask, xK_b), sendMessage ToggleStruts)
133
134 -- Quit xmonad
135 , ((modMask .|. shiftMask, xK_End), io exitSuccess)
136 -- Restart xmonad
137 , ((modMask, xK_End), restart "xmonad" True)
138
139 -- Workspace management
140 -- XF86Back: Switch to previous workspace
141 , ((0, xK_XF86Backward), prevWS)
142 , ((modMask, xK_j), prevWS)
143 -- Switch to next workspace
144 , ((0, xK_XF86Forward), nextWS)
145 , ((modMask, xK_l), nextWS)
146 -- XF86Back: Move the current client to the previous workspace and go there
147 , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
148 , ((modMask .|. shiftMask, xK_j), shiftToPrev >> prevWS)
149 -- Move the current client to the next workspace and go there
150 , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
151 , ((modMask .|. shiftMask, xK_l), shiftToNext >> nextWS)
152 -- Switch to previous workspace
153 -- Switch to next workspace
154 {-
155 -- Move the current client to the previous workspace
156 , ((0 .|. shiftMask , xK_XF86Backward), shiftToPrev )
157 -- Move the current client to the next workspace
158 , ((0 .|. shiftMask , xK_XF86Forward), shiftToNext )
159 -}
160
161 -- Toggle copying window on all workspaces (sticky window)
162 , ((modMask, xK_s), do
163 copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
164 case copies of
165 [] -> windows copyToAll
166 _ -> killAllOtherCopies
167 )
168
169 -- Resize the master area
170 , ((modMask, xK_Left), sendMessage Shrink)
171 , ((modMask, xK_Right), sendMessage Expand)
172 -- Resize windows in ResizableTall mode
173 , ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
174 , ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
175 ] ++
176
177 -- mod-[F1..F9], Switch to workspace N
178 -- mod-shift-[F1..F9], Move client to workspace N
179 [ ((m .|. modMask, k), windows $ f i)
180 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
181 zip (workspaces conf) [xK_1 ..]
182 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
183 ] ++
184 {- NOTE: with Xinerama
185 [((m .|. modMask, k), windows $ onCurrentScreen f i)
186 | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
187 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
188 -}
189
190 -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
191 -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
192 [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
193 | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
194 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
195 ] ++
196
197 -- mod-shift-[F1..F9], Swap workspace with workspace N
198 -- mod-shift-[1..9], Swap workspace with workspace N
199 [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
200 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
201 zip (workspaces conf) [xK_1 ..]
202 ]
203 {- NOTE: with Xinerama
204 [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
205 | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
206 -}
207
208
209 myMouseBindings
210 XConfig{XMonad.modMask} =
211 Map.fromList
212 [
213 -- mod-button1, Set the window to floating mode and move by dragging
214 ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
215
216 -- mod-button2, Raise the window to the top of the stack
217 , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
218
219 -- mod-button3, Set the window to floating mode and resize by dragging
220 , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
221
222 , ((modMask, button4), \_ -> windows W.focusUp)
223 , ((modMask, button5), \_ -> windows W.focusDown)
224
225 -- Cycle through workspaces
226 , ((controlMask .|. modMask, button5), nextNonEmptyWS)
227 , ((controlMask .|. modMask, button4), prevNonEmptyWS)
228 ]
229 where
230 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
231 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
232
233 isWindowSpaceVisible :: X (WindowSpace -> Bool)
234 isWindowSpaceVisible = do
235 vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
236 return (\w -> W.tag w `elem` vs)
237
238 defaults xmproc _nScreens = ewmh $
239 azertyConfig
240 { borderWidth = 1
241 , focusFollowsMouse = True
242 , focusedBorderColor = "#00b10b"
243 , handleEventHook = handleEventHook def
244 <+> XMonad.Hooks.EwmhDesktops.fullscreenEventHook
245 <+> XMonad.Layout.Fullscreen.fullscreenEventHook
246 <+> docksEventHook
247 -- causes new docks to appear immediately,
248 -- instead of waiting for the next focus change.
249 , keys = myKeys
250 , layoutHook = smartBorders $
251 mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
252 avoidStruts $ -- prevents windows from overlapping dock windows
253 let tall = ResizableTall 1 (1%200) (8%13) [] in tall
254 ||| Mirror tall
255 ||| tabbed shrinkText tabConfig
256 ||| magnifiercz (13%10) Grid
257 ||| spiral (6%7)
258 ||| noBorders (fullscreenFull Full)
259 ||| ThreeColMid 1 (1%200) (1%2)
260 -- ||| Tall 1 (3/100) (1/2)
261 , manageHook = composeAll
262 -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
263 [ isFullscreen --> doFullFloat
264 , manageHook def
265 , manageDocks -- NOTE: do not tile dock windows
266 , resource =? "desktop_window" --> doIgnore
267 , className =? "Gimp" --> doFloat
268 , resource =? "gpicview" --> doSink
269 , className =? "mpv" --> doFloat
270 --, className =? "MPlayer" --> doShift "3:media" -- <+> doFloat
271 --, className =? "vlc" --> doShift "3:media"
272 , className =? "stalonetray" --> doIgnore
273 ]
274 , modMask = mod4Mask
275 , mouseBindings = myMouseBindings
276 , normalBorderColor = "#7C7C7C"
277 , startupHook = setWMName "XMonad"
278 <+> spawn "wmname XMonad"
279 <+> spawn "xrdb -all .Xresources"
280 <+> spawn "sleep 1 && xmodmap .Xmodmap"
281 <+> spawn "xset r rate 250 25"
282 <+> spawn "xset b off"
283 <+> spawn "xhost local:root"
284 <+> spawn "setxkbmap -option keypad:pointerkeys"
285 -- <+> spawnOnce "exec arbtt-capture -r 60"
286 -- <+> spawnOnce "exec parcellite"
287 -- <+> spawnOnce "exec urxvtd -o -q"
288 -- <+> spawnOnce "exec xautolock"
289 -- <+> spawnOnce "exec redshift-gtk -l -45.7800:1.9700 -t 6500:3700"
290 <+> spawnOnce "exec nm-applet"
291 <+> spawnOnce (List.unwords
292 [ "exec stalonetray"
293 , "--background '#000000'"
294 , "--geometry 5x1-0+0"
295 , "--icon-gravity E"
296 , "--icon-size 16"
297 , "--kludges force_icons_size"
298 , "--max-geometry 0x1+0+0"
299 , "--skip-taskbar"
300 , "--window-strut none"
301 ])
302 , terminal = "urxvtc"
303 , workspaces = {- withScreens nScreens $ -}
304 {-["1:work","2:web","3:media"] ++-}
305 map show [1::Int .. 9]
306 , logHook =
307 dynamicLogWithPP xmobarPP
308 { ppCurrent = xmobarColor "black" "#CCCCCC"
309 , ppHidden = xmobarColor "#CCCCCC" "black"
310 , ppHiddenNoWindows = xmobarColor "#606060" "black"
311 , ppLayout = \s -> xmobarColor "black" "#606060" $
312 case s of
313 "ResizableTall" -> " | "
314 "Mirror ResizableTall" -> " - "
315 "Tabbed Simplest" -> " + "
316 "Magnifier Grid" -> " ~ "
317 "Spiral" -> " @ "
318 "Full" -> " O "
319 "ThreeCol" -> " # "
320 _ -> s
321 , ppOutput = hPutStrLn xmproc
322 , ppSep = " "
323 , ppTitle = xmobarColor "white" "black" . shorten 100
324 , ppUrgent = xmobarColor "yellow" "black"
325 , ppWsSep = " "
326 }
327 >> updatePointer (0.5, 0.5) (0, 0)
328 -- >> updatePointer (Relative 0.5 0.5)
329 }
330 where
331 tabConfig = def
332 { activeBorderColor = "#7C7C7C"
333 , activeColor = "#000000"
334 , activeTextColor = "#00FF00"
335 , inactiveBorderColor = "#7C7C7C"
336 , inactiveColor = "#000000"
337 , inactiveTextColor = "#EEEEEE"
338 }
339
340 --
341 -- Run xmonad
342 --
343 main = do
344 nScreens <- countScreens
345 xmproc <- spawnPipe "exec xmobar ~/.xmonad/xmobar.hs"
346 xmonad $
347 withUrgencyHook NoUrgencyHook $ -- dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] }
348 defaults xmproc (nScreens::Integer)