LParse-0.3.0.0: A continuation-based parser library

Copyright(c) Marcus Völker 2017-2018
LicenseMIT
Maintainermarcus.voelker@rwth-aachen.de
Safe HaskellSafe
LanguageHaskell2010

Text.LParse.Prebuilt

Description

This module contains prebuilt parsers that fulfill a certain job (formerly in Text.LParse.Atomics) and parser transformers that one or more parsers and modify/combine them in a certain way (formerly in Text.LParse.Transformers)

Some of these parsers depend on their input being given in the form of a TokenStream.

Synopsis

Documentation

noop :: Parser r t () Source #

A parser that always succeeds, parses nothing and returns unit

full :: Parser r [t] [t] Source #

A parser that consumes the whole input and returns it unchanged

discard :: Parser r [t] () Source #

A parser that consumes the whole input and discards it, successfully

eoi :: Parser r [t] () Source #

A parser that parses nothing, but only succeeds if the input is empty

tokenParse :: TokenStream s => (t -> a) -> Parser r (s t) a Source #

Extracts the first token from the input and applies the given function to it

tokenReturn :: TokenStream s => Parser r (s a) a Source #

Consumes and returns the first token of the input

consume :: (Eq t, Show (s t), TokenStream s) => s t -> Parser r (s t) () Source #

Succeeds exactly if the input begins with the given sequence. On success, consumes that sequence

consumeReturn :: (Eq t, Show (s t), TokenStream s) => s t -> a -> Parser r (s t) a Source #

Consumes exactly the given input and then returns the given constant result

consumeSingle :: (Eq t, Show t, TokenStream s) => t -> Parser r (s t) () Source #

Succeeds exactly if the input begins with the given token. On success, consumes that token

consumeSReturn :: (Eq t, Show t, TokenStream s) => t -> a -> Parser r (s t) a Source #

Consumes exactly the given token and then returns the given constant result

digit :: Parser r String Integer Source #

Extracts the first digit and returns it

letter :: Parser r String Char Source #

Extracts the first digit and returns it

word :: Parser r String String Source #

Extracts the first word (i.e. contiguous string of letters) from the input and returns it

integer :: Parser r String Integer Source #

Extracts the first integer (i.e. contiguous string of digits) from the input and returns it

sInteger :: Parser r String Integer Source #

Extracts the first signed integer (i.e. contiguous string of digits) from the input and returns it

peek :: TokenStream s => (t -> Bool) -> String -> Parser r (s t) () Source #

Succeeds if the first token matches the given function, without consuming it

success :: (t -> (a, t)) -> Parser r t a Source #

A parser that always succeeds with the given function

bDigit :: Integer -> Parser r Integer Integer Source #

Parses an integer by removing a single digit in the given base from it. Zero is considered to have no digits

bDigits :: Integer -> Parser r Integer [Integer] Source #

Parses an integer by removing a single digit in the given base from it. Zero is considered to have no digits

(<<) :: Monad m => m a -> m b -> m a Source #

Executes components in the same order as (>>), but returning the first rather than the second monad. Note that a >> b /= b << a

cParse :: (t -> Bool) -> Parser r t a -> String -> Parser r t a Source #

Takes a condition the parser's input has to fulfil in order for the parser to succeed

nParse :: (TokenStream s, Eq (s t)) => (t -> Bool) -> Parser r (s t) a -> String -> Parser r (s t) a Source #

Takes condition the next token has to fulfil in order for the parser to succeed

pParse :: (t -> t) -> Parser r t a -> Parser r t a Source #

Transforms the input before applying the parser

sepSome :: Parser r t () -> Parser r t a -> Parser r t [a] Source #

Takes a parser that consumes separators and a parser that consumes the desired data and returns a non-empty list of desired data (separated by the separator in source) For example: sepSome (consume " ") word applied to "a banana is tasty" returns ["a","banana","is","tasty"]

sepMany :: Parser r t () -> Parser r t a -> Parser r t [a] Source #

Same as sepSome, but allows empty lists

skip :: (Eq t, TokenStream s) => [t] -> Parser r (s t) a -> Parser r (s t) a Source #

Removes all tokens from the given list from the input

skipBy :: TokenStream s => (t -> Bool) -> Parser r (s t) a -> Parser r (s t) a Source #

Same as skip, but with a custom comparator

skipWhitespace :: Parser r String a -> Parser r String a Source #

Skips standard whitespace characters from a String input

replace :: TokenStream s => (t -> t) -> Parser r (s t) a -> Parser r (s t) a Source #

Replaces the first token by applying the given function

try :: Parser r t a -> Parser r t (Maybe a) Source #

Tries to run the given parser, giving back Just result or Nothing

surround :: (Eq t, Show t, TokenStream s) => [t] -> Parser r (s t) a -> Parser r (s t) a Source #

Parses a character before and a character after the given parser, useful for parentheses