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:
2025-01-01 18:53:56 -06:00
committed by James Eversole
parent 1c8457733e
commit 8b0b24e7dc
7 changed files with 80 additions and 64 deletions

View File

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

View File

@ -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))))"
]

View File

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

View File

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