import Data.Attoparsec.Text
import Control.Applicative
import Control.Monad.State
import Data.Attoparsec.Text
import Control.Applicative
import Control.Monad.State
--- >>> let aTerm 0 = liftA (Var . ("x" ++) . show) (arbitrary :: Gen Int)
--- >>> let aTerm n = oneof [aTerm 0, liftA (Lambda "x") $ aTerm (n - 1), liftA2 App (aTerm (n `div` 2)) (aTerm (n `div` 2))]
+-- >>> let aVarName = oneof . map (pure . (:[])) $ ['a'..'e']
+-- >>> let aVar = liftA Var aVarName
+-- >>> let aTerm 0 = aVar
+-- >>> let aTerm n = oneof [aVar, liftA2 Lambda aVarName $ aTerm (n - 1), liftA2 App (aTerm (n `div` 2)) (aTerm (n `div` 2))]
-traversPost :: (Monad m) => (Term -> m Term) -> Term -> m Term
-traversPost f (App t u) = do
- nt <- traversPost f t
- nu <- traversPost f u
- case App nt nu of
- l@(RedEx _ _ _) -> traversPost f =<< f l
- r -> return r
-traversPost f (Lambda x t) = return . Lambda x =<< traversPost f t
-traversPost f (Var x) = return $ (Var x)
-
move (App l r, c, Down) = (l, L c r, Down)
move (Lambda x t, c, Down) = (t, ZL x c, Down)
move (Var x, c, Down) = (Var x, c, Up)
move (App l r, c, Down) = (l, L c r, Down)
move (Lambda x t, c, Down) = (t, ZL x c, Down)
move (Var x, c, Down) = (Var x, c, Up)
move (t, ZL x c, Up) = (Lambda x t, c, Up)
move (t, E, Up) = (t, E, Up)
move (t, ZL x c, Up) = (Lambda x t, c, Up)
move (t, E, Up) = (t, E, Up)
unmove (t, L c r, Down) = (App t r, c, Down)
unmove x = x
unmove (t, L c r, Down) = (App t r, c, Down)
unmove x = x
travPost :: (Monad m) => (Term -> m Term) -> Term -> m Term
travPost fnc term = tr fnc (term, E, Down)
where
tr f (t@(RedEx _ _ _), c, Up) = do
nt <- f t
tr f $ (nt, c, Down)
travPost :: (Monad m) => (Term -> m Term) -> Term -> m Term
travPost fnc term = tr fnc (term, E, Down)
where
tr f (t@(RedEx _ _ _), c, Up) = do
nt <- f t
tr f $ (nt, c, Down)
tr f (t, c, Up) = tr f $ move (t, c, Up)
tr f (t, c, Down) = tr f $ move (t, c, Down)
tr f (t, c, Up) = tr f $ move (t, c, Up)
tr f (t, c, Down) = tr f $ move (t, c, Down)
tr f (t@(RedEx _ _ _), c, Down) = do
nt <- f t
tr f $ unmove (nt, c, Down)
tr f (t@(RedEx _ _ _), c, Down) = do
nt <- f t
tr f $ unmove (nt, c, Down)
tr f (t, c, Up) = tr f $ move (t, c, Up)
tr f (t, c, Down) = tr f $ move (t, c, Down)
tr f (t, c, Up) = tr f $ move (t, c, Up)
tr f (t, c, Down) = tr f $ move (t, c, Down)