Rename "compiler" functionality to Evaluator

Allows for stdin input for evaluation when no input file is provided.
This commit is contained in:
James Eversole 2025-01-01 08:17:05 -06:00
parent 458d3c3b10
commit 7d38d99dcd
8 changed files with 43 additions and 32 deletions

View File

@ -58,7 +58,7 @@ You can easily build and/or run this project using [Nix](https://nixos.org/downl
`./result/bin/tricu --help`
```
tricu - compiler and repl
tricu Evaluator and REPL
tricu [COMMAND] ... [OPTIONS]
tricu: Exploring Tree Calculus
@ -70,17 +70,20 @@ Common flags:
tricu [repl] [OPTIONS]
Start interactive REPL
tricu compile [OPTIONS]
Compile a file and return the result of the expression in the final line
tricu eval [OPTIONS]
Evaluate a file and return the result of the expression in the final line
-f --file=FILE Relative or absolute path to file input for compilation
-o --output=OUTPUT Optional output file path for resulting output
-t --form=FORM Output form: (fsl|tree|ast|ternary|ascii)
-f --file=FILE Optional input file path for evaluation.
Defaults to stdin.
-o --output=OUTPUT Optional output file path for resulting output.
Defaults to stdout.
-t --form=FORM Optional output form: (fsl|tree|ast|ternary|ascii).
Defaults to fsl.
tricu decode [OPTIONS]
Decode a Tree Calculus value into a string representation
-f --input=FILE Optional file path containing a Tree Calculus value.
-f --input=ITEM Optional file path to attempt decoding.
Defaults to stdin.
```

View File

@ -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

View File

@ -1,4 +1,4 @@
module Compiler where
module FileEval where
import Eval
import Library

View File

@ -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

View File

@ -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

View File

@ -1,7 +1,7 @@
module Main where
import Compiler
import Eval
import FileEval
import Lexer
import Library
import Parser
@ -31,7 +31,7 @@ tests = testGroup "Tricu Tests"
, evaluationTests
, lambdaEvalTests
, libraryTests
, compilerTests
, fileEvaluationTests
, propertyTests
]
@ -377,8 +377,8 @@ libraryTests = testGroup "Library Tests"
result env @?= Stem Leaf
]
compilerTests :: TestTree
compilerTests = testGroup "Compiler tests"
fileEvaluationTests :: TestTree
fileEvaluationTests = testGroup "Evaluation tests"
[ testCase "Forks" $ do
res <- liftIO $ evaluateFile "./test/fork.tri"
res @?= Fork Leaf Leaf
@ -388,7 +388,7 @@ compilerTests = testGroup "Compiler tests"
, testCase "Mapping and Equality" $ do
res <- liftIO $ evaluateFile "./test/map.tri"
res @?= Stem Leaf
, testCase "Map evaluation to String -> compilation -> string decoding" $ do
, testCase "Eval and decoding string" $ do
res <- liftIO $ evaluateFile "./test/string.tri"
decodeResult res @?= "String test!"
]

1
test/assignment.tri Normal file
View File

@ -0,0 +1 @@
x = t (t t) t

View File

@ -29,8 +29,8 @@ executable tricu
, mtl
, text
other-modules:
Compiler
Eval
FileEval
Lexer
Library
Parser
@ -58,8 +58,8 @@ test-suite tricu-tests
, text
default-language: Haskell2010
other-modules:
Compiler
Eval
FileEval
Lexer
Library
Parser