perga/lib/Parser.hs

187 lines
4.8 KiB
Haskell
Raw Normal View History

2024-11-30 20:34:09 -08:00
{-# LANGUAGE TupleSections #-}
2024-11-17 01:57:53 -08:00
2024-11-30 20:34:09 -08:00
module Parser where
2024-10-05 13:31:09 -07:00
import Control.Monad.Except
2024-11-30 20:34:09 -08:00
import Data.List (foldl1)
2024-11-14 22:02:04 -08:00
import qualified Data.Text as T
2024-11-17 18:33:14 -08:00
import Errors (Error (..))
2024-11-30 20:34:09 -08:00
import IR
import Preprocessor
2024-11-30 20:34:09 -08:00
import Text.Megaparsec (Parsec, ShowErrorComponent (..), between, choice, chunk, errorBundlePretty, label, runParser, try)
2024-10-05 13:31:09 -07:00
import Text.Megaparsec.Char
import qualified Text.Megaparsec.Char.Lexer as L
2024-10-05 16:04:13 -07:00
2024-11-17 18:33:14 -08:00
newtype TypeError = TE Error
2024-11-22 19:44:31 -08:00
deriving (Eq, Ord)
2024-11-17 01:57:53 -08:00
2024-11-30 20:34:09 -08:00
type Parser = Parsec TypeError Text
2024-10-05 16:04:13 -07:00
2024-11-17 01:57:53 -08:00
instance ShowErrorComponent TypeError where
2024-11-22 19:44:31 -08:00
showErrorComponent (TE e) = toString e
2024-10-05 13:31:09 -07:00
skipSpace :: Parser ()
skipSpace =
2024-11-11 16:38:46 -08:00
L.space
space1
(L.skipLineComment "--")
(L.skipBlockCommentNested "[*" "*]")
2024-10-05 13:31:09 -07:00
lexeme :: Parser a -> Parser a
lexeme = L.lexeme skipSpace
2024-11-22 19:44:31 -08:00
eat :: Text -> Parser ()
eat = void . lexeme . chunk
2024-11-23 09:16:32 -08:00
keywords :: [Text]
keywords = ["forall", "let", "in", "end", "fun"]
2024-11-14 22:02:04 -08:00
pIdentifier :: Parser Text
2024-11-23 09:16:32 -08:00
pIdentifier = try $ label "identifier" $ lexeme $ do
2024-11-11 16:38:46 -08:00
firstChar <- letterChar <|> char '_'
rest <- many $ alphaNumChar <|> char '_'
2024-11-23 09:16:32 -08:00
let ident = T.pack (firstChar : rest)
when (ident `elem` keywords) $
fail $
"Reserved word: " ++ T.unpack ident
pure ident
2024-10-05 13:31:09 -07:00
2024-11-30 20:34:09 -08:00
pVar :: Parser IRExpr
pVar = label "variable" $ lexeme $ Var <$> pIdentifier
2024-10-05 13:31:09 -07:00
2024-11-22 19:44:31 -08:00
defChoice :: NonEmpty Text -> Parser ()
defChoice options = lexeme $ label (T.unpack $ head options) $ void $ choice $ fmap chunk options
2024-11-11 16:38:46 -08:00
2024-11-30 20:34:09 -08:00
pParamGroup :: Parser [Param]
2024-11-11 16:38:46 -08:00
pParamGroup = lexeme $ label "parameter group" $ between (char '(') (char ')') $ do
idents <- some pIdentifier
2024-11-22 19:44:31 -08:00
eat ":"
2024-11-30 20:34:09 -08:00
ty <- pIRExpr
pure $ map (,ty) idents
2024-11-11 16:38:46 -08:00
2024-11-30 20:34:09 -08:00
pSomeParams :: Parser [Param]
2024-11-17 18:33:14 -08:00
pSomeParams = lexeme $ concat <$> some pParamGroup
2024-11-30 20:34:09 -08:00
pManyParams :: Parser [Param]
2024-11-17 18:33:14 -08:00
pManyParams = lexeme $ concat <$> many pParamGroup
2024-10-05 13:31:09 -07:00
2024-11-30 20:34:09 -08:00
pLAbs :: Parser IRExpr
pLAbs = lexeme $ label "λ-abstraction" $ do
2024-11-20 12:44:21 -08:00
_ <- defChoice $ "λ" :| ["fun"]
2024-11-17 18:33:14 -08:00
params <- pSomeParams
2024-11-20 12:44:21 -08:00
_ <- defChoice $ "=>" :| [""]
2024-11-30 20:34:09 -08:00
body <- pIRExpr
2024-11-11 16:38:46 -08:00
pure $ foldr (uncurry Abs) body params
2024-10-05 13:31:09 -07:00
2024-11-30 20:34:09 -08:00
pPAbs :: Parser IRExpr
pPAbs = lexeme $ label "Π-abstraction" $ do
2024-11-20 12:44:21 -08:00
_ <- defChoice $ "" :| ["forall", ""]
2024-11-17 18:33:14 -08:00
params <- pSomeParams
eat ","
2024-11-30 20:34:09 -08:00
body <- pIRExpr
2024-11-11 16:38:46 -08:00
pure $ foldr (uncurry Pi) body params
2024-11-30 20:34:09 -08:00
pBinding :: Parser (Text, Maybe IRExpr, IRExpr)
2024-11-23 09:16:32 -08:00
pBinding = lexeme $ label "binding" $ do
eat "("
ident <- pIdentifier
params <- pManyParams
2024-11-30 20:34:09 -08:00
ascription <- pAscription
2024-11-23 09:16:32 -08:00
eat ":="
2024-11-30 20:34:09 -08:00
value <- pIRExpr
2024-11-23 09:16:32 -08:00
eat ")"
2024-11-30 20:34:09 -08:00
pure
( ident
, flip (foldr (uncurry Pi)) params <$> ascription
, foldr (uncurry Abs) value params
)
pLet :: Parser IRExpr
pLet = lexeme $ label "let expression" $ do
2024-11-23 09:16:32 -08:00
eat "let"
bindings <- some pBinding
eat "in"
2024-11-30 20:34:09 -08:00
body <- try pIRExpr
2024-11-23 09:16:32 -08:00
eat "end"
2024-11-30 20:34:09 -08:00
pure $ foldr letTuple body bindings
where
letTuple :: (Text, Maybe IRExpr, IRExpr) -> IRExpr -> IRExpr
letTuple (name, ascription, value) = Let name ascription value
2024-11-23 09:16:32 -08:00
2024-11-30 20:34:09 -08:00
pArrow :: Parser IRExpr
2024-11-11 16:38:46 -08:00
pArrow = lexeme $ label "->" $ do
a <- pAppTerm
_ <- defChoice $ "->" :| [""]
2024-11-30 20:34:09 -08:00
Pi "" a <$> pIRExpr
2024-10-05 13:31:09 -07:00
2024-11-30 20:34:09 -08:00
pApp :: Parser IRExpr
2024-11-17 18:33:14 -08:00
pApp = lexeme $ foldl1 App <$> some pTerm
2024-10-05 13:31:09 -07:00
2024-11-30 20:34:09 -08:00
pStar :: Parser IRExpr
pStar = lexeme $ Level 0 <$ eat "*"
2024-10-05 13:31:09 -07:00
2024-11-30 20:34:09 -08:00
pNumSort :: Parser IRExpr
pNumSort = lexeme $ label "sort" $ eat "*" >> Level <$> L.decimal
2024-11-30 20:34:09 -08:00
pSort :: Parser IRExpr
pSort = try pNumSort <|> pStar
2024-11-17 18:33:14 -08:00
2024-11-30 20:34:09 -08:00
pAxiom :: Parser IRExpr
pAxiom = Axiom <$ eat "axiom"
2024-11-22 19:44:31 -08:00
2024-11-30 20:34:09 -08:00
pIRDef :: Parser IRDef
pIRDef = lexeme $ label "definition" $ do
2024-11-17 18:33:14 -08:00
skipSpace
ident <- pIdentifier
params <- pManyParams
ascription <- fmap (flip (foldr (uncurry Pi)) params) <$> pAscription
2024-11-22 19:44:31 -08:00
eat ":="
2024-11-30 20:34:09 -08:00
body <- pIRExpr
eat ";"
pure $ Def ident params ascription body
2024-10-05 13:31:09 -07:00
2024-11-30 20:34:09 -08:00
pTerm :: Parser IRExpr
2024-10-05 13:31:09 -07:00
pTerm =
2024-11-11 16:38:46 -08:00
lexeme $
label "term" $
choice
2024-11-30 20:34:09 -08:00
[ between (char '(') (char ')') pIRExpr
, pSort
2024-11-30 20:34:09 -08:00
, pAxiom
2024-11-17 18:33:14 -08:00
, pVar
2024-11-11 16:38:46 -08:00
]
2024-11-30 20:34:09 -08:00
pAppTerm :: Parser IRExpr
2024-11-23 09:16:32 -08:00
pAppTerm =
lexeme $
choice
[ pLAbs
, pPAbs
, pLet
, pApp
]
2024-10-05 13:31:09 -07:00
2024-11-30 20:34:09 -08:00
pIRExpr :: Parser IRExpr
pIRExpr = lexeme $ try pArrow <|> pAppTerm
2024-11-17 18:33:14 -08:00
2024-11-30 20:34:09 -08:00
pAscription :: Parser (Maybe IRExpr)
pAscription = lexeme $ optional $ try $ eat ":" >> label "type" pIRExpr
2024-11-22 19:44:31 -08:00
2024-11-30 20:34:09 -08:00
pIRProgram :: Parser IRProgram
pIRProgram = many pIRDef
2024-11-17 18:33:14 -08:00
2024-11-30 20:34:09 -08:00
parserWrapper :: Parser a -> String -> Text -> Either String a
parserWrapper p filename input = first errorBundlePretty $ runParser p filename input
2024-11-17 18:33:14 -08:00
2024-11-30 20:34:09 -08:00
parseProgram :: String -> Text -> Either String IRProgram
parseProgram = parserWrapper pIRProgram
2024-11-18 14:33:21 -08:00
2024-11-30 20:34:09 -08:00
parseDef :: String -> Text -> Either String IRDef
parseDef = parserWrapper pIRDef
2024-11-17 18:33:14 -08:00
2024-11-30 20:34:09 -08:00
parseExpr :: String -> Text -> Either String IRExpr
parseExpr = parserWrapper pIRExpr
2024-11-30 20:34:09 -08:00
handleFile :: String -> ExceptT String IO IRProgram
handleFile filename = (toString `withExceptT` runPreprocessor filename) >>= hoistEither . parseProgram filename