parsec-pratt-0.1.1: Pratt Parser combinator for Parsec

Safe HaskellSafe
LanguageHaskell2010

Text.Parsec.PrattParser

Description

Implements a Pratt ("top down operator precendence") Parser as a layer on top of Parsec. See http://javascript.crockford.com/tdop/tdop.html and http://journal.stuffwithstuff.com/2011/03/19/pratt-parsers-expression-parsing-made-easy/ for descriptions of the algorithm.

A note on type usage

In all of the types used in this module, the type parameters are named as follows:

  • s => the stream type which will be parsed (typically String)
  • u => the user state type for the parser (e.g. '()')
  • m => the monad underlying the parser (e.g. Identity)
  • e => the type of the expression returned by the parser
  • o => the type of operators (typically String).
  • t => the type of tokens produced from the stream (not actually referenced here, but required to exist by Parsec)

The following instances are required to exist:

  • Stream s m t
  • Show t
  • Monad m
  • Ord o
  • Show o

Synopsis

Documentation

data OperatorPrecedence Source #

Identifies the precedence and associativity of an operator. Higher numbers bind more strongly to the adjacent terms.

Constructors

LAssoc Int 
RAssoc Int 

data OperatorInfo s u m e o Source #

Provides all the information needed to handle an infix operator, i.e. the operator's symbol (type "o", typically a string), precedence, and its LeftDenotation.

Constructors

OperatorInfo o OperatorPrecedence (LeftDenotation s u m e o) 

data PrefixOperatorInfo s u m e o Source #

Provides all the information needed to handle a prefix operator, i.e. the operator's symbol (type "o", typicall a string), and either a PrefixBinder (for simple operators) or a NullDenotation (for operators that need to perform additional parsing).

Constructors

SimplePrefixOperator o (PrefixBinder s u m e o) 
PrefixParserOperator o (NullDenotation s u m e) 

type PrecedenceParser s u m e = OperatorPrecedence -> ParsecT s u m e Source #

A PrecedenceParser is a function that, given a precedence, parses expressions which contain operators whose precedence is greater than or equal to the specified precedence.

type NullDenotation s u m e = PrecedenceParser s u m e -> ParsecT s u m e Source #

A NullDenotation is a function that generates a parser for terms that do not have a left hand term to bind to. It receives a PrecedenceParser as an argument that can be used to recursively parse an expression.

type PrefixBinder s u m e o = PrefixOperatorInfo s u m e o -> e -> e Source #

a PrefixBinder binds a prefix operator with the expression to its right

type LeftDenotation s u m e o = OperatorInfo s u m e o -> e -> PrecedenceParser s u m e -> ParsecT s u m e Source #

a LeftDenotation is a function for producing a parser that binds to a left hand term. Its arguments are:

  • The OperatorInfo of the operator being parsed
  • The expression for the term on the left
  • A function that can be used to parse additional terms up to a given precedence (which should usually be the precedence of the operator itself).

type ContentStripper s u m a = ParsecT s u m a Source #

type of parser transformers that can be used to remove extraneous text (eg removing whitespace and/or comments) before a useful token occurs

type OperatorParser s u m o = ParsecT s u m o Source #

Type for defining a parser that returns operator symbols.

operatorInfoPrecedence :: OperatorInfo s u m e o -> OperatorPrecedence Source #

Return the precedence of an infix operator

operatorInfoName :: OperatorInfo s u m e o -> o Source #

Return the symbol of an infix operator

prefixOperatorInfoName :: PrefixOperatorInfo s u m e o -> o Source #

Return the symbol of a prefix operator

buildPrattParser :: forall s u m e o t a. Stream s m t => Show t => Monad m => Ord o => Show o => [OperatorInfo s u m e o] -> [PrefixOperatorInfo s u m e o] -> ContentStripper s u m a -> OperatorParser s u m o -> NullDenotation s u m e -> ParsecT s u m e Source #

Builds a Pratt parser for expressions with a given set of operators and parsers for individual components. The arguments are:

  • A list of infix operator descriptions
  • A list of prefix operator descriptions
  • A content stripper (a parser whose return value is ignored, which strips whitespacecommentsanything else that isn't part of the expression
  • An operator parser, which returns symbols as used in the operator descriptions
  • A NullDenotation that parses individual terms and recursively calls back into the parser to bind expressions to them.