aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/StackTile.hs
diff options
context:
space:
mode:
authoracura <acura@allyourbase.se>2008-05-20 21:55:59 +0200
committeracura <acura@allyourbase.se>2008-05-20 21:55:59 +0200
commit48cabcb49c74e92c8f5e6e208c5b9704f2806495 (patch)
treedccaca0463fd3136911debd8a31f87c68f2e8ba2 /XMonad/Layout/StackTile.hs
parent64bcd5c45fb82b118365e7c9fbd183346208bc3d (diff)
downloadXMonadContrib-48cabcb49c74e92c8f5e6e208c5b9704f2806495.tar.gz
XMonadContrib-48cabcb49c74e92c8f5e6e208c5b9704f2806495.tar.xz
XMonadContrib-48cabcb49c74e92c8f5e6e208c5b9704f2806495.zip
StackTile
A simple patch to get a dishes like stacking, but with the ability to resize master pane. darcs-hash:20080520195559-aeda8-c943cedb249964ac4ba0e4f66f38a8a651831ddb.gz
Diffstat (limited to 'XMonad/Layout/StackTile.hs')
-rw-r--r--XMonad/Layout/StackTile.hs64
1 files changed, 64 insertions, 0 deletions
diff --git a/XMonad/Layout/StackTile.hs b/XMonad/Layout/StackTile.hs
new file mode 100644
index 0000000..b89cfa9
--- /dev/null
+++ b/XMonad/Layout/StackTile.hs
@@ -0,0 +1,64 @@
+{-# OPTIONS_GHC -fglasgow-exts #-} -- For deriving Data/Typeable
+{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.StackTile
+-- Copyright : (c) Rickard Gustafsson <acura@allyourbase.se>
+-- License : BSD-style (see LICENSE)
+--
+-- Maintainer : Rickard Gustafsson <acura@allyourbase.se>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A stacking layout, like dishes but with the ability to resize master pane.
+-- Moastly usefull on small screens.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.StackTile (
+ -- * Usage
+ -- $usage
+ StackTile(..)
+ ) where
+
+import XMonad hiding (tile)
+import qualified XMonad.StackSet as W
+import Control.Monad
+
+-- $usage
+-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.StackTile
+--
+-- Then edit your @layoutHook@ by adding the ResizableTile layout:
+--
+-- > myLayouts = StackTile 1 (3/100) (1/2) [] ||| etc..
+-- > main = xmonad defaultConfig { layoutHook = myLayouts }
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+--
+data StackTile a = StackTile !Int !Rational !Rational deriving (Show, Read)
+
+instance LayoutClass StackTile a where
+ pureLayout (StackTile nmaster _ frac) r s = zip ws rs
+ where ws = W.integrate s
+ rs = tile frac r nmaster (length ws)
+
+ pureMessage (StackTile nmaster delta frac) m =
+ msum [fmap resize (fromMessage m)
+ ,fmap incmastern (fromMessage m)]
+
+ where resize Shrink = StackTile nmaster delta (max 0 $ frac-delta)
+ resize Expand = StackTile nmaster delta (min 1 $ frac+delta)
+ incmastern (IncMasterN d) = StackTile (max 0 (nmaster+d)) delta frac
+
+ description _ = "StackTile"
+
+tile :: Rational -> Rectangle -> Int -> Int -> [Rectangle]
+tile f r nmaster n = if n <= nmaster || nmaster == 0
+ then splitHorizontally n r
+ else splitHorizontally nmaster r1 ++ splitVertically (n-nmaster) r2 -- two columns
+ where (r1,r2) = splitVerticallyBy f r