From: Tomas Musil Date: Fri, 12 Dec 2014 19:25:07 +0000 (+0100) Subject: Eager and Lazy X-Git-Url: http://git.tomasm.cz/fp.git/commitdiff_plain/16e5b1e83c48bdaf47166d61c780dbbadfa79209 Eager and Lazy --- diff --git a/src/Lambda.hs b/src/Lambda.hs index f89cc7e..f828f4d 100644 --- a/src/Lambda.hs +++ b/src/Lambda.hs @@ -31,17 +31,26 @@ import Control.Monad.State -- $setup -- >>> import Test.QuickCheck -- >>> import Control.Applicative --- >>> let aTerm 0 = pure $ Var "x" --- >>> let aTerm n = oneof [pure (Var "x"), liftA (Lambda "x") $ aTerm (n - 1), liftA2 App (aTerm (n `div` 2)) (aTerm (n `div` 2))] +-- >>> 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))] -- >>> instance Arbitrary Term where arbitrary = sized aTerm +cY :: Term +cY = tRead "λf.(λx.f (x x)) (λx.f (x x))" + +cI :: Term +cI = tRead "λx.x" + +cK :: Term +cK = tRead "λx y.x" + type VarName = String -- | -- >>> print $ Lambda "x" (Var "x") -- (λx.x) -data Term = Var VarName | Lambda VarName Term | App Term Term deriving (Eq) +data Term = EmptyT | Var VarName | Lambda VarName Term | App Term Term deriving (Eq) pattern RedEx x t s = App (Lambda x t) s pattern AppApp a b c = App a (App b c) @@ -68,7 +77,7 @@ tRead s = case parseOnly (parseTerm <* endOfInput) (T.pack s) of parseVar :: Parser Term parseVar = do - x <- many1 letter + x <- many1 (letter <|> digit) return $! Var x parseLambda :: Parser Term @@ -150,17 +159,74 @@ traversPost :: (Monad m) => (Term -> m Term) -> Term -> m Term traversPost f (App t u) = do nt <- traversPost f t nu <- traversPost f u - f (App nt nu) -traversPost f (Lambda x t) = f . Lambda x =<< traversPost f t -traversPost f (Var x) = f (Var x) + 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) + +data Z = R Term Z | L Z Term | ZL VarName Z | E +data D = Up | Down +data Zip = Zip Z Term + +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, L c r, Up) = (r, R t c, Down) +move (t, R l c, Up) = (App l t, c, 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 + +getF (t, _, _) = t + +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, E, Up) = return t + tr f (t, c, Up) = tr f $ move (t, c, Up) + tr f (t, c, Down) = tr f $ move (t, c, Down) + +travPre :: (Monad m) => (Term -> m Term) -> Term -> m Term +travPre fnc term = tr fnc (term, E, Down) + where + tr f (t@(RedEx _ _ _), c, Down) = do + nt <- f t + tr f $ unmove (nt, c, Down) + tr f (t, E, Up) = return t + tr f (t, c, Up) = tr f $ move (t, c, Up) + tr f (t, c, Down) = tr f $ move (t, c, Down) printT :: Term -> IO Term printT t = do print t return t +-- | +-- +-- >>> toNormalForm Eager 100 cI +-- Just (λx.x) +-- +-- >>> toNormalForm Eager 100 $ App cI cI +-- Just (λx.x) +-- +-- >>> toNormalForm Eager 1000 $ (App (App cK cI) cY) +-- Nothing +-- +-- >>> toNormalForm Lazy 1000 $ (App (App cK cI) cY) +-- Just (λx.x) +-- +-- prop> (\ t u -> t == u || t == Nothing || u == Nothing) (toNormalForm Lazy 1000 x) (toNormalForm Eager 1000 x) + + toNormalForm :: Strategy -> Int -> Term -> Maybe Term -toNormalForm Eager n = flip evalStateT 0 . traversPost (short n >=> cnt >=> reduceStep) +toNormalForm Eager n = flip evalStateT 0 . travPost (cnt >=> short n >=> reduceStep) +toNormalForm Lazy n = flip evalStateT 0 . travPre (cnt >=> short n >=> reduceStep) cnt :: (Monad m) => Term -> StateT Int m Term cnt t@(RedEx _ _ _) = do @@ -171,6 +237,6 @@ cnt t = return t short :: Int -> Term -> StateT Int Maybe Term short max t = do n <- get - if n == max + if n > max then lift Nothing else return t