tricu/src/REPL.hs
James Eversole 63504ba939 Rough draft of modules
This includes a naive implementation of a module system where imported
files have their imports recursively handled, strips the module/import
AST nodes, and then evals everything into a flat environment using
namespace prefixes like "Module.function".
2025-01-27 12:24:30 -06:00

62 lines
2.0 KiB
Haskell

module REPL where
import Eval
import FileEval
import Lexer
import Parser
import Research
import Control.Exception (SomeException, catch)
import Control.Monad.IO.Class (liftIO)
import Data.Char (isSpace)
import Data.List (dropWhile, dropWhileEnd, 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 < "
if
| Nothing <- minput -> outputStrLn "Exiting tricu"
| Just s <- minput, strip s == "!exit" -> outputStrLn "Exiting tricu"
| Just s <- minput, strip s == "" -> do
outputStrLn ""
loop env
| Just s <- minput, strip s == "!import" -> do
path <- getInputLine "File path to load < "
if
| Nothing <- path -> do
outputStrLn "No input received; stopping import."
loop env
| Just p <- path -> do
loadedEnv <- liftIO $ evaluateFileWithContext env (strip p) `catch` \e -> errorHandler env e
loop $ Map.delete "!result" (Map.union loadedEnv env)
| Just s <- minput -> do
if
| take 2 s == "--" -> loop env
| otherwise -> do
newEnv <- liftIO $ processInput env s `catch` errorHandler env
loop newEnv
processInput :: Env -> String -> IO Env
processInput env input = do
let asts = parseTricu input
newEnv = evalTricu env asts
if
| Just r <- Map.lookup "!result" newEnv -> do
putStrLn $ "tricu > " ++ decodeResult r
| otherwise -> return ()
return newEnv
errorHandler :: Env -> SomeException -> IO (Env)
errorHandler env e = do
putStrLn $ "Error: " ++ show e
return env
strip :: String -> String
strip = dropWhileEnd isSpace . dropWhile isSpace