]> Git — Sourcephile - julm/julm-nix.git/blob - home-manager/profiles/xmonad/xmonad.hs
nix: revamp home-manager profiles
[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 myKeys
49 conf@XConfig{XMonad.modMask} =
50 Map.fromList $
51 let xK_XF86Backward = 0x1008ff26
52 xK_XF86Forward = 0x1008ff27 in
53 [
54 -- Start a terminal
55 ((modMask, xK_Return), spawn $ XMonad.terminal conf)
56 -- Launch a program
57 , ((modMask, xK_Menu), spawn "exec gmrun")
58 -- Browse the filesystem
59 , ((modMask, xK_BackSpace), spawn "caja")
60
61 -- Lock the screen
62 , ((0, xK_Pause), spawn "xset s activate dpms force off")
63
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")
68
69 -- Volume control
70 , ((0, 0x1008FF12), spawn "amixer -q set Master toggle") -- XF88AudioMute
71 , ((0, 0x1008FF11), spawn "amixer -q set Master 5%-") -- XF86AudioLowerVolume
72 , ((0, 0x1008FF13), spawn "amixer -q set Master 5%+") -- XF86AudioRaiseVolume
73 , ((shiftMask, 0x1008FF12), spawn "amixer -q set PCM toggle") -- XF88AudioMute
74 , ((shiftMask, 0x1008FF11), spawn "amixer -q set PCM 5%-") -- XF86AudioLowerVolume
75 , ((shiftMask, 0x1008FF13), spawn "amixer -q set PCM 5%+") -- XF86AudioRaiseVolume
76 -- Audio previous
77 -- , ((0, 0x1008FF16), spawn "")
78 -- Play/pause
79 -- , ((0, 0x1008FF14), spawn "")
80 -- Audio next
81 -- , ((0, 0x1008FF17), spawn "")
82 -- Eject CD tray
83 -- , ((0, 0x1008FF2C), spawn "eject -T")
84
85 -- Close focused window.
86 , ((modMask, xK_Escape), kill)
87 , ((modMask, xK_q), kill)
88
89 -- Temporarily maximize a window
90 , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
91 -- , ((modMask, xK_f), withFocused (sendMessage . maximizeRestore))
92
93 -- Cycle through the available layout algorithms
94 , ((modMask, 0x13bd), sendMessage NextLayout) -- oe (²)
95 , ((modMask, xK_ampersand), sendMessage $ JumpToLayout "ResizableTall") -- & (1)
96 , ((modMask, xK_eacute), sendMessage $ JumpToLayout "Mirror ResizableTall") -- é (2)
97 , ((modMask, xK_quotedbl), sendMessage $ JumpToLayout "Tabbed Simplest") -- ' (3)
98 , ((modMask, xK_apostrophe), sendMessage $ JumpToLayout "Magnifier Grid") -- " (4)
99 , ((modMask, xK_parenleft), sendMessage $ JumpToLayout "Spiral") -- ( (5)
100 , ((modMask, xK_minus), sendMessage $ JumpToLayout "Full") -- - (6)
101 , ((modMask, xK_egrave), sendMessage $ JumpToLayout "ThreeCol") -- è (7)
102
103 -- Reset the layouts on the current workspace to default
104 -- , ((modMask .|. shiftMask, xK_space), setLayout $ XMonad.layoutHook conf)
105
106 -- Resize viewed windows to the correct size.
107 , ((modMask, xK_n), refresh)
108
109 -- Move focus between windows
110 , ((modMask, xK_Tab), windows W.focusDown)
111 , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp)
112 , ((modMask, xK_i), windows W.focusUp)
113 , ((modMask, xK_k), windows W.focusDown)
114
115 -- Move focus to the master window
116 , ((modMask, xK_m), windows W.focusMaster)
117 -- Swap the focused window and the master window
118 , ((modMask, xK_space), windows W.swapMaster)
119
120 -- Swap the focused window with the next window.
121 --, ((modMask, xK_o), windows W.swapDown >> windows W.focusMaster)
122 -- Swap the focused window with the previous window.
123 , ((modMask, xK_m), windows W.swapUp >> windows W.focusMaster)
124
125 -- Push window back into tiling.
126 , ((modMask, xK_t), withFocused $ windows . W.sink)
127
128 -- Change the number of windows in the master area
129 , ((modMask, xK_Up), sendMessage $ IncMasterN 1)
130 , ((modMask, xK_Down), sendMessage $ IncMasterN (-1))
131
132 -- Toggle the status bar gap.
133 , ((modMask, xK_b), sendMessage ToggleStruts)
134
135 -- Quit xmonad
136 , ((modMask .|. shiftMask, xK_End), io exitSuccess)
137 -- Restart xmonad
138 , ((modMask, xK_End), restart "xmonad" True)
139
140 -- Workspace management
141 -- XF86Back: Switch to previous workspace
142 , ((0, xK_XF86Backward), prevWS)
143 , ((modMask, xK_j), prevWS)
144 -- Switch to next workspace
145 , ((0, xK_XF86Forward), nextWS)
146 , ((modMask, xK_l), nextWS)
147 -- XF86Back: Move the current client to the previous workspace and go there
148 , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
149 , ((modMask .|. shiftMask, xK_j), shiftToPrev >> prevWS)
150 -- Move the current client to the next workspace and go there
151 , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
152 , ((modMask .|. shiftMask, xK_l), shiftToNext >> nextWS)
153 -- Switch to previous workspace
154 -- Switch to next workspace
155 {-
156 -- Move the current client to the previous workspace
157 , ((0 .|. shiftMask , xK_XF86Backward), shiftToPrev )
158 -- Move the current client to the next workspace
159 , ((0 .|. shiftMask , xK_XF86Forward), shiftToNext )
160 -}
161
162 -- Toggle copying window on all workspaces (sticky window)
163 , ((modMask, xK_s), do
164 copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
165 case copies of
166 [] -> windows copyToAll
167 _ -> killAllOtherCopies
168 )
169
170 -- Resize the master area
171 , ((modMask, xK_Left), sendMessage Shrink)
172 , ((modMask, xK_Right), sendMessage Expand)
173 -- Resize windows in ResizableTall mode
174 , ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
175 , ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
176 ] ++
177
178 -- mod-[F1..F9], Switch to workspace N
179 -- mod-shift-[F1..F9], Move client to workspace N
180 [ ((m .|. modMask, k), windows $ f i)
181 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
182 zip (workspaces conf) [xK_1 ..]
183 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
184 ] ++
185 {- NOTE: with Xinerama
186 [((m .|. modMask, k), windows $ onCurrentScreen f i)
187 | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
188 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
189 -}
190
191 -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
192 -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
193 [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
194 | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
195 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
196 ] ++
197
198 -- mod-shift-[F1..F9], Swap workspace with workspace N
199 -- mod-shift-[1..9], Swap workspace with workspace N
200 [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
201 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
202 zip (workspaces conf) [xK_1 ..]
203 ]
204 {- NOTE: with Xinerama
205 [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
206 | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
207 -}
208
209
210 myMouseBindings
211 XConfig{XMonad.modMask} =
212 Map.fromList
213 [
214 -- mod-button1, Set the window to floating mode and move by dragging
215 ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
216
217 -- mod-button2, Raise the window to the top of the stack
218 , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
219
220 -- mod-button3, Set the window to floating mode and resize by dragging
221 , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
222
223 , ((modMask, button4), \_ -> windows W.focusUp)
224 , ((modMask, button5), \_ -> windows W.focusDown)
225
226 -- Cycle through workspaces
227 , ((controlMask .|. modMask, button5), nextNonEmptyWS)
228 , ((controlMask .|. modMask, button4), prevNonEmptyWS)
229 ]
230 where
231 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
232 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
233
234 isWindowSpaceVisible :: X (WindowSpace -> Bool)
235 isWindowSpaceVisible = do
236 vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
237 return (\w -> W.tag w `elem` vs)
238
239 defaults xmproc _nScreens = ewmh $
240 azertyConfig
241 { borderWidth = 1
242 , focusFollowsMouse = True
243 , focusedBorderColor = "#00b10b"
244 , handleEventHook = handleEventHook def
245 <+> XMonad.Hooks.EwmhDesktops.fullscreenEventHook
246 <+> XMonad.Layout.Fullscreen.fullscreenEventHook
247 <+> docksEventHook
248 -- causes new docks to appear immediately,
249 -- instead of waiting for the next focus change.
250 , keys = myKeys
251 , layoutHook = smartBorders $
252 mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
253 avoidStruts $ -- prevents windows from overlapping dock windows
254 let tall = ResizableTall 1 (1%200) (8%13) [] in tall
255 ||| Mirror tall
256 ||| tabbed shrinkText tabConfig
257 ||| magnifiercz (13%10) Grid
258 ||| spiral (6%7)
259 ||| noBorders (fullscreenFull Full)
260 ||| ThreeColMid 1 (1%200) (1%2)
261 -- ||| Tall 1 (3/100) (1/2)
262 , manageHook = composeAll
263 -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
264 [ isFullscreen --> doFullFloat
265 , manageHook def
266 , manageDocks -- NOTE: do not tile dock windows
267 , resource =? "desktop_window" --> doIgnore
268 , className =? "Gimp" --> doFloat
269 , resource =? "gpicview" --> 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)