mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
Use (Int,Int,Int,Int) for arbitrary gaps on any side of the screen
This commit is contained in:
parent
b0cfe9b6ab
commit
1d2c5ca35a
13
Config.hs
13
Config.hs
@ -49,9 +49,14 @@ defaultDelta = 3%100
|
|||||||
defaultWindowsInMaster :: Int
|
defaultWindowsInMaster :: Int
|
||||||
defaultWindowsInMaster = 1
|
defaultWindowsInMaster = 1
|
||||||
|
|
||||||
-- Default height of gap at top of screen for a menu bar (e.g. 15)
|
-- Default offset of drawable screen boundary from physical screen.
|
||||||
defaultStatusGap :: Int
|
-- Anything non-zero here will leave a gap of that many pixels on the
|
||||||
defaultStatusGap = 0 -- 15 for default dzen
|
-- given edge. A useful gap at top of screen for a menu bar (e.g. 15)
|
||||||
|
--
|
||||||
|
-- Fields are: top, bottom, left, right.
|
||||||
|
--
|
||||||
|
defaultGap :: (Int,Int,Int,Int)
|
||||||
|
defaultGap = (0,0,0,0) -- 15 for default dzen
|
||||||
|
|
||||||
-- numlock handling:
|
-- numlock handling:
|
||||||
--
|
--
|
||||||
@ -115,7 +120,7 @@ keys = M.fromList $
|
|||||||
, ((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
|
-- toggle the status bar gap
|
||||||
, ((modMask , xK_b ), modifyGap (\n -> if n == 0 then defaultStatusGap else 0)) -- @@ Toggle the status bar gap
|
, ((modMask , xK_b ), modifyGap (\n -> if n == defaultGap then (0,0,0,0) else defaultGap)) -- @@ 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
|
||||||
|
2
Main.hs
2
Main.hs
@ -61,7 +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
|
, statusGap = defaultGap
|
||||||
, xineScreens = xinesc
|
, xineScreens = xinesc
|
||||||
, dimensions = (fromIntegral (displayWidth dpy dflt),
|
, dimensions = (fromIntegral (displayWidth dpy dflt),
|
||||||
fromIntegral (displayHeight dpy dflt)) }
|
fromIntegral (displayHeight dpy dflt)) }
|
||||||
|
@ -68,8 +68,8 @@ view :: WorkspaceId -> X ()
|
|||||||
view = windows . W.view
|
view = windows . W.view
|
||||||
|
|
||||||
-- | Modify the size of the status gap at the top of the screen
|
-- | Modify the size of the status gap at the top of the screen
|
||||||
modifyGap :: (Int -> Int) -> X ()
|
modifyGap :: ((Int,Int,Int,Int) -> (Int,Int,Int,Int)) -> X ()
|
||||||
modifyGap f = modify (\s -> s { statusGap = max 0 (f (statusGap s)) }) >> refresh
|
modifyGap f = modify (\s -> s { statusGap = 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.
|
||||||
@ -127,7 +127,7 @@ hide w = withDisplay $ \d -> do
|
|||||||
--
|
--
|
||||||
refresh :: X ()
|
refresh :: X ()
|
||||||
refresh = do
|
refresh = do
|
||||||
XState { windowset = ws, layouts = fls, xineScreens = xinesc, statusGap = gap } <- get
|
XState { windowset = ws, layouts = fls, xineScreens = xinesc, statusGap = (gt,gb,gl,gr) } <- get
|
||||||
d <- asks display
|
d <- asks display
|
||||||
|
|
||||||
-- for each workspace, layout the currently visible workspaces
|
-- for each workspace, layout the currently visible workspaces
|
||||||
@ -139,7 +139,10 @@ refresh = do
|
|||||||
|
|
||||||
-- now tile the windows on this workspace, and set gap maybe on current
|
-- now tile the windows on this workspace, and set gap maybe on current
|
||||||
rs <- doLayout l (if w == W.current ws
|
rs <- doLayout l (if w == W.current ws
|
||||||
then Rectangle sx (sy + fromIntegral gap) sw (sh - fromIntegral gap)
|
then Rectangle (sx + fromIntegral gl)
|
||||||
|
(sy + fromIntegral gt)
|
||||||
|
(sw - fromIntegral (gl + gr))
|
||||||
|
(sh - fromIntegral (gt + gb))
|
||||||
else r) (W.index this)
|
else r) (W.index this)
|
||||||
mapM_ (\(win,rect) -> io (tileWindow d win rect)) rs
|
mapM_ (\(win,rect) -> io (tileWindow d win rect)) rs
|
||||||
|
|
||||||
|
25
XMonad.hs
25
XMonad.hs
@ -37,23 +37,20 @@ import qualified Data.Map as M
|
|||||||
-- | XState, the window manager state.
|
-- | XState, the window manager state.
|
||||||
-- Just the display, width, height and a window list
|
-- Just the display, width, height and a window list
|
||||||
data XState = XState
|
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
|
, statusGap :: !(Int,Int,Int,Int) -- ^ width of status bar
|
||||||
-- 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
|
||||||
|
|
||||||
data XConf = XConf
|
data XConf = XConf
|
||||||
{ display :: Display -- ^ the X11 display
|
{ display :: Display -- ^ the X11 display
|
||||||
|
, theRoot :: !Window -- ^ the root window
|
||||||
, theRoot :: !Window -- ^ the root window
|
, wmdelete :: !Atom -- ^ window deletion atom
|
||||||
, wmdelete :: !Atom -- ^ window deletion atom
|
, wmprotocols :: !Atom -- ^ wm protocols atom
|
||||||
, wmprotocols :: !Atom -- ^ wm protocols atom
|
, normalBorder :: !Color -- ^ border color of unfocused windows
|
||||||
|
, focusedBorder :: !Color } -- ^ border color of the focused window
|
||||||
, normalBorder :: !Color -- ^ border color of unfocused windows
|
|
||||||
, focusedBorder :: !Color } -- ^ border color of the focused window
|
|
||||||
|
|
||||||
type WindowSet = StackSet WorkspaceId Window ScreenId
|
type WindowSet = StackSet WorkspaceId Window ScreenId
|
||||||
|
|
||||||
|
Loading…
x
Reference in New Issue
Block a user