xmonad.hs 9.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307
  1. import System.Posix.Env (getEnv)
  2. import Data.Maybe (maybe)
  3. import Control.Monad(when, liftM)
  4. import XMonad
  5. import XMonad.Config.Desktop
  6. import XMonad.Hooks.DynamicLog
  7. import XMonad.Hooks.ManageDocks
  8. import XMonad.Util.Run(spawnPipe, hPutStrLn, runProcessWithInput)
  9. -- Layouts
  10. import XMonad.Layout.Spacing(smartSpacing)
  11. import XMonad.Layout.Tabbed
  12. import XMonad.Layout.NoBorders
  13. import XMonad.Layout.IndependentScreens
  14. -- Shutdown commands and keys
  15. import Data.Map(fromList)
  16. import XMonad.Prompt
  17. import XMonad.Prompt.XMonad
  18. import XMonad.Prompt.ConfirmPrompt
  19. import System.Exit(ExitCode(ExitSuccess), exitWith)
  20. import XMonad.Util.EZConfig(additionalKeys, removeKeys)
  21. import XMonad.Util.Dmenu
  22. -- Brightness and audio keys
  23. import Graphics.X11.ExtraTypes.XF86
  24. import Data.List(elemIndex, foldl1')
  25. import qualified XMonad.StackSet as W
  26. import qualified Data.Map as M
  27. -- kde
  28. import XMonad.Config.Kde
  29. import XMonad.Hooks.EwmhDesktops
  30. myModMask = mod4Mask
  31. myTerminal = "konsole"
  32. -- Command to launch the bar.
  33. myBar = "xmobar"
  34. -- Custom PP, configure it as you like. It determines what is being written to the bar.
  35. myPP = xmobarPP { ppTitle = \_ -> ""
  36. , ppLayout = \_ -> ""}
  37. -- Key binding to toggle the gap for the bar.
  38. toggleStrutsKey XConfig {XMonad.modMask = modMask} = (modMask, xK_b)
  39. -- Main configuration, override the defaults to your liking.
  40. myConfig = defaultConfig { modMask = mod4Mask }
  41. main = do
  42. nScreen <- countScreens
  43. xmprocs <- mapM (\dis -> spawnPipe ("xmobar -x " ++ show dis)) [0..nScreen-1]
  44. xmonad $ ewmh $ docks $ kde4Config {
  45. -- manageHook = manageDocks <+> manageHook kde4Config <+> myManageHook
  46. -- manageHook = manageDocks <+> myManageHook <+> manageHook kde4Config
  47. manageHook = manageDocks <+> myManageHook
  48. -- { manageHook = manageDocks <+> manageHook thisDesktopConfig <+> myManageHook
  49. , layoutHook = avoidStruts $ desktopLayoutModifiers $ smartBorders $
  50. (smartSpacing 5 $ withBorder 2 $ Tall 1 (3/100) (1/2)) |||
  51. (smartSpacing 5 $ withBorder 2 $ Mirror (Tall 1 (3/100) (1/2))) |||
  52. -- Full |||
  53. -- Tabs are bugged/don't work in ewmh. On the
  54. -- bright side, it makes a window float over KDE's
  55. -- bar, which is what I want fullscreen to do.
  56. -- It's not a bug, it's a feature.
  57. simpleTabbed
  58. , logHook = dynamicLogWithPP myPP {ppOutput = \s -> sequence_ [hPutStrLn h s | h <- xmprocs]}
  59. -- , logHook = dynamicLogWithPP xmobarPP {
  60. -- ppOutput = hPutStrLn xmproc
  61. -- , ppTitle = xmobarColor "green" "" . shorten 50
  62. -- }
  63. -- , startupHook = startup (startupList ++ xmonadStartupList)
  64. , startupHook = startup startupList
  65. , handleEventHook = handleEventHook def <+> fullscreenEventHook <+> docksEventHook
  66. , modMask = mod4Mask
  67. , keys = \c -> mySetKeys c `M.union` keys kde4Config c
  68. } --`additionalKeys` (if session == "xmonad" then (myKeys ++ xmonadKeys) else myKeys)
  69. `removeKeys` myRemoveKeys
  70. xmonadStartupList =
  71. [ "feh --bg-scale ~/Owncloud/Backgrounds/Xmbindings.png"
  72. -- , "trayer --edge top --align right --SetDockType true --SetPartialStrut true --expand true --width 10 --transparent true --alpha 0 --tint 0x000000 --height 22"
  73. , "pasystray"
  74. , "xfce4-clipman"
  75. , "xbacklight -set 12"
  76. , "compton"
  77. , "xscreensaver -nosplash"
  78. ]
  79. mySetKeys conf@(XConfig {XMonad.modMask = myModMask}) =
  80. -- M.fromList $ myKeys ++ xmonadKeys
  81. M.fromList $ myKeys
  82. where
  83. -- xmonadKeys = [
  84. -- -- scrot
  85. -- ((controlMask, xK_Print), spawn "sleep 0.2; scrot -s")
  86. -- , ((0, xK_Print), spawn "scrot")
  87. --
  88. -- -- rofi
  89. -- , ((myModMask, xK_p ), spawn "rofi -show run")
  90. -- -- shutdown
  91. -- --, ((myModMask .|. shiftMask, xK_q),
  92. -- -- xmonadPrompt defaultXPConfig
  93. -- -- { promptKeymap = fromList
  94. -- -- [ ((0, xK_r), do
  95. -- -- spawn "emacsclient -e '(kill emacs)'"
  96. -- -- spawn "systemctl reboot")
  97. -- -- , ((0 , xK_s), do
  98. -- -- spawn "emacsclient -e '(kill emacs)'"
  99. -- -- spawn "sudo poweroff")
  100. -- -- , ((0, xK_e), do
  101. -- -- spawn "emacsclient -e '(kill emacs)'"
  102. -- -- io $ exitWith ExitSuccess)
  103. -- -- , ((0, xK_l), do
  104. -- -- spawn "xscreensaver-command -lock"
  105. -- -- quit)
  106. -- -- , ((0, xK_z), do
  107. -- -- spawn "xscreensaver-command -lock"
  108. -- -- spawn "systemctl suspend"
  109. -- -- quit)
  110. -- -- , ((0, xK_Escape), quit)
  111. -- -- ]
  112. -- -- , defaultText = "(r) Reboot, (s) Shutdown, (e) Exit, (l) Lock, (z) Sleep"
  113. -- -- })
  114. -- -- pulseaudio
  115. -- , ((0, xF86XK_AudioRaiseVolume),
  116. -- spawn "pactl set-sink-volume alsa_output.pci-0000_00_1f.3.analog-stereo +5%")
  117. -- , ((0, xF86XK_AudioLowerVolume),
  118. -- spawn "pactl set-sink-volume alsa_output.pci-0000_00_1f.3.analog-stereo -5%")
  119. -- , ((0, xF86XK_AudioMute),
  120. -- spawn "pactl set-sink-mute alsa_output.pci-0000_00_1f.3.analog-stereo toggle")
  121. --
  122. -- -- brightness
  123. -- , ((0, xF86XK_MonBrightnessUp),
  124. -- let
  125. -- returnValM = fmap init $ runProcessWithInput "xbacklight" [] ""
  126. -- in do
  127. -- currentBrightness <- returnValM
  128. -- if (read currentBrightness :: Double) == 0 then
  129. -- spawn "xbacklight -set 2"
  130. -- else
  131. -- spawn "xbacklight -inc 5")
  132. -- , ((0, xF86XK_MonBrightnessDown), spawn "xbacklight -dec 5")
  133. -- ]
  134. myKeys =
  135. [
  136. -- extra programs
  137. ((myModMask, xK_x),
  138. spawn "emacsclient -c")
  139. , ((myModMask, xK_z),
  140. spawn "firefox-nightly")
  141. , ((myModMask, xK_m),
  142. spawn ":"
  143. -- TODO put social stuff here (Discord, Riot) and open it on a particular workspace
  144. )
  145. -- defaults
  146. -- Spawn terminal.
  147. , ((myModMask .|. shiftMask, xK_Return),
  148. spawn myTerminal)
  149. -- Close focused window.
  150. , ((myModMask .|. shiftMask, xK_c),
  151. kill)
  152. -- Cycle through the available layout algorithms.
  153. , ((myModMask, xK_space),
  154. sendMessage NextLayout)
  155. -- Reset the layouts on the current workspace to default.
  156. , ((myModMask .|. shiftMask, xK_space),
  157. setLayout $ XMonad.layoutHook conf)
  158. -- Resize viewed windows to the correct size.
  159. , ((myModMask, xK_n),
  160. refresh)
  161. -- Move focus to the next window.
  162. , ((myModMask, xK_Tab),
  163. windows W.focusDown)
  164. -- Move focus to the next window.
  165. , ((myModMask, xK_j),
  166. windows W.focusDown)
  167. -- Move focus to the previous window.
  168. , ((myModMask, xK_k),
  169. windows W.focusUp )
  170. -- Move focus to the master window.
  171. , ((myModMask, xK_m),
  172. windows W.focusMaster )
  173. -- Swap the focused window and the master window.
  174. , ((myModMask, xK_Return),
  175. windows W.swapMaster)
  176. -- Swap the focused window with the next window.
  177. , ((myModMask .|. shiftMask, xK_j),
  178. windows W.swapDown )
  179. -- Swap the focused window with the previous window.
  180. , ((myModMask .|. shiftMask, xK_k),
  181. windows W.swapUp )
  182. -- Shrink the master area.
  183. , ((myModMask, xK_h),
  184. sendMessage Shrink)
  185. -- Expand the master area.
  186. , ((myModMask, xK_l),
  187. sendMessage Expand)
  188. -- Push window back into tiling.
  189. , ((myModMask, xK_t),
  190. withFocused $ windows . W.sink)
  191. -- Increment the number of windows in the master area.
  192. , ((myModMask, xK_comma),
  193. sendMessage (IncMasterN 1))
  194. -- Decrement the number of windows in the master area.
  195. , ((myModMask, xK_period),
  196. sendMessage (IncMasterN (-1)))
  197. -- Toggle the status bar gap.
  198. -- Restart xmonad.
  199. , ((myModMask, xK_q),
  200. restart "xmonad" True)
  201. ]
  202. ++
  203. -- mod-[1..9], Switch to workspace N
  204. -- mod-shift-[1..9], Move client to workspace N
  205. [((m .|. myModMask, k), windows $ f i)
  206. | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
  207. , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
  208. ++
  209. -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
  210. -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
  211. [((m .|. myModMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
  212. | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
  213. , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
  214. myRemoveKeys =
  215. [ (mod4Mask, xK_Tab)
  216. , (mod4Mask .|. shiftMask, xK_Tab)
  217. ]
  218. ++
  219. -- if s == "xmonad" then
  220. [(mod4Mask, xK_p)]
  221. -- else
  222. -- []
  223. myManageHook = composeAll . concat $
  224. [ [ className =? c --> doFloat | c <- myFloats]
  225. , [ title =? p --> doFloat | p <- plasmaWindows]
  226. ]
  227. where myFloats = ["Gimp"]
  228. plasmaWindows =
  229. [ "yakuake"
  230. , "Yakuake"
  231. , "Kmix"
  232. , "kmix"
  233. , "plasma"
  234. , "Plasma"
  235. , "plasma-desktop"
  236. , "Plasma-desktop"
  237. , "krunner"
  238. , "ksplashsimple"
  239. , "ksplashqml"
  240. , "ksplashx"
  241. , "xmobar"
  242. , "plasmashell"
  243. ]
  244. startupList :: [String]
  245. startupList =
  246. [ "compton"
  247. , "nextcloud"
  248. ]
  249. startup :: [String] -> X ()
  250. startup l = do
  251. foldl1' (>>) $ map (spawn . ifNotRunning) l
  252. -- Wrap a command in Bash that checks if it's running.
  253. ifNotRunning :: String -> String
  254. ifNotRunning s = "if [ `pgrep -c " ++ (basename s) ++ "` == 0 ]; then " ++ s ++ "; fi"
  255. -- Grab the program name from a command (everything up to the space,
  256. -- if there's a space). Doesn't work with escaped spaces.
  257. basename :: String -> String
  258. basename s = case elemIndex ' ' s of
  259. (Just n) -> take n s
  260. Nothing -> s