Portability | unknown |
---|---|
Stability | experimental |
Maintainer | bos@serpentine.com |
Simple, efficient, character-oriented combinator parsing for
ByteString
strings, loosely based on the Parsec library.
- data Parser a
- data Result r
- = Fail ByteString [String] String
- | Partial (ByteString -> Result r)
- | Done ByteString r
- parse :: Parser a -> ByteString -> Result a
- feed :: Result r -> ByteString -> Result r
- parseOnly :: Parser a -> ByteString -> Either String a
- parseTest :: Show a => Parser a -> ByteString -> IO ()
- parseWith :: Monad m => m ByteString -> Parser a -> ByteString -> m (Result a)
- maybeResult :: Result r -> Maybe r
- eitherResult :: Result r -> Either String r
- (<?>) :: Parser a -> String -> Parser a
- try :: Parser a -> Parser a
- module Data.Attoparsec.Combinator
- char :: Char -> Parser Char
- char8 :: Char -> Parser Word8
- anyChar :: Parser Char
- notChar :: Char -> Parser Char
- satisfy :: (Char -> Bool) -> 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
- 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
- endOfInput :: Parser ()
- atEnd :: Parser 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
The Parser
type is a monad.
The result of a parse.
Fail ByteString [String] String | The parse failed. The |
Partial (ByteString -> Result r) | Supply this continuation with more input so that
the parser can resume. To indicate that no more
input is available, use an |
Done ByteString r | The parse succeeded. The |
Running parsers
parse :: Parser a -> ByteString -> Result aSource
Run a parser.
feed :: Result r -> ByteString -> Result rSource
If a parser has returned a Partial
result, supply it with more
input.
parseOnly :: Parser a -> ByteString -> Either String aSource
Run a parser that cannot be resupplied via a Partial
result.
parseTest :: Show a => Parser a -> ByteString -> IO ()Source
Run a parser and print its result to standard output.
:: 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.
Result conversion
maybeResult :: Result r -> Maybe rSource
eitherResult :: Result r -> Either String rSource
Combinators
try :: Parser a -> Parser aSource
Attempt a parse, and if it fails, rewind the input so that no input appears to have been consumed.
This combinator is useful in cases where a parser might consume some input before failing, i.e. the parser needs arbitrary lookahead. The downside to using this combinator is that it can retain input for longer than is desirable.
module Data.Attoparsec.Combinator
Parsing individual characters
satisfy :: (Char -> Bool) -> Parser CharSource
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'
Special character parsers
letter_iso8859_15 :: Parser CharSource
Match a letter, in the ISO-8859-15 encoding.
letter_ascii :: Parser CharSource
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 -> BoolSource
A fast digit predicate.
isAlpha_iso8859_15 :: Char -> BoolSource
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 -> BoolSource
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.
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 Data.Char.isSpace
isSpace_w8 :: Word8 -> BoolSource
Fast Word8
predicate for matching ASCII space characters.
Character classes
inClass :: String -> Char -> BoolSource
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.
notInClass :: String -> Char -> BoolSource
Match any character not in a set.
Efficient string handling
string :: ByteString -> Parser ByteStringSource
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 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 ByteStringSource
Satisfy a literal string, ignoring case.
skipWhile :: (Char -> Bool) -> Parser ()Source
Skip past input for as long as the predicate returns True
.
take :: Int -> Parser ByteStringSource
Consume exactly n
bytes of input.
scan :: s -> (s -> Char -> Maybe s) -> Parser ByteStringSource
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 ByteStringSource
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 ByteStringSource
takeTill :: (Char -> Bool) -> Parser ByteStringSource
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.
Consume all remaining input
takeByteString :: Parser ByteStringSource
Consume all remaining input and return it as a single string.
takeLazyByteString :: Parser ByteStringSource
Consume all remaining input and return it as a single string.
Text parsing
Match either a single newline character '\n'
, or a carriage
return followed by a newline character "\r\n"
.
isEndOfLine :: Word8 -> BoolSource
A predicate that matches either a carriage return '\r'
or
newline '\n'
character.
isHorizontalSpace :: Word8 -> BoolSource
A predicate that matches either a space ' '
or horizontal tab
'\t'
character.
Numeric parsers
hexadecimal :: (Integral a, Bits a) => Parser aSource
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 aSource
Parse a number with an optional leading '+'
or '-'
sign
character.
Parse a rational number.
The syntax accepted by this parser is the same as for rational
.
Note: This function is almost ten times faster than rational
,
but is slightly less accurate.
The Double
type supports about 16 decimal places of accuracy.
For 94.2% of numbers, this function and rational
give identical
results, but for the remaining 5.8%, this function loses precision
around the 15th decimal place. For 0.001% of numbers, this
function will lose precision at the 13th or 14th decimal place.
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
.
Parse a number, attempting to preserve both speed and precision.
The syntax accepted by this parser is the same as for rational
.
Note: This function is almost ten times faster than rational
.
On integral inputs, it gives perfectly accurate answers, and on
floating point inputs, it is slightly less accurate than
rational
.
This function does not accept string representations of "NaN" or "Infinity".
rational :: Fractional a => Parser aSource
Parse a rational number.
This parser accepts an optional leading sign character, followed by
at least one decimal digit. The syntax similar to that accepted by
the read
function, with the exception that a trailing '.'
or
'e'
not followed by a number is not consumed.
Examples with behaviour identical to read
, if you feed an empty
continuation to the first result:
rational "3" == Done 3.0 "" rational "3.1" == Done 3.1 "" rational "3e4" == Done 30000.0 "" rational "3.1e4" == Done 31000.0, ""
State observation and manipulation functions
Match only if all input has been consumed.