fix doctests
[fp.git] / src / Lambda.hs
index f89cc7e..0cedf4a 100644 (file)
@@ -20,10 +20,12 @@ module Lambda
   , tRead
     -- * Reduction
   , reduce
   , tRead
     -- * Reduction
   , reduce
+  , toNormalForm
+  , Strategy(..)
   ) where
   
 
   ) where
   
 
-import Data.Text as T
+import Data.Text as T hiding (map)
 import Data.Attoparsec.Text
 import Control.Applicative
 import Control.Monad.State 
 import Data.Attoparsec.Text
 import Control.Applicative
 import Control.Monad.State 
@@ -31,10 +33,21 @@ import Control.Monad.State
 -- $setup
 -- >>> import Test.QuickCheck
 -- >>> import Control.Applicative
 -- $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 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))] 
 -- >>> instance Arbitrary Term where arbitrary = sized aTerm
 
 -- >>> 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
 
 -- | 
 type VarName = String
 
 -- | 
@@ -68,7 +81,7 @@ tRead s = case parseOnly (parseTerm <* endOfInput) (T.pack s) of
 
 parseVar :: Parser Term
 parseVar = do
 
 parseVar :: Parser Term
 parseVar = do
-  x <- many1 letter
+  x <- many1 (letter <|> digit)
   return $! Var x
 
 parseLambda :: Parser Term
   return $! Var x
 
 parseLambda :: Parser Term
@@ -146,21 +159,68 @@ reduceStep :: (Monad m) => Term -> m Term
 reduceStep (RedEx x s t) = return $ substitute x t s
 reduceStep t = return $ t
 
 reduceStep (RedEx x s t) = return $ substitute x t s
 reduceStep t = return $ t
 
-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)
+data Z = R Term Z | L Z Term | ZL VarName Z | E
+data D = Up | Down
+type TermZipper = (Term, Z, D)
+
+move :: TermZipper -> TermZipper
+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 :: TermZipper -> TermZipper
+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)
+    tr _ (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 _ (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
 
 
 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 100 $ (App (App cK cI) cY)
+-- Nothing
+--
+-- >>> toNormalForm Lazy 100 $ (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 :: 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
 
 cnt :: (Monad m) => Term -> StateT Int m Term
 cnt t@(RedEx _ _ _) = do
@@ -169,8 +229,8 @@ cnt t@(RedEx _ _ _) = do
 cnt t = return t
 
 short :: Int -> Term -> StateT Int Maybe Term
 cnt t = return t
 
 short :: Int -> Term -> StateT Int Maybe Term
-short max t = do
+short maxN t = do
   n <- get
   n <- get
-  if n == max
+  if n > maxN
     then lift Nothing
     else return t
     then lift Nothing
     else return t