Xmonad/Config archive/sereven's xmonad.hs one-host: Difference between revisions
< Xmonad | Config archive
No edit summary |
(fix so file compiles -- apparently was too big for xselection) |
||
Line 1: | Line 1: | ||
Apparently this file is too big to copy all at once without errors, so copy paste in two sections, see -- SPLIT HERE -- comment | |||
<haskell> | |||
------ may not want scaling dzen bar -------- | ------ may not want scaling dzen bar ------------- | ||
import Graphics.X11.Xlib | import Graphics.X11.Xlib | ||
import Graphics.X11.Xinerama | import Graphics.X11.Xinerama | ||
Line 50: | Line 50: | ||
let conf = sConfig "/home/gvg" dz | let conf = sConfig "/home/gvg" dz | ||
let sKeys = keysWithPath "/home/gvg" conf | let sKeys = keysWithPath "/home/gvg" conf | ||
xmonad $ withUrgencyHook NoUrgencyHook $ | xmonad $ withUrgencyHook NoUrgencyHook $ | ||
conf {startupHook = return () >> checkKeymap conf sKeys} | conf {startupHook = return () >> checkKeymap conf sKeys} | ||
Line 91: | Line 90: | ||
, ("M-h", sendMessage $ Go L) | , ("M-h", sendMessage $ Go L) | ||
, ("M-l", sendMessage $ Go R) | , ("M-l", sendMessage $ Go R) | ||
, ("M-S-k", sendMessage $ Swap U) -- shift shifts windows | , ("M-S-k", sendMessage $ Swap U) -- shift shifts windows | ||
, ("M-S-j", sendMessage $ Swap D) | , ("M-S-j", sendMessage $ Swap D) | ||
Line 163: | Line 161: | ||
-- toolbox to top separator or bar of toolbox to add and re-arrange. | -- toolbox to top separator or bar of toolbox to add and re-arrange. | ||
-------- !! SPLIT HERE !! ------------------- | |||
-- (theming, font, colors) ------------------ | -- (theming, font, colors) ------------------ | ||
-- from cross-host conf, better to just use 'color' where needed, but I'm too | -- from cross-host conf, better to just use 'color' where needed, but I'm too | ||
-- lazy to edit this file for colors. | -- lazy to edit this whole file for colors. | ||
data Colorset = Colorset | data Colorset = Colorset | ||
{ ltCol :: String , dkCol :: String | { ltCol :: String | ||
, currentCol :: String , hlightCol :: String | , dkCol :: String | ||
, currentCol :: String | |||
, hlightCol :: String | |||
, visibleCol :: String | , visibleCol :: String | ||
, hiddenCol :: String , fadedCol :: String | , hiddenCol :: String | ||
, urgentCol | , fadedCol :: String | ||
} | , urgentCol :: String | ||
} | |||
dkCols = Colorset | dkCols = Colorset | ||
{ ltCol = "#d7e19f" | { ltCol = "#d7e19f" | ||
, dkCol = "#230" | , dkCol = "#230" | ||
Line 197: | Line 187: | ||
, fadedCol = "#ab9" | , fadedCol = "#ab9" | ||
, urgentCol = "#e30" | , urgentCol = "#e30" | ||
} | } | ||
Line 229: | Line 218: | ||
++ " -w " ++ show width | ++ " -w " ++ show width | ||
++ " -h " ++ (show $ height xpc) | ++ " -h " ++ (show $ height xpc) | ||
++ " -fn | ++ " -fn '" ++ (font xpc) ++ "'" | ||
++ " -bg | ++ " -bg '" ++ (bgColor xpc) ++ "'" | ||
++ " -fg | ++ " -fg '" ++ (fgColor xpc) ++ "'" | ||
++ " -ta l" | ++ " -ta l" | ||
-- normal dzen config -- | -- normal dzen config -- | ||
Line 239: | Line 228: | ||
width = sx + sw - sw * 7 `div` 64 - xpos -- and c`div`d to right | width = sx + sw - sw * 7 `div` 64 - xpos -- and c`div`d to right | ||
-- (space for .xinіtrc bar and tray) | -- (space for .xinіtrc bar and tray) | ||
stripDzen :: String -> String -- strip dzen formatting to undo ppHidden | stripDzen :: String -> String -- strip dzen formatting to undo ppHidden | ||
Line 246: | Line 234: | ||
aux x acc = (\(good,bad) -> aux (dropDzen bad) (acc++good)) $ span (/= '^') x | aux x acc = (\(good,bad) -> aux (dropDzen bad) (acc++good)) $ span (/= '^') x | ||
where dropDzen b = drop 1 $ dropWhile (/= ')') b | where dropDzen b = drop 1 $ dropWhile (/= ')') b | ||
-- dropDzen doesn't properly handle ^^ or non-dzen ')' in text | -- dropDzen doesn't properly handle "^^" or non-dzen ')' in text | ||
xpm :: String -> String -> String | xpm :: String -> String -> String | ||
Line 262: | Line 250: | ||
, ppOrder = \(ws:_:_:xs) -> [" "] ++ [ws] ++ xs | , ppOrder = \(ws:_:_:xs) -> [" "] ++ [ws] ++ xs | ||
, ppOutput = hPutStrLn dzIn | , ppOutput = hPutStrLn dzIn | ||
} | } | ||
where kernedsp = "^p(+12)" | where kernedsp = "^p(+12)" | ||
dzfg c = dzenColor (c dkCols) "" -- (Colorset -> String) -> String -> String | dzfg c = dzenColor (c dkCols) "" -- (Colorset -> String) -> String -> String |
Revision as of 07:04, 2 November 2008
Apparently this file is too big to copy all at once without errors, so copy paste in two sections, see -- SPLIT HERE -- comment
------ may not want scaling dzen bar -------------
import Graphics.X11.Xlib
import Graphics.X11.Xinerama
import Data.Maybe (fromMaybe)
------ normal imports --
import XMonad
import qualified XMonad.StackSet as W
------ --
import qualified Data.Map as M
import Data.Ratio ((%)) -- for Layout.IM
------ --
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers(doCenterFloat)
import XMonad.Hooks.UrgencyHook
import XMonad.Hooks.DynamicLog
------ --
import XMonad.Actions.CycleWS
import XMonad.Actions.WindowGo
import XMonad.Actions.Warp
------ --
import XMonad.Layout.IM
import XMonad.Layout.Reflect
import XMonad.Layout.PerWorkspace
import XMonad.Layout.ResizableTile
import XMonad.Layout.WindowNavigation
import XMonad.Layout.NoBorders
import qualified XMonad.Layout.ToggleLayouts as TL
------ --
import XMonad.Prompt
import XMonad.Prompt.Shell
import XMonad.Prompt.RunOrRaise
------ --
import XMonad.Util.Run
import XMonad.Util.Scratchpad
import XMonad.Util.EZConfig
-- "Make it so, Mr. X!" --------------------
main = do
scrxpw <- getXPositionAndWidthOfScreen 0 -- dzen screen number
let dzencmd = uncurry dzenWithParamsFrom (fromMaybe (0, 1024) scrxpw) darkXPC
dz <- spawnPipe dzencmd
-- uncomment to show dzen params while setting up other bars in .xinitrc
-- spawn $ "xmessage " ++ "'" ++ dzencmd ++ "'"
let conf = sConfig "/home/gvg" dz
let sKeys = keysWithPath "/home/gvg" conf
xmonad $ withUrgencyHook NoUrgencyHook $
conf {startupHook = return () >> checkKeymap conf sKeys}
`additionalKeysP` sKeys
-- using this XConfig
sConfig hm dzh = defaultConfig
{ workspaces = sWorkspaces
, manageHook = sManageHook
, layoutHook = sLayout
, logHook = dynamicLogWithPP $ dzdarkPP hm dzh
, borderWidth = 1
, focusedBorderColor = hlightCol dkCols -- ltCol dkCols
, normalBorderColor = dkCol dkCols
, focusFollowsMouse = True
, modMask = mod4Mask
, terminal = "urxvtc"
}
-- (frequently edited bits nearer the top) -------
keysWithPath hm cfg =
[ ("M-<F1>", shellPrompt darkXPC)
, ("M-<F2>", runOrRaisePrompt darkXPC)
, ("M-<F3>", scratchpadSpawnAction cfg)
, ("M-<F12>", spawn "xscreensaver-command -lock")
, ("M-x f", runOrRaise "firefox" (className =? "Firefox"))
, ("M-x o", runOrRaise "opera" (className =? "Opera"))
, ("M-x r", runOrRaise (hm ++ "/bin/shfmRun") (title =? "shellfm"))
, ("M-x h", runOrRaise "hback" (className =? "Hback"))
, ("M-x g", spawn "gimp")
]
++ -- vi directional window navigation similar to XMonad defaults
[ ("M-k", sendMessage $ Go U)
, ("M-j", sendMessage $ Go D)
, ("M-h", sendMessage $ Go L)
, ("M-l", sendMessage $ Go R)
, ("M-S-k", sendMessage $ Swap U) -- shift shifts windows
, ("M-S-j", sendMessage $ Swap D)
, ("M-S-h", sendMessage $ Swap L)
, ("M-S-l", sendMessage $ Swap R)
, ("M-C-k", sendMessage MirrorExpand) -- ctrl controls size
, ("M-C-j", sendMessage MirrorShrink)
, ("M-C-h", sendMessage Shrink)
, ("M-C-l", sendMessage Expand)
]
++ -- mod-<key> and mod-shift-<key> are as default (plus 0 and = too)
-- mod-ctrl-<key> shifts focused window *and* view to <key>'s ws
[ (addtlmods ++ "M-" ++ [key], action tag)
| (tag, key) <- zip sWorkspaces "1234567890="
, (addtlmods, action) <- [ ("", windows . W.greedyView)
, ("S-", windows . W.shift)
, ("C-", \x -> (windows . W.shift) x >> (windows . W.view) x)]
]
++ -- mod + m + {left arrow or 'a' key} does action with ws to "left"
[ (m ++ "M-" ++ key, action) | key <- ["<L>","a"]
, (m, action) <- [ ("", prevWS), ("S-", shiftToPrev), ("C-", shiftToPrev >> prevWS)]
]
++ -- mod + m + {right arrow or 'd' key} does action with ws to "right"
[ (m ++ "M-" ++ key, action) | key <- ["<R>","d"]
, (m, action) <- [ ("", nextWS), ("S-", shiftToNext), ("C-", shiftToNext >> nextWS)]
]
++
[ ("M-<Space>", sendMessage TL.ToggleLayout ) -- noBorders Full
, ("M-b", sendMessage ToggleStruts)
, ("M-C-b", warpToScreen 0 (1/2) 0) -- open XM dzen slave; exit mouse manually to collapse :(
, ("M-S-b", warpToScreen 0 0 0) -- open sys dzen slave; exit mouse manually to collapse :(
, ("M-m", warpToWindow 1 1) -- banish mouse to lower right of focused window
]
sWorkspaces = ["'%", "%", "%'"] ++ ["'*", "*", "*'"] ++ ["c", "m", "#"] ++ ["@", "SP"]
sManageHook = composeAll
[ doF avoidMaster
, scratchpadManageHookDefault
, title =? "shellfm" --> doShift "'*"
, className =? "Gimp" --> doShift "*" -- don't float, IM layout
, className =? "MPlayer" --> doShift "*'"
, title =? "" --> doFloat -- SOE graphics
, title =? "shellfm" --> doFloat
, className =? "Hback" --> doCenterFloat
, className =? "MPlayer" --> doFloat
, className =? "XFontSel" --> doCenterFloat
, className =? "Xmessage" --> doCenterFloat
]
where avoidMaster :: W.StackSet i l a s sd -> W.StackSet i l a s sd
avoidMaster = W.modify' $ \c -> case c of
W.Stack t [] (r:rs) -> W.Stack t [r] rs
otherwise -> c
sLayout =
avoidStruts $ configurableNavigation (noNavigateBorders) $
TL.toggleLayouts (noBorders Full) $
modWorkspace "*" reflectHoriz $ withIM (11%64) (Role "gimp-toolbox") $ -- see [gimp]
ResizableTall 2 -- default number of masters
(1/118) -- resize increment
(11/20) -- horizontal ratio: mstr/(mstr+slv)?
[5/4 -- master column ~ top/bottom?
,5/4 -- no effect w/ 2 masters
,5/4 -- slave column ~ top/bottom
] -- then defaults to (repeat 1)
-- [gimp] -- Combining gimp-toolbox and gimp-dock into one works
-- well in IM layout roster column. Drag panes from gimp-dock or
-- toolbox to top separator or bar of toolbox to add and re-arrange.
-------- !! SPLIT HERE !! -------------------
-- (theming, font, colors) ------------------
-- from cross-host conf, better to just use 'color' where needed, but I'm too
-- lazy to edit this whole file for colors.
data Colorset = Colorset
{ ltCol :: String
, dkCol :: String
, currentCol :: String
, hlightCol :: String
, visibleCol :: String
, hiddenCol :: String
, fadedCol :: String
, urgentCol :: String
}
dkCols = Colorset
{ ltCol = "#d7e19f"
, dkCol = "#230"
, currentCol = "black"
, hlightCol = "#0e3"
, visibleCol = "#443"
, hiddenCol = "#564"
, fadedCol = "#ab9"
, urgentCol = "#e30"
}
darkXPC = defaultXPConfig
{ font = "-*-dejavu sans mono-medium-r-*-*-17-*-*-*-*-*-*-*"
, height = 22
, bgColor = dkCol dkCols
, fgColor = ltCol dkCols
, bgHLight = ltCol dkCols
, fgHLight = dkCol dkCols
, promptBorderWidth = 0
}
-- (dzen) ----------------------------------
getXPositionAndWidthOfScreen :: Int -> IO (Maybe (Int, Int))
getXPositionAndWidthOfScreen n = do
d <- openDisplay ""
screens <- getScreenInfo d
let rn = screens!!(min (abs n) (length screens - 1))
case screens of
[] -> return Nothing
[r] -> return $ Just (fromIntegral $ rect_x r , fromIntegral $ rect_width r)
otherwise -> return $ Just (fromIntegral $ rect_x rn, fromIntegral $ rect_width rn)
-- adjust dzen position & width to screen; use XPConfig theming
dzenWithParamsFrom :: Int -> Int -> XPConfig -> String
dzenWithParamsFrom sx sw xpc =
"dzen2 -x " ++ show xpos
++ " -w " ++ show width
++ " -h " ++ (show $ height xpc)
++ " -fn '" ++ (font xpc) ++ "'"
++ " -bg '" ++ (bgColor xpc) ++ "'"
++ " -fg '" ++ (fgColor xpc) ++ "'"
++ " -ta l"
-- normal dzen config --
++ " -e 'onstart=lower'"
where xpos = sx + sw * 11 `div` 32 -- a`div`b screenwidth empty to left
width = sx + sw - sw * 7 `div` 64 - xpos -- and c`div`d to right
-- (space for .xinіtrc bar and tray)
stripDzen :: String -> String -- strip dzen formatting to undo ppHidden
stripDzen s = aux s []
where aux [] acc = acc
aux x acc = (\(good,bad) -> aux (dropDzen bad) (acc++good)) $ span (/= '^') x
where dropDzen b = drop 1 $ dropWhile (/= ')') b
-- dropDzen doesn't properly handle "^^" or non-dzen ')' in text
xpm :: String -> String -> String
xpm path = wrap ("^i(" ++ path ++ "/.dzen/icons/") ".xpm)"
dzdarkPP hm dzIn = defaultPP
{ ppCurrent = wrap (dzfg hlightCol "^p(;+7)^r(5x5)^p(+2;-7)") "" . dzfg currentCol
, ppVisible = dzfg visibleCol . ("^p(;+7)^ro(5x5)^p(+2;-7)" ++)
, ppHidden = dzfg hiddenCol
, ppHiddenNoWindows = dzfg fadedCol
, ppUrgent = dzfg urgentCol . (\s -> stripDzen s)
, ppWsSep = kernedsp
, ppSep = ""
, ppExtras = [xmonicon]
, ppOrder = \(ws:_:_:xs) -> [" "] ++ [ws] ++ xs
, ppOutput = hPutStrLn dzIn
}
where kernedsp = "^p(+12)"
dzfg c = dzenColor (c dkCols) "" -- (Colorset -> String) -> String -> String
xmonicon = io $ return . Just $
kernedsp ++ "^p(;4)" ++ xpm hm "xmonad16" ++ "^p(;-4)" ++ kernedsp
-- for layouts and titles use something like ppOrder = \(ws:l:t:xs) -> [l,ws,t] ++ xs