module XMonad.Layout.ComboP (
                             
                             
                             combineTwoP,
                             CombineTwoP,
                             SwapWindow(..),
                             Property(..)
                            ) where
import Data.List ( delete, intersect, (\\) )
import Data.Maybe ( isJust )
import Control.Monad
import XMonad hiding (focus)
import XMonad.StackSet ( integrate, Workspace (..), Stack(..) )
import XMonad.Layout.WindowNavigation
import XMonad.Util.WindowProperties
import qualified XMonad.StackSet as W
data SwapWindow =  SwapWindow        
                 | SwapWindowN Int   
                 deriving (Read, Show, Typeable)
instance Message SwapWindow
data CombineTwoP l l1 l2 a = C2P [a] [a] [a] l (l1 a) (l2 a) Property
                                deriving (Read, Show)
combineTwoP :: (LayoutClass super(), LayoutClass l1 Window, LayoutClass l2 Window) =>
                super () -> l1 Window -> l2 Window -> Property -> CombineTwoP (super ()) l1 l2 Window
combineTwoP = C2P [] [] []
instance (LayoutClass l (), LayoutClass l1 Window, LayoutClass l2 Window) =>
    LayoutClass (CombineTwoP (l ()) l1 l2) Window where
    doLayout (C2P f w1 w2 super l1 l2 prop) rinput s =
        let origws = W.integrate s           
            w1c = origws `intersect` w1      
            w2c = origws `intersect` w2      
            new = origws \\ (w1c ++ w2c)     
            superstack = Just Stack { focus=(), up=[], down=[()] }
            f' = focus s:delete (focus s) f  
        in do
            matching <- (hasProperty prop) `filterM` new  
            let w1' = w1c ++ matching                     
                w2' = w2c ++ (new \\ matching)            
                s1 = differentiate f' w1'                 
                s2 = differentiate f' w2'                 
            ([((),r1),((),r2)], msuper') <- runLayout (Workspace "" super superstack) rinput
            (wrs1, ml1') <- runLayout (Workspace "" l1 s1) r1
            (wrs2, ml2') <- runLayout (Workspace "" l2 s2) r2
            return  (wrs1++wrs2, Just $ C2P f' w1' w2' (maybe super id msuper')
                (maybe l1 id ml1') (maybe l2 id ml2') prop)
    handleMessage us@(C2P f ws1 ws2 super l1 l2 prop) m
        | Just SwapWindow      <- fromMessage m = swap us
        | Just (SwapWindowN 0) <- fromMessage m = swap us
        | Just (SwapWindowN n) <- fromMessage m = forwardToFocused us $ SomeMessage $ SwapWindowN $ n1
        | Just (MoveWindowToWindow w1 w2) <- fromMessage m,
          w1 `elem` ws1,
          w2 `elem` ws2 = return $ Just $ C2P f (delete w1 ws1) (w1:ws2) super l1 l2 prop
        | Just (MoveWindowToWindow w1 w2) <- fromMessage m,
          w1 `elem` ws2,
          w2 `elem` ws1 = return $ Just $ C2P f (w1:ws1) (delete w1 ws2) super l1 l2 prop
        | otherwise = do ml1' <- handleMessage l1 m
                         ml2' <- handleMessage l2 m
                         msuper' <- handleMessage super m
                         if isJust msuper' || isJust ml1' || isJust ml2'
                            then return $ Just $ C2P f ws1 ws2
                                                 (maybe super id msuper')
                                                 (maybe l1 id ml1')
                                                 (maybe l2 id ml2') prop
                            else return Nothing
    description (C2P _ _ _ super l1 l2 prop) = "combining " ++ description l1 ++ " and "++
                                description l2 ++ " with " ++ description super ++ " using "++ (show prop)
swap :: (LayoutClass s a, LayoutClass l1 Window, LayoutClass l2 Window) =>
        CombineTwoP (s a) l1 l2 Window -> X (Maybe (CombineTwoP (s a) l1 l2 Window))
swap (C2P f ws1 ws2 super l1 l2 prop) = do
    mst <- gets (W.stack . W.workspace . W.current . windowset)
    let (ws1', ws2') = case mst of
            Nothing -> (ws1, ws2)
            Just st -> if foc `elem` ws1
                           then (foc `delete` ws1, foc:ws2)
                           else if foc `elem` ws2
                               then (foc:ws1, foc `delete` ws2)
                               else (ws1, ws2)
                       where foc = W.focus st
    if (ws1,ws2) == (ws1',ws2')
        then return Nothing
        else return $ Just $ C2P f ws1' ws2' super l1 l2 prop
forwardToFocused :: (LayoutClass l1 Window, LayoutClass l2 Window, LayoutClass s a) =>
                    CombineTwoP (s a) l1 l2 Window -> SomeMessage -> X (Maybe (CombineTwoP (s a) l1 l2 Window))
forwardToFocused (C2P f ws1 ws2 super l1 l2 prop) m = do
    ml1 <- forwardIfFocused l1 ws1 m
    ml2 <- forwardIfFocused l2 ws2 m
    ms <- if isJust ml1 || isJust ml2
            then return Nothing
            else handleMessage super m
    if isJust ml1 || isJust ml2 || isJust ms
        then return $ Just $ C2P f ws1 ws2 (maybe super id ms) (maybe l1 id ml1) (maybe l2 id ml2) prop
        else return Nothing
forwardIfFocused :: (LayoutClass l Window) => l Window -> [Window] -> SomeMessage -> X (Maybe (l Window))
forwardIfFocused l w m = do
    mst <- gets (W.stack . W.workspace . W.current . windowset)
    maybe (return Nothing) send mst where
    send st = if (W.focus st) `elem` w
                then handleMessage l m
                else return Nothing
differentiate :: Eq q => [q] -> [q] -> Maybe (Stack q)
differentiate (z:zs) xs | z `elem` xs = Just $ Stack { focus=z
                                                     , up = reverse $ takeWhile (/=z) xs
                                                     , down = tail $ dropWhile (/=z) xs }
                        | otherwise = differentiate zs xs
differentiate [] xs = W.differentiate xs