Xmonad/Config archive/Robert Manea's Config.hs and support scripts
< Xmonad | Config archive
Jump to navigation
Jump to search
Rob's setup
Besides the haskell part you can find all other bits and pieces of my setup here
Config.hs:
module Config where
--
-- Useful imports
--
import XMonad
import Operations
import qualified StackSet as W
import Data.Ratio
import Data.Bits ((.|.))
import qualified Data.Map as M
import System.Exit
import Graphics.X11.Xlib
--
-- Contributed modules
--
import XMonadContrib.DwmPromote
import XMonadContrib.DynamicLog
import XMonadContrib.NoBorders
import XMonadContrib.XPrompt
import XMonadContrib.ShellPrompt
-- | The default number of workspaces (virtual screens) and their names.
-- By default we use numeric strings, but any string may be used as a
-- workspace name. The number of workspaces is determined by the length
-- of this list.
--
-- A tagging example:
--
-- > workspaces = ["web", "irc", "code" ] ++ map show [4..9]
--
workspaces :: [WorkspaceId]
workspaces = ["1:dev", "2:mail", "3:web", "4:comm", "5:ham", "6:tmp" :: String]
-- | modMask lets you specify which modkey you want to use. The default
-- is mod1Mask ("left alt"). You may also consider using mod3Mask
-- ("right alt"), which does not conflict with emacs keybindings. The
-- "windows key" is usually mod4Mask.
--
modMask :: KeyMask
modMask = mod4Mask
-- | The mask for the numlock key. Numlock status is "masked" from the
-- current modifier status, so the keybindings will work with numlock on or
-- off. You may need to change this on some systems.
--
-- You can find the numlock modifier by running "xmodmap" and looking for a
-- modifier with Num_Lock bound to it:
--
-- > $ xmodmap | grep Num
-- > mod2 Num_Lock (0x4d)
--
-- Set numlockMask = 0 if you don't have a numlock key, or want to treat
-- numlock status separately.
--
numlockMask :: KeyMask
numlockMask = mod2Mask
-- | Width of the window border in pixels.
--
borderWidth :: Dimension
borderWidth = 1
-- | Border colors for unfocused and focused windows, respectively.
--
normalBorderColor, focusedBorderColor :: String
normalBorderColor = "#111111"
focusedBorderColor = "#aecf96"
-- | Default offset of drawable screen boundaries from each physical
-- screen. Anything non-zero here will leave a gap of that many pixels
-- on the given edge, on the that screen. A useful gap at top of screen
-- for a menu bar (e.g. 15)
--
-- An example, to set a top gap on monitor 1, and a gap on the bottom of
-- monitor 2, you'd use a list of geometries like so:
--
-- > defaultGaps = [(18,0,0,0),(0,18,0,0)] -- 2 gaps on 2 monitors
--
-- Fields are: top, bottom, left, right.
--
defaultGaps :: [(Int,Int,Int,Int)]
defaultGaps = [(13,0,0,0)] -- 15 for default dzen
------------------------------------------------------------------------
-- Window rules
-- | Execute arbitrary actions and WindowSet manipulations when managing
-- a new window. You can use this to, for example, always float a
-- particular program, or have a client always appear on a particular
-- workspace.
--
manageHook :: Window -- ^ the new window to manage
-> String -- ^ window title
-> String -- ^ window resource name
-> String -- ^ window resource class
-> X (WindowSet -> WindowSet)
-- Always float various programs:
manageHook w _ _ c | c `elem` floats = fmap (W.float w . snd) (floatLocation w)
where floats = ["MPlayer", "Gimp"]
-- Desktop panels and dock apps should be ignored by xmonad:
manageHook w _ n _ | n `elem` ignore = reveal w >> return (W.delete w)
where ignore = ["gnome-panel", "desktop_window", "kicker", "kdesktop"]
-- Automatically send Firefox windows to the "web" workspace:
-- If a workspace named "web" doesn't exist, the window will appear on the
-- current workspace.
manageHook _ _ "Gecko" _ = return $ W.shift "web"
-- The default rule: return the WindowSet unmodified. You typically do not
-- want to modify this line.
manageHook _ _ _ _ = return id
------------------------------------------------------------------------
-- Extensible layouts
-- |
-- ShellPrompt config
--
mySPConfig :: XPConfig
mySPConfig = XPC { font = "-*-profont-*-*-*-*-11-*-*-*-*-*-iso8859"
, bgColor = "#111111"
, fgColor = "#d5d3a7"
, bgHLight = "#aecf96"
, fgHLight = "black"
, borderColor = "black"
, promptBorderWidth = 0
, position = Bottom
, height = 15
, historySize = 256
}
--
-- | The list of possible layouts. Add your custom layouts to this list.
layouts :: [Layout Window]
layouts = [ Layout tiled
, Layout $ Mirror tiled
, Layout $ noBorders Full
-- Extension-provided layouts
]
where
-- default tiling algorithm partitions the screen into two panes
tiled = Tall nmaster delta ratio
-- The default number of windows in the master pane
nmaster = 1
-- Default proportion of screen occupied by master pane
-- ratio = 1%2
ratio = recip 1.618
-- Percent of screen to increment by when resizing panes
delta = 3%100
-- | The top level layout switcher. Most users will not need to modify this binding.
--
-- By default, we simply switch between the layouts listed in `layouts'
-- above, but you may program your own selection behaviour here. Layout
-- transformers, for example, would be hooked in here.
--
layoutHook :: Layout Window
layoutHook = Layout $ Select layouts
-- | Register with xmonad a list of layouts whose state we can preserve over restarts.
-- There is typically no need to modify this list, the defaults are fine.
--
serialisedLayouts :: [Layout Window]
serialisedLayouts = layoutHook : layouts
------------------------------------------------------------------------
-- Logging
-- | Perform an arbitrary action on each internal state change or X event.
-- Examples include:
-- * do nothing
-- * log the state to stdout
--
-- See the 'DynamicLog' extension for examples.
--
logHook :: X ()
logHook = dynamicLogWithPP robPP
-- logHook = dynamicLogWithTitleColored "white"
------------------------------------------------------------------------
-- Key bindings:
-- | The preferred terminal program, which is used in a binding below and by
-- certain contrib modules.
terminal :: String
terminal = "xterm"
-- | The xmonad key bindings. Add, modify or remove key bindings here.
--
-- (The comment formatting character is used when generating the manpage)
--
keys :: M.Map (KeyMask, KeySym) (X ())
keys = M.fromList $
-- launching and killing programs
[ ((modMask .|. shiftMask, xK_Return), spawn "/home/robert/bin/uterm")
, ((modMask .|. shiftMask, xK_c ), kill) -- @@ Close the focused window
, ((modMask, xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms
, ((modMask, xK_p ), shellPrompt mySPConfig)
, ((modMask, xK_c ), spawn "/home/robert/bin/dzencal.sh")
, ((modMask .|. shiftMask, xK_space ), setLayout layoutHook) -- %! Reset the layouts on the current workspace to default
, ((modMask, xK_n ), refresh) -- %! Resize viewed windows to the correct size
-- move focus up or down the window stack
, ((modMask, xK_Tab ), windows W.focusDown) -- %! Move focus to the next window
, ((modMask, xK_j ), windows W.focusDown) -- %! Move focus to the next window
, ((modMask, xK_k ), windows W.focusUp ) -- %! Move focus to the previous window
, ((modMask, xK_m ), windows W.focusMaster ) -- %! Move focus to the master window
-- modifying the window order
-- , ((modMask, xK_Return), windows W.swapMaster) -- %! Swap the focused window and the master window
, ((modMask .|. shiftMask, xK_j ), windows W.swapDown ) -- %! Swap the focused window with the next window
, ((modMask .|. shiftMask, xK_k ), windows W.swapUp ) -- %! Swap the focused window with the previous window
, ((modMask, xK_Return), dwmpromote) -- @@ Swap the focused window and the master window
-- resizing the master/slave ratio
, ((modMask, xK_h ), sendMessage Shrink) -- %! Shrink the master area
, ((modMask, xK_l ), sendMessage Expand) -- %! Expand the master area
-- floating layer support
, ((modMask, xK_t ), withFocused $ windows . W.sink) -- %! Push window back into tiling
-- increase or decrease number of windows in the master area
, ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
, ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
-- toggle the status bar gap
, ((modMask , xK_b ), modifyGap (\i n -> let x = (defaultGaps ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap
-- quit, or restart
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
, ((modMask , xK_q ), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad
-- % Extension-provided key bindings
]
++
-- mod-[1..9] %! Switch to workspace N
-- mod-shift-[1..9] %! Move client to workspace N
[((m .|. modMask, k), windows $ f i)
| (i, k) <- zip workspaces [xK_1 .. xK_9]
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
++
-- mod-{w,e,r} %! Switch to physical/Xinerama screens 1, 2, or 3
-- mod-shift-{w,e,r} %! Move client to screen 1, 2, or 3
[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
-- % Extension-provided key bindings lists
-- | Mouse bindings: default actions bound to mouse events
--
mouseBindings :: M.Map (KeyMask, Button) (Window -> X ())
mouseBindings = M.fromList $
-- mod-button1 %! Set the window to floating mode and move by dragging
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
-- mod-button2 %! Raise the window to the top of the stack
, ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
-- mod-button3 %! Set the window to floating mode and resize by dragging
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w))
-- you may also bind events to the mouse scroll wheel (button4 and button5)
-- % Extension-provided mouse bindings
]
DynamicLog.hs:
module XMonadContrib.DynamicLog (
-- * Usage
-- $usage
dynamicLog,
dynamicLogWithPP,
dynamicLogXinerama,
pprWindowSet,
pprWindowSetXinerama,
PP(..), defaultPP, sjanssenPP, robPP,
wrap, dzenColor, xmobarColor, shorten
) where
--
-- Useful imports
--
import XMonad
import {-# SOURCE #-} Config (workspaces)
import Operations () -- for ReadableSomeLayout instance
import Data.Maybe ( isJust )
import Data.List
import Data.Ord ( comparing )
import qualified StackSet as S
import Data.Monoid
import XMonadContrib.NamedWindows
-- $usage
--
-- To use, set:
--
-- > import XMonadContrib.DynamicLog
-- > logHook = dynamicLog
-- %import XMonadContrib.DynamicLog
-- %def -- comment out default logHook definition above if you uncomment any of these:
-- %def logHook = dynamicLog
-- |
-- An example log hook, print a status bar output to stdout, in the form:
--
-- > 1 2 [3] 4 7 : full : title
--
-- That is, the currently populated workspaces, the current
-- workspace layout, and the title of the focused window.
--
dynamicLog :: X ()
dynamicLog = dynamicLogWithPP defaultPP
-- |
-- A log function that uses the 'PP' hooks to customize output.
dynamicLogWithPP :: PP -> X ()
dynamicLogWithPP pp = do
-- layout description
ld <- withWindowSet $ return . description . S.layout . S.workspace . S.current
-- workspace list
ws <- withWindowSet $ return . pprWindowSet pp
-- window title
wt <- withWindowSet $ maybe (return "") (fmap show . getName) . S.peek
io . putStrLn . sepBy (ppSep pp) . ppOrder pp $
[ ppLayout pp ld
, ws
, ppTitle pp wt
]
-- [ ws
-- , ppLayout pp ld
-- , ppTitle pp wt
-- ]
pprWindowSet :: PP -> WindowSet -> String
pprWindowSet pp s = sepBy (ppWsSep pp) $ map fmt $ sortBy cmp
(map S.workspace (S.current s : S.visible s) ++ S.hidden s)
where f Nothing Nothing = EQ
f (Just _) Nothing = LT
f Nothing (Just _) = GT
f (Just x) (Just y) = compare x y
wsIndex = flip elemIndex workspaces . S.tag
cmp a b = f (wsIndex a) (wsIndex b) `mappend` compare (S.tag a) (S.tag b)
this = S.tag (S.workspace (S.current s))
visibles = map (S.tag . S.workspace) (S.visible s)
fmt w = printer pp (S.tag w)
where printer | S.tag w == this = ppCurrent
| S.tag w `elem` visibles = ppVisible
| isJust (S.stack w) = ppHidden
| otherwise = ppHiddenNoWindows
-- |
-- Workspace logger with a format designed for Xinerama:
--
-- > [1 9 3] 2 7
--
-- where 1, 9, and 3 are the workspaces on screens 1, 2 and 3, respectively,
-- and 2 and 7 are non-visible, non-empty workspaces
--
dynamicLogXinerama :: X ()
dynamicLogXinerama = withWindowSet $ io . putStrLn . pprWindowSetXinerama
pprWindowSetXinerama :: WindowSet -> String
pprWindowSetXinerama ws = "^bg(#aecf96)^fg(#111111)^p(6)[" ++ unwords onscreen ++ "]^p(6)^fg()^bg() " ++ unwords offscreen
where onscreen = map (S.tag . S.workspace)
. sortBy (comparing S.screen) $ S.current ws : S.visible ws
offscreen = map S.tag . filter (isJust . S.stack)
. sortBy (comparing S.tag) $ S.hidden ws
wrap :: String -> String -> String -> String
wrap _ _ "" = ""
wrap l r m = l ++ m ++ r
shorten :: Int -> String -> String
shorten n xs | length xs < n = xs
| otherwise = (take (n - length end) xs) ++ end
where
end = "..."
sepBy :: String -> [String] -> String
sepBy sep = concat . intersperse sep . filter (not . null)
dzenColor :: String -> String -> String -> String
dzenColor fg bg = wrap (fg1++bg1) (fg2++bg2)
where (fg1,fg2) | null fg = ("","")
| otherwise = ("^fg(" ++ fg ++ ")","^fg()")
(bg1,bg2) | null bg = ("","")
| otherwise = ("^bg(" ++ bg ++ ")","^bg()")
-- | The 'PP' type allows the user to customize various behaviors of
-- dynamicLogPP
data PP = PP { ppCurrent, ppVisible
, ppHidden, ppHiddenNoWindows :: WorkspaceId -> String
, ppSep, ppWsSep :: String
, ppTitle :: String -> String
, ppLayout :: String -> String
, ppOrder :: [String] -> [String] }
-- | The default pretty printing options, as seen in dynamicLog
defaultPP :: PP
defaultPP = PP { ppCurrent = wrap "[" "]"
, ppVisible = wrap "<" ">"
, ppHidden = id
, ppHiddenNoWindows = const ""
, ppSep = " : "
, ppWsSep = " "
, ppTitle = shorten 80
, ppLayout = id
, ppOrder = id }
robPP :: PP
robPP = defaultPP { ppCurrent = wrap "^fg(#000000)^bg(#a6c292)^p(2)^i(/home/robert/dzen_bitmaps/has_win.xbm)" "^p(2)^fg()^bg()"
, ppVisible = wrap "^bg(grey30)^fg(grey75)^p(2)" "^p(2)^fg()^bg()"
, ppLayout = wrap "(" ")"
, ppTitle = dzenColor "white" "grey30" . shorten 80
, ppSep = " ^fg(grey50)^r(2x8)^p(1)^fg(grey70)^r(2x8)^fg(grey50)^p(1)^r(2x8)^fg() "
}