xmonad.hs 6.2 KB

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