diff options
author | Adam Vogt <vogt.adam@gmail.com> | 2009-06-22 02:01:15 +0200 |
---|---|---|
committer | Adam Vogt <vogt.adam@gmail.com> | 2009-06-22 02:01:15 +0200 |
commit | dad19f299b837f3d5a37b7126daa96ec6fefc760 (patch) | |
tree | 7f486adbdb0d1055bf39fa81141e4bd85b972e56 /XMonad | |
parent | 5975bb73c3b3ec8f3b126de4e3cdd0115810dba0 (diff) | |
download | XMonadContrib-dad19f299b837f3d5a37b7126daa96ec6fefc760.tar.gz XMonadContrib-dad19f299b837f3d5a37b7126daa96ec6fefc760.tar.xz XMonadContrib-dad19f299b837f3d5a37b7126daa96ec6fefc760.zip |
L.LimitWindows add usage information, functions to modify the limit
Ignore-this: 813473c5f42540ed0d575bb273f8652
darcs-hash:20090622000115-1499c-3ea35fc8f2bf4d07c0f74d84f0ebc803185c957f.gz
Diffstat (limited to 'XMonad')
-rw-r--r-- | XMonad/Layout/LimitWindows.hs | 49 |
1 files changed, 46 insertions, 3 deletions
diff --git a/XMonad/Layout/LimitWindows.hs b/XMonad/Layout/LimitWindows.hs index 9feb462..7007c18 100644 --- a/XMonad/Layout/LimitWindows.hs +++ b/XMonad/Layout/LimitWindows.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- 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 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. 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) --- 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 + 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 = runLayout ws { W.stack = f n `fmap` W.stack ws } r 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) $ 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 n (W.Stack f u d) = W.Stack f (take (nu + unusedD) u) |