haskell - Parsing an expression grammar having function application with parser combinators (left-recursion) -
as simplified subproblem of parser real language, trying implement parser expressions of fictional language looks similar standard imperative languages (like python, javascript, , so). syntax features next construct:
integer numbers identifiers ([a-za-z]+
) arithmetic expressions +
, *
, parenthesis structure access .
(eg foo.bar.buz
) tuples (eg (1, foo, bar.buz)
) (to remove ambiguity one-tuples written (x,)
) function application (eg foo(1, bar, buz())
) functions first class can returned other functions , straight applied (eg foo()()
legal because foo()
might homecoming function) so complex programme in language is
(1+2*3, f(4,5,6)(bar) + qux.quux()().quuux)
the associativity supposed be
( (1+(2*3)), ( ((f(4,5,6))(bar)) + ((((qux.quux)())()).quuux) ) )
i'm using nice uu-parsinglib
applicative parser combinator library.
the first problem intuitive look grammar (expr -> identifier | number | expr * expr | expr + expr | (expr)
left-recursive. solve problem using the pchainl
combinator (see parseexpr
in illustration below).
the remaining problem (hence question) function application functions returned other functions (f()()
). again, grammar left recursive expr -> fun-call | ...; fun-call -> expr ( parameter-list )
. ideas how can solve problem elegantly using uu-parsinglib
? (the problem should straight apply parsec
, attoparsec
, other parser combinators guess).
see below current version of program. works function application working on identifiers remove left-recursion:
{-# language flexiblecontexts #-} {-# language rankntypes #-} module testexprgrammar ( ) import data.foldable (asum) import data.list (intercalate) import text.parsercombinators.uu import text.parsercombinators.uu.utils import text.parsercombinators.uu.basicinstances info node = numberliteral integer | identifier string | tuple [node] | memberaccess node node | functioncall node [node] | binaryoperation string node node parsefunctioncall :: parser node parsefunctioncall = functioncall <$> parseidentifier {- `parseexpr' right left-recursive -} <*> parseparenthesisednodelist 0 operators :: [[(char, node -> node -> node)]] operators = [ [('+', binaryoperation "+")] , [('*' , binaryoperation "*")] , [('.', memberaccess)] ] sameprio :: [(char, node -> node -> node)] -> parser (node -> node -> node) sameprio ops = asum [op <$ psym c <* pspaces | (c, op) <- ops] parseexpr :: parser node parseexpr = foldr pchainl (parseidentifier <|> parsenumber <|> parsetuple <|> parsefunctioncall <|> pparens parseexpr ) (map sameprio operators) parsenodelist :: int -> parser [node] parsenodelist n = case n of _ | n < 0 -> parsenodelist 0 0 -> plistsep (psymbol ",") parseexpr n -> (:) <$> parseexpr <* psymbol "," <*> parsenodelist (n-1) parseparenthesisednodelist :: int -> parser [node] parseparenthesisednodelist n = pparens (parsenodelist n) parseidentifier :: parser node parseidentifier = identifier <$> psome pletter <* pspaces parsenumber :: parser node parsenumber = numberliteral <$> pnatural parsetuple :: parser node parsetuple = tuple <$> parseparenthesisednodelist 1 <|> tuple [] <$ psymbol "()" instance show node show n = allow shownodelist ns = intercalate ", " (map show ns) showparenthesisednodelist ns = "(" ++ shownodelist ns ++ ")" in case n of identifier -> tuple ns -> showparenthesisednodelist ns numberliteral n -> show n functioncall f args -> show f ++ showparenthesisednodelist args memberaccess f g -> show f ++ "." ++ show g binaryoperation op l r -> "(" ++ show l ++ op ++ show r ++ ")"
looking briefly @ the list-like combinators uu-parsinglib
(i'm more familiar parsec
), think can solve folding on result of psome
combinator:
parsefunctioncall :: parser node parsefunctioncall = foldl' functioncall <$> parseidentifier {- `parseexpr' right left-recursive -} <*> psome (parseparenthesisednodelist 0)
this equivalent alternative
some
combinator, should indeed apply other parsing libs mentioned.
parsing haskell parsec recursive-descent uu-parsinglib
No comments:
Post a Comment