Rename "compiler" functionality to Evaluator
Allows for stdin input for evaluation when no input file is provided.
This commit is contained in:
@ -13,7 +13,7 @@ evalSingle env term = case term of
|
||||
SFunc name [] body ->
|
||||
let lineNoLambda = eliminateLambda body
|
||||
result = evalAST env lineNoLambda
|
||||
in Map.insert name result env
|
||||
in Map.insert "__result" result (Map.insert name result env)
|
||||
SLambda _ body ->
|
||||
let result = evalAST env body
|
||||
in Map.insert "__result" result env
|
||||
|
@ -1,4 +1,4 @@
|
||||
module Compiler where
|
||||
module FileEval where
|
||||
|
||||
import Eval
|
||||
import Library
|
35
src/Main.hs
35
src/Main.hs
@ -1,7 +1,7 @@
|
||||
module Main where
|
||||
|
||||
import Compiler
|
||||
import Eval (evalTricu, result)
|
||||
import FileEval
|
||||
import Library (library)
|
||||
import Parser (parseTricu)
|
||||
import REPL
|
||||
@ -14,7 +14,7 @@ import qualified Data.Map as Map
|
||||
|
||||
data TricuArgs
|
||||
= Repl
|
||||
| Compile { file :: FilePath, output :: Maybe FilePath, form :: CompiledForm }
|
||||
| Evaluate { file :: Maybe FilePath, output :: Maybe FilePath, form :: EvaluatedForm }
|
||||
| Decode { input :: Maybe FilePath }
|
||||
deriving (Show, Data, Typeable)
|
||||
|
||||
@ -24,24 +24,24 @@ replMode = Repl
|
||||
&= auto
|
||||
&= name "repl"
|
||||
|
||||
compileMode :: TricuArgs
|
||||
compileMode = Compile
|
||||
evaluateMode :: TricuArgs
|
||||
evaluateMode = Evaluate
|
||||
{ file = def &= typ "FILE"
|
||||
&= help "Relative or absolute path to file input for compilation" &= name "f"
|
||||
&= help "Optional input file path for evaluation.\nDefaults to stdin." &= name "f"
|
||||
, output = def &= typ "OUTPUT"
|
||||
&= help "Optional output file path for resulting output" &= name "o"
|
||||
&= help "Optional output file path for resulting output.\nDefaults to stdout." &= name "o"
|
||||
, form = FSL &= typ "FORM"
|
||||
&= help "Output form: (fsl|tree|ast|ternary|ascii)"
|
||||
&= help "Optional output form: (fsl|tree|ast|ternary|ascii).\nDefaults to fsl."
|
||||
&= name "t"
|
||||
}
|
||||
&= help "Compile a file and return the result of the expression in the final line"
|
||||
&= help "Evaluate a file and return the result of the expression in the final line"
|
||||
&= explicit
|
||||
&= name "compile"
|
||||
&= name "eval"
|
||||
|
||||
decodeMode :: TricuArgs
|
||||
decodeMode = Decode
|
||||
{ input = def &= typ "FILE"
|
||||
&= help "Optional file path containing a Tree Calculus value. Defaults to stdin." &= name "f"
|
||||
&= help "Optional file path to attempt decoding.\nDefaults to stdin." &= name "f"
|
||||
}
|
||||
&= help "Decode a Tree Calculus value into a string representation"
|
||||
&= explicit
|
||||
@ -49,18 +49,22 @@ decodeMode = Decode
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
args <- cmdArgs $ modes [replMode, compileMode, decodeMode]
|
||||
args <- cmdArgs $ modes [replMode, evaluateMode, decodeMode]
|
||||
&= help "tricu: Exploring Tree Calculus"
|
||||
&= program "tricu"
|
||||
&= summary "tricu - compiler and repl"
|
||||
&= summary "tricu Evaluator and REPL"
|
||||
|
||||
case args of
|
||||
Repl -> do
|
||||
putStrLn "Welcome to the tricu REPL"
|
||||
putStrLn "You can exit with `CTRL+D` or the `:_exit` command.`"
|
||||
repl library
|
||||
Compile { file = filePath, output = maybeOutputPath, form = form } -> do
|
||||
result <- evaluateFile filePath
|
||||
Evaluate { file = maybeFilePath, output = maybeOutputPath, form = form } -> do
|
||||
result <- case maybeFilePath of
|
||||
Just filePath -> evaluateFile filePath
|
||||
Nothing -> do
|
||||
t <- getContents
|
||||
pure $ runTricu t
|
||||
let fRes = formatResult form result
|
||||
case maybeOutputPath of
|
||||
Just outputPath -> do
|
||||
@ -72,3 +76,6 @@ main = do
|
||||
Just inputPath -> readFile inputPath
|
||||
Nothing -> getContents
|
||||
putStrLn $ decodeResult $ result $ evalTricu library $ parseTricu value
|
||||
|
||||
runTricu :: String -> T
|
||||
runTricu = result . evalTricu Map.empty . parseTricu
|
||||
|
@ -45,7 +45,7 @@ data LToken
|
||||
deriving (Show, Eq, Ord)
|
||||
|
||||
-- Output formats
|
||||
data CompiledForm = TreeCalculus | FSL | AST | Ternary | Ascii
|
||||
data EvaluatedForm = TreeCalculus | FSL | AST | Ternary | Ascii
|
||||
deriving (Show, Data, Typeable)
|
||||
|
||||
-- Environment containing previously evaluated TC terms
|
||||
@ -122,7 +122,7 @@ toList (Fork x rest) = case toList rest of
|
||||
toList _ = Left "Invalid Tree Calculus list"
|
||||
|
||||
-- Outputs
|
||||
formatResult :: CompiledForm -> T -> String
|
||||
formatResult :: EvaluatedForm -> T -> String
|
||||
formatResult TreeCalculus = toSimpleT . show
|
||||
formatResult FSL = show
|
||||
formatResult AST = show . toAST
|
||||
|
Reference in New Issue
Block a user