diff options
author | portnov84 <portnov84@rambler.ru> | 2009-06-05 20:45:15 +0200 |
---|---|---|
committer | portnov84 <portnov84@rambler.ru> | 2009-06-05 20:45:15 +0200 |
commit | 2a246eab26096eba4476688e530e5da41c0b3ded (patch) | |
tree | 2e0dd08dc48030ab7870ba782fd9304c5403a57f | |
parent | 27fc990db7a030a11354e036919d134b5500b6be (diff) | |
download | XMonadContrib-2a246eab26096eba4476688e530e5da41c0b3ded.tar.gz XMonadContrib-2a246eab26096eba4476688e530e5da41c0b3ded.tar.xz XMonadContrib-2a246eab26096eba4476688e530e5da41c0b3ded.zip |
Column_layout.dpatch
Ignore-this: ea5ebf0d6e8ac5c044d9291b3c55479d
This module defines layot named Column. It places all windows in one
column. Windows heights are calculated from equation: H1/H2
darcs-hash:20090605184515-94bf2-6842ff495fc3bcf3850291a3fc7f63a4d2c498d9.gz
Diffstat (limited to '')
-rw-r--r-- | XMonad/Layout/Column.hs | 71 | ||||
-rw-r--r-- | xmonad-contrib.cabal | 1 |
2 files changed, 72 insertions, 0 deletions
diff --git a/XMonad/Layout/Column.hs b/XMonad/Layout/Column.hs new file mode 100644 index 0000000..279525e --- /dev/null +++ b/XMonad/Layout/Column.hs @@ -0,0 +1,71 @@ +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-} +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Layout.Column +-- Copyright : (c) 2009 Ilya Portnov +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : Ilya Portnov <portnov84@rambler.ru> +-- Stability : unstable +-- Portability : unportable +-- +-- Provides Column layout that places all windows in one column. Windows +-- heights are calculated from equation: H1/H2 = H2/H3 = ... = q, where q is +-- given. With Shrink/Expand messages you can change the q value. +-- +----------------------------------------------------------------------------- + +module XMonad.Layout.Column ( + -- * Usage + -- $usage + Column (..) + ) where +import XMonad +import qualified XMonad.StackSet as W + +-- $usage +-- This module defines layot named Column. It places all windows in one +-- column. Windows heights are calculated from equation: H1/H2 = H2/H3 = ... = +-- q, where `q' is given (thus, windows heights are members of geometric +-- progression). With Shrink/Expand messages one can change the `q' value. +-- +-- You can use this module by adding folowing in your @xmonad.hs@: +-- +-- > import XMonad.Layout.Column +-- +-- Then add layouts to your layoutHook: +-- +-- > myLayoutHook = Column 1.6 ||| ... +-- +-- In this example, each next window will have height 1.6 times less then +-- previous window. + +data Column a = Column Float deriving (Read,Show) + +instance LayoutClass Column a where + pureLayout = columnLayout + pureMessage = columnMessage + +columnMessage :: Column a -> SomeMessage -> Maybe (Column a) +columnMessage (Column q) m = fmap resize (fromMessage m) + where resize Shrink = Column (q-0.1) + resize Expand = Column (q+0.1) + +columnLayout :: Column a -> Rectangle -> W.Stack a -> [(a,Rectangle)] +columnLayout (Column q) rect stack = zip ws rects + where ws = W.integrate stack + n = length ws + heights = map (xn n rect q) [1..n] + ys = [fromIntegral $ sum $ take k heights | k <- [0..n-1]] + rects = map (mkRect rect) $ zip heights ys + +mkRect :: Rectangle -> (Dimension,Position) -> Rectangle +mkRect (Rectangle xs ys ws _) (h,y) = Rectangle xs (ys+fromIntegral y) ws h + +xn :: Int -> Rectangle -> Float -> Int -> Dimension +xn n (Rectangle _ _ _ h) q k = if q==1 then + h `div` (fromIntegral n) + else + round ((fromIntegral h)*q^(n-k)*(1-q)/(1-q^n)) + + diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal index 9161e33..9faa4d7 100644 --- a/xmonad-contrib.cabal +++ b/xmonad-contrib.cabal @@ -132,6 +132,7 @@ library XMonad.Layout.CenteredMaster XMonad.Layout.Circle XMonad.Layout.Cross + XMonad.Layout.Column XMonad.Layout.Combo XMonad.Layout.ComboP XMonad.Layout.Decoration |