From 4866f2e367dfcf22a9591231ba40948826a1b438 Mon Sep 17 00:00:00 2001 From: Spencer Janssen Date: Thu, 1 Nov 2007 21:10:59 +0100 Subject: Hierarchify darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz --- XMonad/Layout/TwoPane.hs | 61 ++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 61 insertions(+) create mode 100644 XMonad/Layout/TwoPane.hs (limited to 'XMonad/Layout/TwoPane.hs') 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 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : Spencer Janssen +-- 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 + -- cgit v1.2.3