{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TupleSections #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.Grid
-- Description :  A simple layout that attempts to put all windows in a square grid.
-- Copyright   :  (c) Lukas Mai
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  <l.mai@web.de>
-- Stability   :  unstable
-- Portability :  unportable
--
-- A simple layout that attempts to put all windows in a square grid.
--
-----------------------------------------------------------------------------

module XMonad.Layout.Grid (
    -- * Usage
    -- $usage
    Grid(..), arrange, defaultRatio
) where

import XMonad
import XMonad.StackSet

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.Grid
--
-- Then edit your @layoutHook@ by adding the Grid layout:
--
-- > myLayout = Grid ||| Full ||| etc..
-- > main = xmonad def { layoutHook = myLayout }
--
-- You can also specify an aspect ratio for Grid to strive for with the
-- GridRatio constructor.  For example, if you want Grid to try to make a grid
-- four windows wide and three windows tall, you could use
--
-- > myLayout = GridRatio (4/3) ||| etc.
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"

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

defaultRatio :: Double
defaultRatio :: Double
defaultRatio = Double
16Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
9

instance LayoutClass Grid a where
    pureLayout :: Grid a -> Rectangle -> Stack a -> [(a, Rectangle)]
pureLayout Grid a
Grid          Rectangle
r = Grid a -> Rectangle -> Stack a -> [(a, Rectangle)]
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
pureLayout (Double -> Grid a
forall a. Double -> Grid a
GridRatio Double
defaultRatio) Rectangle
r
    pureLayout (GridRatio Double
d) Rectangle
r = Double -> Rectangle -> [a] -> [(a, Rectangle)]
forall a. Double -> Rectangle -> [a] -> [(a, Rectangle)]
arrange Double
d Rectangle
r ([a] -> [(a, Rectangle)])
-> (Stack a -> [a]) -> Stack a -> [(a, Rectangle)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stack a -> [a]
forall a. Stack a -> [a]
integrate

arrange :: Double -> Rectangle -> [a] -> [(a, Rectangle)]
arrange :: forall a. Double -> Rectangle -> [a] -> [(a, Rectangle)]
arrange Double
aspectRatio (Rectangle Position
rx Position
ry Dimension
rw Dimension
rh) [a]
st = [a] -> [Rectangle] -> [(a, Rectangle)]
forall a b. [a] -> [b] -> [(a, b)]
zip [a]
st [Rectangle]
rectangles
    where
    nwins :: Int
nwins = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
st
    ncols :: Int
ncols = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
1 (Int -> Int) -> (Double -> Int) -> Double -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
nwins (Int -> Int) -> (Double -> Int) -> Double -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Int) -> (Double -> Double) -> Double -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Double
forall a. Floating a => a -> a
sqrt (Double -> Int) -> Double -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nwins Double -> Double -> Double
forall a. Num a => a -> a -> a
* Dimension -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
rw Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Dimension -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
rh Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
aspectRatio)
    mincs :: Int
mincs = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
1 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
nwins Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
ncols
    extrs :: Int
extrs = Int
nwins Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ncols Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
mincs
    chop :: Int -> Dimension -> [(Position, Dimension)]
    chop :: Int -> Dimension -> [(Position, Dimension)]
chop Int
n Dimension
m = ((Position
0, Dimension
m Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
k Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
* Int -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int
forall a. Enum a => a -> a
pred Int
n)) (Position, Dimension)
-> [(Position, Dimension)] -> [(Position, Dimension)]
forall a. a -> [a] -> [a]
:) ([(Position, Dimension)] -> [(Position, Dimension)])
-> (Position -> [(Position, Dimension)])
-> Position
-> [(Position, Dimension)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Position -> (Position, Dimension))
-> [Position] -> [(Position, Dimension)]
forall a b. (a -> b) -> [a] -> [b]
map (, Dimension
k) ([Position] -> [(Position, Dimension)])
-> (Position -> [Position]) -> Position -> [(Position, Dimension)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Position] -> [Position]
forall a. [a] -> [a]
tail ([Position] -> [Position])
-> (Position -> [Position]) -> Position -> [Position]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Position] -> [Position]
forall a. [a] -> [a]
reverse ([Position] -> [Position])
-> (Position -> [Position]) -> Position -> [Position]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Position] -> [Position]
forall a. Int -> [a] -> [a]
take Int
n ([Position] -> [Position])
-> (Position -> [Position]) -> Position -> [Position]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Position] -> [Position]
forall a. [a] -> [a]
tail ([Position] -> [Position])
-> (Position -> [Position]) -> Position -> [Position]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Position -> Position) -> Position -> [Position]
forall a. (a -> a) -> a -> [a]
iterate (Position -> Position -> Position
forall a. Num a => a -> a -> a
subtract Position
k') (Position -> [(Position, Dimension)])
-> Position -> [(Position, Dimension)]
forall a b. (a -> b) -> a -> b
$ Position
m'
        where
        k :: Dimension
        k :: Dimension
k = Dimension
m 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
        m' :: Position
m' = Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
m
        k' :: Position
        k' :: Position
k' = Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
k
    xcoords :: [(Position, Dimension)]
xcoords = Int -> Dimension -> [(Position, Dimension)]
chop Int
ncols Dimension
rw
    ycoords :: [(Position, Dimension)]
ycoords = Int -> Dimension -> [(Position, Dimension)]
chop Int
mincs Dimension
rh
    ycoords' :: [(Position, Dimension)]
ycoords' = Int -> Dimension -> [(Position, Dimension)]
chop (Int -> Int
forall a. Enum a => a -> a
succ Int
mincs) Dimension
rh
    ([(Position, Dimension)]
xbase, [(Position, Dimension)]
xext) = Int
-> [(Position, Dimension)]
-> ([(Position, Dimension)], [(Position, Dimension)])
forall a. Int -> [a] -> ([a], [a])
splitAt (Int
ncols Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
extrs) [(Position, Dimension)]
xcoords
    rectangles :: [Rectangle]
rectangles = [(Position, Dimension)] -> [(Position, Dimension)] -> [Rectangle]
combine [(Position, Dimension)]
ycoords [(Position, Dimension)]
xbase [Rectangle] -> [Rectangle] -> [Rectangle]
forall a. [a] -> [a] -> [a]
++ [(Position, Dimension)] -> [(Position, Dimension)] -> [Rectangle]
combine [(Position, Dimension)]
ycoords' [(Position, Dimension)]
xext
        where
        combine :: [(Position, Dimension)] -> [(Position, Dimension)] -> [Rectangle]
combine [(Position, Dimension)]
ys [(Position, Dimension)]
xs = [Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
rx Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Position
x) (Position
ry Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Position
y) Dimension
w Dimension
h | (Position
x, Dimension
w) <- [(Position, Dimension)]
xs, (Position
y, Dimension
h) <- [(Position, Dimension)]
ys]