module Language.Melody.API (runExpr, runTopLevel, runFile) where import Text.Parsec import Language.Melody.Interpret.Types import Language.Melody.Interpret import Language.Melody.Parser import Language.Melody.Syntax import Control.Monad.Trans.Either data Error = Parser ParseError | Eval EvalError deriving (Show) type Stack = [Expr Compiled] type MelodyResult = IO (Either Error Stack) liftError :: (e -> Error) -> Either e a -> Either Error a liftError f = either (Left . f) Right run :: [TopLevel] -> MelodyResult run = fmap (liftError Eval) . runMelody . mapM_ eval liftParser :: (String -> Either ParseError a) -> String -> EitherT Error IO a liftParser p = hoistEither . liftError Parser . p liftIOParser :: (String -> IO (Either ParseError a)) -> String -> EitherT Error IO a liftIOParser p = EitherT . fmap (liftError Parser) . p runExpr, runTopLevel, runFile :: String -> MelodyResult runExpr s = runEitherT $ liftParser parseMelodyExpr s >>= EitherT . run . (:[]) . Exec runTopLevel t = runEitherT $ liftParser parseMelody t >>= EitherT . run . (:[]) runFile f = runEitherT $ liftIOParser parseSrcFile f >>= EitherT . run