xmonad.hs 6.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215
  1. import XMonad
  2. import XMonad.Hooks.DynamicLog(dynamicLogWithPP
  3. , xmobarPP
  4. , ppOutput
  5. , ppLayout
  6. , ppTitle)
  7. import XMonad.Hooks.ManageDocks(docks, docksEventHook, manageDocks, avoidStruts)
  8. import XMonad.Util.Run(spawnPipe, hPutStrLn, runProcessWithInput)
  9. import XMonad.Util.SpawnOnce(spawnOnce)
  10. -- Layouts
  11. import XMonad.Layout.Spacing(smartSpacing)
  12. import XMonad.Layout.Tabbed(simpleTabbed)
  13. import XMonad.Layout.NoBorders(withBorder, smartBorders)
  14. import XMonad.Layout.IndependentScreens(countScreens)
  15. -- Shutdown commands and keys
  16. import Data.Map(fromList)
  17. import XMonad.Util.EZConfig(removeKeys)
  18. -- For starting up a list of programs
  19. import Data.List(elemIndex, foldl1')
  20. import qualified XMonad.StackSet as W
  21. import qualified Data.Map as M
  22. import XMonad.Config.Kde(kde4Config, desktopLayoutModifiers)
  23. import XMonad.Hooks.EwmhDesktops(ewmh, fullscreenEventHook)
  24. myModMask = mod4Mask
  25. myTerminal = "konsole"
  26. -- Only show workspaces on xmobar, as everything else will be on KDE's panels
  27. myPP = xmobarPP { ppTitle = \_ -> ""
  28. , ppLayout = \_ -> ""}
  29. -- Make xmobar workspaces clickable
  30. xmobarEscape = concatMap doubleLts
  31. where doubleLts '<' = "<<"
  32. doubleLts x = [x]
  33. myWorkspaces = clickable . (map xmobarEscape) $ map show [1..9]
  34. where
  35. clickable l = [ "<action=xdotool key super+" ++ show (n) ++ ">" ++ ws ++ "</action>" |
  36. (i,ws) <- zip [1..9] l,
  37. let n = i ]
  38. main = do
  39. -- Spawn an xmobar on each screen
  40. nScreen <- countScreens
  41. xmprocs <- mapM (\dis -> spawnPipe ("xmobar -x " ++ show dis)) [0..nScreen-1]
  42. xmonad $ ewmh $ docks $ kde4Config {
  43. manageHook = manageDocks <+> myManageHook <+> manageHook kde4Config
  44. , workspaces = myWorkspaces
  45. , layoutHook = avoidStruts $ desktopLayoutModifiers $ smartBorders $
  46. (smartSpacing 5 $ withBorder 2 $ Tall 1 (3/100) (1/2)) |||
  47. (smartSpacing 5 $ withBorder 2 $ Mirror (Tall 1 (3/100) (1/2))) |||
  48. -- Full |||
  49. -- Tabs are bugged/don't work in ewmh. On the
  50. -- bright side, it makes a window float over KDE's
  51. -- bar, which is what I want fullscreen to do.
  52. -- It's not a bug, it's a feature.
  53. simpleTabbed
  54. -- Write signals to all xmobars.
  55. , logHook = dynamicLogWithPP myPP {
  56. ppOutput = \s -> sequence_ [hPutStrLn h s | h <- xmprocs]
  57. }
  58. , startupHook = sequence_ [spawnOnce s | s <- startupList]
  59. , handleEventHook = handleEventHook kde4Config <+> fullscreenEventHook <+> docksEventHook
  60. , modMask = mod4Mask
  61. , keys = \c -> myKeys c `M.union` keys kde4Config c
  62. }
  63. `removeKeys` myRemoveKeys
  64. myKeys conf@(XConfig {XMonad.modMask = myModMask}) = M.fromList $
  65. -- extra programs
  66. [ ((myModMask, xK_x),
  67. spawn "emacsclient -c")
  68. , ((myModMask, xK_z),
  69. spawn "firefox-nightly")
  70. , ((myModMask, xK_m),
  71. spawn ":")
  72. -- TODO put social stuff here (Discord, Riot) and open it on a particular workspace
  73. -- defaults
  74. -- Spawn terminal.
  75. , ((myModMask .|. shiftMask, xK_Return),
  76. spawn myTerminal)
  77. -- Close focused window.
  78. , ((myModMask .|. shiftMask, xK_c),
  79. kill)
  80. -- Cycle through the available layout algorithms.
  81. , ((myModMask, xK_space),
  82. sendMessage NextLayout)
  83. -- Reset the layouts on the current workspace to default.
  84. , ((myModMask .|. shiftMask, xK_space),
  85. setLayout $ XMonad.layoutHook conf)
  86. -- Resize viewed windows to the correct size.
  87. , ((myModMask, xK_n),
  88. refresh)
  89. -- Move focus to the next window.
  90. , ((myModMask, xK_Tab),
  91. windows W.focusDown)
  92. -- Move focus to the next window.
  93. , ((myModMask, xK_j),
  94. windows W.focusDown)
  95. -- Move focus to the previous window.
  96. , ((myModMask, xK_k),
  97. windows W.focusUp )
  98. -- Move focus to the master window.
  99. , ((myModMask, xK_m),
  100. windows W.focusMaster )
  101. -- Swap the focused window and the master window.
  102. , ((myModMask, xK_Return),
  103. windows W.swapMaster)
  104. -- Swap the focused window with the next window.
  105. , ((myModMask .|. shiftMask, xK_j),
  106. windows W.swapDown )
  107. -- Swap the focused window with the previous window.
  108. , ((myModMask .|. shiftMask, xK_k),
  109. windows W.swapUp )
  110. -- Shrink the master area.
  111. , ((myModMask, xK_h),
  112. sendMessage Shrink)
  113. -- Expand the master area.
  114. , ((myModMask, xK_l),
  115. sendMessage Expand)
  116. -- Push window back into tiling.
  117. , ((myModMask, xK_t),
  118. withFocused $ windows . W.sink)
  119. -- Increment the number of windows in the master area.
  120. , ((myModMask, xK_comma),
  121. sendMessage (IncMasterN 1))
  122. -- Decrement the number of windows in the master area.
  123. , ((myModMask, xK_period),
  124. sendMessage (IncMasterN (-1)))
  125. -- Toggle the status bar gap.
  126. -- Restart xmonad.
  127. , ((myModMask, xK_q),
  128. restart "xmonad" True)
  129. ]
  130. ++
  131. -- mod-[1..9], Switch to workspace N
  132. -- mod-shift-[1..9], Move client to workspace N
  133. [ ((m .|. myModMask, k), windows $ f i)
  134. | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
  135. , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
  136. ]
  137. ++
  138. -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
  139. -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
  140. [ ((m .|. myModMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
  141. | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
  142. , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
  143. ]
  144. myRemoveKeys =
  145. [ (mod4Mask, xK_Tab)
  146. , (mod4Mask .|. shiftMask, xK_Tab)
  147. , (mod4Mask, xK_p)
  148. ]
  149. myManageHook = composeAll . concat $
  150. [ [ className =? c --> doFloat | c <- myFloats]
  151. , [ title =? p --> doFloat | p <- plasmaWindows]
  152. ]
  153. where myFloats = ["Gimp"]
  154. plasmaWindows =
  155. [ "yakuake"
  156. , "Yakuake"
  157. , "Kmix"
  158. , "kmix"
  159. , "plasma"
  160. , "Plasma"
  161. , "plasma-desktop"
  162. , "Plasma-desktop"
  163. , "krunner"
  164. , "ksplashsimple"
  165. , "ksplashqml"
  166. , "ksplashx"
  167. ]
  168. startupList :: [String]
  169. startupList =
  170. [ "compton"
  171. , "nextcloud"
  172. -- TODO find a way around this dirty hack
  173. , "sleep 5 && for i in `xdotool search --all --name xmobar`; do xdotool windowraise $i; done"
  174. ]