summaryrefslogtreecommitdiffstats
path: root/XMonad.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@cse.unsw.edu.au>2007-04-11 08:56:07 +0200
committerDon Stewart <dons@cse.unsw.edu.au>2007-04-11 08:56:07 +0200
commit43ee17b194d37d2efdaad9167cca368585eacdec (patch)
treef74688539e54ad0e3f6e39776b6cb618dbbf73fc /XMonad.hs
parent35349b183768c504fc002102303c5e08272490cc (diff)
downloadmetatile-43ee17b194d37d2efdaad9167cca368585eacdec.tar
metatile-43ee17b194d37d2efdaad9167cca368585eacdec.zip
clean up only
darcs-hash:20070411065607-9c5c1-dcbe0dac9354e1588ab6970daf65bc1405a204b0
Diffstat (limited to 'XMonad.hs')
-rw-r--r--XMonad.hs51
1 files changed, 29 insertions, 22 deletions
diff --git a/XMonad.hs b/XMonad.hs
index abc422b..642a038 100644
--- a/XMonad.hs
+++ b/XMonad.hs
@@ -33,32 +33,24 @@ import qualified Data.Map as M
-- | XState, the window manager state.
-- Just the display, width, height and a window list
data XState = XState
- { display :: Display -- ^ the X11 display
-
- , xineScreens :: ![Rectangle] -- ^ dimensions of each screen
-
- , theRoot :: !Window -- ^ the root window
- , wmdelete :: !Atom -- ^ window deletion atom
- , wmprotocols :: !Atom -- ^ wm protocols atom
- , dimensions :: !(Int,Int) -- ^ dimensions of the screen, used for hiding windows
- , workspace :: !WorkSpace -- ^ workspace list
- , defaultLayoutDesc :: !LayoutDesc -- ^ default layout
- , layoutDescs :: !(M.Map WorkspaceId LayoutDesc) -- ^ mapping of workspaces to descriptions of their layouts
+ { display :: Display -- ^ the X11 display
+
+ , theRoot :: !Window -- ^ the root window
+ , wmdelete :: !Atom -- ^ window deletion atom
+ , wmprotocols :: !Atom -- ^ wm protocols atom
+ , dimensions :: !(Int,Int) -- ^ dimensions of the screen,
+ -- used for hiding windows
+ , workspace :: !WorkSpace -- ^ workspace list
+
+ , xineScreens :: ![Rectangle] -- ^ dimensions of each screen
+ , defaultLayoutDesc :: !LayoutDesc -- ^ default layout
+ , layoutDescs :: !(M.Map WorkspaceId LayoutDesc) -- ^ mapping of workspaces
+ -- to descriptions of their layouts
}
type WorkSpace = StackSet Window
--- | The different layout modes
-data Layout = Full | Tall | Wide deriving (Enum, Bounded, Eq)
-
--- | 'rot' for Layout.
-rot :: Layout -> Layout
-rot x = if x == maxBound then minBound else succ x
-
--- | A full description of a particular workspace's layout parameters.
-data LayoutDesc = LayoutDesc { layoutType :: !Layout
- , tileFraction :: !Rational
- }
+------------------------------------------------------------------------
-- | The X monad, a StateT transformer over IO encapsulating the window
-- manager state
@@ -81,6 +73,21 @@ withDisplay f = gets display >>= f
isRoot :: Window -> X Bool
isRoot w = liftM (w==) (gets theRoot)
+------------------------------------------------------------------------
+-- Layout handling
+
+-- | The different layout modes
+data Layout = Full | Tall | Wide deriving (Enum, Bounded, Eq)
+
+-- | 'rot' for Layout.
+rot :: Layout -> Layout
+rot x = if x == maxBound then minBound else succ x
+
+-- | A full description of a particular workspace's layout parameters.
+data LayoutDesc = LayoutDesc { layoutType :: !Layout
+ , tileFraction :: !Rational
+ }
+
-- ---------------------------------------------------------------------
-- Utilities