From 8fc2edf1a9a2f60442031776a22d1b77d1a44936 Mon Sep 17 00:00:00 2001 From: Spencer Janssen Date: Tue, 25 Mar 2008 10:15:26 +0100 Subject: Remove gaps darcs-hash:20080325091526-a5988-e6ed58b0d493845525a4c7e5977352cfb12b9c92.gz --- XMonad/Config.hs | 24 +++--------------------- XMonad/Core.hs | 7 ++----- XMonad/Main.hs | 4 +--- XMonad/Operations.hs | 18 ++---------------- 4 files changed, 8 insertions(+), 45 deletions(-) (limited to 'XMonad') diff --git a/XMonad/Config.hs b/XMonad/Config.hs index 7b78b00..d65cf47 100644 --- a/XMonad/Config.hs +++ b/XMonad/Config.hs @@ -26,12 +26,10 @@ module XMonad.Config (defaultConfig) where -- import XMonad.Core as XMonad hiding (workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings - ,defaultGaps,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor - ,focusFollowsMouse) + ,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse) import qualified XMonad.Core as XMonad (workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings - ,defaultGaps,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor - ,focusFollowsMouse) + ,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse) import XMonad.Layout import XMonad.Operations @@ -89,21 +87,6 @@ normalBorderColor, focusedBorderColor :: String normalBorderColor = "#dddddd" focusedBorderColor = "#ff0000" --- | 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 = [(0,0,0,0)] -- 15 for default dzen font - ------------------------------------------------------------------------ -- Window rules @@ -216,7 +199,7 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $ , ((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 = (XMonad.defaultGaps conf ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap + --, ((modMask , xK_b ), modifyGap (\i n -> let x = (XMonad.defaultGaps conf ++ 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 @@ -252,7 +235,6 @@ mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $ defaultConfig = XConfig { XMonad.borderWidth = borderWidth , XMonad.workspaces = workspaces - , XMonad.defaultGaps = defaultGaps , XMonad.layoutHook = layout , XMonad.terminal = terminal , XMonad.normalBorderColor = normalBorderColor diff --git a/XMonad/Core.hs b/XMonad/Core.hs index 397c39a..26f2617 100644 --- a/XMonad/Core.hs +++ b/XMonad/Core.hs @@ -79,7 +79,6 @@ data XConfig l = XConfig , layoutHook :: !(l Window) -- ^ The available layouts , manageHook :: !ManageHook -- ^ The action to run when a new window is opened , workspaces :: ![String] -- ^ The list of workspaces' names - , defaultGaps :: ![(Int,Int,Int,Int)] -- ^ The list of gaps, per screen , numlockMask :: !KeyMask -- ^ The numlock modifier , modMask :: !KeyMask -- ^ the mod modifier , keys :: !(XConfig Layout -> M.Map (ButtonMask,KeySym) (X ())) @@ -102,10 +101,8 @@ type WorkspaceId = String -- | Physical screen indices newtype ScreenId = S Int deriving (Eq,Ord,Show,Read,Enum,Num,Integral,Real) --- | The 'Rectangle' with screen dimensions and the list of gaps -data ScreenDetail = SD { screenRect :: !Rectangle - , statusGap :: !(Int,Int,Int,Int) -- ^ gaps on the sides of the screen that shouldn't be tiled, usually for status bars - } deriving (Eq,Show, Read) +-- | The 'Rectangle' with screen dimensions +data ScreenDetail = SD { screenRect :: !Rectangle } deriving (Eq,Show, Read) ------------------------------------------------------------------------ diff --git a/XMonad/Main.hs b/XMonad/Main.hs index 3840c53..ab276af 100644 --- a/XMonad/Main.hs +++ b/XMonad/Main.hs @@ -64,7 +64,7 @@ xmonad initxmc = do let layout = layoutHook xmc lreads = readsLayout layout - initialWinset = new layout (workspaces xmc) $ zipWith SD xinesc gaps + initialWinset = new layout (workspaces xmc) $ map SD xinesc maybeRead reads' s = case reads' s of [(x, "")] -> Just x @@ -76,8 +76,6 @@ xmonad initxmc = do return . W.ensureTags layout (workspaces xmc) $ W.mapLayout (fromMaybe layout . maybeRead lreads) ws - gaps = take (length xinesc) $ defaultGaps xmc ++ repeat (0,0,0,0) - cf = XConf { display = dpy , config = xmc diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs index 56e04bb..7daf309 100644 --- a/XMonad/Operations.hs +++ b/XMonad/Operations.hs @@ -77,15 +77,6 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do unmanage :: Window -> X () unmanage = windows . W.delete --- | Modify the size of the status gap at the top of the current screen --- Taking a function giving the current screen, and current geometry. -modifyGap :: (Int -> (Int,Int,Int,Int) -> (Int,Int,Int,Int)) -> X () -modifyGap f = do - windows $ \ws@(W.StackSet { W.current = c@(W.Screen { W.screenDetail = sd }) }) -> - let n = fromIntegral . W.screen $ c - g = f n . statusGap $ sd - in ws { W.current = c { W.screenDetail = sd { statusGap = g } } } - -- | Kill the currently focused client. If we do kill it, we'll get a -- delete notify back from X. -- @@ -136,10 +127,7 @@ windows f = do tiled = (W.stack . W.workspace . W.current $ this) >>= W.filter (`M.notMember` W.floating ws) >>= W.filter (`notElem` vis) - (SD (Rectangle sx sy sw sh) - (gt,gb,gl,gr)) = W.screenDetail w - viewrect = Rectangle (sx + fromIntegral gl) (sy + fromIntegral gt) - (sw - fromIntegral (gl + gr)) (sh - fromIntegral (gt + gb)) + viewrect@(Rectangle sx sy sw sh) = screenRect $ W.screenDetail w -- just the tiled windows: -- now tile the windows on this workspace, modified by the gap @@ -276,9 +264,7 @@ rescreen = do windows $ \ws@(W.StackSet { W.current = v, W.visible = vs, W.hidden = hs }) -> let (xs, ys) = splitAt (length xinesc) $ map W.workspace (v:vs) ++ hs - (a:as) = zipWith3 W.Screen xs [0..] $ zipWith SD xinesc gs - sgs = map (statusGap . W.screenDetail) (v:vs) - gs = take (length xinesc) (sgs ++ repeat (0,0,0,0)) + (a:as) = zipWith3 W.Screen xs [0..] $ map SD xinesc in ws { W.current = a , W.visible = as , W.hidden = ys } -- cgit v1.2.3