mod-b, toggle on or off the status bar gap

This commit is contained in:
Don Stewart 2007-05-27 12:59:28 +00:00
parent a64c9f1856
commit bb4bd97c87
6 changed files with 88 additions and 8 deletions

View File

@ -49,9 +49,9 @@ defaultDelta = 3%100
defaultWindowsInMaster :: Int defaultWindowsInMaster :: Int
defaultWindowsInMaster = 1 defaultWindowsInMaster = 1
-- Default width of gap at top of screen for a menu bar (e.g. 16) -- Default height of gap at top of screen for a menu bar (e.g. 15)
defaultMenuGap :: Int defaultStatusGap :: Int
defaultMenuGap = 0 defaultStatusGap = 0 -- 15 for default dzen
-- numlock handling: -- numlock handling:
-- --
@ -114,6 +114,9 @@ keys = M.fromList $
, ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- @@ Increment the 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 , ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- @@ Deincrement the number of windows in the master area
-- toggle the status bar gap
, ((modMask , xK_b ), modifyGap (\n -> if n == 0 then defaultStatusGap else 0)) -- @@ Toggle the status bar gap
-- quit, or restart -- quit, or restart
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- @@ Quit xmonad , ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- @@ Quit xmonad
, ((modMask .|. shiftMask .|. controlMask, xK_q ), restart Nothing True) -- @@ Restart xmonad , ((modMask .|. shiftMask .|. controlMask, xK_q ), restart Nothing True) -- @@ Restart xmonad

View File

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

View File

@ -61,6 +61,7 @@ main = do
st = XState st = XState
{ windowset = winset { windowset = winset
, layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]] , layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]]
, statusGap = defaultStatusGap
, xineScreens = xinesc , xineScreens = xinesc
, dimensions = (fromIntegral (displayWidth dpy dflt), , dimensions = (fromIntegral (displayWidth dpy dflt),
fromIntegral (displayHeight dpy dflt)) } fromIntegral (displayHeight dpy dflt)) }

View File

@ -15,7 +15,7 @@ module Operations where
import XMonad import XMonad
import qualified StackSet as W import qualified StackSet as W
import {-# SOURCE #-} Config (borderWidth,defaultMenuGap) import {-# SOURCE #-} Config (borderWidth)
import Data.Maybe import Data.Maybe
import Data.List (genericIndex, intersectBy) import Data.List (genericIndex, intersectBy)
@ -67,6 +67,12 @@ shift n = withFocused hide >> windows (W.shift n)
view :: WorkspaceId -> X () view :: WorkspaceId -> X ()
view = windows . W.view view = windows . W.view
-- | Modify the size of the status gap at the top of the screen
modifyGap :: (Int -> Int) -> X ()
modifyGap f = do modify $ \s -> s { statusGap = max 0 (f (statusGap s)) }
refresh
-- | Kill the currently focused client. If we do kill it, we'll get a -- | Kill the currently focused client. If we do kill it, we'll get a
-- delete notify back from X. -- delete notify back from X.
-- --
@ -123,7 +129,7 @@ hide w = withDisplay $ \d -> do
-- --
refresh :: X () refresh :: X ()
refresh = do refresh = do
XState { windowset = ws, layouts = fls, xineScreens = xinesc } <- get XState { windowset = ws, layouts = fls, xineScreens = xinesc, statusGap = gap } <- get
d <- asks display d <- asks display
-- for each workspace, layout the currently visible workspaces -- for each workspace, layout the currently visible workspaces
@ -133,8 +139,8 @@ refresh = do
Just l = fmap fst $ M.lookup n fls Just l = fmap fst $ M.lookup n fls
Rectangle sx sy sw sh = genericIndex xinesc (W.screen w) Rectangle sx sy sw sh = genericIndex xinesc (W.screen w)
-- now tile the windows on this workspace -- now tile the windows on this workspace
rs <- doLayout l (Rectangle sx (sy + fromIntegral defaultMenuGap) rs <- doLayout l (Rectangle sx (sy + fromIntegral gap)
sw (sh - fromIntegral defaultMenuGap)) (W.index this) sw (sh - fromIntegral gap)) (W.index this)
mapM_ (\(win,rect) -> io (tileWindow d win rect)) rs mapM_ (\(win,rect) -> io (tileWindow d win rect)) rs
-- and raise the focused window if there is one. -- and raise the focused window if there is one.

View File

@ -40,6 +40,7 @@ data XState = XState
{ windowset :: !WindowSet -- ^ workspace list { windowset :: !WindowSet -- ^ workspace list
, xineScreens :: ![Rectangle] -- ^ dimensions of each screen , xineScreens :: ![Rectangle] -- ^ dimensions of each screen
, dimensions :: !(Position,Position) -- ^ dimensions of the screen, , dimensions :: !(Position,Position) -- ^ dimensions of the screen,
, statusGap :: !Int -- ^ width of status bar
-- used for hiding windows -- used for hiding windows
, layouts :: !(M.Map WorkspaceId (Layout, [Layout])) } , layouts :: !(M.Map WorkspaceId (Layout, [Layout])) }
-- ^ mapping of workspaces to descriptions of their layouts -- ^ mapping of workspaces to descriptions of their layouts

70
util/gapcalc.c Normal file
View File

@ -0,0 +1,70 @@
/* gapcalc - calculate height of given font
* Copyright (C) 2007 by Robert Manea <rob.manea@gmail.com>
*
* Compile with: cc -lX11 -o gapcalc gapcalc.c
*/
#include<stdio.h>
#include<stdlib.h>
#include<stdarg.h>
#include <X11/Xlib.h>
#include <X11/Xutil.h>
void
eprint(const char *errstr, ...) {
va_list ap;
va_start(ap, errstr);
vfprintf(stderr, errstr, ap);
va_end(ap);
exit(EXIT_FAILURE);
}
int
main(int argc, char *argv[]) {
Display *dpy;
XFontStruct *xfont;
XFontSet set;
char *def, **missing;
char *fontstr;
int i, n, ascent, descent;
if(argc < 2)
eprint("Usage: gapcalc <font>\n");
if(!(dpy = XOpenDisplay(0)))
eprint("fatal: cannot open display\n");
fontstr = argv[1];
missing = NULL;
set = XCreateFontSet(dpy, fontstr, &missing, &n, &def);
if(missing)
XFreeStringList(missing);
if(set) {
XFontSetExtents *font_extents;
XFontStruct **xfonts;
char **font_names;
ascent = descent = 0;
font_extents = XExtentsOfFontSet(set);
n = XFontsOfFontSet(set, &xfonts, &font_names);
for(i = 0, ascent = 0, descent = 0; i < n; i++) {
if(ascent < (*xfonts)->ascent)
ascent = (*xfonts)->ascent;
if(descent < (*xfonts)->descent)
descent = (*xfonts)->descent;
xfonts++;
}
} else if(!set && (xfont = XLoadQueryFont(dpy, fontstr))) {
ascent = xfont->ascent;
descent = xfont->descent;
} else
eprint("fatal: cannot find specified font\n");
printf("%d\n", ascent + descent + 2);
return EXIT_SUCCESS;
}