Add Config.hs-boot, remove defaultLayoutDesc from XConf

This commit is contained in:
Spencer Janssen
2007-04-30 16:26:47 +00:00
parent ecbff364c9
commit 08e514b28f
5 changed files with 9 additions and 8 deletions

View File

@@ -114,8 +114,8 @@ focusedBorderColor = "#ff0000"
-- What layout to start in, and what the default proportion for the -- What layout to start in, and what the default proportion for the
-- left pane should be in the tiled layout. See LayoutDesc and -- left pane should be in the tiled layout. See LayoutDesc and
-- friends in XMonad.hs for options. -- friends in XMonad.hs for options.
startingLayoutDesc :: LayoutDesc defaultLayoutDesc :: LayoutDesc
startingLayoutDesc = defaultLayoutDesc =
LayoutDesc { layoutType = Full LayoutDesc { layoutType = Full
, tileFraction = 1%2 } , tileFraction = 1%2 }

3
Config.hs-boot Normal file
View File

@@ -0,0 +1,3 @@
module Config where
import XMonad (LayoutDesc)
defaultLayoutDesc :: LayoutDesc

View File

@@ -54,7 +54,6 @@ main = do
-- fromIntegral needed for X11 versions that use Int instead of CInt. -- fromIntegral needed for X11 versions that use Int instead of CInt.
, dimensions = (fromIntegral (displayWidth dpy dflt), , dimensions = (fromIntegral (displayWidth dpy dflt),
fromIntegral (displayHeight dpy dflt)) fromIntegral (displayHeight dpy dflt))
, defaultLayoutDesc = startingLayoutDesc
, normalBorder = nbc , normalBorder = nbc
, focusedBorder = fbc , focusedBorder = fbc
} }

View File

@@ -29,6 +29,7 @@ import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras import Graphics.X11.Xlib.Extras
import XMonad import XMonad
import {-# SOURCE #-} Config
import qualified StackSet as W import qualified StackSet as W
@@ -41,11 +42,11 @@ import qualified StackSet as W
refresh :: X () refresh :: X ()
refresh = do refresh = do
XState { workspace = ws, layoutDescs = fls } <- get XState { workspace = ws, layoutDescs = fls } <- get
XConf { xineScreens = xinesc, display = d, defaultLayoutDesc = dfltfl } <- ask XConf { xineScreens = xinesc, display = d } <- ask
flip mapM_ (M.assocs (W.screen2ws ws)) $ \(scn, n) -> do flip mapM_ (M.assocs (W.screen2ws ws)) $ \(scn, n) -> do
let sc = genericIndex xinesc scn -- temporary coercion! let sc = genericIndex xinesc scn -- temporary coercion!
fl = M.findWithDefault dfltfl n fls fl = M.findWithDefault defaultLayoutDesc n fls
mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) $ mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) $
case layoutType fl of case layoutType fl of
Full -> fmap (flip (,) sc) $ maybeToList $ W.peekStack n ws Full -> fmap (flip (,) sc) $ maybeToList $ W.peekStack n ws
@@ -104,11 +105,10 @@ changeSplit delta = layout $ \fl ->
-- function and refresh. -- function and refresh.
layout :: (LayoutDesc -> LayoutDesc) -> X () layout :: (LayoutDesc -> LayoutDesc) -> X ()
layout f = do layout f = do
dfl <- asks defaultLayoutDesc
modify $ \s -> modify $ \s ->
let fls = layoutDescs s let fls = layoutDescs s
n = W.current . workspace $ s n = W.current . workspace $ s
fl = M.findWithDefault dfl n fls fl = M.findWithDefault defaultLayoutDesc n fls
in s { layoutDescs = M.insert n (f fl) fls } in s { layoutDescs = M.insert n (f fl) fls }
refresh refresh

View File

@@ -49,7 +49,6 @@ data XConf = XConf
-- used for hiding windows -- used for hiding windows
, xineScreens :: ![Rectangle] -- ^ dimensions of each screen , xineScreens :: ![Rectangle] -- ^ dimensions of each screen
, defaultLayoutDesc :: !LayoutDesc -- ^ default layout
, normalBorder :: !Color -- ^ border color of unfocused windows , normalBorder :: !Color -- ^ border color of unfocused windows
, focusedBorder :: !Color -- ^ border color of the focused window , focusedBorder :: !Color -- ^ border color of the focused window
} }