summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-04-30 18:26:47 +0200
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-04-30 18:26:47 +0200
commit0f366aba734661ab6cc97ed368fe683d00fcc2d3 (patch)
tree60c97016528716492060a95ad6ab7df330258938
parentd12e2d6006888fbcb325b76457fc76cdfadb2621 (diff)
downloadmetatile-0f366aba734661ab6cc97ed368fe683d00fcc2d3.tar
metatile-0f366aba734661ab6cc97ed368fe683d00fcc2d3.zip
Add Config.hs-boot, remove defaultLayoutDesc from XConf
darcs-hash:20070430162647-a5988-70420c2db283eb1585c96d977e5ac5ca3d0d1532
-rw-r--r--Config.hs4
-rw-r--r--Config.hs-boot3
-rw-r--r--Main.hs1
-rw-r--r--Operations.hs8
-rw-r--r--XMonad.hs1
5 files changed, 9 insertions, 8 deletions
diff --git a/Config.hs b/Config.hs
index a49f845..7d2c714 100644
--- a/Config.hs
+++ b/Config.hs
@@ -114,8 +114,8 @@ focusedBorderColor = "#ff0000"
-- What layout to start in, and what the default proportion for the
-- left pane should be in the tiled layout. See LayoutDesc and
-- friends in XMonad.hs for options.
-startingLayoutDesc :: LayoutDesc
-startingLayoutDesc =
+defaultLayoutDesc :: LayoutDesc
+defaultLayoutDesc =
LayoutDesc { layoutType = Full
, tileFraction = 1%2 }
diff --git a/Config.hs-boot b/Config.hs-boot
new file mode 100644
index 0000000..f5e7206
--- /dev/null
+++ b/Config.hs-boot
@@ -0,0 +1,3 @@
+module Config where
+import XMonad (LayoutDesc)
+defaultLayoutDesc :: LayoutDesc
diff --git a/Main.hs b/Main.hs
index 00f1948..ecd975d 100644
--- a/Main.hs
+++ b/Main.hs
@@ -54,7 +54,6 @@ main = do
-- fromIntegral needed for X11 versions that use Int instead of CInt.
, dimensions = (fromIntegral (displayWidth dpy dflt),
fromIntegral (displayHeight dpy dflt))
- , defaultLayoutDesc = startingLayoutDesc
, normalBorder = nbc
, focusedBorder = fbc
}
diff --git a/Operations.hs b/Operations.hs
index ae9232b..ed25b31 100644
--- a/Operations.hs
+++ b/Operations.hs
@@ -29,6 +29,7 @@ import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import XMonad
+import {-# SOURCE #-} Config
import qualified StackSet as W
@@ -41,11 +42,11 @@ import qualified StackSet as W
refresh :: X ()
refresh = do
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
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) $
case layoutType fl of
Full -> fmap (flip (,) sc) $ maybeToList $ W.peekStack n ws
@@ -104,11 +105,10 @@ changeSplit delta = layout $ \fl ->
-- function and refresh.
layout :: (LayoutDesc -> LayoutDesc) -> X ()
layout f = do
- dfl <- asks defaultLayoutDesc
modify $ \s ->
let fls = layoutDescs 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 }
refresh
diff --git a/XMonad.hs b/XMonad.hs
index 44cc017..70e41f1 100644
--- a/XMonad.hs
+++ b/XMonad.hs
@@ -49,7 +49,6 @@ data XConf = XConf
-- used for hiding windows
, xineScreens :: ![Rectangle] -- ^ dimensions of each screen
- , defaultLayoutDesc :: !LayoutDesc -- ^ default layout
, normalBorder :: !Color -- ^ border color of unfocused windows
, focusedBorder :: !Color -- ^ border color of the focused window
}