From 39f0e9b18d6613bff455a31fa76ab79384c3ac2f Mon Sep 17 00:00:00 2001 From: hughes Date: Sun, 1 Apr 2007 03:47:06 +0200 Subject: Vertical/horizontal split, and resizability. darcs-hash:20070401014706-3a569-26a764b57274f67057adf0b81eb71158b58f49de.gz --- XMonad.hs | 42 ++++++++++++++++++++++++++++++++++++------ 1 file changed, 36 insertions(+), 6 deletions(-) (limited to 'XMonad.hs') diff --git a/XMonad.hs b/XMonad.hs index 7ffab6c..c70ead1 100644 --- a/XMonad.hs +++ b/XMonad.hs @@ -15,12 +15,15 @@ -- module XMonad ( - X, WorkSpace, XState(..), Layout(..), LayoutDesc(..), + X, WorkSpace, XState(..), Layout(..), LayoutDesc(..), Disposition(..), + basicLayoutDesc, currentDesc, disposition, runX, io, withDisplay, isRoot, spawn, trace, whenJust, swap ) where import StackSet (StackSet) +import qualified StackSet as W +import Data.Ratio import Control.Monad.State import System.IO @@ -43,15 +46,27 @@ 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 + +-- --------------------------------------------------------------------- +-- Dispositions 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 | Tile +data Layout = Full | Horz | Vert -- | 'not' for Layout. swap :: Layout -> Layout @@ -59,10 +74,23 @@ swap Full = Tile swap _ = Full -- | A full description of a particular workspace's layout parameters. -data LayoutDesc = LayoutDesc { layoutType :: !Layout - , tileFraction :: !Rational - } +data LayoutDesc = LayoutDesc { layoutType :: !Layout, + horzTileFrac :: !Rational, + vertTileFrac :: !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) @@ -87,6 +115,8 @@ withDisplay f = gets display >>= f isRoot :: Window -> X Bool isRoot w = liftM (w==) (gets theRoot) + + -- --------------------------------------------------------------------- -- Utilities -- cgit v1.2.3