]> Git — Sourcephile - julm/julm-nix.git/blob - home-manager/profiles/xmonad/xmonad.hs
nix: override lanzaboote's input to avoid pulling yet another nixpkgs
[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 qualified Data.Char as Char
6 import Data.List as List
7 import Data.Ratio
8 import System.Exit
9 import qualified Data.Map as Map
10 import Control.Arrow (first)
11
12 -- import XMonad.Actions.DwmPromote
13 -- import XMonad.Actions.Warp
14 -- import XMonad.Layout.Maximize
15 -- import XMonad.Layout.Monitor
16 -- import XMonad.Layout.ResizableTile
17 -- import XMonad.Layout.TabBarDecoration
18 -- import XMonad.Util.EZConfig
19 -- import XMonad.Util.EZConfig(additionalKeys)
20 -- import XMonad.Util.WorkspaceCompare
21 import XMonad hiding ((|||))
22 import XMonad.Actions.CopyWindow
23 import XMonad.Actions.CycleWS
24 import XMonad.Actions.SwapWorkspaces
25 import XMonad.Actions.UpdatePointer
26 import XMonad.Config.Azerty
27 import XMonad.Hooks.DynamicLog
28 import XMonad.Hooks.EwmhDesktops
29 import XMonad.Hooks.ManageDocks
30 import XMonad.Hooks.ManageHelpers
31 import XMonad.Hooks.Rescreen
32 import XMonad.Hooks.SetWMName
33 import XMonad.Hooks.StatusBar
34 import XMonad.Hooks.UrgencyHook
35 import XMonad.Layout.Columns
36 import XMonad.Layout.Fullscreen
37 import XMonad.Layout.Grid
38 import XMonad.Layout.LayoutCombinators
39 import XMonad.Layout.Magnifier
40 import XMonad.Layout.MultiToggle
41 import XMonad.Layout.MultiToggle.Instances
42 import XMonad.Layout.NoBorders
43 import XMonad.Layout.ResizableTile
44 import XMonad.Layout.Spiral
45 import XMonad.Layout.Tabbed
46 import XMonad.Layout.ThreeColumns
47 import XMonad.Layout.WindowNavigation
48 import XMonad.Operations (unGrab)
49 import XMonad.Prompt
50 import XMonad.Prompt.FuzzyMatch
51 import XMonad.Prompt.Pass
52 import XMonad.Prompt.Window
53 import XMonad.Util.SpawnOnce
54 import qualified XMonad.StackSet as W
55
56 main = xmonad $
57 withUrgencyHook NoUrgencyHook $
58 -- dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] } $
59 --addAfterRescreenHook myAfterRescreenHook $
60 addRandrChangeHook (spawnExec "autorandr --change") $
61 dynamicSBs barSpawner $
62 docks $
63 setEwmhActivateHook doAskUrgent $
64 ewmhFullscreen $
65 ewmh $
66 azertyConfig
67 { borderWidth = 1
68 , focusFollowsMouse = True
69 , focusedBorderColor = "#00b10b"
70 , handleEventHook = handleEventHook def
71 , keys = \conf@XConfig{XMonad.modMask} ->
72 Map.fromList $
73 let xK_XF86Backward = 0x1008ff26
74 xK_XF86Forward = 0x1008ff27 in
75 [
76 -- Start a terminal
77 ((modMask, xK_Return), spawnExec $ XMonad.terminal conf)
78 -- Launch a program
79 , ((modMask, xK_Menu), spawnCommand)
80 , ((modMask, xK_space), spawnCommand)
81 -- Browse the filesystem
82 , ((modMask, xK_BackSpace), spawnExec "systemd-run --user --unit=app-org.rofi.caja@$RANDOM -p CollectMode=inactive-or-failed caja")
83
84 -- Lock the screen
85 , ((0, xK_Pause), unGrab >> spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
86 , ((modMask, xK_Delete), unGrab >> spawnExec "loginctl lock-session \"$XDG_SESSION_ID\"")
87
88 -- Take a full screenshot
89 , ((0, xK_Print), spawn "mkdir -p ~/Images/screenshots && scrot --quality 42 ~/Images/screenshots/'%Y-%m-%d_%H-%M-%S.png' && caja ~/Images/screenshots")
90 -- Take a selective screenshot
91 , ((modMask, xK_Print), spawn "select-screenshot")
92
93 -- Volume control
94 , ((0, 0x1008FF12), spawnExec "pactl -- set-sink-mute @DEFAULT_SINK@ toggle") -- XF88AudioMute
95 , ((0, 0x1008FF11), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ -5%") -- XF86AudioLowerVolume
96 , ((0, 0x1008FF13), spawnExec "pactl -- set-sink-volume @DEFAULT_SINK@ +5%") -- XF86AudioRaiseVolume
97 -- Audio previous
98 -- , ((0, 0x1008FF16), spawnExec "")
99 -- Play/pause
100 -- , ((0, 0x1008FF14), spawnExec "")
101 -- Audio next
102 -- , ((0, 0x1008FF17), spawnExec "")
103 -- Eject CD tray
104 -- , ((0, 0x1008FF2C), spawnExec "eject -T")
105
106 -- Close focused window.
107 , ((modMask, xK_Escape), kill)
108
109 -- Clipboard
110 , ((modMask, xK_c), spawnExec "clipster --select --primary")
111
112 -- Temporarily maximize a window
113 , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle FULL)
114 -- , ((modMask, xK_f), withFocused (sendMessage . maximizeRestore))
115
116 -- Cycle through the available layout algorithms
117 , ((modMask, 0x13bd), sendMessage NextLayout) -- oe (²)
118 , ((modMask, xK_ampersand), sendMessage $ JumpToLayout "ResizableTall") -- & (1)
119 , ((modMask, xK_eacute), sendMessage $ JumpToLayout "Mirror ResizableTall") -- é (2)
120 , ((modMask, xK_quotedbl), sendMessage $ JumpToLayout "Tabbed Simplest") -- ' (3)
121 , ((modMask, xK_apostrophe), sendMessage $ JumpToLayout "Magnifier Grid") -- " (4)
122 , ((modMask, xK_parenleft), sendMessage $ JumpToLayout "Spiral") -- ( (5)
123 , ((modMask, xK_minus), sendMessage $ JumpToLayout "Full") -- - (6)
124 , ((modMask, xK_egrave), sendMessage $ JumpToLayout "ThreeCol") -- è (7)
125 , ((modMask, xK_underscore), sendMessage $ JumpToLayout "Columns") -- _ (8)
126
127 -- Reset the layouts on the current workspace to default
128 -- , ((modMask .|. shiftMask, xK_space), setLayout $ XMonad.layoutHook conf)
129
130 -- Resize viewed windows to the correct size.
131 , ((modMask, xK_n), refresh)
132
133 -- Move focus to the master window
134 , ((modMask .|. shiftMask, xK_exclam), windows W.focusMaster)
135 -- Swap the focused window and the master window
136 , ((modMask, xK_exclam), windows W.swapMaster)
137
138 -- Swap the focused window with the next window.
139 --, ((modMask, xK_o), windows W.swapDown >> windows W.focusMaster)
140 -- Swap the focused window with the previous window.
141 , ((modMask, xK_m), windows W.swapUp >> windows W.focusMaster)
142
143 -- Move focus
144 , ((modMask, xK_h), sendMessage $ Go L)
145 , ((modMask, xK_m), sendMessage $ Go R)
146 --, ((modMask, xK_i), sendMessage $ Go U)
147 --, ((modMask, xK_k), sendMessage $ Go D)
148 , ((modMask, xK_i), windows W.focusUp)
149 , ((modMask, xK_k), windows W.focusDown)
150 , ((modMask, xK_j), prevWS)
151 , ((modMask, xK_l), nextWS)
152 , ((modMask, xK_Left), windows W.focusUp)
153 , ((modMask, xK_Right), windows W.focusDown)
154 --, ((modMask, xK_Left), onGroup W.focusUp')
155 --, ((modMask, xK_Right), onGroup W.focusDown')
156 , ((modMask, xK_Up), sendMessage $ Go U)
157 , ((modMask, xK_Down), sendMessage $ Go D)
158
159 -- Move windows
160 , ((modMask .|. shiftMask, xK_h), sendMessage MoveLeft)
161 , ((modMask .|. shiftMask, xK_m), sendMessage MoveRight)
162 , ((modMask .|. controlMask, xK_h), sendMessage MoveLeft)
163 , ((modMask .|. controlMask, xK_m), sendMessage MoveRight)
164 , ((modMask .|. controlMask, xK_i), sendMessage MoveUp)
165 , ((modMask .|. controlMask, xK_k), sendMessage MoveDown)
166 , ((modMask .|. controlMask, xK_j), shiftToPrev >> prevWS)
167 , ((modMask .|. controlMask, xK_l), shiftToNext >> nextWS)
168
169 -- Resize windows
170 , ((modMask .|. shiftMask, xK_l), sendMessage HorizontalExpand)
171 , ((modMask .|. shiftMask, xK_j), sendMessage HorizontalShrink)
172 , ((modMask .|. shiftMask, xK_i), sendMessage VerticalExpand)
173 , ((modMask .|. shiftMask, xK_k), sendMessage VerticalShrink)
174
175 -- Push window back into tiling.
176 , ((modMask, xK_t), withFocused $ windows . W.sink)
177
178 -- Change the number of windows in the master area
179 , ((modMask, xK_Up), sendMessage $ IncMasterN 1)
180 , ((modMask, xK_Down), sendMessage $ IncMasterN (-1))
181
182 -- Toggle the status bar gap.
183 , ((modMask, xK_b), sendMessage ToggleStruts)
184
185 -- Quit xmonad
186 , ((modMask .|. shiftMask, xK_End), io exitSuccess)
187 -- Restart xmonad
188 , ((modMask, xK_End), restart "xmonad" True)
189
190 , ((modMask, xK_p), passPrompt promptConfig)
191 , ((modMask .|. controlMask, xK_p), passGeneratePrompt promptConfig)
192 , ((modMask .|. controlMask .|. shiftMask, xK_p), passRemovePrompt promptConfig)
193 , ((modMask, xK_Tab), windowMultiPrompt promptConfig [(Goto, allWindows), (Goto, wsWindows)])
194
195 -- Workspace management
196 -- XF86Back: Switch to previous workspace
197 , ((0, xK_XF86Backward), prevWS)
198 , ((modMask, xK_Page_Up), prevWS)
199 -- Switch to next workspace
200 , ((0, xK_XF86Forward), nextWS)
201 , ((modMask, xK_Page_Down), nextWS)
202 -- XF86Back: Move the current client to the previous workspace and go there
203 , ((modMask, xK_XF86Backward), shiftToPrev >> prevWS)
204 -- Move the current client to the next workspace and go there
205 , ((modMask, xK_XF86Forward), shiftToNext >> nextWS)
206 -- Switch to previous workspace
207 -- Switch to next workspace
208 {-
209 -- Move the current client to the previous workspace
210 , ((0 .|. shiftMask , xK_XF86Backward), shiftToPrev )
211 -- Move the current client to the next workspace
212 , ((0 .|. shiftMask , xK_XF86Forward), shiftToNext )
213 -}
214
215 -- Toggle copying window on all workspaces (sticky window)
216 , ((modMask, xK_s), do
217 copies <- wsContainingCopies -- NOTE: consider only hidden workspaces
218 case copies of
219 [] -> windows copyToAll
220 _ -> killAllOtherCopies
221 )
222
223 -- Resize the master area
224 --, ((modMask, xK_Left), sendMessage Shrink)
225 --, ((modMask, xK_Right), sendMessage Expand)
226 -- Resize windows in ResizableTall mode
227 --, ((modMask .|. shiftMask, xK_Left), sendMessage MirrorShrink)
228 --, ((modMask .|. shiftMask, xK_Right), sendMessage MirrorExpand)
229 ] ++
230
231 -- mod-[F1..F9], Switch to workspace N
232 -- mod-shift-[F1..F9], Move client to workspace N
233 [ ((m .|. modMask, k), windows $ f i)
234 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
235 zip (workspaces conf) [xK_1 ..]
236 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
237 ] ++
238 {- NOTE: with Xinerama
239 [((m .|. modMask, k), windows $ onCurrentScreen f i)
240 | (i, k) <- zip (workspaces' conf) [xK_F1 ..]
241 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] ]
242 -}
243
244 -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
245 -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
246 [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
247 | (key, sc) <- zip [xK_w, xK_e, xK_r] [0 ..]
248 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
249 ] ++
250
251 -- mod-shift-[F1..F9], Swap workspace with workspace N
252 -- mod-shift-[1..9], Swap workspace with workspace N
253 [ ((modMask .|. controlMask, k), windows $ swapWithCurrent i)
254 | (i, k) <- zip (workspaces conf) [xK_F1 ..] ++
255 zip (workspaces conf) [xK_1 ..]
256 ]
257 {- NOTE: with Xinerama
258 [((modMask .|. controlMask, k), windows $ onCurrentScreen swapWithCurrent i)
259 | (i, k) <- zip (workspaces' conf) [xK_F1 ..] ]
260 -}
261 , layoutHook = smartBorders $
262 mkToggle (NOBORDERS ?? FULL ?? EOT) $ -- enable temporarily maximizing a window
263 avoidStruts $ -- prevents windows from overlapping dock windows
264 let tall = ResizableTall 1 (1%200) (8%13) [] in
265 windowNavigation $
266 -- addTabs shrinkText tabBar (subLayout [] Simplest (Columns 1 []))
267 Columns 1 []
268 ||| tabbed shrinkText tabConfig
269 ||| tall
270 ||| Mirror tall
271 ||| magnifiercz (13%10) Grid
272 ||| spiral (6%7)
273 ||| noBorders (fullscreenFull Full)
274 ||| ThreeColMid 1 (1%200) (1%2)
275 -- ||| Tall 1 (3/100) (1/2)
276 , manageHook = composeAll
277 -- [ , isFullscreen --> (doF W.focusDown <+> doFullFloat)
278 [ isFullscreen --> doFullFloat
279 , manageHook def
280 , manageDocks -- NOTE: do not tile dock windows
281 , resource =? "desktop_window" --> doIgnore
282 , className =? "Gimp" --> doFloat
283 , resource =? "gpicview" --> doSink
284 , className =? "mpv" --> doFloat
285 , className =? "ultrastardx" --> doSink
286 --, className =? "MPlayer" --> doShift "3:media" -- <+> doFloat
287 --, className =? "vlc" --> doShift "3:media"
288 , className =? "trayer" --> doIgnore
289 ]
290 , modMask = mod4Mask
291 , mouseBindings = \XConfig{XMonad.modMask} ->
292 Map.fromList
293 [
294 -- mod-button1, Set the window to floating mode and move by dragging
295 ((modMask, button1), \w -> focus w >> mouseMoveWindow w)
296
297 -- mod-button2, Raise the window to the top of the stack
298 , ((modMask, button2), \w -> focus w >> windows W.swapMaster)
299
300 -- mod-button3, Set the window to floating mode and resize by dragging
301 , ((modMask, button3), \w -> focus w >> mouseResizeWindow w)
302
303 , ((modMask, button4), \_ -> windows W.focusUp)
304 , ((modMask, button5), \_ -> windows W.focusDown)
305
306 -- Cycle through workspaces
307 , ((controlMask .|. modMask, button5), nextNonEmptyWS)
308 , ((controlMask .|. modMask, button4), prevNonEmptyWS)
309 ]
310 , normalBorderColor = "#7C7C7C"
311 , startupHook = setWMName "XMonad"
312 <+> spawnExec "wmname XMonad"
313 <+> spawnExec "xrdb -all .Xresources"
314 <+> spawn "sleep 1 && xmodmap .Xmodmap"
315 <+> spawnExec "xset r rate 250 25"
316 <+> spawnExec "xset b off"
317 <+> spawnExec "xhost local:root"
318 <+> spawnExec "setxkbmap -option keypad:pointerkeys"
319 -- Useful for programs launched by rofi
320 <+> spawnExec (unwords [ "systemctl --user import-environment"
321 , "DBUS_SESSION_BUS_ADDRESS"
322 , "GDK_PIXBUF_MODULE_FILE"
323 , "GIO_EXTRA_MODULES"
324 , "GLFW_IM_MODULE"
325 , "GNUPGHOME"
326 , "GTK2_RC_FILES"
327 , "GTK_A11Y"
328 , "GTK_IM_MODULE"
329 , "GTK_PATH"
330 , "LANG"
331 , "LD_LIBRARY_PATH" -- For sane and pipewire
332 , "LIBEXEC_PATH"
333 , "NIX_PROFILES" -- fcitx5 does not work without it…
334 , "PASSWORD_STORE_DIR"
335 , "PATH"
336 , "QTWEBKIT_PLUGIN_PATH"
337 , "QT_IM_MODULE"
338 , "QT_PLUGIN_PATH"
339 , "SPEECHD_CMD"
340 , "SSH_ASKPASS"
341 , "XCURSOR_PATH"
342 , "XMODIFIERS"
343 ])
344 -- <+> spawnOnce "exec arbtt-capture -r 60"
345 -- <+> spawnOnce "exec parcellite"
346 -- <+> spawnOnce "exec xautolock"
347 -- <+> spawnOnce "exec redshift-gtk -l -45.7800:1.9700 -t 6500:3700"
348 <+> spawnOnce "exec nm-applet"
349 , terminal = "urxvtc"
350 , workspaces = {- withScreens nScreens $ -}
351 {-["1:work","2:web","3:media"] ++-}
352 map show [1::Int .. 9]
353 , logHook = updatePointer (0.5, 0.5) (0, 0)
354 -- >> updatePointer (Relative 0.5 0.5)
355 }
356 where
357 tabConfig = def
358 { activeBorderColor = "#7C7C7C"
359 , activeColor = "#000000"
360 , activeTextColor = "#00FF00"
361 , inactiveBorderColor = "#7C7C7C"
362 , inactiveColor = "#000000"
363 , inactiveTextColor = "#EEEEEE"
364 , fontName = "Hack 7"
365 }
366
367 spawnCommand = spawnExec "rofi -show run -no-disable-history -run-command \"bash -c 'systemd-run --user --unit=app-org.rofi.\\$(systemd-escape \\\"{cmd}\\\")@\\$RANDOM -p CollectMode=inactive-or-failed {cmd}'\""
368
369 barSpawner :: ScreenId -> X StatusBarConfig
370 barSpawner 0 = pure $ topXmobar <> traySB
371 --barSpawner 1 = pure $ xmobar1
372 barSpawner _ = pure $ topXmobar -- nothing on the rest of the screens
373
374 -- Display properties of the root window:
375 -- xprop -display $DISPLAY -root
376 topXmobar = statusBarPropTo "_XMONAD_XMOBAR0" "xmobar -x 0 ~/.config/xmonad/xmobar0.hs" (pure topPP)
377 where
378 topPP =
379 xmobarPP
380 { ppCurrent = xmobarColor "black" "#CCCCCC"
381 , ppHidden = xmobarColor "#CCCCCC" "black"
382 , ppHiddenNoWindows = xmobarColor "#606060" "black"
383 , ppLayout = \s -> xmobarColor "black" "#606060" $
384 case s of
385 "Columns" -> " \" "
386 "ResizableTall" -> " | "
387 "Mirror ResizableTall" -> " - "
388 "Tabbed Simplest" -> " + "
389 "Magnifier Grid" -> " ~ "
390 "Spiral" -> " @ "
391 "Full" -> " O "
392 "ThreeCol" -> " # "
393 _ -> s
394 , ppSep = " "
395 , ppTitle = xmobarColor "white" "black" . shorten 50
396 , ppUrgent = xmobarColor "yellow" "black"
397 , ppWsSep = " "
398 }
399
400 traySB :: StatusBarConfig
401 traySB =
402 statusBarGeneric
403 ( List.unwords
404 [ "trayer"
405 , "--align right"
406 , "--distance 0,0"
407 , "--distancefrom top,right"
408 , "--edge top"
409 , "--expand true"
410 , "--height 16"
411 , "--monitor primary"
412 , "--tint 0x000000"
413 , "--iconspacing 0"
414 , "--transparent true"
415 , "--widthtype request"
416 , "-l"
417 ]
418 )
419 mempty
420
421 nextNonEmptyWS _ = moveTo Next (WSIs ((not .) <$> isWindowSpaceVisible))
422 prevNonEmptyWS _ = moveTo Prev (WSIs ((not .) <$> isWindowSpaceVisible))
423
424 isWindowSpaceVisible :: X (WindowSpace -> Bool)
425 isWindowSpaceVisible = do
426 vs <- gets (map (W.tag . W.workspace) . W.visible . windowset)
427 return (\w -> W.tag w `elem` vs)
428
429 spawnExec s = spawn $ List.unwords $ [ "exec" ] <> systemdCat <> [ s ]
430 systemdCat = [ "systemd-cat" , "--priority=info", "--stderr-priority=warning", "--level-prefix=false" , "--" ]
431
432 promptConfig :: XPConfig
433 promptConfig = def
434 { font = "xft:monospace-"<>show fontSize
435 , bgColor = "black"
436 , fgColor = "grey"
437 , bgHLight = "green"
438 , fgHLight = "#000000"
439 , borderColor = "darkgreen"
440 , promptBorderWidth = 1
441 , promptKeymap = promptKeyMap
442 , position = CenteredAt { xpCenterY = 0.3, xpWidth = 0.5 }
443 , height = fontSize + 11
444 , historySize = 16
445 , historyFilter = id
446 , defaultText = ""
447 , autoComplete = Nothing -- Just 500000 -- nanoseconds
448 , showCompletionOnTab = False
449 , completionKey = (0, xK_Down)
450 , prevCompletionKey = (0, xK_Up)
451 , searchPredicate = fuzzyMatch -- isPrefixOf
452 , sorter = fuzzySort
453 , defaultPrompter = const ""
454 , alwaysHighlight = True
455 , maxComplRows = Just 10
456 , maxComplColumns = Just 1
457 , changeModeKey = xK_twosuperior
458 }
459 where
460 fontSize = 11
461
462 promptKeyMap :: Map.Map (KeyMask,KeySym) (XP ())
463 promptKeyMap = Map.fromList $
464 List.map (first $ (,) controlMask) -- control + <key>
465 [ (xK_z, killBefore) -- kill line backwards
466 , (xK_k, killAfter) -- kill line forwards
467 , (xK_u, killBefore) -- kill line backwards
468 , (xK_a, startOfLine) -- move to the beginning of the line
469 , (xK_e, endOfLine) -- move to the end of the line
470 , (xK_m, deleteString Next) -- delete a character foward
471 , (xK_b, moveCursor Prev) -- move cursor forward
472 , (xK_f, moveCursor Next) -- move cursor backward
473 , (xK_BackSpace, killWord Prev) -- kill the previous word
474 , (xK_y, pasteString) -- paste a string
475 , (xK_g, quit) -- quit out of prompt
476 , (xK_bracketleft, quit)
477 ]
478 ++
479 List.map (first $ (,) altMask) -- meta key + <key>
480 [ (xK_BackSpace, killWord Prev) -- kill the prev word
481 , (xK_f, moveWord Next) -- move a word forward
482 , (xK_b, moveWord Prev) -- move a word backward
483 , (xK_d, killWord Next) -- kill the next word
484 , (xK_n, moveHistory W.focusUp') -- move up through history
485 , (xK_p, moveHistory W.focusDown') -- move down through history
486 ]
487 ++
488 List.map (first $ (,) 0) -- <key>
489 [ (xK_Return, setSuccess True >> setDone True)
490 , (xK_KP_Enter, setSuccess True >> setDone True)
491 , (xK_BackSpace, deleteString Prev)
492 , (xK_Delete, deleteString Next)
493 , (xK_Left, moveCursor Prev)
494 , (xK_Right, moveCursor Next)
495 , (xK_Home, startOfLine)
496 , (xK_End, endOfLine)
497 , (xK_Down, moveHistory W.focusUp')
498 , (xK_Up, moveHistory W.focusDown')
499 , (xK_Escape, quit)
500 ]
501
502 altMask :: KeyMask
503 altMask = mod1Mask