summaryrefslogtreecommitdiffstats
path: root/XMonad.hs
diff options
context:
space:
mode:
authorhughes <hughes@rpi.edu>2007-04-01 03:47:06 +0200
committerhughes <hughes@rpi.edu>2007-04-01 03:47:06 +0200
commitf649b54049a3a184a89070772cd45d0c5c015b1c (patch)
treef4c38c17a83bf624c4cd1122e88d78f55951caeb /XMonad.hs
parentdd72a298b8f79546105ffbbd6005bbfa887e1e6a (diff)
downloadmetatile-f649b54049a3a184a89070772cd45d0c5c015b1c.tar
metatile-f649b54049a3a184a89070772cd45d0c5c015b1c.zip
Vertical/horizontal split, and resizability.
darcs-hash:20070401014706-3a569-26a764b57274f67057adf0b81eb71158b58f49de
Diffstat (limited to 'XMonad.hs')
-rw-r--r--XMonad.hs42
1 files changed, 36 insertions, 6 deletions
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