diff options
-rw-r--r-- | Combo.hs | 3 | ||||
-rw-r--r-- | LayoutCombinators.hs | 41 | ||||
-rw-r--r-- | MetaModule.hs | 1 |
3 files changed, 44 insertions, 1 deletions
@@ -17,7 +17,8 @@ module XMonadContrib.Combo ( -- * Usage -- $usage - combo, combineTwo + combo, combineTwo, + CombineTwo ) where import Control.Arrow ( first ) diff --git a/LayoutCombinators.hs b/LayoutCombinators.hs new file mode 100644 index 0000000..c7e065d --- /dev/null +++ b/LayoutCombinators.hs @@ -0,0 +1,41 @@ +{-# OPTIONS_GHC -fglasgow-exts #-} -- For deriving Data/Typeable +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} + +----------------------------------------------------------------------------- +-- | +-- Module : XMonadContrib.LayoutCombinators +-- Copyright : (c) David Roundy <droundy@darcs.net> +-- License : BSD +-- +-- Maintainer : David Roundy <droundy@darcs.net> +-- Stability : unstable +-- Portability : portable +-- +-- A module for combining Layouts +----------------------------------------------------------------------------- + +module XMonadContrib.LayoutCombinators ( + -- * Usage + -- $usage + (<|>), (</>), (<||>), (<//>) + ) where + +import XMonad +import Operations ( Tall(..), Mirror(..) ) +import XMonadContrib.Combo +import XMonadContrib.DragPane + +-- $usage +-- Use LayoutCombinators to easily combine Layouts. + +(<||>), (<//>) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => + l1 a -> l2 a -> CombineTwo DragPane l1 l2 a +(<|>) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) + => l1 a -> l2 a -> CombineTwo Tall l1 l2 a +(</>) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) + => l1 a -> l2 a -> CombineTwo (Mirror Tall) l1 l2 a + +(<||>) = combineTwo (dragPane Vertical 0.1 0.5) +(<//>) = combineTwo (dragPane Horizontal 0.1 0.5) +(<|>) = combineTwo (Tall 1 0.1 0.5) +(</>) = combineTwo (Mirror $ Tall 1 0.1 0.5) diff --git a/MetaModule.hs b/MetaModule.hs index 6893c1a..80e222f 100644 --- a/MetaModule.hs +++ b/MetaModule.hs @@ -44,6 +44,7 @@ import XMonadContrib.FocusNth () import XMonadContrib.Grid () import XMonadContrib.Invisible () -- import XMonadContrib.HintedTile () +import XMonadContrib.LayoutCombinators () import XMonadContrib.LayoutModifier () import XMonadContrib.LayoutHints () import XMonadContrib.LayoutScreens () |