Add new config value, defaultMenuGap, for specifying a gap for a status bar

By default, it is 0 (set in Config.hs), but set this to a pixel count to
get a permanent gap at the top of the screen. You can then at startup
launch dzen, and it will run in this gap, and not be obscured by other
windows.

Perfect for a persistant status bar.
This commit is contained in:
Don Stewart
2007-05-27 12:27:02 +00:00
parent e5e4b46ffa
commit a64c9f1856
3 changed files with 9 additions and 2 deletions

View File

@@ -49,6 +49,10 @@ defaultDelta = 3%100
defaultWindowsInMaster :: Int
defaultWindowsInMaster = 1
-- Default width of gap at top of screen for a menu bar (e.g. 16)
defaultMenuGap :: Int
defaultMenuGap = 0
-- numlock handling:
--
-- The mask for the numlock key. You may need to change this on some systems.

View File

@@ -1,3 +1,4 @@
module Config where
import Graphics.X11.Xlib.Types (Dimension)
borderWidth :: Dimension
defaultMenuGap :: Int

View File

@@ -15,7 +15,7 @@ module Operations where
import XMonad
import qualified StackSet as W
import {-# SOURCE #-} Config (borderWidth)
import {-# SOURCE #-} Config (borderWidth,defaultMenuGap)
import Data.Maybe
import Data.List (genericIndex, intersectBy)
@@ -131,8 +131,10 @@ refresh = do
let n = W.tag (W.workspace w)
this = W.view n ws
Just l = fmap fst $ M.lookup n fls
Rectangle sx sy sw sh = genericIndex xinesc (W.screen w)
-- now tile the windows on this workspace
rs <- doLayout l (genericIndex xinesc (W.screen w)) (W.index this)
rs <- doLayout l (Rectangle sx (sy + fromIntegral defaultMenuGap)
sw (sh - fromIntegral defaultMenuGap)) (W.index this)
mapM_ (\(win,rect) -> io (tileWindow d win rect)) rs
-- and raise the focused window if there is one.