module Main where
-import Data.Text as T (Text)
+import Data.Text as T (Text, pack)
import qualified Data.Text.IO as T
import Data.Attoparsec.Text
import qualified Data.Map as M
import Control.Applicative
+import Control.Monad
import System.Environment
import Lambda
t <- parseTerm
return $! Definition name t
-parseFile :: Text -> ([Definition], [Term])
+parseImport :: Parser String
+parseImport = do
+ string (T.pack "import ")
+ many1 letter
+
+parseFile :: Text -> ([FilePath], [Definition], [Term])
parseFile txt = case cnt of
(Right t) -> t
(Left e) -> error e
where cnt = parseOnly (parserF <* endOfInput) txt
parserF = do
+ imports <- many (parseImport <* char '\n')
defs <- many (parseDefinition <* char '\n')
terms <- many (parseTerm <* char '\n')
- return $! (defs, terms)
+ return (imports, defs, terms)
-printEval :: Term -> IO ()
-printEval t = do
+printEval :: (Term -> Term) -> Term -> IO ()
+printEval def t = do
putStrLn $ show t ++ ":"
- putStrLn $ " " ++ show (reduce t)
+ putStrLn $ " " ++ show (reduce $ def t)
putStrLn ""
+makeDefTerm :: [Definition] -> Term -> Term
+makeDefTerm (Definition name dTerm : ds) t = App (Lambda name (makeDefTerm ds t)) dTerm
+makeDefTerm [] t = t
+
main :: IO ()
main = do
[filename] <- getArgs
- (defs, terms) <- parseFile <$> T.readFile filename
- mapM_ printEval terms
+ (imports, defs, terms) <- parseFile <$> T.readFile filename
+ importDefs <- forM imports $ \ file -> do
+ (_, idefs, _) <- parseFile <$> T.readFile (file ++ ".lc")
+ return idefs
+ let defT = makeDefTerm $ concat importDefs ++ defs
+ mapM_ (printEval defT) terms