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