aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/TwoPane.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Layout/TwoPane.hs')
-rw-r--r--XMonad/Layout/TwoPane.hs61
1 files changed, 61 insertions, 0 deletions
diff --git a/XMonad/Layout/TwoPane.hs b/XMonad/Layout/TwoPane.hs
new file mode 100644
index 0000000..bca49a7
--- /dev/null
+++ b/XMonad/Layout/TwoPane.hs
@@ -0,0 +1,61 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.TwoPane
+-- Copyright : (c) Spencer Janssen <sjanssen@cse.unl.edu>
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Spencer Janssen <sjanssen@cse.unl.edu>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A layout that splits the screen horizontally and shows two windows. The
+-- left window is always the master window, and the right is either the
+-- currently focused window or the second window in layout order.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.TwoPane (
+ -- * Usage
+ -- $usage
+ TwoPane (..)
+ ) where
+
+import XMonad
+import XMonad.Layouts ( Resize(..), splitHorizontallyBy )
+import XMonad.StackSet ( focus, up, down)
+
+-- $usage
+--
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonad.Layout.TwoPane
+--
+-- and add, to the list of layouts:
+--
+-- > , (Layout $ TwoPane 0.03 0.5)
+
+-- %import XMonad.Layout.TwoPane
+-- %layout , (Layout $ TwoPane 0.03 0.5)
+
+data TwoPane a =
+ TwoPane Rational Rational
+ deriving ( Show, Read )
+
+instance LayoutClass TwoPane a where
+ doLayout (TwoPane _ split) r s = return (arrange r s,Nothing)
+ where
+ arrange rect st = case reverse (up st) of
+ (master:_) -> [(master,left),(focus st,right)]
+ [] -> case down st of
+ (next:_) -> [(focus st,left),(next,right)]
+ [] -> [(focus st, rect)]
+ where (left, right) = splitHorizontallyBy split rect
+
+ handleMessage (TwoPane delta split) x =
+ return $ case fromMessage x of
+ Just Shrink -> Just (TwoPane delta (split - delta))
+ Just Expand -> Just (TwoPane delta (split + delta))
+ _ -> Nothing
+