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:
2024-12-30 14:19:43 -06:00
committed by James Eversole
parent 78dd2f4d8f
commit 7abc7061d9
13 changed files with 131 additions and 57 deletions

View File

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

1
test/ascii.tri Normal file
View File

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

9
test/comments-1.tri Normal file
View File

@ -0,0 +1,9 @@
-- This is a tricu comment!
-- t (t t) (t (t t t))
-- t (t t t) (t t)
-- x = (\a : a)
t (t t) t -- Fork (Stem Leaf) Leaf
-- t t
-- x
-- x = (\a : a)
-- t

1
test/fork.tri Normal file
View File

@ -0,0 +1 @@
t t t

24
test/map.tri Normal file
View File

@ -0,0 +1,24 @@
false = t
true = t t
_ = t
k = t t
i = t (t k) t
s = t (t (k t)) t
m = s i i
b = s (k s) k
c = s (s (k s) (s (k k) s)) (k k)
iC = (\a b c : s a (k c) b)
yi = (\i : b m (c b (i m)))
y = yi iC
triage = (\a b c : t (t a b) c)
pair = t
matchList = (\oe oc : triage oe _ oc)
lconcat = y (\self : matchList (\k : k) (\h r k : pair h (self r k)))
hmap = y (\self : matchList (\f : t) (\hd tl f : pair (f hd) (self tl f)))
map = (\f l : hmap l f)
lAnd = triage (\x : false) (\_ x : x) (\_ _ x : x)
lOr = triage (\x : x) (\_ _ : true) (\_ _ x : true)
equal = y (\self : triage (triage true (\z : false) (\y z : false)) (\ax : triage false (self ax) (\y z : false)) (\ax ay : triage false (\z : false) (\bx by : lAnd (self ax bx) (self ay by))))
x = map (\i : lconcat "Successfully concatenated " i) [("two strings!")]
equal x [("Successfully concatenated two strings!")]