Expands CLI support with output forms and decoding
Adds CLI options for compiling to a Tree Calculus, AST, Ternary, and ASCII tree view. Adds CLI command for attempted decoding of a compiled result to Number/String/List.
This commit is contained in:
21
test/Spec.hs
21
test/Spec.hs
@ -1,12 +1,15 @@
|
||||
module Main where
|
||||
|
||||
import Compiler
|
||||
import Eval
|
||||
import Lexer
|
||||
import Library
|
||||
import Parser
|
||||
import REPL
|
||||
import Research
|
||||
|
||||
import Control.Exception (evaluate, try, SomeException)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit
|
||||
import Test.Tasty.QuickCheck
|
||||
@ -28,6 +31,7 @@ tests = testGroup "Tricu Tests"
|
||||
, evaluationTests
|
||||
, lambdaEvalTests
|
||||
, libraryTests
|
||||
, compilerTests
|
||||
, propertyTests
|
||||
]
|
||||
|
||||
@ -213,7 +217,7 @@ evaluationTests = testGroup "Evaluation Tests"
|
||||
let input = "x = t t\nx = t\nx"
|
||||
env = evalTricu Map.empty (parseTricu input)
|
||||
(result env) @?= Leaf
|
||||
, testCase "Apply identity to Boolean Not" $ do
|
||||
, testCase "Apply identity to Boolean Not" $ do
|
||||
let not = "(t (t (t t) (t t t)) t)"
|
||||
let input = "x = (\\a : a)\nx " ++ not
|
||||
env = evalTricu Map.empty (parseTricu input)
|
||||
@ -364,7 +368,7 @@ libraryTests = testGroup "Library Tests"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
, testCase "Concatenate strings" $ do
|
||||
let input = "listConcat \"Hello, \" \"world!\""
|
||||
let input = "lconcat \"Hello, \" \"world!\""
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "Hello, world!"
|
||||
, testCase "Verifying Equality" $ do
|
||||
@ -373,6 +377,19 @@ libraryTests = testGroup "Library Tests"
|
||||
result env @?= Stem Leaf
|
||||
]
|
||||
|
||||
compilerTests :: TestTree
|
||||
compilerTests = testGroup "Compiler tests"
|
||||
[ testCase "Forks" $ do
|
||||
res <- liftIO $ evaluateFile "./test/fork.tri"
|
||||
res @?= Fork Leaf Leaf
|
||||
, testCase "File ends with comment" $ do
|
||||
res <- liftIO $ evaluateFile "./test/comments-1.tri"
|
||||
res @?= Fork (Stem Leaf) Leaf
|
||||
, testCase "Mapping and Equality" $ do
|
||||
res <- liftIO $ evaluateFile "./test/map.tri"
|
||||
res @?= Stem Leaf
|
||||
]
|
||||
|
||||
propertyTests :: TestTree
|
||||
propertyTests = testGroup "Property Tests"
|
||||
[ testProperty "Lexing and parsing round-trip" $ \input ->
|
||||
|
Reference in New Issue
Block a user