Compare commits

..

No commits in common. "fe70aa72ac16ebd8110d97bd4b69ce45d8812187" and "467e11edb38d0f9515d94d66c0a82f96a49a5ddd" have entirely different histories.

7 changed files with 12 additions and 69 deletions

View File

@ -1,23 +0,0 @@
module Compiler where
import Eval
import Parser
import Research
import System.IO
import qualified Data.Map as Map
evaluateFile :: FilePath -> IO T
evaluateFile filePath = do
contents <- readFile filePath
let linesOfFile = lines contents
let env = foldl evaluateLine Map.empty linesOfFile
case Map.lookup "__result" env of
Just finalResult -> return finalResult
Nothing -> error "No result found in final environment"
evaluateLine :: Env -> String -> Env
evaluateLine env line =
let ast = parseSingle line
in evalSingle env ast

View File

@ -6,7 +6,7 @@ import Research
import qualified Data.Map as Map
library :: Env
library :: Map.Map String T
library = evalTricu Map.empty $ parseTricu $ unlines
[ "false = t"
, "true = t t"

View File

@ -1,6 +1,5 @@
module Main where
import Compiler
import Eval (evalTricu, result)
import Library (library)
import Parser (parseTricu)
@ -8,40 +7,16 @@ import REPL (repl)
import Research (T)
import Text.Megaparsec (runParser)
import System.Console.CmdArgs
import qualified Data.Map as Map
data TricuArgs
= Repl
| Compile { file :: FilePath }
deriving (Show, Data, Typeable)
replMode :: TricuArgs
replMode = Repl
&= help "Start interactive REPL"
&= auto
&= name "repl"
compileMode :: TricuArgs
compileMode = Compile { file = def &= typ "FILE" &= help "Relative or absolute path to compile" }
&= help "Compile a file and return the result of the expression in the final line"
&= explicit
&= name "compile"
main :: IO ()
main = do
args <- cmdArgs $ modes [replMode, compileMode]
&= help "tricu: Exploring Tree Calculus"
&= program "tricu"
&= summary "tricu - compiler 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
Compile filePath -> do
result <- evaluateFile filePath
print result
putStrLn "Welcome to the tricu Interpreter"
putStrLn "You can exit at any time by typing and entering: "
putStrLn ":_exit"
repl library
runTricu :: String -> T
runTricu s = result (evalTricu Map.empty $ parseTricu s)
runTricuEnv env s = result (evalTricu env $ parseTricu s)

View File

@ -12,10 +12,10 @@ import System.Console.Haskeline
import qualified Data.Map as Map
repl :: Env -> IO ()
repl :: Map.Map String T -> IO ()
repl env = runInputT defaultSettings (loop env)
where
loop :: Env -> InputT IO ()
loop :: Map.Map String T -> InputT IO ()
loop env = do
minput <- getInputLine "tricu < "
case minput of
@ -28,7 +28,7 @@ repl env = runInputT defaultSettings (loop env)
newEnv <- liftIO $ (processInput env input `catch` errorHandler env)
loop newEnv
processInput :: Env -> String -> IO (Env)
processInput :: Map.Map String T -> String -> IO (Map.Map String T)
processInput env input = do
let clearEnv = Map.delete "__result" env
newEnv = evalSingle clearEnv (parseSingle input)
@ -39,7 +39,7 @@ repl env = runInputT defaultSettings (loop env)
Nothing -> return ()
return newEnv
errorHandler :: Env -> SomeException -> IO (Env)
errorHandler :: Map.Map String T -> SomeException -> IO (Map.Map String T)
errorHandler env e = do
putStrLn $ "Error: " ++ show e
return env

View File

@ -89,8 +89,6 @@ toList (Fork x rest) = case toList rest of
toList _ = Left "Invalid Tree Calculus list"
-- Utility
type Env = Map.Map String T
toAscii :: T -> String
toAscii tree = go tree "" True
where

View File

@ -1,2 +0,0 @@
x = t t t
x

View File

@ -19,7 +19,6 @@ executable tricu
default-extensions:
ConstraintKinds
DataKinds
DeriveDataTypeable
DeriveGeneric
FlexibleContexts
FlexibleInstances
@ -29,13 +28,11 @@ executable tricu
ghc-options: -threaded -rtsopts -with-rtsopts=-N -optl-pthread -fPIC
build-depends:
base >=4.7
, cmdargs
, containers
, haskeline
, megaparsec
, mtl
other-modules:
Compiler
Eval
Lexer
Library
@ -50,7 +47,6 @@ test-suite tricu-tests
hs-source-dirs: test, src
build-depends:
base
, cmdargs
, containers
, haskeline
, megaparsec
@ -60,7 +56,6 @@ test-suite tricu-tests
, tasty-quickcheck
default-language: Haskell2010
other-modules:
Compiler
Eval
Lexer
Library