This convenience module re-exports from Text.Syntactical.Yard
and Text.Syntactical.Data
everything a typical usage of Syntactical
would need.
- shunt :: Token a => Table a -> [SExpr a] -> Either (Failure a) (SExpr a)
- steps :: Token a => Table a -> [SExpr a] -> IO ()
- data Failure a
- = MissingBefore [[a]] a
- | MissingAfter [a] [a]
- | CantMix (Part a) (Part a)
- | MissingSubBetween a a
- | MissingSubBefore a
- | MissingSubAfter a
- | Ambiguity Ambiguity
- | Unexpected
- data Ambiguity
- showFailure :: Token a => Failure a -> String
- data Op a
- data Associativity
- data Hole
- = SExpression
- | Distfix
- infx :: Associativity -> a -> Op a
- prefx :: a -> Op a
- postfx :: a -> Op a
- closed :: a -> Hole -> a -> Op a
- infx_ :: Associativity -> a -> Op a
- prefx_ :: a -> Op a
- postfx_ :: a -> Op a
- closed_ :: a -> Hole -> a -> Op a
- sexpr :: Op a -> a -> Op a
- distfix :: Op a -> a -> Op a
- arity :: Part a -> Int
- symbol :: Part a -> a
- symbols :: Op a -> [a]
- next :: Part a -> [a]
- previous :: Part a -> [a]
- current :: Part a -> [a]
- data Table a
- buildTable :: [[Op a]] -> Table a
- class Token a where
- data SExpr a
- showSExpr :: Token a => SExpr a -> String
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.
The different failure cases the shunt
function can return.
The showFailure
function can be used to give them a textual
representation.
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 |
Operators
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.
data Associativity Source
Specify the associativity of an infix operator.
The Hole is used to give various behaviours when dealing with internal holes.
SExpression | SExpression means the |
Distfix | Distfix means the |
infx :: Associativity -> a -> Op aSource
Build a infix 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.
Build a prefix operator with the keep property set to False. The precedence is set to 0.
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.
Return the arity of a complete Part. It is an error to call this function on a First or Middle part.
Operator tables
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
The class of the types that can be parsed.
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
The s-expression data type used as input and output of the parser. The type is parametrized by the type of the token.