module Compiler.Parser where import Control.Monad.IO.Class (liftIO) import Compiler.AST.Parser.Common import Compiler.AST.Program import Compiler.Lexer import Data.Text as T import Parser tokenize :: Text -> IO [Token] tokenize src = liftIO $ runParserEither (parser @[Token]) (toTextWithOffset src) >>= \case Right ts -> pure ts Left (ParseErrorWithParsed (Just partial) _ (FatalError IncompleteParse)) -> pure partial Left _ -> pure [] parse :: [Token] -> IO Program parse tks = parseEither tks >>= \case Right p -> pure p Left err -> error $ show err parseEither :: (Show a, HasAstParser a) => [Token] -> IO (Either (ParseErrorWithParsed a) a) parseEither tks = runParserEither astParser (mkAstParserState tks) parseRaw :: Text -> AstParser a -> IO (Either (ParseErrorWithParsed a) a) parseRaw src astP = do tokens <- tokenize src runParserEither astP (mkAstParserState tokens) compile :: (Show a, HasAstParser a) => Text -> IO a compile src = compileEither src >>= \case Right p -> pure p Left err -> error $ show err compileEither :: forall a. (Show a, HasAstParser a) => Text -> IO (Either (ParseErrorWithParsed a) a) compileEither src = tokenize src >>= parseEither