Xmonad/Config archive/lithis's xmonad.hs
< Xmonad | Config archive
import XMonad
import XMonad.Actions.DwmPromote
import XMonad.Actions.Warp
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.UrgencyHook
import XMonad.Layout.LayoutHints
import XMonad.Layout.NoBorders
import XMonad.Layout.Spiral
import XMonad.Layout.Tabbed
import XMonad.Prompt
import XMonad.Prompt.Shell
import XMonad.Prompt.Ssh
import XMonad.Util.Run (spawnPipe)
import System.IO (hPutStrLn)
import qualified Data.Map as M
import Data.Ratio
import Control.Monad
pointerFollowsFocus :: Rational -> Rational -> X ()
pointerFollowsFocus h v = withFocused $ \w -> do
dpy <- asks display
root <- asks theRoot
wa <- io $ getWindowAttributes dpy w
(sameRoot,_,w',_,_,_,_,_) <- io $ queryPointer dpy root
unless (sameRoot && w == w') $
io $ warpPointer dpy none w 0 0 0 0
(fraction h (wa_width wa)) (fraction v (wa_height wa))
where fraction x y = floor (x * fromIntegral y)
main :: IO ()
main = do
xmobar <- spawnPipe "xmobar"
xmonad $ withUrgencyHook NoUrgencyHook $ defaultConfig
{ normalBorderColor = backgroundColor
, focusedBorderColor = focusColor
, terminal = "$XTERMCMD"
, layoutHook = myLayout
, manageHook = manageDocks
, modMask = mod4Mask
, borderWidth = 2
, keys = \c -> myKeys c `M.union` keys defaultConfig c
, logHook = dynamicLogWithPP hethraelPP
{ ppOutput = hPutStrLn xmobar }
>> pointerFollowsFocus 1 1
}
where
myLayout = layoutHints $ avoidStruts $ smartBorders $ tiled
||| Mirror tiled
||| Full
||| tabbed shrinkText hethraelTheme
||| spiral (1 % 1)
tiled = Tall nmaster delta ratio
nmaster = 1
ratio = 1/2
delta = 3/100
hethraelPP :: PP
hethraelPP = defaultPP
{ ppCurrent = xmobarColor focusColor ""
, ppVisible = xmobarColor lightTextColor ""
, ppHiddenNoWindows = xmobarColor lightBackgroundColor ""
, ppUrgent = xmobarColor "#ffc000" ""
, ppSep = " · "
, ppWsSep = ""
, ppTitle = xmobarColor lightTextColor "" . shorten 90
}
hethraelTheme :: Theme
hethraelTheme = defaultTheme
{ activeColor = lightBackgroundColor
, inactiveColor = backgroundColor
, activeBorderColor = textColor
, inactiveTextColor = textColor
, inactiveBorderColor = lightBackgroundColor
, activeTextColor = lightTextColor
, fontName = myFont
}
hethraelXPConfig :: XPConfig
hethraelXPConfig = defaultXPConfig
{ font = myFont
, bgColor = backgroundColor
, fgColor = textColor
, fgHLight = lightTextColor
, bgHLight = lightBackgroundColor
, borderColor = lightBackgroundColor
}
myFont = "xft:DejaVu Sans:size=10"
focusColor = "#60ff45"
textColor = "#c0c0a0"
lightTextColor = "#fffff0"
backgroundColor = "#304520"
lightBackgroundColor = "#456030"
myKeys (XConfig {modMask = modm, workspaces = ws}) = M.fromList $
[ ((modm, xK_Return), dwmpromote)
, ((modm, xK_b), sendMessage ToggleStruts)
, ((modm .|. controlMask, xK_x), shellPrompt hethraelXPConfig)
, ((modm .|. controlMask, xK_s), sshPrompt hethraelXPConfig)
, ((modm, xK_z), warpToWindow 1 1)
, ((modm .|. controlMask, xK_l), spawn "exec xlogo -render -fg `randomdarkcolor` -bg `randomdarkcolor`")
]