aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorIlya Portnov <portnov84@rambler.ru>2013-12-01 08:26:34 +0100
committerIlya Portnov <portnov84@rambler.ru>2013-12-01 08:26:34 +0100
commitf481476d4b3ac200fc3ee2aae1f3801e5bccbe86 (patch)
treea3e547771fd66f00ef513cf6443183c3e9ab2578
parent7827be678f34718d71e987dec905477a6c3d9c7b (diff)
downloadXMonadContrib-f481476d4b3ac200fc3ee2aae1f3801e5bccbe86.tar.gz
XMonadContrib-f481476d4b3ac200fc3ee2aae1f3801e5bccbe86.tar.xz
XMonadContrib-f481476d4b3ac200fc3ee2aae1f3801e5bccbe86.zip
IfMax-Layout
Ignore-this: dac53f2a0505e740f05fdf03f1db0c21 This adds a new ("conditional") layout, IfMax, which simply runs one layout, if there are < darcs-hash:20131201072634-c5067-1caf5f9de962285cf1b656266e78a0c46979f9c7.gz
-rw-r--r--XMonad/Layout/IfMax.hs77
-rw-r--r--xmonad-contrib.cabal1
2 files changed, 78 insertions, 0 deletions
diff --git a/XMonad/Layout/IfMax.hs b/XMonad/Layout/IfMax.hs
new file mode 100644
index 0000000..c8b8cba
--- /dev/null
+++ b/XMonad/Layout/IfMax.hs
@@ -0,0 +1,77 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.IfMax
+-- Copyright : (c) 2013 Ilya Portnov
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Ilya Portnov <portnov84@rambler.ru>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Provides IfMax layout, which will run one layout if there are maximum N
+-- windows on workspace, and another layout, when number of windows is greater
+-- than N.
+--
+-----------------------------------------------------------------------------
+
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+
+module XMonad.Layout.IfMax
+ ( -- * Usage
+ -- $usage
+ IfMax (..)
+ , ifMax
+ ) where
+
+import Data.Maybe
+
+import XMonad
+import qualified XMonad.StackSet as W
+
+-- $usage
+-- IfMax layout will run one layout if number of windows on workspace is as
+-- maximum N, and else will run another layout.
+--
+-- You can use this module by adding folowing in your @xmonad.hs@:
+--
+-- > import XMonad.Layout.IfMax
+--
+-- Then add layouts to your layoutHook:
+--
+-- > myLayoutHook = IfMax 2 Full (Tall ...) ||| ...
+--
+-- In this example, if there are 1 or 2 windows, Full layout will be used;
+-- otherwise, Tall layout will be used.
+--
+
+data IfMax l1 l2 w = IfMax Int (l1 w) (l2 w)
+ deriving (Read, Show)
+
+instance (LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a)
+ => LayoutClass (IfMax l1 l2) a where
+
+ runLayout (W.Workspace _ (IfMax n l1 l2) s) rect = arrange (W.integrate' s)
+ where
+ arrange [] = do l1' <- maybe l1 id `fmap` handleMessage l1 (SomeMessage ReleaseResources)
+ l2' <- maybe l2 id `fmap` handleMessage l2 (SomeMessage ReleaseResources)
+ return ([], Just $ IfMax n l1' l2')
+ arrange ws | length ws <= n = do
+ (wrs, ml1') <- runLayout (W.Workspace "" l1 s) rect
+ let l1' = fromMaybe l1 ml1'
+ return (wrs, Just $ IfMax n l1' l2)
+ | otherwise = do
+ (wrs, ml2') <- runLayout (W.Workspace "" l2 s) rect
+ let l2' = fromMaybe l2 ml2'
+ return (wrs, Just $ IfMax n l1 l2')
+
+ description (IfMax n l1 l2) = "If number of windows is <= " ++ show n ++ ", then " ++
+ description l1 ++ ", else " ++ description l2
+
+-- | Layout itself
+ifMax :: (LayoutClass l1 w, LayoutClass l2 w)
+ => Int -- ^ Maximum number of windows for the first layout
+ -> l1 w -- ^ First layout
+ -> l2 w -- ^ Second layout
+ -> IfMax l1 l2 w
+ifMax n l1 l2 = IfMax n l1 l2
+
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index 05259d4..0ad136a 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -217,6 +217,7 @@ library
XMonad.Layout.Groups.Wmii
XMonad.Layout.HintedGrid
XMonad.Layout.HintedTile
+ XMonad.Layout.IfMax
XMonad.Layout.IM
XMonad.Layout.ImageButtonDecoration
XMonad.Layout.IndependentScreens