module XMonad.Layout.ResizableTile (
                                    
                                    
                                    ResizableTall(..), MirrorResize(..)
                                   ) where
import XMonad hiding (tile, splitVertically, splitHorizontallyBy)
import qualified XMonad.StackSet as W
import Control.Monad
import qualified Data.Map as M
import Data.List ((\\))
data MirrorResize = MirrorShrink | MirrorExpand deriving Typeable
instance Message MirrorResize
data ResizableTall a = ResizableTall
    { _nmaster :: Int       
    , _delta  :: Rational   
                            
    , _frac   :: Rational   
    , _slaves :: [Rational] 
                            
                            
                            
                            
                            
                            
    } deriving (Show, Read)
instance LayoutClass ResizableTall a where
    doLayout (ResizableTall nmaster _ frac mfrac) r =
        return . (\x->(x,Nothing)) .
        ap zip (tile frac (mfrac ++ repeat 1) r nmaster . length) . W.integrate
    handleMessage (ResizableTall nmaster delta frac mfrac) m =
        do ms <- (W.stack . W.workspace . W.current) `fmap` gets windowset
           fs <- (M.keys . W.floating) `fmap` gets windowset
           return $ ms >>= unfloat fs >>= handleMesg
        where handleMesg s = msum [fmap resize (fromMessage m)
                                  ,fmap (\x -> mresize x s) (fromMessage m)
                                  ,fmap incmastern (fromMessage m)]
              unfloat fs s = if W.focus s `elem` fs
                               then Nothing
                               else Just (s { W.up = (W.up s) \\ fs
                                            , W.down = (W.down s) \\ fs })
              resize Shrink = ResizableTall nmaster delta (max 0 $ fracdelta) mfrac
              resize Expand = ResizableTall nmaster delta (min 1 $ frac+delta) mfrac
              mresize MirrorShrink s = mresize' s delta
              mresize MirrorExpand s = mresize' s (0delta)
              mresize' s d = let n = length $ W.up s
                                 total = n + (length $ W.down s) + 1
                                 pos = if n == (nmaster1) || n == (total1) then n1 else n
                                 mfrac' = modifymfrac (mfrac ++ repeat 1) d pos
                             in ResizableTall nmaster delta frac $ take total mfrac'
              modifymfrac [] _ _ = []
              modifymfrac (f:fx) d n | n == 0    = f+d : fx
                                     | otherwise = f : modifymfrac fx d (n1)
              incmastern (IncMasterN d) = ResizableTall (max 0 (nmaster+d)) delta frac mfrac
    description _ = "ResizableTall"
tile :: Rational -> [Rational] -> Rectangle -> Int -> Int -> [Rectangle]
tile f mf r nmaster n = if n <= nmaster || nmaster == 0
    then splitVertically mf n r
    else splitVertically mf nmaster r1 ++ splitVertically (drop nmaster mf) (nnmaster) r2 
  where (r1,r2) = splitHorizontallyBy f r
splitVertically :: RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically [] _ r = [r]
splitVertically _ n r | n < 2 = [r]
splitVertically (f:fx) n (Rectangle sx sy sw sh) = Rectangle sx sy sw smallh :
    splitVertically fx (n1) (Rectangle sx (sy+fromIntegral smallh) sw (shsmallh))
  where smallh = min sh (floor $ fromIntegral (sh `div` fromIntegral n) * f) 
splitHorizontallyBy :: RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
splitHorizontallyBy f (Rectangle sx sy sw sh) =
    ( Rectangle sx sy leftw sh
    , Rectangle (sx + fromIntegral leftw) sy (swfromIntegral leftw) sh)
  where leftw = floor $ fromIntegral sw * f