summaryrefslogtreecommitdiffstats
path: root/XMonad.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-04-02 06:51:14 +0200
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-04-02 06:51:14 +0200
commit00b6fb5f9b3f3fcb8ff16ebde7314673c81f3f8b (patch)
tree0f3504644bc62692564277973cd161321fd24a54 /XMonad.hs
parent3d25c0a7eda56ea56e5c3bc622ec64b3b640b4c2 (diff)
downloadmetatile-00b6fb5f9b3f3fcb8ff16ebde7314673c81f3f8b.tar
metatile-00b6fb5f9b3f3fcb8ff16ebde7314673c81f3f8b.zip
Revert to the old layout code.
darcs-hash:20070402045114-a5988-3fa15b1c4d8d79494bf430dcad921d22cdfa8d16
Diffstat (limited to 'XMonad.hs')
-rw-r--r--XMonad.hs46
1 files changed, 7 insertions, 39 deletions
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