xmonad.hs 9.2 KB

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