Skip to content

Commit

Permalink
main and tests
Browse files Browse the repository at this point in the history
  • Loading branch information
mbuszka committed Jan 27, 2018
1 parent b87da0d commit 25bf838
Show file tree
Hide file tree
Showing 2 changed files with 62 additions and 3 deletions.
63 changes: 62 additions & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,65 @@
module Main where

import Control.Monad
import Control.Monad.Except

import Data.Text as Text
import Data.Text.IO as Text

import System.Environment
import System.Exit

import Inference
import Inference.Env
import Error
import Syntax
import Print
import Evaluation

data Command
= Check [FilePath]
| Eval [FilePath]

parseFiles :: (MonadIO m, MonadError Error m) => [FilePath] -> m [Top]
parseFiles fs = do
ts <- liftIO $ mapM Text.readFile fs
Prelude.concat <$> mapM parse ts

parseArgs :: (MonadIO m) => [String] -> m Command
parseArgs ("check" : fs) = return $ Check fs
parseArgs ("eval" : fs) = return $ Eval fs
parseArgs _ = do
liftIO $ putDocW 80 "usage: aleph-exe <eval | check> [files]"
liftIO $ exitFailure

main :: IO ()
main = putStrLn "Hello World\n"
main = do
args <- getArgs
cmd <- parseArgs args
case cmd of
Check fs -> do
errs <- runExceptT $ parseFiles fs
ps <- reportAndExit errs
t <- typecheck ps
liftIO $ putDocW 80 $ pretty t
Eval fs -> do
errs <- runExceptT $ parseFiles fs
ps <- reportAndExit errs
typecheck ps
(e, res) <- eval ps
case e of
Just e -> liftIO $ putDocW 80 $ pretty e <> line
Nothing -> liftIO $ putDocW 80 $ "Program finished successfully" <> line
liftIO $ putDocW 80 $ "Results:"
<+> indent 2 (align $ vsep (fmap pretty res)) <> line <> line

reportAndExit :: (MonadIO m) => Either Error a -> m a
reportAndExit (Left e) = do
liftIO $ putDocW 80 $ pretty e <> line
liftIO $ exitFailure
reportAndExit (Right v) = return v

typecheck :: [Top] -> (MonadIO m) => m Env
typecheck p = do
e <- runExceptT $ check p
reportAndExit e
2 changes: 0 additions & 2 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,6 @@
, OverloadedStrings
#-}

import Control.Lens

import Control.Monad
import Control.Monad.Except

Expand Down

0 comments on commit 25bf838

Please sign in to comment.