From 70452ed192481f965836058bdc8697b5e49ce99f Mon Sep 17 00:00:00 2001 From: Spencer Janssen Date: Mon, 2 Apr 2007 06:51:14 +0200 Subject: Revert to the old layout code. darcs-hash:20070402045114-a5988-3fa15b1c4d8d79494bf430dcad921d22cdfa8d16.gz --- XMonad.hs | 46 +++++++--------------------------------------- 1 file changed, 7 insertions(+), 39 deletions(-) (limited to 'XMonad.hs') diff --git a/XMonad.hs b/XMonad.hs index 8dc5ffb..3a8297b 100644 --- a/XMonad.hs +++ b/XMonad.hs @@ -15,15 +15,12 @@ -- module XMonad ( - X, WorkSpace, XState(..), Layout(..), LayoutDesc(..), Disposition(..), - basicLayoutDesc, currentDesc, disposition, + X, WorkSpace, XState(..), Layout(..), LayoutDesc(..), runX, io, withDisplay, isRoot, spawn, trace, whenJust, rot ) where import StackSet (StackSet) -import qualified StackSet as W -import Data.Ratio import Control.Monad.State import System.IO @@ -46,52 +43,25 @@ data XState = XState , wmprotocols :: {-# UNPACK #-} !Atom , dimensions :: {-# UNPACK #-} !(Int,Int) , workspace :: {-# UNPACK #-} !WorkSpace -- ^ workspace list + , defaultLayoutDesc :: {-# UNPACK #-} !LayoutDesc , layoutDescs :: {-# UNPACK #-} !(M.Map Int LayoutDesc) - , dispositions :: {-# UNPACK #-} !(M.Map Window Disposition) -- ^ mapping of workspaces to descriptions of their layouts } type WorkSpace = StackSet Window - --- --------------------------------------------------------------------- --- Display Positions and Layout - --- | Disposition. Short for 'Display Position,' it describes how much --- of the screen a window would like to occupy, when tiled with others. -data Disposition - = Disposition { vertFrac, horzFrac :: {-# UNPACK #-} !Rational } - -basicDisposition :: Disposition -basicDisposition = Disposition (1%3) (1%3) - -- | The different layout modes -data Layout = Full | Horz | Vert +data Layout = Full | Horz deriving (Enum, Bounded) -- | 'rot' for Layout. rot :: Layout -> Layout -rot Full = Horz -rot Horz = Vert -rot Vert = Full +rot x = toEnum $ (fromEnum x + 1) `mod` (fromEnum (maxBound `asTypeOf` x) + 1) -- | A full description of a particular workspace's layout parameters. -data LayoutDesc = LayoutDesc { layoutType :: !Layout, - horzTileFrac :: !Rational, - vertTileFrac :: !Rational } +data LayoutDesc = LayoutDesc { layoutType :: !Layout + , tileFraction :: !Rational + } -basicLayoutDesc :: LayoutDesc -basicLayoutDesc = LayoutDesc { layoutType = Full, - horzTileFrac = 1%2, - vertTileFrac = 1%2 } - --- | disposition. Gets the disposition of a particular window. -disposition :: Window -> XState -> Disposition -disposition w s = M.findWithDefault basicDisposition w (dispositions s) - --- | Gets the current layoutDesc. -currentDesc :: XState -> LayoutDesc -currentDesc s = M.findWithDefault basicLayoutDesc n (layoutDescs s) - where n = (W.current . workspace $ s) @@ -116,8 +86,6 @@ withDisplay f = gets display >>= f isRoot :: Window -> X Bool isRoot w = liftM (w==) (gets theRoot) - - -- --------------------------------------------------------------------- -- Utilities -- cgit v1.2.3