parsley-2.0.0.1: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilitystable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Parsley.Precedence

Description

This module exposes the required machinery for parsing expressions given by a precedence table. Unlike those found in parser-combinators or parsec, this implementation allows the precedence layers to change type in the table. This implementation is based off of Design Patterns for Parser Combinators (Willis and Wu 21).

Since: 0.1.0.0

Synopsis

Main Precedence Combinators

Compared to using chain combinators to construct parsers for expression grammars, precedence combinators provide a light-weight and convenient representation of a precedence table. In parsley these take two forms: a more traditional version called precHomo which takes a list of precedence levels which are all of the same, monolithic, type; and a heterogeneous version called precedence.

In Design Patterns for Parser Combinators it is mentioned that the homogeneous approach to encoding precedence tables can inadvertently misrepresent the grammar: say by changing left-associative operators into right-associative ones. When the grammar doesn't specify associativities, then precHomo is perfectly appropriate, as it becomes an implementation decision. Otherwise, precedence uses a heterogeneous list to form a precedence table, allowing each layer of operators to form part of a different datatype. By encoding the resulting AST as a hierarchy of independent datatypes for each grammar rule, the precedence table can be made to be very strict: reordering levels or switching their associativities will fail to compile!

precedence :: Prec a -> Parser a Source #

This combinator will construct and expression parser will provided with a table of precedence.

Since: 2.0.0.0

precHomo Source #

Arguments

:: Parser a

The root atom of the precedence hierarchy

-> [Op a a]

Each layer laid out strongest-to-weakest binding.

-> Parser a 

A simplified version of precedence that does not use the heterogeneous list Prec, but instead requires all layers of the table to have the same type. The list encodes the precedence in strongest-to-weakest layout.

Since: 2.0.0.0

Operator Fixity

data Fixity a b sig where Source #

Denotes the fixity of a given level in a precedence table. The type parameter sig encodes the types of the operators on this level, in a heterogeneous fashion.

Since: 2.0.0.0

Constructors

InfixL :: Fixity a b (b -> a -> b)

Denotes a left-associative binary operator.

InfixR :: Fixity a b (a -> b -> b)

Denotes a right-associative binary operator.

InfixN :: Fixity a b (a -> a -> b)

Denotes a non-associative binary operator.

Prefix :: Fixity a b (b -> b)

Denotes a prefix unary operator.

Postfix :: Fixity a b (b -> b)

Denotes a postfix unary operator.

Level Construction

By combining a Fixity with a Parser which can read the operators at a given level, a new level can be created, ready to add to the table. To provide uniformity and safety, the Fixity type exposes a sig type that expresses the shape of operators that match it. The Op datatype, which is not constructed directly, ties the operators to this signature using existentials.

There are three ways to create a value of type Op: ops, sops, and gops. These functions represent different degrees of relations between this layer of the table, and the one that comes below:

  • ops says that the level below is the same type as this one, in other words the classic a -> a -> a type for binary operators.
  • sops is stronger, and says that the level below must be a sub-type of this one (see Subtype). This means that there is a known canonical embedding from one layer into the other, called an upcast.
  • gops is the most general, and says that the level below is related to this one by some more complex transformation than the canonical sub-type embedding. Any arbitrary function from underlying -> this can be provided to this level to handle the translation.

data Op a b Source #

Packages together a level of a precedence table, by associating a Fixity with the operators that match that specific signature converting from one layer of type a to a new layer of type b. See ops, sops, and gops for how to construct them.

Since: 2.0.0.0

class GOps rep where Source #

This typeclass is used to allow abstraction of the representation of user-level functions. See the instances for information on what these representations are.

Since: 2.0.0.0

Methods

gops :: Fixity a b sig -> [Parser sig] -> rep (a -> b) -> Op a b Source #

Sometimes, the relationship between two levels of a heterogeneous precedence hierarchy is non-trivial. By using gops, the conversion function can be used to adapt one layer into the type of the next.

Since: 2.0.0.0

Instances

Instances details
GOps Defunc Source #

This is used to allow defunctionalised versions of many standard Haskell functions to be used directly as an argument to relevant combinators.

Since: 2.0.0.0

Instance details

Defined in Parsley.Precedence

Methods

gops :: Fixity a b sig -> [Parser sig] -> Defunc (a -> b) -> Op a b Source #

x ~ WQ => GOps x Source #

This is the default representation used for user-level functions and values: plain old code.

Since: 2.0.0.0

Instance details

Defined in Parsley.Precedence

Methods

gops :: Fixity a b sig -> [Parser sig] -> x (a -> b) -> Op a b Source #

sops :: Subtype a b => Fixity a b sig -> [Parser sig] -> Op a b Source #

When two levels of a precedence hierarchy are in a subtyping relation, the conversion between the two can be trivially provided as the upcast function.

Since: 2.0.0.0

ops :: Fixity a a sig -> [Parser sig] -> Op a a Source #

When two levels in a precedence hierarchy are the same type, they are trivially embedded using the identity function.

Since: 2.0.0.0

Level Combining

Independently, Ops are meaningless: they must be combined together to form a table to be useful. The Prec datatype encodes the structure linking together each Op level in turn.

The base case for the table is called Atom, which takes a parser for the root of the table: think numbers, variables, bracketed expressions, and the like.

The Level constructor is used to add layers on top of the growing table. It's not designed to be used directly, which would be clunky, instead use the (>+) and (+<) operators. These operators are sugar for Level, but allow freedom over which way round the table should be expressed: use (>+) to build the table from strongest- to weakest-binding (with the atom at the front); use (+<) to build the table from weakest- to strongest-binding (with the atom at the end). The direction the table should be built in is purely stylistic.

data Prec a where Source #

A heterogeneous list that represents a precedence table so that Prec a produces values of type a.

Since: 2.0.0.0

Constructors

Level :: Prec a -> Op a b -> Prec b

A Level of the table, containing the sub-level and the operators. See (>+) and (+<).

Atom :: Parser a -> Prec a

The terminal atom in the table.

(>+) :: Prec a -> Op a b -> Prec b infixl 5 Source #

Sugar for the Level constructor, this operator - along with its sibling - is hungry and greedy: it eats the levels with the higher precedence: in lvls >+ lvl, lvl is lower precedence than lvls.

Since: 2.0.0.0

(+<) :: Op a b -> Prec a -> Prec b infixr 5 Source #

Sugar for the Level constructor, this operator - along with its sibling - is hungry and greedy: it eats the levels with the higher precedence: in lvl +< lvls, lvl is lower precedence than lvls.

Since: 2.0.0.0

Subtype Relation

class Subtype sub sup where Source #

Encodes a subtyping relationship between two types sub and sup. This allows for the conversion or embedding of one type into the other, as well as their extraction.

It should be the case that:

fmap upcast . downcast = Just
downcast . upcast = Just

Since: 2.0.0.0

Methods

upcast :: sub -> sup Source #

Casts a value of the subtype into one of the supertype, likely by wrapping it in some constructor

downcast :: sup -> Maybe sub Source #

Attempts to extract a value of a subtype from a supertype