module SMR.Source.Parser where
import SMR.Core.Exp.Base
import SMR.Source.Expected
import SMR.Source.Token
import SMR.Source.Lexer
import SMR.Data.Located
import Data.Text (Text)
import qualified SMR.Source.Parsec as P
import qualified SMR.Data.Bag as Bag
import qualified Data.Text as Text
type Parser s p a
= P.Parser (Located Token) (Expected (Located Token) s p) a
type Error s p
= ParseError (Located Token) (Expected (Located Token) s p)
data Config s p
= Config
{ configReadSym :: Text -> Maybe s
, configReadPrm :: Text -> Maybe p }
parseDecls
:: Config s p
-> [Located Token]
-> Either (Error s p) [Decl s p]
parseDecls c ts
= case P.parse pDeclsEnd ts of
P.ParseSkip es -> Left $ ParseError (Bag.toList es)
P.ParseReturn _ xx -> Right xx
P.ParseFailure bs -> Left $ ParseError (Bag.toList bs)
P.ParseSuccess xx _ -> Right xx
where
pDeclsEnd
= do ds <- pDecls c
_ <- pEnd
return ds
parseExp
:: Config s p
-> [Located Token]
-> Either (Error s p) (Exp s p)
parseExp c ts
= case P.parse pExpEnd ts of
P.ParseSkip es -> Left $ ParseError (Bag.toList es)
P.ParseReturn _ xx -> Right xx
P.ParseFailure bs -> Left $ ParseError (Bag.toList bs)
P.ParseSuccess xx _ -> Right xx
where
pExpEnd
= do x <- pExp c
_ <- pEnd
return x
pDecls :: Config s p -> Parser s p [Decl s p]
pDecls c
= P.some (pDecl c)
pDecl :: Config s p -> Parser s p (Decl s p)
pDecl c
= P.alts
[ P.enterOn (pNameOfSpace SMac) ExContextDecl $ \name
-> do psParam <- P.some pParam
_ <- pPunc '='
xBody <- pExp c
_ <- pPunc ';'
if length psParam == 0
then return (DeclMac name xBody)
else return (DeclMac name $ XAbs psParam xBody)
, P.enterOn (pNameOfSpace SSet) ExContextDecl $ \name
-> do _ <- pPunc '='
xBody <- pExp c
_ <- pPunc ';'
return (DeclSet name xBody)
]
pExp :: Config s p -> Parser s p (Exp s p)
pExp c
= P.alts
[ do _ <- pPunc '\\'
psParam <- P.some pParam
_ <- pPunc '.'
xBody <- pExp c
return $ XAbs psParam xBody
, do csTrain <- pTrain c
_ <- pPunc '.'
xBody <- pExp c
return $ XSub (reverse csTrain) xBody
, do xHead <- pExpApp c
P.alt
(do _ <- pPunc '$'
xRest <- pExp c
return $ XApp xHead [xRest])
(return xHead)
]
pExpApp :: Config s p -> Parser s p (Exp s p)
pExpApp c
= P.alts
[ do nKey
<- do nKey' <- pNameOfSpace SKey
if nKey' == Text.pack "box" then return KBox
else if nKey' == Text.pack "run" then return KRun
else P.fail
xArg <- pExpAtom c
return $ XKey nKey xArg
, do xFun <- pExpAtom c
xsArgs <- P.some (pExpAtom c)
case xsArgs of
[] -> return $ xFun
_ -> return $ XApp xFun xsArgs
]
pExpAtom :: Config s p -> Parser s p (Exp s p)
pExpAtom c
= P.alts
[ do _ <- pPunc '('
x <- pExp c
_ <- pPunc ')'
return x
, do _ <- pPunc '?'
n <- pNat
return $ XRef (RNom n)
, do tx <- pText
return $ XRef (RTxt tx)
, do (space, name) <- pName
case space of
SVar
-> P.alt (do _ <- pPunc '^'
ix <- pNat
return $ XVar name ix)
(return $ XVar name 0)
SMac -> return $ XRef (RMac name)
SSet -> return $ XRef (RSet name)
SSym
-> case configReadSym c name of
Just s -> return (XRef (RSym s))
Nothing -> P.fail
SPrm
-> case configReadPrm c name of
Just p -> return (XRef (RPrm p))
Nothing -> P.fail
SKey -> P.fail
SNom -> P.fail
]
pParam :: Parser s p Param
pParam
= P.alts
[ do _ <- pPunc '!'
n <- pNameOfSpace SVar
return $ PParam n PVal
, do _ <- pPunc '~'
n <- pNameOfSpace SVar
return $ PParam n PExp
, do n <- pNameOfSpace SVar
return $ PParam n PVal
]
pTrain :: Config s p -> Parser s p [Car s p]
pTrain c
= do cCar <- pTrainCar c
P.alt
(do csCar <- pTrain c
return $ cCar : csCar)
(do return $ cCar : [])
pTrainCar :: Config s p -> Parser s p (Car s p)
pTrainCar c
= P.alt
(do car <- pCarSimRec c
return car)
(do
ups <- pUps
return (CUps ups))
pCarSimRec :: Config s p -> Parser s p (Car s p)
pCarSimRec c
= do _ <- pPunc '['
P.alt
(do _ <- pPunc '['
bs <- P.sepBy (pBind c) (pPunc ',')
_ <- pPunc ']'
_ <- pPunc ']'
return $ CRec (SSnv (reverse bs)))
(do bs <- P.sepBy (pBind c) (pPunc ',')
_ <- pPunc ']'
return $ CSim (SSnv (reverse bs)))
pBind :: Config s p -> Parser s p (SnvBind s p)
pBind c
= P.alt
(P.enterOn (pNameOfSpace SVar) ExContextBind $ \name
-> P.alt
(do _ <- pPunc '='
x <- pExp c
return $ BindVar name 0 x)
(do _ <- pPunc '^'
bump <- pNat
_ <- pPunc '='
x <- pExp c
return $ BindVar name bump x))
(do pPunc '?'
ix <- pNat
_ <- pPunc '='
x <- pExp c
return $ BindNom ix x)
pUps :: Parser s p Ups
pUps
= do _ <- pPunc '{'
bs <- P.sepBy pBump (pPunc ',')
_ <- pPunc '}'
return $ UUps (reverse bs)
pBump :: Parser s p UpsBump
pBump
= do name <- pNameOfSpace SVar
P.alt
(do _ <- pPunc ':'
inc <- pNat
return ((name, 0), inc))
(do _ <- pPunc '^'
depth <- pNat
_ <- pPunc ':'
inc <- pNat
return ((name, depth), inc))
pNat :: Parser s p Integer
pNat = P.from ExBaseNat (takeNatOfToken . valueOfLocated)
pText :: Parser s p Text
pText = P.from ExBaseText (takeTextOfToken . valueOfLocated)
pNameOfSpace :: Space -> Parser s p Text
pNameOfSpace s
= P.from (ExBaseNameOf s) (takeNameOfToken s . valueOfLocated)
pName :: Parser s p (Space, Text)
pName
= P.from ExBaseNameAny (takeAnyNameOfToken . valueOfLocated)
pEnd :: Parser s p ()
pEnd
= do _ <- P.satisfies ExBaseEnd (isToken KEnd . valueOfLocated)
return ()
pPunc :: Char -> Parser s p ()
pPunc c
= do _ <- P.satisfies (ExBasePunc c) (isToken (KPunc c) . valueOfLocated)
return ()