xmonad.hs 9.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297
  1. import System.Posix.Env (getEnv)
  2. import Data.Maybe (maybe)
  3. import Control.Monad(when)
  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. -- Shutdown commands and keys
  14. import Data.Map(fromList)
  15. import XMonad.Prompt
  16. import XMonad.Prompt.XMonad
  17. import XMonad.Prompt.ConfirmPrompt
  18. import System.Exit(ExitCode(ExitSuccess), exitWith)
  19. import XMonad.Util.EZConfig(additionalKeys, removeKeys)
  20. import XMonad.Util.Dmenu
  21. -- Brightness and audio keys
  22. import Graphics.X11.ExtraTypes.XF86
  23. import Data.List(elemIndex, foldl1')
  24. import qualified XMonad.StackSet as W
  25. import qualified Data.Map as M
  26. -- kde
  27. import XMonad.Config.Kde
  28. import XMonad.Hooks.EwmhDesktops
  29. myModMask = mod4Mask
  30. myTerminal = "konsole"
  31. -- Command to launch the bar.
  32. myBar = "xmobar"
  33. -- Custom PP, configure it as you like. It determines what is being written to the bar.
  34. myPP = xmobarPP {ppTitle = xmobarColor "green" "" . shorten 50}
  35. -- Key binding to toggle the gap for the bar.
  36. toggleStrutsKey XConfig {XMonad.modMask = modMask} = (modMask, xK_b)
  37. -- Main configuration, override the defaults to your liking.
  38. myConfig = defaultConfig { modMask = mod4Mask }
  39. main = do
  40. xmonad =<< statusBar myBar myPP toggleStrutsKey (ewmh $ docks kde4Config {
  41. -- manageHook = manageDocks <+> manageHook kde4Config <+> myManageHook
  42. manageHook = manageDocks <+> myManageHook <+> manageHook kde4Config
  43. -- { manageHook = manageDocks <+> manageHook thisDesktopConfig <+> myManageHook
  44. , layoutHook = desktopLayoutModifiers $ smartBorders $ avoidStruts $
  45. (smartSpacing 5 $ withBorder 2 $ Tall 1 (3/100) (1/2)) |||
  46. (smartSpacing 5 $ withBorder 2 $ Mirror (Tall 1 (3/100) (1/2))) |||
  47. -- Full |||
  48. -- Tabs are bugged/don't work in ewmh. On the
  49. -- bright side, it makes a window float over KDE's
  50. -- bar, which is what I want fullscreen to do.
  51. -- It's not a bug, it's a feature.
  52. simpleTabbed
  53. -- , logHook = dynamicLogWithPP xmobarPP {
  54. -- ppOutput = hPutStrLn xmproc
  55. -- , ppTitle = xmobarColor "green" "" . shorten 50
  56. -- }
  57. , startupHook = startup (startupList ++ xmonadStartupList)
  58. , handleEventHook = handleEventHook def <+> fullscreenEventHook
  59. , modMask = mod4Mask
  60. , keys = \c -> mySetKeys c `M.union` keys kde4Config c
  61. } --`additionalKeys` (if session == "xmonad" then (myKeys ++ xmonadKeys) else myKeys)
  62. `removeKeys` myRemoveKeys)
  63. xmonadStartupList =
  64. [ "feh --bg-scale ~/Owncloud/Backgrounds/Xmbindings.png"
  65. , "trayer --edge top --align right --SetDockType true --SetPartialStrut true --expand true --width 10 --transparent true --alpha 0 --tint 0x000000 --height 22"
  66. , "pasystray"
  67. , "xfce4-clipman"
  68. , "xbacklight -set 12"
  69. , "compton"
  70. , "xscreensaver -nosplash"
  71. ]
  72. mySetKeys conf@(XConfig {XMonad.modMask = myModMask}) =
  73. M.fromList $ myKeys ++ xmonadKeys
  74. where
  75. xmonadKeys = [
  76. -- scrot
  77. ((controlMask, xK_Print), spawn "sleep 0.2; scrot -s")
  78. , ((0, xK_Print), spawn "scrot")
  79. -- rofi
  80. , ((myModMask, xK_p ), spawn "rofi -show run")
  81. -- shutdown
  82. --, ((myModMask .|. shiftMask, xK_q),
  83. -- xmonadPrompt defaultXPConfig
  84. -- { promptKeymap = fromList
  85. -- [ ((0, xK_r), do
  86. -- spawn "emacsclient -e '(kill emacs)'"
  87. -- spawn "systemctl reboot")
  88. -- , ((0 , xK_s), do
  89. -- spawn "emacsclient -e '(kill emacs)'"
  90. -- spawn "sudo poweroff")
  91. -- , ((0, xK_e), do
  92. -- spawn "emacsclient -e '(kill emacs)'"
  93. -- io $ exitWith ExitSuccess)
  94. -- , ((0, xK_l), do
  95. -- spawn "xscreensaver-command -lock"
  96. -- quit)
  97. -- , ((0, xK_z), do
  98. -- spawn "xscreensaver-command -lock"
  99. -- spawn "systemctl suspend"
  100. -- quit)
  101. -- , ((0, xK_Escape), quit)
  102. -- ]
  103. -- , defaultText = "(r) Reboot, (s) Shutdown, (e) Exit, (l) Lock, (z) Sleep"
  104. -- })
  105. -- pulseaudio
  106. , ((0, xF86XK_AudioRaiseVolume),
  107. spawn "pactl set-sink-volume alsa_output.pci-0000_00_1f.3.analog-stereo +5%")
  108. , ((0, xF86XK_AudioLowerVolume),
  109. spawn "pactl set-sink-volume alsa_output.pci-0000_00_1f.3.analog-stereo -5%")
  110. , ((0, xF86XK_AudioMute),
  111. spawn "pactl set-sink-mute alsa_output.pci-0000_00_1f.3.analog-stereo toggle")
  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. ]
  237. startup :: [String] -> X ()
  238. startup l = do
  239. foldl1' (>>) $ map (spawn . ifNotRunning) l
  240. -- Wrap a command in Bash that checks if it's running.
  241. ifNotRunning :: String -> String
  242. ifNotRunning s = "if [ `pgrep -c " ++ (basename s) ++ "` == 0 ]; then " ++ s ++ "; fi"
  243. -- Grab the program name from a command (everything up to the space,
  244. -- if there's a space). Doesn't work with escaped spaces.
  245. basename :: String -> String
  246. basename s = case elemIndex ' ' s of
  247. (Just n) -> take n s
  248. Nothing -> s