Copyright | Bryan O'Sullivan 2007-2015 |
---|---|
License | BSD3 |
Maintainer | bos@serpentine.com |
Stability | experimental |
Portability | unknown |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Simple, efficient, character-oriented combinator parsing for
ByteString
strings, loosely based on the Parsec library.
Synopsis
- type Parser = Parser ByteString
- type Result = IResult ByteString
- data IResult i r
- compareResults :: (Eq i, Eq r) => IResult i r -> IResult i r -> Maybe Bool
- parse :: Parser a -> ByteString -> Result a
- feed :: Monoid i => IResult i r -> i -> IResult i r
- parseOnly :: Parser a -> ByteString -> Either String a
- parseWith :: Monad m => m ByteString -> Parser a -> ByteString -> m (Result a)
- parseTest :: Show a => Parser a -> ByteString -> IO ()
- maybeResult :: Result r -> Maybe r
- eitherResult :: Result r -> Either String r
- char :: Char -> Parser Char
- char8 :: Char -> Parser Word8
- anyChar :: Parser Char
- notChar :: Char -> Parser Char
- satisfy :: (Char -> Bool) -> Parser Char
- peekChar :: Parser (Maybe Char)
- peekChar' :: Parser Char
- digit :: Parser Char
- letter_iso8859_15 :: Parser Char
- letter_ascii :: Parser Char
- space :: Parser Char
- isDigit :: Char -> Bool
- isDigit_w8 :: Word8 -> Bool
- isAlpha_iso8859_15 :: Char -> Bool
- isAlpha_ascii :: Char -> Bool
- isSpace :: Char -> Bool
- isSpace_w8 :: Word8 -> Bool
- inClass :: String -> Char -> Bool
- notInClass :: String -> Char -> Bool
- string :: ByteString -> Parser ByteString
- stringCI :: ByteString -> Parser ByteString
- skipSpace :: Parser ()
- skipWhile :: (Char -> Bool) -> Parser ()
- take :: Int -> Parser ByteString
- scan :: s -> (s -> Char -> Maybe s) -> Parser ByteString
- takeWhile :: (Char -> Bool) -> Parser ByteString
- takeWhile1 :: (Char -> Bool) -> Parser ByteString
- takeTill :: (Char -> Bool) -> Parser ByteString
- (.*>) :: ByteString -> Parser a -> Parser a
- (<*.) :: Parser a -> ByteString -> Parser a
- takeByteString :: Parser ByteString
- takeLazyByteString :: Parser ByteString
- endOfLine :: Parser ()
- isEndOfLine :: Word8 -> Bool
- isHorizontalSpace :: Word8 -> Bool
- decimal :: Integral a => Parser a
- hexadecimal :: (Integral a, Bits a) => Parser a
- signed :: Num a => Parser a -> Parser a
- double :: Parser Double
- data Number
- number :: Parser Number
- rational :: Fractional a => Parser a
- scientific :: Parser Scientific
- try :: Parser i a -> Parser i a
- (<?>) :: Parser i a -> String -> Parser i a
- choice :: Alternative f => [f a] -> f a
- count :: Monad m => Int -> m a -> m [a]
- option :: Alternative f => a -> f a -> f a
- many' :: MonadPlus m => m a -> m [a]
- many1 :: Alternative f => f a -> f [a]
- many1' :: MonadPlus m => m a -> m [a]
- manyTill :: Alternative f => f a -> f b -> f [a]
- manyTill' :: MonadPlus m => m a -> m b -> m [a]
- sepBy :: Alternative f => f a -> f s -> f [a]
- sepBy' :: MonadPlus m => m a -> m s -> m [a]
- sepBy1 :: Alternative f => f a -> f s -> f [a]
- sepBy1' :: MonadPlus m => m a -> m s -> m [a]
- skipMany :: Alternative f => f a -> f ()
- skipMany1 :: Alternative f => f a -> f ()
- eitherP :: Alternative f => f a -> f b -> f (Either a b)
- match :: Parser a -> Parser (ByteString, a)
- endOfInput :: forall t. Chunk t => Parser t ()
- atEnd :: Chunk t => Parser t Bool
Character encodings
This module is intended for parsing text that is represented using an 8-bit character set, e.g. ASCII or ISO-8859-15. It does not make any attempt to deal with character encodings, multibyte characters, or wide characters. In particular, all attempts to use characters above code point U+00FF will give wrong answers.
Code points below U+0100 are simply translated to and from their
numeric values, so e.g. the code point U+00A4 becomes the byte
0xA4
(which is the Euro symbol in ISO-8859-15, but the generic
currency sign in ISO-8859-1). Haskell Char
values above U+00FF
are truncated, so e.g. U+1D6B7 is truncated to the byte 0xB7
.
Parser types
type Parser = Parser ByteString Source #
type Result = IResult ByteString Source #
The result of a parse. This is parameterised over the type i
of string that was processed.
This type is an instance of Functor
, where fmap
transforms the
value in a Done
result.
Fail i [String] String | The parse failed. The |
Partial (i -> IResult i r) | Supply this continuation with more input so that the parser can resume. To indicate that no more input is available, pass an empty string to the continuation. Note: if you get a |
Done i r | The parse succeeded. The |
Running parsers
feed :: Monoid i => IResult i r -> i -> IResult i r Source #
If a parser has returned a Partial
result, supply it with more
input.
parseOnly :: Parser a -> ByteString -> Either String a Source #
Run a parser that cannot be resupplied via a Partial
result.
This function does not force a parser to consume all of its input. Instead, any residual input will be discarded. To force a parser to consume all of its input, use something like this:
parseOnly
(myParser<*
endOfInput
)
:: Monad m | |
=> m ByteString | An action that will be executed to provide the parser
with more input, if necessary. The action must return an
|
-> Parser a | |
-> ByteString | Initial input for the parser. |
-> m (Result a) |
Run a parser with an initial input string, and a monadic action that can supply more input if needed.
parseTest :: Show a => Parser a -> ByteString -> IO () Source #
Run a parser and print its result to standard output.
Result conversion
maybeResult :: Result r -> Maybe r Source #
Parsing individual characters
satisfy :: (Char -> Bool) -> Parser Char Source #
The parser satisfy p
succeeds for any byte for which the
predicate p
returns True
. Returns the byte that is actually
parsed.
digit = satisfy isDigit where isDigit c = c >= '0' && c <= '9'
Lookahead
peekChar :: Parser (Maybe Char) Source #
Match any character, to perform lookahead. Returns Nothing
if
end of input has been reached. Does not consume any input.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
peekChar' :: Parser Char Source #
Match any character, to perform lookahead. Does not consume any input, but will fail if end of input has been reached.
Special character parsers
letter_iso8859_15 :: Parser Char Source #
Match a letter, in the ISO-8859-15 encoding.
letter_ascii :: Parser Char Source #
Match a letter, in the ASCII encoding.
Parse a space character.
Note: This parser only gives correct answers for the ASCII encoding. For instance, it does not recognise U+00A0 (non-breaking space) as a space character, even though it is a valid ISO-8859-15 byte.
Fast predicates
isDigit_w8 :: Word8 -> Bool Source #
A fast digit predicate.
isAlpha_iso8859_15 :: Char -> Bool Source #
A fast alphabetic predicate for the ISO-8859-15 encoding
Note: For all character encodings other than ISO-8859-15, and almost all Unicode code points above U+00A3, this predicate gives wrong answers.
isAlpha_ascii :: Char -> Bool Source #
A fast alphabetic predicate for the ASCII encoding
Note: For all character encodings other than ASCII, and almost all Unicode code points above U+007F, this predicate gives wrong answers.
isSpace :: Char -> Bool Source #
Fast predicate for matching ASCII space characters.
Note: This predicate only gives correct answers for the ASCII
encoding. For instance, it does not recognise U+00A0 (non-breaking
space) as a space character, even though it is a valid ISO-8859-15
byte. For a Unicode-aware and only slightly slower predicate,
use isSpace
Character classes
inClass :: String -> Char -> Bool Source #
Match any character in a set.
vowel = inClass "aeiou"
Range notation is supported.
halfAlphabet = inClass "a-nA-N"
To add a literal '-' to a set, place it at the beginning or end of the string.
Efficient string handling
string :: ByteString -> Parser ByteString Source #
string s
parses a sequence of bytes that identically match
s
. Returns the parsed string (i.e. s
). This parser consumes no
input if it fails (even if a partial match).
Note: The behaviour of this parser is different to that of the
similarly-named parser in Parsec, as this one is all-or-nothing.
To illustrate the difference, the following parser will fail under
Parsec given an input of "for"
:
string "foo" <|> string "for"
The reason for its failure is that the first branch is a
partial match, and will consume the letters 'f'
and 'o'
before failing. In attoparsec, the above parser will succeed on
that input, because the failed first branch will consume nothing.
stringCI :: ByteString -> Parser ByteString Source #
Satisfy a literal string, ignoring case.
skipWhile :: (Char -> Bool) -> Parser () Source #
Skip past input for as long as the predicate returns True
.
scan :: s -> (s -> Char -> Maybe s) -> Parser ByteString Source #
A stateful scanner. The predicate consumes and transforms a
state argument, and each transformed state is passed to successive
invocations of the predicate on each byte of the input until one
returns Nothing
or the input ends.
This parser does not fail. It will return an empty string if the
predicate returns Nothing
on the first byte of input.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
takeWhile :: (Char -> Bool) -> Parser ByteString Source #
Consume input as long as the predicate returns True
, and return
the consumed input.
This parser does not fail. It will return an empty string if the
predicate returns False
on the first byte of input.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
takeWhile1 :: (Char -> Bool) -> Parser ByteString Source #
takeTill :: (Char -> Bool) -> Parser ByteString Source #
Consume input as long as the predicate returns False
(i.e. until it returns True
), and return the consumed input.
This parser does not fail. It will return an empty string if the
predicate returns True
on the first byte of input.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
String combinators
If you enable the OverloadedStrings
language extension, you can
use the *>
and <*
combinators to simplify the common task of
matching a statically known string, then immediately parsing
something else.
Instead of writing something like this:
string
"foo"*>
wibble
Using OverloadedStrings
, you can omit the explicit use of
string
, and write a more compact version:
"foo" *>
wibble
(Note: the .*>
and <*.
combinators that were originally
provided for this purpose are obsolete and unnecessary, and will be
removed in the next major version.)
(.*>) :: ByteString -> Parser a -> Parser a Source #
Deprecated: This is no longer necessary, and will be removed. Use *>
instead.
Obsolete. A type-specialized version of *>
for
ByteString
. Use *>
instead.
(<*.) :: Parser a -> ByteString -> Parser a Source #
Deprecated: This is no longer necessary, and will be removed. Use <*
instead.
Obsolete. A type-specialized version of <*
for
ByteString
. Use <*
instead.
Consume all remaining input
takeByteString :: Parser ByteString Source #
Consume all remaining input and return it as a single string.
takeLazyByteString :: Parser ByteString Source #
Consume all remaining input and return it as a single string.
Text parsing
endOfLine :: Parser () Source #
Match either a single newline character '\n'
, or a carriage
return followed by a newline character "\r\n"
.
isEndOfLine :: Word8 -> Bool Source #
A predicate that matches either a carriage return '\r'
or
newline '\n'
character.
isHorizontalSpace :: Word8 -> Bool Source #
A predicate that matches either a space ' '
or horizontal tab
'\t'
character.
Numeric parsers
hexadecimal :: (Integral a, Bits a) => Parser a Source #
Parse and decode an unsigned hexadecimal number. The hex digits
'a'
through 'f'
may be upper or lower case.
This parser does not accept a leading "0x"
string.
signed :: Num a => Parser a -> Parser a Source #
Parse a number with an optional leading '+'
or '-'
sign
character.
double :: Parser Double Source #
Parse a Double
.
This parser accepts an optional leading sign character, followed by
at most one decimal digit. The syntax is similar to that accepted by
the read
function, with the exception that a trailing '.'
is
consumed.
Examples
These examples use this helper:
r ::Parser
a ->ByteString
->Result
a r p s =feed
(parse
p s)mempty
Examples with behaviour identical to read
, if you feed an empty
continuation to the first result:
double "3" == Done "" 3.0 double "3.1" == Done "" 3.1 double "3e4" == Done "" 30000.0 double "3.1e4" == Done "" 31000.0 double "3e" == Done "e" 3.0
Examples with behaviour identical to read
:
double ".3" == Fail ".3" _ _ double "e3" == Fail "e3" _ _
Example of difference from read
:
double "3.foo" == Done "foo" 3.0
This function does not accept string representations of "NaN" or "Infinity".
A numeric type that can represent integers accurately, and
floating point numbers to the precision of a Double
.
Note: this type is deprecated, and will be removed in the next
major release. Use the Scientific
type instead.
Instances
Eq Number Source # | |
Fractional Number Source # | |
Data Number Source # | |
Defined in Data.Attoparsec.Number gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Number -> c Number # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Number # toConstr :: Number -> Constr # dataTypeOf :: Number -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Number) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Number) # gmapT :: (forall b. Data b => b -> b) -> Number -> Number # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Number -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Number -> r # gmapQ :: (forall d. Data d => d -> u) -> Number -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Number -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Number -> m Number # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Number -> m Number # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Number -> m Number # | |
Num Number Source # | |
Ord Number Source # | |
Real Number Source # | |
Defined in Data.Attoparsec.Number toRational :: Number -> Rational # | |
RealFrac Number Source # | |
Show Number Source # | |
NFData Number Source # | |
Defined in Data.Attoparsec.Number |
number :: Parser Number Source #
Deprecated: Use scientific
instead.
Parse a number, attempting to preserve both speed and precision.
The syntax accepted by this parser is the same as for double
.
rational :: Fractional a => Parser a Source #
Parse a rational number.
The syntax accepted by this parser is the same as for double
.
Note: this parser is not safe for use with inputs from untrusted
sources. An input with a suitably large exponent such as
"1e1000000000"
will cause a huge Integer
to be allocated,
resulting in what is effectively a denial-of-service attack.
In most cases, it is better to use double
or scientific
instead.
scientific :: Parser Scientific Source #
Parse a scientific number.
The syntax accepted by this parser is the same as for double
.
Combinators
try :: Parser i a -> Parser i a Source #
Attempt a parse, and if it fails, rewind the input so that no input appears to have been consumed.
This combinator is provided for compatibility with Parsec. attoparsec parsers always backtrack on failure.
Name the parser, in case failure occurs.
choice :: Alternative f => [f a] -> f a Source #
choice ps
tries to apply the actions in the list ps
in order,
until one of them succeeds. Returns the value of the succeeding
action.
count :: Monad m => Int -> m a -> m [a] Source #
Apply the given action repeatedly, returning every result.
option :: Alternative f => a -> f a -> f a Source #
option x p
tries to apply action p
. If p
fails without
consuming input, it returns the value x
, otherwise the value
returned by p
.
priority = option 0 (digitToInt <$> digit)
many' :: MonadPlus m => m a -> m [a] Source #
many' p
applies the action p
zero or more times. Returns a
list of the returned values of p
. The value returned by p
is
forced to WHNF.
word = many' letter
many1 :: Alternative f => f a -> f [a] Source #
many1 p
applies the action p
one or more times. Returns a
list of the returned values of p
.
word = many1 letter
many1' :: MonadPlus m => m a -> m [a] Source #
many1' p
applies the action p
one or more times. Returns a
list of the returned values of p
. The value returned by p
is
forced to WHNF.
word = many1' letter
manyTill :: Alternative f => f a -> f b -> f [a] Source #
manyTill p end
applies action p
zero or more times until
action end
succeeds, and returns the list of values returned by
p
. This can be used to scan comments:
simpleComment = string "<!--" *> manyTill anyChar (string "-->")
(Note the overlapping parsers anyChar
and string "-->"
.
While this will work, it is not very efficient, as it will cause a
lot of backtracking.)
manyTill' :: MonadPlus m => m a -> m b -> m [a] Source #
manyTill' p end
applies action p
zero or more times until
action end
succeeds, and returns the list of values returned by
p
. This can be used to scan comments:
simpleComment = string "<!--" *> manyTill' anyChar (string "-->")
(Note the overlapping parsers anyChar
and string "-->"
.
While this will work, it is not very efficient, as it will cause a
lot of backtracking.)
The value returned by p
is forced to WHNF.
sepBy :: Alternative f => f a -> f s -> f [a] Source #
sepBy p sep
applies zero or more occurrences of p
, separated
by sep
. Returns a list of the values returned by p
.
commaSep p = p `sepBy` (char ',')
sepBy' :: MonadPlus m => m a -> m s -> m [a] Source #
sepBy' p sep
applies zero or more occurrences of p
, separated
by sep
. Returns a list of the values returned by p
. The value
returned by p
is forced to WHNF.
commaSep p = p `sepBy'` (char ',')
sepBy1 :: Alternative f => f a -> f s -> f [a] Source #
sepBy1 p sep
applies one or more occurrences of p
, separated
by sep
. Returns a list of the values returned by p
.
commaSep p = p `sepBy1` (char ',')
sepBy1' :: MonadPlus m => m a -> m s -> m [a] Source #
sepBy1' p sep
applies one or more occurrences of p
, separated
by sep
. Returns a list of the values returned by p
. The value
returned by p
is forced to WHNF.
commaSep p = p `sepBy1'` (char ',')
skipMany :: Alternative f => f a -> f () Source #
Skip zero or more instances of an action.
skipMany1 :: Alternative f => f a -> f () Source #
Skip one or more instances of an action.
eitherP :: Alternative f => f a -> f b -> f (Either a b) Source #
Combine two alternatives.
match :: Parser a -> Parser (ByteString, a) Source #
Return both the result of a parse and the portion of the input that was consumed while it was being parsed.
State observation and manipulation functions
endOfInput :: forall t. Chunk t => Parser t () Source #
Match only if all input has been consumed.
atEnd :: Chunk t => Parser t Bool Source #
Return an indication of whether the end of input has been reached.
Orphan instances
a ~ ByteString => IsString (Parser a) Source # | |
fromString :: String -> Parser a # |