{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.Column
-- Description :  Layout that places all windows in one 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.

newtype Column a = Column Float deriving (ReadPrec [Column a]
ReadPrec (Column a)
Int -> ReadS (Column a)
ReadS [Column a]
(Int -> ReadS (Column a))
-> ReadS [Column a]
-> ReadPrec (Column a)
-> ReadPrec [Column a]
-> Read (Column a)
forall a. ReadPrec [Column a]
forall a. ReadPrec (Column a)
forall a. Int -> ReadS (Column a)
forall a. ReadS [Column a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Column a]
$creadListPrec :: forall a. ReadPrec [Column a]
readPrec :: ReadPrec (Column a)
$creadPrec :: forall a. ReadPrec (Column a)
readList :: ReadS [Column a]
$creadList :: forall a. ReadS [Column a]
readsPrec :: Int -> ReadS (Column a)
$creadsPrec :: forall a. Int -> ReadS (Column a)
Read,Int -> Column a -> ShowS
[Column a] -> ShowS
Column a -> String
(Int -> Column a -> ShowS)
-> (Column a -> String) -> ([Column a] -> ShowS) -> Show (Column a)
forall a. Int -> Column a -> ShowS
forall a. [Column a] -> ShowS
forall a. Column a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Column a] -> ShowS
$cshowList :: forall a. [Column a] -> ShowS
show :: Column a -> String
$cshow :: forall a. Column a -> String
showsPrec :: Int -> Column a -> ShowS
$cshowsPrec :: forall a. Int -> Column a -> ShowS
Show)

instance LayoutClass Column a where
    pureLayout :: Column a -> Rectangle -> Stack a -> [(a, Rectangle)]
pureLayout = Column a -> Rectangle -> Stack a -> [(a, Rectangle)]
forall a. Column a -> Rectangle -> Stack a -> [(a, Rectangle)]
columnLayout
    pureMessage :: Column a -> SomeMessage -> Maybe (Column a)
pureMessage = Column a -> SomeMessage -> Maybe (Column a)
forall a. Column a -> SomeMessage -> Maybe (Column a)
columnMessage

columnMessage :: Column a -> SomeMessage -> Maybe (Column a)
columnMessage :: forall a. Column a -> SomeMessage -> Maybe (Column a)
columnMessage (Column Float
q) SomeMessage
m = (Resize -> Column a) -> Maybe Resize -> Maybe (Column a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Resize -> Column a
forall {a}. Resize -> Column a
resize (SomeMessage -> Maybe Resize
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m)
    where resize :: Resize -> Column a
resize Resize
Shrink = Float -> Column a
forall a. Float -> Column a
Column (Float
qFloat -> Float -> Float
forall a. Num a => a -> a -> a
-Float
0.1)
          resize Resize
Expand = Float -> Column a
forall a. Float -> Column a
Column (Float
qFloat -> Float -> Float
forall a. Num a => a -> a -> a
+Float
0.1)

columnLayout :: Column a -> Rectangle -> W.Stack a -> [(a,Rectangle)]
columnLayout :: forall a. Column a -> Rectangle -> Stack a -> [(a, Rectangle)]
columnLayout (Column Float
q) Rectangle
rect Stack a
stack = [a] -> [Rectangle] -> [(a, Rectangle)]
forall a b. [a] -> [b] -> [(a, b)]
zip [a]
ws [Rectangle]
rects
    where ws :: [a]
ws = Stack a -> [a]
forall a. Stack a -> [a]
W.integrate Stack a
stack
          n :: Int
n = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
ws
          heights :: [Dimension]
heights = (Int -> Dimension) -> [Int] -> [Dimension]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Rectangle -> Float -> Int -> Dimension
xn Int
n Rectangle
rect Float
q) [Int
1..Int
n]
          ys :: [Position]
ys = [Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Dimension -> Position) -> Dimension -> Position
forall a b. (a -> b) -> a -> b
$ [Dimension] -> Dimension
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Dimension] -> Dimension) -> [Dimension] -> Dimension
forall a b. (a -> b) -> a -> b
$ Int -> [Dimension] -> [Dimension]
forall a. Int -> [a] -> [a]
take Int
k [Dimension]
heights | Int
k <- [Int
0..Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1]]
          rects :: [Rectangle]
rects = (Dimension -> Position -> Rectangle)
-> [Dimension] -> [Position] -> [Rectangle]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (((Dimension, Position) -> Rectangle)
-> Dimension -> Position -> Rectangle
forall a b c. ((a, b) -> c) -> a -> b -> c
curry (Rectangle -> (Dimension, Position) -> Rectangle
mkRect Rectangle
rect)) [Dimension]
heights [Position]
ys

mkRect :: Rectangle -> (Dimension,Position) -> Rectangle
mkRect :: Rectangle -> (Dimension, Position) -> Rectangle
mkRect (Rectangle Position
xs Position
ys Dimension
ws Dimension
_) (Dimension
h,Position
y) = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
xs (Position
ysPosition -> Position -> Position
forall a. Num a => a -> a -> a
+Position -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
y) Dimension
ws Dimension
h

xn :: Int -> Rectangle -> Float -> Int -> Dimension
xn :: Int -> Rectangle -> Float -> Int -> Dimension
xn Int
n (Rectangle Position
_ Position
_ Dimension
_ Dimension
h) Float
q Int
k = if Float
qFloat -> Float -> Bool
forall a. Eq a => a -> a -> Bool
==Float
1 then
                                  Dimension
h Dimension -> Dimension -> Dimension
forall a. Integral a => a -> a -> a
`div` Int -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n
                               else
                                  Float -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
hFloat -> Float -> Float
forall a. Num a => a -> a -> a
*Float
qFloat -> Int -> Float
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
k)Float -> Float -> Float
forall a. Num a => a -> a -> a
*(Float
1Float -> Float -> Float
forall a. Num a => a -> a -> a
-Float
q)Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/(Float
1Float -> Float -> Float
forall a. Num a => a -> a -> a
-Float
qFloat -> Int -> Float
forall a b. (Num a, Integral b) => a -> b -> a
^Int
n))