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