aboutsummaryrefslogblamecommitdiffstats
path: root/TwoPane.hs
blob: 1fdabc77198618e0409f59ca68f0f24f265c740a (plain) (tree)
1
2
3
4
5
6
7
8
9


                                                                             
                                                            




                                                        
  


                                                                           
  
                                                                             
 




                                        

             

                                                     










                                                                     
                                           
                                                                                                        
      





                                                                          
 
                                              


                                                                       
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonadContrib.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 XMonadContrib.TwoPane (
                              -- * Usage
                              -- $usage
                              twoPane
                             ) where

import XMonad
import Operations ( Resize(..), splitHorizontallyBy )
import StackSet ( focus, up, down)

-- $usage
--
-- You can use this module with the following in your Config.hs file:
--
-- > import XMonadContrib.TwoPane
--
--  and add, to the list of layouts:
--
-- > twoPane defaultDelta (1%2)

twoPane :: Rational -> Rational -> Layout a
twoPane delta split = Layout { doLayout = \r s -> return (arrange r s,Nothing), modifyLayout = message }
 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

    message x = return $ case fromMessage x of
                    Just Shrink -> Just (twoPane delta (split - delta))
                    Just Expand -> Just (twoPane delta (split + delta))
                    _           -> Nothing