module XMonad.Actions.MouseGestures (
    
    
    Direction2D(..),
    mouseGestureH,
    mouseGesture,
    mkCollect
) where
import XMonad
import XMonad.Util.Types (Direction2D(..))
import Data.IORef
import qualified Data.Map as M
import Data.Map (Map)
import Data.Maybe
import Control.Monad
type Pos = (Position, Position)
delta :: Pos -> Pos -> Position
delta (ax, ay) (bx, by) = max (d ax bx) (d ay by)
    where
    d a b = abs (a  b)
dir :: Pos -> Pos -> Direction2D
dir (ax, ay) (bx, by) = trans . (/ pi) $ atan2 (fromIntegral $ ay  by) (fromIntegral $ bx  ax)
    where
    trans :: Double -> Direction2D
    trans x
        | rg (3/4) (1/4) x = D
        | rg (1/4)  (1/4) x = R
        | rg  (1/4)  (3/4) x = U
        | otherwise          = L
    rg a z x = a <= x && x < z
gauge :: (Direction2D -> X ()) -> Pos -> IORef (Maybe (Direction2D, Pos)) -> Position -> Position -> X ()
gauge hook op st nx ny = do
    let np = (nx, ny)
    stx <- io $ readIORef st
    let
        (~(Just od), pivot) = case stx of
            Nothing -> (Nothing, op)
            Just (d, zp) -> (Just d, zp)
        cont = do
            guard $ significant np pivot
            return $ do
                let d' = dir pivot np
                when (isNothing stx || od /= d') $ hook d'
                io $ writeIORef st (Just (d', np))
    fromMaybe (return ()) cont
    where
    significant a b = delta a b >= 10
mouseGestureH :: (Direction2D -> X ()) -> X () -> X ()
mouseGestureH moveHook endHook = do
    dpy <- asks display
    root <- asks theRoot
    (pos, acc) <- io $ do
        (_, _, _, ix, iy, _, _, _) <- queryPointer dpy root
        r <- newIORef Nothing
        return ((fromIntegral ix, fromIntegral iy), r)
    mouseDrag (gauge moveHook pos acc) endHook
mouseGesture :: Map [Direction2D] (Window -> X ()) -> Window -> X ()
mouseGesture tbl win = do
    (mov, end) <- mkCollect
    mouseGestureH (\d -> mov d >> return ()) $ end >>= \gest ->
        case M.lookup gest tbl of
            Nothing -> return ()
            Just f -> f win
mkCollect :: (MonadIO m, MonadIO m') => m (Direction2D -> m' [Direction2D], m' [Direction2D])
mkCollect = liftIO $ do
    acc <- newIORef []
    let
        mov d = liftIO $ do
            ds <- readIORef acc
            let ds' = d : ds
            writeIORef acc ds'
            return $ reverse ds'
        end = liftIO $ do
            ds <- readIORef acc
            writeIORef acc []
            return $ reverse ds
    return (mov, end)