L.LimitWindows add usage information, functions to modify the limit

This commit is contained in:
Adam Vogt 2009-06-22 00:01:15 +00:00
parent f541602f0b
commit 708b8a7d96

View File

@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.LimitWindows -- Module : XMonad.Layout.LimitWindows
@ -13,11 +13,45 @@
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
module XMonad.Layout.LimitWindows (limitWindows,limitSlice) where module XMonad.Layout.LimitWindows (
-- * Usage
-- $usage
-- Layout Modifiers
limitWindows,limitSlice,
-- Change the number of windows
increaseLimit,decreaseLimit,setLimit
) where
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad import XMonad
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import Control.Monad((<=<),guard)
-- $usage
-- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.LimitWindows
--
-- > myLayout = limitWindows 6 $ Tall 1 0.03 0.5 ||| Full ||| RandomOtherLayout...
-- > main = xmonad defaultConfig { layoutHook = myLayout }
--
-- You may also be interested in dynamically changing the number dynamically,
-- by binding keys to the 'increaseLimit', 'decreaseLimit', or 'setLimit'
-- actions.
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".
increaseLimit :: X ()
increaseLimit = sendMessage $ LimitChange succ
decreaseLimit :: X ()
decreaseLimit = sendMessage . LimitChange $ max 1 . pred
setLimit :: Int -> X ()
setLimit tgt = sendMessage . LimitChange $ const tgt
-- | Only display the first @n@ windows. -- | Only display the first @n@ windows.
limitWindows :: Int -> l a -> ModifiedLayout LimitWindows l a limitWindows :: Int -> l a -> ModifiedLayout LimitWindows l a
@ -32,8 +66,16 @@ data LimitWindows a = LimitWindows SliceStyle Int deriving (Read,Show)
data SliceStyle = FirstN | Slice deriving (Read,Show) data SliceStyle = FirstN | Slice deriving (Read,Show)
-- do the runLayout call in an environment with only the windows chosen by f ... ? data LimitChange = LimitChange { unLC :: (Int -> Int) } deriving (Typeable)
instance Message LimitChange
instance LayoutModifier LimitWindows a where instance LayoutModifier LimitWindows a where
pureMess (LimitWindows s n) =
fmap (LimitWindows s) . pos <=< (`app` n) . unLC <=< fromMessage
where pos x = guard (x>=0) >> return x
app f x = guard (f x /= x) >> return (f x)
modifyLayout (LimitWindows style n) ws r = modifyLayout (LimitWindows style n) ws r =
runLayout ws { W.stack = f n `fmap` W.stack ws } r runLayout ws { W.stack = f n `fmap` W.stack ws } r
where f = case style of where f = case style of
@ -45,6 +87,7 @@ firstN n st = W.Stack f (reverse u) d
where (u,f:d) = splitAt (min (n-1) $ length $ W.up st) where (u,f:d) = splitAt (min (n-1) $ length $ W.up st)
$ take n $ W.integrate st $ take n $ W.integrate st
-- | A non-wrapping, fixed-size slice of a stack around the focused element
slice :: Int -> W.Stack t -> W.Stack t slice :: Int -> W.Stack t -> W.Stack t
slice n (W.Stack f u d) = slice n (W.Stack f u d) =
W.Stack f (take (nu + unusedD) u) W.Stack f (take (nu + unusedD) u)