{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.MultiDishes
-- Description :  A layout stacking groups of extra windows underneath the master windows.
-- Copyright   :  (c) Jeremy Apthorp, Nathan Fairhurst
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  Nathan Fairhurst <nathan.p3pictures@gmail.com>
-- Stability   :  unstable
-- Portability :  portable
--
-- MultiDishes is a layout that stacks groups of extra windows underneath
-- the master windows.
--
-----------------------------------------------------------------------------

module XMonad.Layout.MultiDishes (
                              -- * Usage
                              -- $usage
                              MultiDishes (..)
                            ) where

import XMonad
import XMonad.StackSet (integrate)
import XMonad.Prelude (ap)

-- $usage
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.MultiDishes
--
-- Then edit your @layoutHook@ by adding the MultiDishes layout:
--
-- > myLayout = MultiDishes 2 3 (1/6) ||| Full ||| etc..
-- > main = xmonad def { layoutHook = myLayout }
--
-- This is based on the Layout Dishes, but accepts another parameter for
-- the maximum number of dishes allowed within a stack.
--
-- > MultiDishes x 1 y
-- is equivalent to
-- > Dishes x y
--
-- The stack with the fewest dishes is always on top, so 4 windows
-- with the layout `MultiDishes 1 2 (1/5)` would look like this:
--
-- > _________
-- > |       |
-- > |   M   |
-- > |_______|
-- > |_______|
-- > |___|___|
--
-- For more detailed instructions on editing the layoutHook see
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
-- "XMonad.Doc.Extending#Editing_the_layout_hook".

data MultiDishes a = MultiDishes Int Int Rational deriving (Int -> MultiDishes a -> ShowS
forall a. Int -> MultiDishes a -> ShowS
forall a. [MultiDishes a] -> ShowS
forall a. MultiDishes a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MultiDishes a] -> ShowS
$cshowList :: forall a. [MultiDishes a] -> ShowS
show :: MultiDishes a -> String
$cshow :: forall a. MultiDishes a -> String
showsPrec :: Int -> MultiDishes a -> ShowS
$cshowsPrec :: forall a. Int -> MultiDishes a -> ShowS
Show, ReadPrec [MultiDishes a]
ReadPrec (MultiDishes a)
ReadS [MultiDishes a]
forall a. ReadPrec [MultiDishes a]
forall a. ReadPrec (MultiDishes a)
forall a. Int -> ReadS (MultiDishes a)
forall a. ReadS [MultiDishes a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MultiDishes a]
$creadListPrec :: forall a. ReadPrec [MultiDishes a]
readPrec :: ReadPrec (MultiDishes a)
$creadPrec :: forall a. ReadPrec (MultiDishes a)
readList :: ReadS [MultiDishes a]
$creadList :: forall a. ReadS [MultiDishes a]
readsPrec :: Int -> ReadS (MultiDishes a)
$creadsPrec :: forall a. Int -> ReadS (MultiDishes a)
Read)
instance LayoutClass MultiDishes a where
    pureLayout :: MultiDishes a -> Rectangle -> Stack a -> [(a, Rectangle)]
pureLayout (MultiDishes Int
nmaster Int
dishesPerStack Rational
h) Rectangle
r =
        forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap forall a b. [a] -> [b] -> [(a, b)]
zip (Rational -> Rectangle -> Int -> Int -> Int -> [Rectangle]
multiDishes Rational
h Rectangle
r Int
nmaster Int
dishesPerStack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Stack a -> [a]
integrate
    pureMessage :: MultiDishes a -> SomeMessage -> Maybe (MultiDishes a)
pureMessage (MultiDishes Int
nmaster Int
dishesPerStack Rational
h) SomeMessage
m = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {a}. IncMasterN -> MultiDishes a
incmastern (forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m)
        where incmastern :: IncMasterN -> MultiDishes a
incmastern (IncMasterN Int
d) = forall a. Int -> Int -> Rational -> MultiDishes a
MultiDishes (forall a. Ord a => a -> a -> a
max Int
0 (Int
nmasterforall a. Num a => a -> a -> a
+Int
d)) Int
dishesPerStack Rational
h

multiDishes :: Rational -> Rectangle -> Int -> Int -> Int -> [Rectangle]
multiDishes :: Rational -> Rectangle -> Int -> Int -> Int -> [Rectangle]
multiDishes Rational
h Rectangle
s Int
nmaster Int
dishesPerStack Int
n = if Int
n forall a. Ord a => a -> a -> Bool
<= Int
nmaster
                        then Int -> Rectangle -> [Rectangle]
splitHorizontally Int
n Rectangle
s
                        else [Rectangle]
ws
 where
    (Int
filledDishStackCount, Int
remainder) =
      (Int
n forall a. Num a => a -> a -> a
- Int
nmaster) forall a. Integral a => a -> a -> (a, a)
`quotRem` forall a. Ord a => a -> a -> a
max Int
1 Int
dishesPerStack

    (Int
firstDepth, Int
dishStackCount) =
      if Int
remainder forall a. Eq a => a -> a -> Bool
== Int
0 then
        (Int
dishesPerStack, Int
filledDishStackCount)
      else
        (Int
remainder, Int
filledDishStackCount forall a. Num a => a -> a -> a
+ Int
1)

    (Rectangle
masterRect, Rectangle
dishesRect) =
      forall r. RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
splitVerticallyBy (Rational
1 forall a. Num a => a -> a -> a
- forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dishStackCount forall a. Num a => a -> a -> a
* Rational
h) Rectangle
s

    dishStackRects :: [Rectangle]
dishStackRects =
      Int -> Rectangle -> [Rectangle]
splitVertically Int
dishStackCount Rectangle
dishesRect

    allDishRects :: [Rectangle]
allDishRects = case [Rectangle]
dishStackRects of
      (Rectangle
firstStack:[Rectangle]
bottomDishStacks) ->
        Int -> Rectangle -> [Rectangle]
splitHorizontally Int
firstDepth Rectangle
firstStack forall a. [a] -> [a] -> [a]
++ ([Rectangle]
bottomDishStacks forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Rectangle -> [Rectangle]
splitHorizontally Int
dishesPerStack)
      [] -> []

    ws :: [Rectangle]
ws =
      Int -> Rectangle -> [Rectangle]
splitHorizontally Int
nmaster Rectangle
masterRect forall a. [a] -> [a] -> [a]
++ [Rectangle]
allDishRects