syntactical-0.1: Distfix expression parsing library

Text.Syntactical

Contents

Description

This convenience module re-exports from Text.Syntactical.Yard and Text.Syntactical.Data everything a typical usage of Syntactical would need.

Synopsis

Parsing

shunt :: Token a => Table a -> [SExpr a] -> Either (Failure a) (SExpr a)Source

Parse a list of s-expressions according to an operator table. Usually the s-expressions will be the result of applying Atom to each token.

steps :: Token a => Table a -> [SExpr a] -> IO ()Source

Similar to the shunt function but print the steps performed by the modified shunting yard algorithm. This function is useful to understand (and debug) the modified shunting-yard algorithm.

data Failure a Source

The different failure cases the shunt function can return. The showFailure function can be used to give them a textual representation.

Constructors

MissingBefore [[a]] a

missing parts before part

MissingAfter [a] [a]

missing parts after parts

CantMix (Part a) (Part a)

can't mix two operators

MissingSubBetween a a

missing sub-expression between parts

MissingSubBefore a

missing sub-expression before string

MissingSubAfter a

missing sub-expression after string

Ambiguity Ambiguity

a part is used ambiguously in multiple operators

Unexpected

this is a bug if it happens

Instances

Eq a => Eq (Failure a) 
Show a => Show (Failure a) 

showFailure :: Token a => Failure a -> StringSource

Give a textual representation of a Failure.

Operators

data Op a Source

The operator representation, parametrized by the token type. It allows infix, prefix, postfix, and closed operators, with possibly multiple internal holes. Different holes are possible, to drive the parse in specific ways.

Instances

Eq a => Eq (Op a) 
Show a => Show (Op a) 

data Associativity Source

Specify the associativity of an infix operator.

data Hole Source

The Hole is used to give various behaviours when dealing with internal holes.

Constructors

SExpression

SExpression means the content of the hole should be parsed as an s-expression. The resulting value is a List. This means the hole can be empty or contain one or more sub-expression(s).

Distfix

Distfix means the content of the hole should be parsed as a distfix expression. In this case feeding an empty hole will generate a parse error.

Instances

infx :: Associativity -> a -> Op aSource

Build a infix operator. The precedence is set to 0.

prefx :: a -> Op aSource

Build a prefix operator. The precedence is set to 0.

postfx :: a -> Op aSource

Build a postfix operator. The precedence is set to 0.

closed :: a -> Hole -> a -> Op aSource

Build a closed operator. The precedence is set to 0.

infx_ :: Associativity -> a -> Op aSource

Build a infix operator with the keep property set to False. The precedence is set to 0.

prefx_ :: a -> Op aSource

Build a prefix operator with the keep property set to False. The precedence is set to 0.

postfx_ :: a -> Op aSource

Build a postfix operator with the keep property set to False. The precedence is set to 0.

closed_ :: a -> Hole -> a -> Op aSource

Build a closed operator with the keep property set to False. The precedence is set to 0.

sexpr :: Op a -> a -> Op aSource

Add a new part separated by an SExpression hole to the right of an operator.

distfix :: Op a -> a -> Op aSource

Add a new part separated by a Distfix hole to the right of an operator.

arity :: Part a -> IntSource

Return the arity of a complete Part. It is an error to call this function on a First or Middle part.

symbol :: Part a -> aSource

Return the token of a given Part.

symbols :: Op a -> [a]Source

Return all the tokens of a given operator.

next :: Part a -> [a]Source

Return the possible tokens continuing the given part.

previous :: Part a -> [a]Source

Return the tokens preceding the given part.

current :: Part a -> [a]Source

Return the tokens of the given part.

Operator tables

data Table a Source

The type of the operator table.

buildTable :: [[Op a]] -> Table aSource

buildTable constructs an operator table that can be used with the shunt function. Operators are given in decreasing precedence order.

Tokens

class Token a whereSource

The class of the types that can be parsed.

Methods

toString :: a -> StringSource

convert to a string (for showing purpose)

operator :: Op a -> [SExpr a] -> SExpr aSource

create an output node from an operator and its arguments

consider :: a -> a -> BoolSource

test if two tokens are the same (used to find match from the operator table). A default definition that compares the result of toString is provided.

S-Expressions

data SExpr a Source

The s-expression data type used as input and output of the parser. The type is parametrized by the type of the token.

Constructors

List [SExpr a] 
Atom a 

Instances

Eq a => Eq (SExpr a) 
Show a => Show (SExpr a) 

showSExpr :: Token a => SExpr a -> StringSource

Show an s-expression using nested angle brackets.