tricu/src/Main.hs
James Eversole 33c2119708
All checks were successful
Test, Build, and Release / test (push) Successful in 1m11s
Test, Build, and Release / build (push) Successful in 1m12s
Don't require available library to run REPL or decoder
2025-01-27 16:28:40 -06:00

86 lines
2.5 KiB
Haskell

module Main where
import Eval (evalTricu, mainResult, result)
import FileEval
import Parser (parseTricu)
import REPL
import Research
import Control.Monad (foldM)
import Control.Monad.IO.Class (liftIO)
import Text.Megaparsec (runParser)
import System.Console.CmdArgs
import qualified Data.Map as Map
data TricuArgs
= Repl
| Evaluate { file :: [FilePath], form :: EvaluatedForm }
| TDecode { file :: [FilePath] }
deriving (Show, Data, Typeable)
replMode :: TricuArgs
replMode = Repl
&= help "Start interactive REPL"
&= auto
&= name "repl"
evaluateMode :: TricuArgs
evaluateMode = Evaluate
{ file = def &= help "Input file path(s) for evaluation.\n \
\ Defaults to stdin."
&= name "f" &= typ "FILE"
, form = TreeCalculus &= typ "FORM"
&= help "Optional output form: (tree|fsl|ast|ternary|ascii|decode).\n \
\ Defaults to tricu-compatible `t` tree form."
&= name "t"
}
&= help "Evaluate tricu and return the result of the final expression."
&= explicit
&= name "eval"
decodeMode :: TricuArgs
decodeMode = TDecode
{ file = def
&= help "Optional input file path to attempt decoding.\n \
\ Defaults to stdin."
&= name "f" &= typ "FILE"
}
&= help "Decode a Tree Calculus value into a string representation."
&= explicit
&= name "decode"
main :: IO ()
main = do
args <- cmdArgs $ modes [replMode, evaluateMode, decodeMode]
&= help "tricu: Exploring Tree Calculus"
&= program "tricu"
&= 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 Map.empty
Evaluate { file = filePaths, form = form } -> do
result <- case filePaths of
[] -> do
t <- getContents
pure $ runTricu t
(filePath:restFilePaths) -> do
initialEnv <- evaluateFile filePath
finalEnv <- foldM evaluateFileWithContext initialEnv restFilePaths
pure $ mainResult finalEnv
let fRes = formatResult form result
putStr fRes
TDecode { file = filePaths } -> do
value <- case filePaths of
[] -> getContents
(filePath:_) -> readFile filePath
putStrLn $ decodeResult $ result $ evalTricu Map.empty $ parseTricu value
runTricu :: String -> T
runTricu input =
let asts = parseTricu input
finalEnv = evalTricu Map.empty asts
in result finalEnv