From a0c7989fdfcbe3a1238e48fa4d3a10fa05fc8098 Mon Sep 17 00:00:00 2001 From: Adam Vogt Date: Fri, 19 Jun 2009 07:27:31 +0200 Subject: Add L.LimitWindows layout modifier Ignore-this: e91c07885f0ab662f70e0ebd82fb7a5d darcs-hash:20090619052731-1499c-b68f6df5d8d5c750be9cc68c67a9b7e50c51e7dc.gz --- XMonad/Layout/LimitWindows.hs | 55 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 55 insertions(+) create mode 100644 XMonad/Layout/LimitWindows.hs (limited to 'XMonad') diff --git a/XMonad/Layout/LimitWindows.hs b/XMonad/Layout/LimitWindows.hs new file mode 100644 index 0000000..9feb462 --- /dev/null +++ b/XMonad/Layout/LimitWindows.hs @@ -0,0 +1,55 @@ +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Layout.LimitWindows +-- Copyright : (c) 2009 Adam Vogt +-- License : BSD-style (see xmonad/LICENSE) +-- +-- Maintainer : vogt.adam@gmail.com +-- Stability : unstable +-- Portability : unportable +-- +-- A layout modifier that limits the number of windows that can be shown. +-- +----------------------------------------------------------------------------- + +module XMonad.Layout.LimitWindows (limitWindows,limitSlice) where + +import XMonad.Layout.LayoutModifier +import XMonad +import qualified XMonad.StackSet as W + +-- | Only display the first @n@ windows. +limitWindows :: Int -> l a -> ModifiedLayout LimitWindows l a +limitWindows n = ModifiedLayout (LimitWindows FirstN n) + +-- | Only display @n@ windows around the focused window. This makes sense with +-- layouts that arrange windows linearily, like 'XMonad.Layout.Layout.Accordion'. +limitSlice :: Int -> l a -> ModifiedLayout LimitWindows l a +limitSlice n = ModifiedLayout (LimitWindows Slice n) + +data LimitWindows a = LimitWindows SliceStyle Int deriving (Read,Show) + +data SliceStyle = FirstN | Slice deriving (Read,Show) + +-- do the runLayout call in an environment with only the windows chosen by f ... ? +instance LayoutModifier LimitWindows a where + modifyLayout (LimitWindows style n) ws r = + runLayout ws { W.stack = f n `fmap` W.stack ws } r + where f = case style of + FirstN -> firstN + Slice -> slice + +firstN :: Int -> W.Stack a -> W.Stack a +firstN n st = W.Stack f (reverse u) d + where (u,f:d) = splitAt (min (n-1) $ length $ W.up st) + $ take n $ W.integrate st + +slice :: Int -> W.Stack t -> W.Stack t +slice n (W.Stack f u d) = + W.Stack f (take (nu + unusedD) u) + (take (nd + unusedU) d) + where unusedD = max 0 $ nd - length d + unusedU = max 0 $ nu - length u + nd = div (n - 1) 2 + nu = uncurry (+) $ divMod (n - 1) 2 -- cgit v1.2.3