curry-base-1.1.1: Functions for manipulating Curry programs

Copyright(c) 1999-2004 Wolfgang Lux
2016 Jan Tikovsky
LicenseBSD-3-clause
Maintainerbjp@informatik.uni-kiel.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Curry.Base.LLParseComb

Contents

Description

The parsing combinators implemented in this module are based on the LL(1) parsing combinators developed by Swierstra and Duponcheel. They have been adapted to using continuation passing style in order to work with the lexing combinators described in the previous section. In addition, the facilities for error correction are omitted in this implementation.

The two functions applyParser and prefixParser use the specified parser for parsing a string. When applyParser is used, an error is reported if the parser does not consume the whole string, whereas prefixParser discards the rest of the input string in this case.

Synopsis

Data types

data Parser a s b Source #

CPS-Parser type

Instances
Symbol s => Functor (Parser a s) Source # 
Instance details

Defined in Curry.Base.LLParseComb

Methods

fmap :: (a0 -> b) -> Parser a s a0 -> Parser a s b #

(<$) :: a0 -> Parser a s b -> Parser a s a0 #

Symbol s => Applicative (Parser a s) Source # 
Instance details

Defined in Curry.Base.LLParseComb

Methods

pure :: a0 -> Parser a s a0 #

(<*>) :: Parser a s (a0 -> b) -> Parser a s a0 -> Parser a s b #

liftA2 :: (a0 -> b -> c) -> Parser a s a0 -> Parser a s b -> Parser a s c #

(*>) :: Parser a s a0 -> Parser a s b -> Parser a s b #

(<*) :: Parser a s a0 -> Parser a s b -> Parser a s a0 #

Show s => Show (Parser a s b) Source # 
Instance details

Defined in Curry.Base.LLParseComb

Methods

showsPrec :: Int -> Parser a s b -> ShowS #

show :: Parser a s b -> String #

showList :: [Parser a s b] -> ShowS #

Parser application

fullParser :: Symbol s => Parser a s a -> Lexer s a -> FilePath -> String -> CYM a Source #

Apply a parser and lexer to a String, whereas the FilePath is used to identify the origin of the String in case of parsing errors.

prefixParser :: Symbol s => Parser a s a -> Lexer s a -> FilePath -> String -> CYM a Source #

Apply a parser and lexer to parse the beginning of a String. The FilePath is used to identify the origin of the String in case of parsing errors.

Basic parsers

position :: Parser a s Position Source #

Return the current position without consuming the input

succeed :: b -> Parser a s b Source #

Always succeeding parser

failure :: String -> Parser a s b Source #

Always failing parser with a given message

symbol :: s -> Parser a s s Source #

Create a parser accepting the given Symbol

parser combinators

(<?>) :: Symbol s => Parser a s b -> String -> Parser a s b infixl 2 Source #

Behave like the given parser, but use the given String as the error message if the parser fails

(<|>) :: Symbol s => Parser a s b -> Parser a s b -> Parser a s b infixl 3 Source #

Deterministic choice between two parsers. The appropriate parser is chosen based on the next Symbol

(<|?>) :: Symbol s => Parser a s b -> Parser a s b -> Parser a s b infixl 3 Source #

Non-deterministic choice between two parsers.

The other parsing combinators require that the grammar being parsed is LL(1). In some cases it may be difficult or even impossible to transform a grammar into LL(1) form. As a remedy, we include a non-deterministic version of the choice combinator in addition to the deterministic combinator adapted from the paper. For every symbol from the intersection of the parser's first sets, the combinator '(|?)' applies both parsing functions to the input stream and uses that one which processes the longer prefix of the input stream irrespective of whether it succeeds or fails. If both functions recognize the same prefix, we choose the one that succeeds and report an ambiguous parse error if both succeed.

(<*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 4 #

Sequential application.

A few functors support an implementation of <*> that is more efficient than the default one.

(<\>) :: Symbol s => Parser a s b -> Parser a s c -> Parser a s b infixl 5 Source #

Restrict the first parser by the first Symbols of the second

(<\\>) :: Symbol s => Parser a s b -> [s] -> Parser a s b infixl 5 Source #

Restrict a parser by a list of first Symbols

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

 ($)  ::              (a -> b) ->   a ->   b
(<$>) :: Functor f => (a -> b) -> f a -> f b

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Expand

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

(<$->) :: Symbol s => a -> Parser b s c -> Parser b s a infixl 4 Source #

Replace the result of the parser with the first argument

(<*->) :: Symbol s => Parser a s b -> Parser a s c -> Parser a s b infixl 4 Source #

Apply two parsers in sequence, but return only the result of the first parser

(<-*>) :: Symbol s => Parser a s b -> Parser a s c -> Parser a s c infixl 4 Source #

Apply two parsers in sequence, but return only the result of the second parser

(<**>) :: Symbol s => Parser a s b -> Parser a s (b -> c) -> Parser a s c infixl 4 Source #

Apply the parsers in sequence and apply the result function of the second parse to the result of the first

(<??>) :: Symbol s => Parser a s b -> Parser a s (b -> b) -> Parser a s b infixl 4 Source #

Same as (**), but only applies the function if the second parser succeeded.

(<.>) :: Symbol s => Parser a s (b -> c) -> Parser a s (c -> d) -> Parser a s (b -> d) infixl 4 Source #

Flipped function composition on parsers

opt :: Symbol s => Parser a s b -> b -> Parser a s b infixl 2 Source #

Try the first parser, but return the second argument if it didn't succeed

choice :: Symbol s => [Parser a s b] -> Parser a s b Source #

Choose the first succeeding parser from a non-empty list of parsers

flag :: Symbol s => Parser a s b -> Parser a s Bool Source #

Try to apply a given parser and return a boolean value if the parser succeeded.

optional :: Symbol s => Parser a s b -> Parser a s () Source #

Try to apply a parser but forget if it succeeded

option :: Symbol s => Parser a s b -> Parser a s (Maybe b) Source #

Try to apply a parser and return its result in a Maybe type

many :: Symbol s => Parser a s b -> Parser a s [b] Source #

Repeatedly apply a parser for 0 or more occurences

many1 :: Symbol s => Parser a s b -> Parser a s [b] Source #

Repeatedly apply a parser for 1 or more occurences

sepBy :: Symbol s => Parser a s b -> Parser a s c -> Parser a s [b] Source #

Parse a list with is separated by a seperator

sepBy1 :: Symbol s => Parser a s b -> Parser a s c -> Parser a s [b] Source #

Parse a non-empty list with is separated by a seperator

sepBySp :: Symbol s => Parser a s b -> Parser a s c -> Parser a s ([b], [Span]) Source #

Parse a list with is separated by a seperator

sepBy1Sp :: Symbol s => Parser a s b -> Parser a s c -> Parser a s ([b], [Span]) Source #

chainr :: Symbol s => Parser a s b -> Parser a s (b -> b -> b) -> b -> Parser a s b Source #

chainr p op x parses zero or more occurrences of p, separated by op. Returns a value produced by a *right* associative application of all functions returned by op. If there are no occurrences of p, x is returned.

chainr1 :: Symbol s => Parser a s b -> Parser a s (b -> b -> b) -> Parser a s b Source #

Like chainr, but parses one or more occurrences of p.

chainl :: Symbol s => Parser a s b -> Parser a s (b -> b -> b) -> b -> Parser a s b Source #

chainr p op x parses zero or more occurrences of p, separated by op. Returns a value produced by a *left* associative application of all functions returned by op. If there are no occurrences of p, x is returned.

chainl1 :: Symbol s => Parser a s b -> Parser a s (b -> b -> b) -> Parser a s b Source #

Like chainl, but parses one or more occurrences of p.

between :: Symbol s => Parser a s b -> Parser a s c -> Parser a s b -> Parser a s c Source #

Parse an expression between an opening and a closing part.

ops :: Symbol s => [(s, b)] -> Parser a s b Source #

Parse one of the given operators

Layout combinators

layoutOn :: Symbol s => Parser a s b Source #

Add a new scope for layout

layoutOff :: Symbol s => Parser a s b Source #

Disable layout-awareness for the following

layoutEnd :: Symbol s => Parser a s b Source #

End the current layout scope (or re-enable layout-awareness if it is currently disabled