module Data.Generics.Zipper (
Zipper(),
toZipper, fromZipper,
left, right, down, down', up,
query,
trans,
transM,
getHole,
setHole,
setHole',
moveQ, leftQ, rightQ, downQ, upQ,
moveT, leftT, rightT, downT, upT,
moveM, rightM, downM, upM,
leftmost, rightmost,
zmapQ,
zmapT,
zmapM,
zmapMp,
zeverywhere, zeverywhere', zsomewhere, zreduce,
) where
import Data.Generics
import Control.Monad ((<=<), MonadPlus, mzero, mplus, liftM)
import Data.Maybe (fromJust)
data Zipper root =
forall hole. (Data hole) =>
Zipper hole (Context hole root)
data Context hole root where
CtxtNull :: Context a a
CtxtCons ::
forall hole root rights parent. (Data parent) =>
Left (hole -> rights)
-> Right rights parent
-> Context parent root
-> Context hole root
combine :: Left (hole -> rights)
-> hole
-> Right rights parent
-> parent
combine lefts hole rights =
fromRight ((fromLeft lefts) hole) rights
data Left expects
= LeftUnit expects
| forall b. (Data b) => LeftCons (Left (b -> expects)) b
toLeft :: (Data a) => a -> Left a
toLeft a = gfoldl LeftCons LeftUnit a
fromLeft :: Left r -> r
fromLeft (LeftUnit a) = a
fromLeft (LeftCons f b) = fromLeft f b
data Right provides parent where
RightNull :: Right parent parent
RightCons ::
(Data b) => b -> Right a t -> Right (b -> a) t
fromRight :: r -> Right r parent -> parent
fromRight f (RightNull) = f
fromRight f (RightCons b r) = fromRight (f b) r
fromZipper :: Zipper a -> a
fromZipper (Zipper hole CtxtNull) = hole
fromZipper (Zipper hole (CtxtCons l r ctxt)) =
fromZipper (Zipper (combine l hole r) ctxt)
toZipper :: (Data a) => a -> Zipper a
toZipper x = Zipper x CtxtNull
left :: Zipper a -> Maybe (Zipper a)
left (Zipper _ CtxtNull) = Nothing
left (Zipper _ (CtxtCons (LeftUnit _) _ _)) = Nothing
left (Zipper h (CtxtCons (LeftCons l h') r c)) =
Just (Zipper h' (CtxtCons l (RightCons h r) c))
right :: Zipper a -> Maybe (Zipper a)
right (Zipper _ CtxtNull) = Nothing
right (Zipper _ (CtxtCons _ RightNull _)) = Nothing
right (Zipper h (CtxtCons l (RightCons h' r) c)) =
Just (Zipper h' (CtxtCons (LeftCons l h) r c))
down :: Zipper a -> Maybe (Zipper a)
down (Zipper hole ctxt) =
case toLeft hole of
LeftUnit _ -> Nothing
LeftCons l hole' ->
Just (Zipper hole' (CtxtCons l RightNull ctxt))
down' :: Zipper a -> Maybe (Zipper a)
down' z = liftM leftmost (down z)
up :: Zipper a -> Maybe (Zipper a)
up (Zipper _ CtxtNull) = Nothing
up (Zipper hole (CtxtCons l r ctxt)) =
Just (Zipper (combine l hole r) ctxt)
query :: GenericQ b -> Zipper a -> b
query f (Zipper hole _ctxt) = f hole
trans :: GenericT -> Zipper a -> Zipper a
trans f (Zipper hole ctxt) = Zipper (f hole) ctxt
transM :: (Monad m) => GenericM m -> Zipper a -> m (Zipper a)
transM f (Zipper hole ctxt) = do
hole' <- f hole
return (Zipper hole' ctxt)
getHole :: (Typeable b) => Zipper a -> Maybe b
getHole = query cast
setHole :: (Typeable a) => a -> Zipper b -> Zipper b
setHole h z = trans (mkT (const h)) z
setHole' :: (Typeable a) => a -> Zipper b -> Maybe (Zipper b)
setHole' h z = transM (mkMp (const (return h))) z
type Move a = Zipper a -> Maybe (Zipper a)
moveQ :: Move a
-> b
-> (Zipper a -> b)
-> Zipper a
-> b
moveQ move b f z = case move z of
Nothing -> b
Just z' -> f z'
moveT :: Move a
-> Move a
-> Zipper a
-> (Zipper a -> Zipper a)
-> Zipper a
-> Zipper a
moveT move1 move2 b f z =
moveQ move1 b (moveQ move2 b id . f) z
moveM :: (Monad m)
=> Move a
-> Move a
-> m (Zipper a)
-> (Zipper a -> m (Zipper a))
-> Zipper a
-> m (Zipper a)
moveM move1 move2 b f z = moveQ move1 b (moveQ move2 b return <=< f) z
leftQ :: b
-> (Zipper a -> b) -> Zipper a -> b
leftQ b f z = moveQ left b f z
rightQ :: b
-> (Zipper a -> b) -> Zipper a -> b
rightQ b f z = moveQ right b f z
downQ :: b
-> (Zipper a -> b) -> Zipper a -> b
downQ b f z = moveQ down b f z
upQ :: b
-> (Zipper a -> b) -> Zipper a -> b
upQ b f z = moveQ up b f z
leftT :: (Zipper a -> Zipper a) -> Zipper a -> Zipper a
leftT f z = moveT left right z f z
rightT :: (Zipper a -> Zipper a) -> Zipper a -> Zipper a
rightT f z = moveT right left z f z
downT :: (Zipper a -> Zipper a) -> Zipper a -> Zipper a
downT f z = moveT down up z f z
upT :: (Zipper a -> Zipper a) -> Zipper a -> Zipper a
upT f z = g z where
g z' = moveT right left (h z') g z'
h z' = moveT up down z' f z'
leftM :: (Monad m) => m (Zipper a)
-> (Zipper a -> m (Zipper a)) -> Zipper a -> m (Zipper a)
leftM b f z = moveM left right b f z
rightM :: (Monad m) => m (Zipper a)
-> (Zipper a -> m (Zipper a)) -> Zipper a -> m (Zipper a)
rightM b f z = moveM right left b f z
downM :: (Monad m) => m (Zipper a)
-> (Zipper a -> m (Zipper a)) -> Zipper a -> m (Zipper a)
downM b f z = moveM down up b f z
upM :: (Monad m) => m (Zipper a)
-> (Zipper a -> m (Zipper a)) -> Zipper a -> m (Zipper a)
upM b f z = g z where
g z' = moveM right left (h z') g z'
h z' = moveM up down b f z'
leftmost :: Zipper a -> Zipper a
leftmost z = leftQ z leftmost z
rightmost :: Zipper a -> Zipper a
rightmost z = rightQ z rightmost z
zmapQ :: GenericQ b -> Zipper a -> [b]
zmapQ f z = reverse $ downQ [] g z where
g z' = query f z' : leftQ [] g z'
zmapT :: GenericT -> Zipper a -> Zipper a
zmapT f z = downT g z where
g z' = trans f (leftT g z')
zmapM :: (Monad m) => GenericM m -> Zipper a -> m (Zipper a)
zmapM f z = downM (return z) g z where
g z' = leftM (return z') (transM f) z'
zmapMp :: (MonadPlus m) => GenericM m -> Zipper a -> m (Zipper a)
zmapMp f z = downQ mzero (g . leftmost) z where
g z' = (transM f z' >>= (return . fromJust . up)) `mplus` rightQ mzero g z'
zeverywhere :: GenericT -> Zipper a -> Zipper a
zeverywhere f z = trans f (downT g z) where
g z' = leftT g (zeverywhere f z')
zeverywhere' :: GenericT -> Zipper a -> Zipper a
zeverywhere' f z =
downQ (g x) (zeverywhere' f . leftmost) x where
x = trans f z
g z' = rightQ (upQ z' g z') (zeverywhere' f) z'
zsomewhere :: (MonadPlus m) => GenericM m -> Zipper a -> m (Zipper a)
zsomewhere f z = transM f z `mplus` downM mzero (g . leftmost) z where
g z' = transM f z `mplus` rightM mzero (zsomewhere f) z'
zreduce :: GenericM Maybe -> Zipper a -> Zipper a
zreduce f z =
case transM f z of
Nothing ->
downQ (g z) (zreduce f . leftmost) z where
g z' = rightQ (upQ z' g z') (zreduce f) z'
Just x -> zreduce f (reduceAncestors f x x)
reduceAncestors ::
GenericM Maybe -> Zipper a -> Zipper a -> Zipper a
reduceAncestors f z def = upQ def g z where
g z' = reduceAncestors f z' def' where
def' = case transM f z' of
Nothing -> def
Just x -> reduceAncestors f x x