module XMonad.Layout.LayoutBuilder (
  
  
  layoutN,
  layoutR,
  layoutAll,
  IncLayoutN (..),
  SubMeasure (..),
  SubBox (..),
  absBox,
  relBox,
  LayoutN,
) where
import XMonad
import qualified XMonad.StackSet as W
import Data.Maybe (isJust,isNothing,listToMaybe)
type WindowNum = Either Int (Rational,Rational)
data LayoutN l1 l2 a =
    LayoutN (Maybe a) (Maybe a) WindowNum SubBox (Maybe SubBox) (l1 a) (Maybe (l2 a))
    deriving (Show,Read)
layoutN :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a) =>
       Int                          
    -> SubBox                       
    -> Maybe SubBox                 
    -> l1 a                         
    -> LayoutN l2 l3 a              
    -> LayoutN l1 (LayoutN l2 l3) a 
layoutN num box mbox sub next = LayoutN Nothing Nothing (Left num) box mbox sub (Just next)
layoutR :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a) =>
       Rational                     
    -> Rational                     
    -> SubBox                       
    -> Maybe SubBox                 
    -> l1 a                         
    -> LayoutN l2 l3 a              
    -> LayoutN l1 (LayoutN l2 l3) a 
layoutR numdiff num box mbox sub next = LayoutN Nothing Nothing (Right (numdiff,num)) box mbox sub (Just next)
layoutAll :: (Read a, Eq a, LayoutClass l1 a) =>
       SubBox             
    -> l1 a               
    -> LayoutN l1 Full a  
layoutAll box sub = LayoutN Nothing Nothing (Right (0,1)) box Nothing sub Nothing
data IncLayoutN = IncLayoutN Int deriving Typeable
instance Message IncLayoutN
data SubMeasure = Abs Int | Rel Rational deriving (Show,Read)
data SubBox = SubBox SubMeasure SubMeasure SubMeasure SubMeasure deriving (Show,Read)
absBox :: Int     
       -> Int     
       -> Int     
       -> Int     
       -> SubBox  
absBox x y w h = SubBox (Abs x) (Abs y) (Abs w) (Abs h)
relBox :: Rational  
       -> Rational  
       -> Rational  
       -> Rational  
       -> SubBox    
relBox x y w h = SubBox (Rel x) (Rel y) (Rel w) (Rel h)
instance (LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) =>
    LayoutClass (LayoutN l1 l2) a where
        
        runLayout (W.Workspace _ (LayoutN subf nextf num box mbox sub next) s) rect
            = do let (subs,nexts,subf',nextf') = splitStack s num subf nextf
                     selBox = if isJust nextf'
                              then box
                              else maybe box id mbox
                 (sublist,sub',schange) <- handle sub subs $ calcArea selBox rect
                 (nextlist,next',nchange) <- case next of Nothing -> return ([], Nothing, False)
                                                          Just n -> do (res, l, ch) <- handle n nexts rect
                                                                       return (res, Just l, ch)
                 let newlist =  if (length $ maybe [] W.up s) < (length $ W.integrate' subs)
                                then sublist++nextlist
                                else nextlist++sublist
                     newstate = if subf' /= subf || nextf' /= nextf || schange || nchange
                                then Just $ LayoutN subf' nextf' num box mbox sub' next'
                                else Nothing
                 return (newlist, newstate)
              where
                  handle l s' r = do (res,ml) <- runLayout (W.Workspace "" l s') r
                                     l' <- return $ maybe l id ml
                                     return (res, l', isNothing ml)
        
        handleMessage l m
            | Just (IncLayoutN _) <- fromMessage m = windowNum l m
            | Just (IncMasterN _) <- fromMessage m = sendFocus l m
            | Just (Shrink) <- fromMessage m = sendFocus l m
            | Just (Expand) <- fromMessage m = sendFocus l m
            | otherwise = sendBoth l m
        
        description (LayoutN _ _ _ _ _ sub Nothing) = "layoutAll "++ description sub
        description (LayoutN _ _ (Left _) _ _ sub (Just next)) = "layoutN "++ description sub ++" "++ description next
        description (LayoutN _ _ (Right _) _ _ sub (Just next)) = "layoutR "++ description sub ++" "++ description next
windowNum :: (LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) => LayoutN l1 l2 a -> SomeMessage -> X (Maybe (LayoutN l1 l2 a))
windowNum l@(LayoutN subf nextf num box mbox subl nextl) m | (Just (IncLayoutN n)) <- fromMessage m =
    do foc <- isFocus subf
       if foc then do let newnum = case num of
                                       (Left oldnum) -> Left $ max 1 $ oldnum + n
                                       (Right (diff,oldnum)) -> Right (diff, min 1 $ max 0 $ oldnum + (fromIntegral n)*diff)
                      return $ Just $ LayoutN subf nextf newnum box mbox subl nextl
              else sendNext l m
windowNum l m = sendNext l m
sendSub :: (LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) => LayoutN l1 l2 a -> SomeMessage -> X (Maybe (LayoutN l1 l2 a))
sendSub (LayoutN subf nextf num box mbox sub next) m =
    do sub' <- handleMessage sub m
       return $ if isJust sub'
                then Just $ LayoutN subf nextf num box mbox (maybe sub id sub') next
                else Nothing
sendBoth :: (LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) => LayoutN l1 l2 a -> SomeMessage -> X (Maybe (LayoutN l1 l2 a))
sendBoth l@(LayoutN _ _ _ _ _ _ Nothing) m = sendSub l m
sendBoth (LayoutN subf nextf num box mbox sub (Just next)) m =
    do sub' <- handleMessage sub m
       next' <- handleMessage next m
       return $ if isJust sub' || isJust next'
                then Just $ LayoutN subf nextf num box mbox (maybe sub id sub') (Just $ maybe next id next')
                else Nothing
sendNext :: (LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) => LayoutN l1 l2 a -> SomeMessage -> X (Maybe (LayoutN l1 l2 a))
sendNext (LayoutN _ _ _ _ _ _ Nothing) _ = return Nothing
sendNext (LayoutN subf nextf num box mbox sub (Just next)) m =
    do next' <- handleMessage next m
       return $ if isJust next'
                then Just $ LayoutN subf nextf num box mbox sub next'
                else Nothing
sendFocus :: (LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) => LayoutN l1 l2 a -> SomeMessage -> X (Maybe (LayoutN l1 l2 a))
sendFocus l@(LayoutN subf _ _ _ _ _ _) m = do foc <- isFocus subf
                                              if foc then sendSub l m
                                                     else sendNext l m
isFocus :: (Show a) => Maybe a -> X Bool
isFocus Nothing = return False
isFocus (Just w) = do ms <- (W.stack . W.workspace . W.current) `fmap` gets windowset
                      return $ maybe False (\s -> show w == (show $ W.focus s)) ms
calcNum :: Int -> WindowNum -> Int
calcNum tot num = max 1 $ case num of Left i -> i
                                      Right (_,r) -> ceiling $ r * fromIntegral tot
splitStack :: Eq a => Maybe (W.Stack a) -> WindowNum -> Maybe a -> Maybe a -> (Maybe (W.Stack a),Maybe (W.Stack a),Maybe a,Maybe a)
splitStack Nothing _ _ _ = (Nothing,Nothing,Nothing,Nothing)
splitStack (Just s) num subf nextf = ( differentiate' subf' subl
                                     , differentiate' nextf' nextl
                                     , subf'
                                     , nextf'
                                     )
    where
        ws = W.integrate s
        n = calcNum (length ws) num
        subl = take n ws
        nextl = drop n ws
        subf' = foc subl subf
        nextf' = foc nextl nextf
        foc [] _ = Nothing
        foc l f | W.focus s `elem` l = Just $ W.focus s
                | maybe False (`elem` l) f = f
                | otherwise = listToMaybe l
calcArea :: SubBox -> Rectangle -> Rectangle
calcArea (SubBox xpos ypos width height) rect = Rectangle (rect_x rect + fromIntegral xpos') (rect_y rect + fromIntegral ypos') width' height'
    where
        xpos' = calc False xpos $ rect_width rect
        ypos' = calc False ypos $ rect_height rect
        width' = calc True width $ rect_width rect  xpos'
        height' = calc True height $ rect_height rect  ypos'
        calc zneg val tot = fromIntegral $ min (fromIntegral tot) $ max 0 $
            case val of Rel v -> floor $ v * fromIntegral tot
                        Abs v -> if v<0 || (zneg && v==0)
                                 then (fromIntegral tot)+v
                                 else v
differentiate' :: Eq q => Maybe q -> [q] -> Maybe (W.Stack q)
differentiate' _ [] = Nothing
differentiate' Nothing w = W.differentiate w
differentiate' (Just f) w
    | f `elem` w = Just $ W.Stack { W.focus = f
                                  , W.up    = reverse $ takeWhile (/=f) w
                                  , W.down  = tail $ dropWhile (/=f) w
                                  }
    | otherwise = W.differentiate w