tricu/src/REPL.hs
James Eversole 7abc7061d9 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.
2024-12-30 14:22:37 -06:00

55 lines
1.5 KiB
Haskell

module REPL where
import Eval
import Lexer
import Parser
import Research
import Control.Exception (SomeException, catch)
import Control.Monad.IO.Class (liftIO)
import Data.List (intercalate)
import System.Console.Haskeline
import qualified Data.Map as Map
repl :: Env -> IO ()
repl env = runInputT defaultSettings (loop env)
where
loop :: Env -> InputT IO ()
loop env = do
minput <- getInputLine "tricu < "
case minput of
Nothing -> outputStrLn "Goodbye!"
Just ":_exit" -> outputStrLn "Goodbye!"
Just "" -> do
outputStrLn ""
loop env
Just input -> do
newEnv <- liftIO $ (processInput env input `catch` errorHandler env)
loop newEnv
processInput :: Env -> String -> IO Env
processInput env input = do
let asts = parseTricu input
newEnv = evalTricu env asts
case Map.lookup "__result" newEnv of
Just r -> do
putStrLn $ "tricu > " ++ show r
putStrLn $ "READ -: \"" ++ decodeResult r ++ "\""
Nothing -> return ()
return newEnv
errorHandler :: Env -> SomeException -> IO (Env)
errorHandler env e = do
putStrLn $ "Error: " ++ show e
return env
decodeResult :: T -> String
decodeResult tc = case toNumber tc of
Right num -> show num
Left _ -> case toString tc of
Right str -> str
Left _ -> case toList tc of
Right list -> "[" ++ intercalate ", " (map decodeResult list) ++ "]"
Left _ -> ""