Provide "library" via tricu file directly
Allows easier loading of other files and drops the list of Haskell strings containing the basic tools included
This commit is contained in:
parent
39be66a4d1
commit
a2c459b148
35
lib/base.tri
Normal file
35
lib/base.tri
Normal file
@ -0,0 +1,35 @@
|
||||
false = t
|
||||
_ = t
|
||||
true = 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)
|
||||
iD = b (b iC) iC
|
||||
iE = b (b iD) iC
|
||||
yi = (\i : b m (c b (i m)))
|
||||
y = yi iC
|
||||
yC = yi iD
|
||||
yD = yi iE
|
||||
id = (\a : a)
|
||||
triage = (\a b c : t (t a b) c)
|
||||
pair = t
|
||||
matchBool = (\ot of : triage of (\_ : ot) (\_ _ : ot))
|
||||
matchList = (\oe oc : triage oe _ oc)
|
||||
matchPair = (\op : triage _ _ op)
|
||||
not = matchBool false true
|
||||
and = matchBool id (\z : false)
|
||||
if = (\cond then else : t (t else (t t then)) t cond)
|
||||
test = triage "Leaf" (\z : "Stem") (\a b : "Fork")
|
||||
emptyList = matchList true (\y z : false)
|
||||
head = matchList t (\hd tl : hd)
|
||||
tail = matchList t (\hd tl : tl)
|
||||
lconcat = y (\self : matchList (\k : k) (\h r k : pair h (self r k)))
|
||||
lAnd = triage (\x : false) (\_ x : x) (\_ _ x : x)
|
||||
lOr = triage (\x : x) (\_ _ : true) (\_ _ x : true)
|
||||
hmap = y (\self : matchList (\f : t) (\hd tl f : pair (f hd) (self tl f)))
|
||||
map = (\f l : hmap l f)
|
||||
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))))
|
@ -1,7 +1,6 @@
|
||||
module FileEval where
|
||||
|
||||
import Eval
|
||||
import Library
|
||||
import Parser
|
||||
import Research
|
||||
|
||||
@ -9,17 +8,23 @@ import System.IO
|
||||
|
||||
import qualified Data.Map as Map
|
||||
|
||||
evaluateFile :: FilePath -> IO T
|
||||
evaluateFile filePath = do
|
||||
evaluateFileResult :: FilePath -> IO T
|
||||
evaluateFileResult filePath = do
|
||||
contents <- readFile filePath
|
||||
let asts = parseTricu contents
|
||||
let finalEnv = evalTricu library asts
|
||||
let finalEnv = evalTricu Map.empty asts
|
||||
case Map.lookup "__result" finalEnv of
|
||||
Just finalResult -> return finalResult
|
||||
Nothing -> error "No result found in final environment"
|
||||
|
||||
evaluateFileEnv :: FilePath -> IO Env
|
||||
evaluateFileEnv filePath = do
|
||||
evaluateFile :: FilePath -> IO Env
|
||||
evaluateFile filePath = do
|
||||
contents <- readFile filePath
|
||||
let asts = parseTricu contents
|
||||
pure $ evalTricu library asts
|
||||
pure $ evalTricu Map.empty asts
|
||||
|
||||
evaluateFileWithContext :: Env -> FilePath -> IO Env
|
||||
evaluateFileWithContext env filePath = do
|
||||
contents <- readFile filePath
|
||||
let asts = parseTricu contents
|
||||
pure $ evalTricu env asts
|
||||
|
@ -1,46 +0,0 @@
|
||||
module Library where
|
||||
|
||||
import Eval
|
||||
import Parser
|
||||
import Research
|
||||
|
||||
import Data.Map (empty)
|
||||
|
||||
library :: Env
|
||||
library = evalTricu empty $ parseTricu $ unlines
|
||||
[ "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)"
|
||||
, "iD = b (b iC) iC"
|
||||
, "iE = b (b iD) iC"
|
||||
, "yi = (\\i : b m (c b (i m)))"
|
||||
, "y = yi iC"
|
||||
, "yC = yi iD"
|
||||
, "yD = yi iE"
|
||||
, "id = (\\a : a)"
|
||||
, "triage = (\\a b c : t (t a b) c)"
|
||||
, "pair = t"
|
||||
, "matchBool = (\\ot of : triage of (\\_ : ot) (\\_ _ : ot))"
|
||||
, "matchList = (\\oe oc : triage oe _ oc)"
|
||||
, "matchPair = (\\op : triage _ _ op)"
|
||||
, "not = matchBool false true"
|
||||
, "and = matchBool id (\\z : false)"
|
||||
, "if = (\\cond then else : t (t else (t t then)) t cond)"
|
||||
, "test = triage \"Leaf\" (\\z : \"Stem\") (\\a b : \"Fork\")"
|
||||
, "emptyList = matchList true (\\y z : false)"
|
||||
, "head = matchList t (\\hd tl : hd)"
|
||||
, "tail = matchList t (\\hd tl : tl)"
|
||||
, "lconcat = y (\\self : matchList (\\k : k) (\\h r k : pair h (self r k)))"
|
||||
, "lAnd = triage (\\x : false) (\\_ x : x) (\\_ _ x : x)"
|
||||
, "lOr = triage (\\x : x) (\\_ _ : true) (\\_ _ x : true)"
|
||||
, "hmap = y (\\self : matchList (\\f : t) (\\hd tl f : pair (f hd) (self tl f)))"
|
||||
, "map = (\\f l : hmap l f)"
|
||||
, "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))))"
|
||||
]
|
@ -2,11 +2,11 @@ module Main where
|
||||
|
||||
import Eval (evalTricu, result)
|
||||
import FileEval
|
||||
import Library (library)
|
||||
import Parser (parseTricu)
|
||||
import REPL
|
||||
import Research
|
||||
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Text.Megaparsec (runParser)
|
||||
import System.Console.CmdArgs
|
||||
|
||||
@ -68,10 +68,11 @@ main = do
|
||||
Repl -> do
|
||||
putStrLn "Welcome to the tricu REPL"
|
||||
putStrLn "You can exit with `CTRL+D` or the `:_exit` command.`"
|
||||
library <- liftIO $ evaluateFile "./lib/base.tri"
|
||||
repl library
|
||||
Evaluate { file = maybeFilePath, output = maybeOutputPath, form = form } -> do
|
||||
result <- case maybeFilePath of
|
||||
Just filePath -> evaluateFile filePath
|
||||
Just filePath -> evaluateFileResult filePath
|
||||
Nothing -> do
|
||||
t <- getContents
|
||||
pure $ runTricu t
|
||||
@ -85,6 +86,7 @@ main = do
|
||||
value <- case maybeFilePath of
|
||||
Just filePath -> readFile filePath
|
||||
Nothing -> getContents
|
||||
library <- liftIO $ evaluateFile "./lib/base.tri"
|
||||
putStrLn $ decodeResult $ result $ evalTricu library $ parseTricu value
|
||||
|
||||
runTricu :: String -> T
|
||||
|
@ -29,7 +29,7 @@ repl env = runInputT defaultSettings (loop env)
|
||||
outputStrLn "No input received; stopping import."
|
||||
loop env
|
||||
Just path -> do
|
||||
loadedEnv <- liftIO $ evaluateFileEnv path
|
||||
loadedEnv <- liftIO $ evaluateFile path
|
||||
loop $ Map.union loadedEnv env
|
||||
Just "" -> do
|
||||
outputStrLn ""
|
||||
|
34
test/Spec.hs
34
test/Spec.hs
@ -3,7 +3,6 @@ module Main where
|
||||
import Eval
|
||||
import FileEval
|
||||
import Lexer
|
||||
import Library
|
||||
import Parser
|
||||
import REPL
|
||||
import Research
|
||||
@ -288,90 +287,112 @@ lambdaEvalTests = testGroup "Lambda Evaluation Tests"
|
||||
libraryTests :: TestTree
|
||||
libraryTests = testGroup "Library Tests"
|
||||
[ testCase "K combinator 1" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "k (t) (t t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
, testCase "K combinator 2" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "k (t t) (t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
, testCase "K combinator 3" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "k (t t t) (t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Fork Leaf Leaf
|
||||
, testCase "S combinator" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "s (t) (t) (t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Fork Leaf (Stem Leaf)
|
||||
, testCase "SKK == I (fully expanded)" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "s k k"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Fork (Stem (Stem Leaf)) (Stem Leaf)
|
||||
, testCase "I combinator" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "i not"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Fork (Fork (Stem Leaf) (Fork Leaf Leaf)) (Fork Leaf (Fork Leaf Leaf))
|
||||
, testCase "Triage test Leaf" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "test t"
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "Leaf"
|
||||
, testCase "Triage test (Stem Leaf)" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "test (t t)"
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "Stem"
|
||||
, testCase "Triage test (Fork Leaf Leaf)" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "test (t t t)"
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "Fork"
|
||||
, testCase "Boolean NOT: true" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "not true"
|
||||
env = result $ evalTricu library (parseTricu input)
|
||||
env @?= Leaf
|
||||
, testCase "Boolean NOT: false" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "not false"
|
||||
env = result $ evalTricu library (parseTricu input)
|
||||
env @?= Stem Leaf
|
||||
, testCase "Boolean AND TF" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "and (t t) (t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
, testCase "Boolean AND FT" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "and (t) (t t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
, testCase "Boolean AND FF" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "and (t) (t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
, testCase "Boolean AND TT" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "and (t t) (t t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
, testCase "List head" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "head [(t) (t t) (t t t)]"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
, testCase "List tail" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "head (tail (tail [(t) (t t) (t t t)]))"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Fork Leaf Leaf
|
||||
, testCase "List map" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "head (tail (map (\\a : (t t t)) [(t) (t) (t)]))"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Fork Leaf Leaf
|
||||
, testCase "Empty list check" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "emptyList []"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
, testCase "Non-empty list check" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "not (emptyList [(1) (2) (3)])"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
, testCase "Concatenate strings" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "lconcat \"Hello, \" \"world!\""
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "Hello, world!"
|
||||
, testCase "Verifying Equality" $ do
|
||||
library <- evaluateFile "./lib/base.tri"
|
||||
let input = "equal (t t t) (t t t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
@ -380,17 +401,18 @@ libraryTests = testGroup "Library Tests"
|
||||
fileEvaluationTests :: TestTree
|
||||
fileEvaluationTests = testGroup "Evaluation tests"
|
||||
[ testCase "Forks" $ do
|
||||
res <- liftIO $ evaluateFile "./test/fork.tri"
|
||||
res <- liftIO $ evaluateFileResult "./test/fork.tri"
|
||||
res @?= Fork Leaf Leaf
|
||||
, testCase "File ends with comment" $ do
|
||||
res <- liftIO $ evaluateFile "./test/comments-1.tri"
|
||||
res <- liftIO $ evaluateFileResult "./test/comments-1.tri"
|
||||
res @?= Fork (Stem Leaf) Leaf
|
||||
, testCase "Mapping and Equality" $ do
|
||||
res <- liftIO $ evaluateFile "./test/map.tri"
|
||||
res <- liftIO $ evaluateFileResult "./test/map.tri"
|
||||
res @?= Stem Leaf
|
||||
, testCase "Eval and decoding string" $ do
|
||||
res <- liftIO $ evaluateFile "./test/string.tri"
|
||||
decodeResult res @?= "String test!"
|
||||
library <- liftIO $ evaluateFile "./lib/base.tri"
|
||||
res <- liftIO $ evaluateFileWithContext library "./test/string.tri"
|
||||
decodeResult (result res) @?= "String test!"
|
||||
]
|
||||
|
||||
propertyTests :: TestTree
|
||||
|
@ -32,7 +32,6 @@ executable tricu
|
||||
Eval
|
||||
FileEval
|
||||
Lexer
|
||||
Library
|
||||
Parser
|
||||
REPL
|
||||
Research
|
||||
@ -61,7 +60,6 @@ test-suite tricu-tests
|
||||
Eval
|
||||
FileEval
|
||||
Lexer
|
||||
Library
|
||||
Parser
|
||||
REPL
|
||||
Research
|
||||
|
Loading…
x
Reference in New Issue
Block a user