xmonad.hs 6.6 KB

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