Stability | provisional |
---|---|
Maintainer | iavor.diatchki@gmail.com |
Safe Haskell | Safe-Infered |
The basics of the Parsimony library.
- data Parser t a
- parse :: Parser t a -> t -> Either ParseError a
- parseSource :: Parser t a -> SourceName -> t -> Either ParseError a
- runParser :: Parser t a -> PrimParser t a
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
- try :: Parser t a -> Parser t a
- choice :: [Parser t a] -> Parser t a
- many :: Parser t a -> Parser t [a]
- many1 :: Parser t a -> Parser t [a]
- skipMany :: Parser t a -> Parser t ()
- skipMany1 :: Parser t a -> Parser t ()
- match :: Eq a => (a -> String) -> [a] -> Parser t a -> Parser t ()
- sepBy :: Parser t a -> Parser t sep -> Parser t [a]
- sepBy1 :: Parser t a -> Parser t sep -> Parser t [a]
- endBy1, endBy :: Parser t a -> Parser t sep -> Parser t [a]
- sepEndBy :: Parser t a -> Parser t sep -> Parser t [a]
- sepEndBy1 :: Parser t a -> Parser t sep -> Parser t [a]
- manyTill :: Parser t a -> Parser t end -> Parser t [a]
- count :: Int -> Parser t a -> Parser t [a]
- foldMany :: (b -> a -> b) -> b -> Parser t a -> Parser t b
- option :: a -> Parser t a -> Parser t a
- optional :: Alternative f => f a -> f (Maybe a)
- (<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b
- (<*) :: Applicative f => forall a b. f a -> f b -> f a
- (*>) :: Applicative f => forall a b. f a -> f b -> f b
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<$) :: Functor f => forall a b. a -> f b -> f a
- pure :: Applicative f => forall a. a -> f a
- between :: Parser t open -> Parser t close -> Parser t a -> Parser t a
- skip :: Parser t a -> Parser t ()
- eof :: Stream s t => Parser s ()
- notFollowedBy :: Show a => Parser t a -> Parser t ()
- notFollowedBy' :: (a -> String) -> Parser t a -> Parser t ()
- lookAhead :: Parser t a -> Parser t a
- anyToken :: Stream s t => Parser s t
- data ParseError
- errorPos :: ParseError -> SourcePos
- (<?>) :: Parser t a -> String -> Parser t a
- unexpected :: String -> Parser t a
- empty :: Alternative f => forall a. f a
- parseError :: (SourcePos -> ParseError) -> Parser t a
- labels :: Parser t a -> [String] -> Parser t a
- data State t = State {
- stateInput :: !t
- statePos :: !SourcePos
- setState :: State t -> Parser t ()
- updateState :: (State s -> State s) -> Parser s ()
- mapState :: (State big -> (State small, extra)) -> (State small -> extra -> State big) -> Parser small a -> Parser big a
- getInput :: Parser t t
- setInput :: t -> Parser t ()
- updateInput :: (t -> t) -> Parser t ()
- data SourcePos
- type SourceName = String
- type Line = Int
- type Column = Int
- getPosition :: Parser t SourcePos
- setPosition :: SourcePos -> Parser t ()
- updatePosition :: (SourcePos -> SourcePos) -> Parser t ()
- type PrimParser s a = State s -> Reply s a
- data Reply s a
- = Ok !a !(State s)
- | Error !ParseError
- primParser :: PrimParser t a -> Parser t a
Basic Types
A parser constructing values of type a
, with an input
buffer of type t
.
Monad (Parser t) | |
Functor (Parser t) | |
MonadPlus (Parser t) | |
Applicative (Parser t) | |
Alternative (Parser t) |
Applying Parsers
:: Parser t a | The parser to apply |
-> t | The input |
-> Either ParseError a |
Apply a parser to the given input.
:: Parser t a | The parser to apply |
-> SourceName | A name for the input (used in errors) |
-> t | The input |
-> Either ParseError a |
Apply a parser to the given named input.
runParser :: Parser t a -> PrimParser t aSource
Convert a parser into a PrimParser
.
Choices
(<|>) :: Alternative f => forall a. f a -> f a -> f a
An associative binary operation
try :: Parser t a -> Parser t aSource
Allow a parser to back-track. The resulting parser behaves like the input parser unless it fails. In that case, we backtrack without consuming any input. Because we may have to back-track, we keep a hold of the parser input so over-use of this function may result in memory leaks.
choice :: [Parser t a] -> Parser t aSource
The resulting parser behaves like one of the parsers in the list. The chosen parser is the first one that (i) consumes some input, or (ii) succeeds with a result.
Repetition
many :: Parser t a -> Parser t [a]Source
Apply a parser repeatedly, and collect the results in a list.
many1 :: Parser t a -> Parser t [a]Source
Apply a parser repeatedly, and collect the results in a list. The resulting list is guaranteed to be at leats of length one.
skipMany :: Parser t a -> Parser t ()Source
Apply a parser repeatedly, ignoring the results. We stop when an application of the parser fails without consuming any input. If the parser fails after it has consumed some input, then the repeated parser will also fail.
skipMany1 :: Parser t a -> Parser t ()Source
Skip at leats one occurance of input recognized by the parser.
match :: Eq a => (a -> String) -> [a] -> Parser t a -> Parser t ()Source
Produces a parser that succeeds if it can extract the list of values specified by the list. The function argument specifies how to show the expectations in error messages.
manyTill :: Parser t a -> Parser t end -> Parser t [a]Source
Parse a list of values recognized by the given parser. The sequence of values should be terminated by a pattern recognized by the terminator patser. The terminator is tried before the value pattern, so if there is overlap between the two, the terminator is recognized.
foldMany :: (b -> a -> b) -> b -> Parser t a -> Parser t bSource
Apply a parser repeatedly, combining the results with the
given functions. This function is similar to the strict foldl
.
We stop when an application of the parser fails without consuming any
input. If the parser fails after it has consumed some input, then
the repeated parser will also fail.
Optoinal content
option :: a -> Parser t a -> Parser t aSource
Behaves like the parameter parser, unless it fails without consuming any input. In that case we succeed with the given value.
optional :: Alternative f => f a -> f (Maybe a)
One or none.
Delimeters and Combinators
(<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b
Sequential application.
(<*) :: Applicative f => forall a b. f a -> f b -> f a
Sequence actions, discarding the value of the second argument.
(*>) :: Applicative f => forall a b. f a -> f b -> f b
Sequence actions, discarding the value of the first argument.
pure :: Applicative f => forall a. a -> f a
Lift a value.
eof :: Stream s t => Parser s ()Source
Matches the end of the input (i.e., when there are no more tokens to extract).
Look Ahead
notFollowedBy :: Show a => Parser t a -> Parser t ()Source
Succeeds if the given parser fails.
Uses the Show
instance of the result type in error messages.
notFollowedBy' :: (a -> String) -> Parser t a -> Parser t ()Source
Succeeds if the given parser fails. The function is used to display the result in error messages.
anyToken :: Stream s t => Parser s tSource
Matches any token. Fails if there are no more tokens left.
Errors
(<?>) :: Parser t a -> String -> Parser t aSource
Specify the name to be used if the given parser fails.
unexpected :: String -> Parser t aSource
empty :: Alternative f => forall a. f a
The identity of <|>
parseError :: (SourcePos -> ParseError) -> Parser t aSource
Fail with the given parser error without consuming any input. The error is applied to the current source position.
labels :: Parser t a -> [String] -> Parser t aSource
The resulting parser behaves like the input parser, except that in case of failure we use the given expectation messages.
Parser State
The parser state.
State | |
|
updateState :: (State s -> State s) -> Parser s ()Source
Modify the current parser state. Returns the old state. Does not consume input.
mapState :: (State big -> (State small, extra)) -> (State small -> extra -> State big) -> Parser small a -> Parser big aSource
Change the input stream of a parser. This is useful for extending the input stream with extra information. The first function splits the extended state into a state suitable for use by the given parser and some additional information. The second function combines the extra infomration of the original state with the new partial state, to compute a new extended state.
updateInput :: (t -> t) -> Parser t ()Source
type SourceName = StringSource
setPosition :: SourcePos -> Parser t ()Source
Primitive Parsers
type PrimParser s a = State s -> Reply s aSource
primParser :: PrimParser t a -> Parser t aSource
Define a primitive parser. Consumes input on success.