diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Eval.hs | 45 | ||||
-rw-r--r-- | src/Parser.hs | 66 |
2 files changed, 111 insertions, 0 deletions
diff --git a/src/Eval.hs b/src/Eval.hs new file mode 100644 index 0000000..72c8985 --- /dev/null +++ b/src/Eval.hs @@ -0,0 +1,45 @@ +module Eval + ( evalMain + ) where + +import Control.Exception +import Control.Monad.State +import System.Console.Haskeline +import System.Environment +import System.Exit +import System.IO + +type Environment = [String] + +eval :: String -> IO () +eval code = putStrLn "ok" + +evalFile :: String -> IO () +evalFile path = do + file <- try $ readFile path :: IO (Either IOError String) + case file of + Left exception -> print (exception :: IOError) + Right file -> eval file + +evalRepl :: String -> Environment -> InputT IO Environment +evalRepl line env = outputStrLn (show env) >> pure env + +repl :: Environment -> InputT IO () +repl env = + getInputLine ":: " + >>= (\case + Nothing -> pure () + Just line -> evalRepl line env >>= repl + ) + +usage :: IO () +usage = putStrLn "Invalid arguments. Use 'bruijn [file]' instead" + +evalMain :: IO () +evalMain = do + args <- getArgs + case args of + [] -> runInputT defaultSettings { historyFile = Just ".brown-history" } + $ repl [] + [path] -> evalFile path + _ -> usage diff --git a/src/Parser.hs b/src/Parser.hs new file mode 100644 index 0000000..611261f --- /dev/null +++ b/src/Parser.hs @@ -0,0 +1,66 @@ +module Parser where + +import Data.Functor.Identity +import Text.Parsec +import Text.Parsec.Language +import qualified Text.Parsec.Token as Token + +languageDef :: GenLanguageDef String u Identity +languageDef = emptyDef { Token.commentLine = "#" + , Token.identStart = letter + , Token.identLetter = alphaNum <|> char '_' + , Token.reservedOpNames = ["[", "]"] + } + +type Parser = Parsec String () + +lexer :: Token.GenTokenParser String u Identity +lexer = Token.makeTokenParser languageDef + +identifier :: Parser String +identifier = Token.identifier lexer + +reservedOp :: String -> Parser () +reservedOp = Token.reservedOp lexer + +parens :: Parser a -> Parser a +parens = Token.parens lexer + +data Expression = Index Int | Abstraction Int Expression | Application Expression Expression + deriving (Ord, Eq) +data Instruction = Define String Expression | Evaluate Expression | Comment String + +parseAbstraction :: Parser Expression +parseAbstraction = do + reservedOp "[" + idc <- endBy1 digit spaces + build idc <$> parseExpression + where + build (idx : idc) body = + Abstraction ((read . pure :: Char -> Int) idx) $ build idc body + curry [] body = body + +parseApplication :: Parser Expression +parseApplication = do + s <- sepBy1 parseSingleton spaces + pure $ foldl1 Application s + +parseSingleton :: Parser Expression +parseSingleton = parseAbstraction <|> parens parseApplication + +parseExpression :: Parser Expression +parseExpression = do + expr <- parseApplication <|> parseSingleton + pure expr + +parseDefine :: Parser Instruction +parseDefine = do + var <- identifier + space + Define var <$> parseExpression + +parseLine :: Parser Instruction +parseLine = try parseDefine + +parseReplLine :: Parser Expression +parseReplLine = try parseExpression |