gdritter repos dotfiles / 5df4ea3
Added xmonad cabal file + major source refactor Getty Ritter 7 years ago
3 changed file(s) with 166 addition(s) and 87 deletion(s). Collapse all Expand all
1 name: myx
2 version: 0.1.0.0
3 -- synopsis:
4 -- description:
5 license: BSD3
6 license-file: LICENSE
7 author: Getty Ritter <gdritter@galois.com>
8 maintainer: Getty Ritter <gdritter@galois.com>
9 copyright: ©2017 Getty Ritter
10 -- category:
11 build-type: Simple
12 cabal-version: >= 1.14
13
14 executable xmonad
15 hs-source-dirs: src
16 main-is: xmonad.hs
17 default-extensions: OverloadedStrings,
18 ScopedTypeVariables
19 ghc-options: -Wall
20 build-depends: base >=4.7 && <4.10
21 , xmonad
22 , containers
23 , unix
24 , process
25 , directory
26 , xmonad-contrib
27 , data-default
28 default-language: Haskell2010
1 {-# LANGUAGE RankNTypes #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE ExistentialQuantification #-}
4 {-# LANGUAGE RecordWildCards #-}
5
6 import Control.Monad (when, void)
7 import Data.Default (def)
8 import qualified Data.Map as M
9 import qualified System.Directory as Sys
10 import qualified System.Environment as Sys
11 import qualified System.Exit as Sys
12 import qualified System.IO as Sys
13 import qualified System.Process as Sys
14
15 import XMonad ((|||), (<+>))
16 import qualified XMonad as XM
17 import qualified XMonad.Hooks.DynamicLog as Log
18 import qualified XMonad.Hooks.ManageDocks as XM
19 import qualified XMonad.Layout.NoBorders as XM
20 import qualified XMonad.Layout.Tabbed as Tab
21 import XMonad.ManageHook ((-->), (=?))
22 import qualified XMonad.Util.Run as Run
23
24 -- | A 'ColorScheme' represents a handful of salient colors used in
25 -- the configuration.
26 data ColorScheme = ColorScheme
27 { normalC :: String
28 , focusedC :: String
29 , blackC :: String
30 , grayC :: String
31 , whiteC :: String
32 } deriving (Eq, Show, Read)
33
34 -- | Here's a reasonable default color scheme with some blues!
35 blueScheme :: ColorScheme
36 blueScheme = ColorScheme
37 { normalC = "#336699"
38 , focusedC = "#9ebedf"
39 , blackC = "#ffffff"
40 , grayC = "#999999"
41 , whiteC = "#000000"
42 }
43
44 -- | Here's a reasonable default color scheme with some blues!
45 purpScheme :: ColorScheme
46 purpScheme = ColorScheme
47 { normalC = "#993366"
48 , focusedC = "#bf4080"
49 , blackC = "#ffffff"
50 , grayC = "#999999"
51 , whiteC = "#000000"
52 }
53
54 keys :: XM.XConfig XM.Layout -> M.Map (XM.ButtonMask, XM.KeySym) (XM.X ())
55 keys (XM.XConfig {XM.modMask = mdMask}) = M.fromList
56 [ ((mdMask, XM.xK_p), XM.spawn "dmenu_run")
57 , ((mdMask, XM.xK_period), XM.spawn "ibus engine xkb:us::eng")
58 , ((mdMask, XM.xK_u), XM.spawn "amixer -q sset Master 3%+")
59 , ((mdMask, XM.xK_d), XM.spawn "amixer -q sset Master 3%-")
60 , ((mdMask, XM.xK_m), XM.spawn "amixer -q sset Master 0%")
61 ]
62
63 recompile :: IO ()
64 recompile = do
65 putStrLn "recompiling with new-build"
66 let cmd = (Sys.proc "cabal" ["new-build"]) { Sys.cwd = Just "/home/gdritter/.xmonad" }
67 (code,stdout,stderr) <-
68 Sys.readCreateProcessWithExitCode cmd ""
69 putStr stdout
70 putStr stderr
71 putStrLn "Done!"
72 Sys.exitWith code
73
74 -- This is just out of programmer laziness: a typical XMonad config
75 -- has a pretty huge type parameter representing the possible layouts.
76 -- This just wraps an existential around the configuration so that
77 -- we don't have to write it at the top-level!
78 data XMConfig
79 = forall l. ( XM.LayoutClass l XM.Window
80 , Read (l XM.Window)
81 ) => XMConfig (XM.XConfig l)
82
83 -- This builds a config after being given a handle to the xmobar process
84 -- as well as a color scheme to use.
85 config :: Sys.Handle -> ColorScheme -> XMConfig
86 config xmproc ColorScheme { .. } = XMConfig conf
87 where conf = def
88 { XM.modMask = XM.mod4Mask
89 , XM.terminal = "urxvt -e tmux"
90 , XM.keys = keys <+> XM.keys def
91 , XM.layoutHook =
92 XM.avoidStruts (tabbed ||| tiled ||| XM.Mirror tiled)
93 ||| XM.noBorders (XM.smartBorders XM.Full)
94 , XM.manageHook = XM.composeAll
95 [ XM.className =? "Vkdraw" --> XM.doFloat
96 , XM.manageHook def
97 ]
98 , XM.normalBorderColor = normalC
99 , XM.focusedBorderColor = focusedC
100 , XM.logHook = Log.dynamicLogWithPP $ Log.xmobarPP
101 { Log.ppOutput = Sys.hPutStrLn xmproc
102 , Log.ppTitle = Log.xmobarColor grayC "" . Log.shorten 50
103 , Log.ppCurrent = Log.xmobarColor grayC "" . ("<" ++) . (++ ">")
104 }
105 }
106 tiled = XM.Tall 1 (3/100) (1/2)
107 tabbed = Tab.tabbed Tab.shrinkText def
108 { Tab.activeColor = focusedC
109 , Tab.inactiveColor = normalC
110 , Tab.activeBorderColor = blackC
111 , Tab.inactiveBorderColor = blackC
112 , Tab.activeTextColor = whiteC
113 , Tab.inactiveTextColor = whiteC
114 , Tab.fontName = "Inconsolata"
115 }
116
117 main :: IO ()
118 main = do
119 -- Here we're going to intercept the arguments before xmonad can so we
120 -- can hook our own recompile step
121 args <- Sys.getArgs
122 when ("--recompile" `elem` args) recompile
123
124 -- The .xm-init file gets run if it exists to do setup of the X11
125 -- environment.
126 xmInitExists <- Sys.doesFileExist "/home/gdritter/.xm-init"
127 when xmInitExists $
128 void (Sys.createProcess (Sys.proc "sh" ["/home/gdritter/.xm-init"]))
129
130 -- Run an xmobar instance
131 xmproc <- Run.spawnPipe "xmobar /home/gdritter/.xmobarrc"
132 -- Run a graphical-only runit instance.
133 -- XXX: kill this when xmonad dies somehow!
134 void (Run.spawnPipe "runsvdir /home/gdritter/.run/service")
135
136 -- Finally, build the config and run xmonad!
137 case config xmproc blueScheme of
138 XMConfig c -> XM.xmonad c
+0
-87
xmonad.hs less more
1 {-# LANGUAGE TupleSections #-}
2
3 import Control.Monad (when, void)
4 import qualified Data.Map as M
5 import Data.Maybe (maybe)
6 import System.Directory (doesFileExist)
7 import System.IO (hPutStrLn)
8 import System.Posix.Env (getEnv)
9 import System.Process (createProcess, proc)
10
11 import XMonad
12 import XMonad.Hooks.DynamicLog
13 import XMonad.Hooks.ManageDocks (manageDocks, avoidStruts)
14 import XMonad.Layout.NoBorders (noBorders, smartBorders)
15 import XMonad.Layout.Tabbed
16 import XMonad.ManageHook((-->), (=?))
17 import XMonad.Util.Run(spawnPipe)
18
19 data ColorScheme = ColorScheme
20 { normalColor :: String
21 , focusedColor :: String
22 }
23
24 grayScheme = ColorScheme "#dddddd" "#999999"
25 white = "#ffffff"
26 black = "#000000"
27
28 myKeys (XConfig {XMonad.modMask = modMask}) = M.fromList
29 [ ((modMask, xK_p), spawn "dmenu_run")
30 ]
31
32 myLayout = avoidStruts (myTabbed ||| tiled ||| Mirror tiled) ||| noBorders (smartBorders Full)
33 where tiled = Tall nmaster delta ratio
34 nmaster = 1
35 ratio = 1/2
36 delta = 3/100
37 myTabbed = tabbed shrinkText def
38 { activeColor = focusedColor grayScheme
39 , inactiveColor = normalColor grayScheme
40 , activeBorderColor = black
41 , inactiveBorderColor = black
42 , activeTextColor = white
43 , inactiveTextColor = white
44 }
45
46 workspaceOnScreen :: (WorkspaceId -> WindowSet -> WindowSet) ->
47 WorkspaceId -> X ()
48 workspaceOnScreen f w =
49 maybe (return ()) check (lookup w wsMap)
50 where check s = do
51 mws <- screenWorkspace s
52 case mws of
53 Nothing -> windows (f w)
54 Just ws -> do
55 windows (f ws)
56 windows (f w)
57
58 onScreen :: ScreenId -> [String] -> [(String, ScreenId)]
59 onScreen i ws = map (,i) ws
60
61 wsMap :: [(String, ScreenId)]
62 wsMap = (onScreen 0 $ words "1 2 3 4 5") ++
63 (onScreen 1 $ words "6 7 8 9")
64
65 main :: IO ()
66 main = do
67 fehBgExists <- doesFileExist "/home/gdritter/.xm-init"
68 when fehBgExists $
69 void (createProcess (proc "sh" ["/home/gdritter/.xm-init"]))
70 xmproc <- spawnPipe "xmobar /home/gdritter/.xmobarrc"
71 void (spawnPipe "runsvdir /home/gdritter/.run/service")
72 xmonad $ def
73 { modMask = mod4Mask
74 , terminal = "urxvt -e tmux"
75 , keys = myKeys <+> keys def
76 , layoutHook = myLayout
77 , manageHook = composeAll [ className =? "Vkdraw" --> doFloat
78 , manageHook def
79 ]
80 , normalBorderColor = normalColor grayScheme
81 , focusedBorderColor = focusedColor grayScheme
82 , logHook = dynamicLogWithPP $ xmobarPP
83 { ppOutput = hPutStrLn xmproc
84 , ppTitle = xmobarColor "#999999" "" . shorten 50
85 , ppCurrent = xmobarColor "#999999" "" . ("<" ++) . (++ ">")
86 }
87 }