xmonad.hs 9.1 KB

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