| 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
|