hsemail-1.0: Internet Message ParsersContentsIndex
Text.ParserCombinators.Parsec.Rfc2234
Portabilityportable
Stabilityprovisional
Maintainersimons@cryp.to
Contents
Parser Combinators
Primitive Parsers
Useful additions
Description
This module provides parsers for the grammar defined in RFC2234, "Augmented BNF for Syntax Specifications: ABNF", http://www.faqs.org/rfcs/rfc2234.html. The terminal called char in the RFC is called character here to avoid conflicts with Parsec's char function.
Synopsis
caseChar :: Char -> CharParser st Char
caseString :: String -> CharParser st ()
manyN :: Int -> GenParser a b c -> GenParser a b [c]
manyNtoM :: Int -> Int -> GenParser a b c -> GenParser a b [c]
parsec2read :: Parser a -> String -> [(a, String)]
alpha :: CharParser st Char
bit :: CharParser st Char
character :: CharParser st Char
cr :: CharParser st Char
lf :: CharParser st Char
crlf :: CharParser st String
ctl :: CharParser st Char
dquote :: CharParser st Char
hexdig :: CharParser st Char
htab :: CharParser st Char
lwsp :: CharParser st String
octet :: CharParser st Char
sp :: CharParser st Char
vchar :: CharParser st Char
wsp :: CharParser st Char
quoted_pair :: CharParser st String
quoted_string :: CharParser st String
Parser Combinators
caseChar :: Char -> CharParser st Char
Case-insensitive variant of Parsec's char function.
caseString :: String -> CharParser st ()
Case-insensitive variant of Parsec's string function.
manyN :: Int -> GenParser a b c -> GenParser a b [c]
Match a parser at least n times.
manyNtoM :: Int -> Int -> GenParser a b c -> GenParser a b [c]
Match a parser at least n times, but no more than m times.
parsec2read :: Parser a -> String -> [(a, String)]
Helper function to generate Parser-based instances for the Read class.
Primitive Parsers
alpha :: CharParser st Char
Match any character of the alphabet.
bit :: CharParser st Char
Match either "1" or "0".
character :: CharParser st Char
Match any 7-bit US-ASCII character except for NUL (ASCII value 0, that is).
cr :: CharParser st Char
Match the carriage return character \r.
lf :: CharParser st Char
Match returns the linefeed character \n.
crlf :: CharParser st String
Match the Internet newline \r\n.
ctl :: CharParser st Char
Match any US-ASCII control character. That is any character with a decimal value in the range of [0..31,127].
dquote :: CharParser st Char
Match the double quote character """.
hexdig :: CharParser st Char
Match any character that is valid in a hexadecimal number; ['0'..'9'] and ['A'..'F','a'..'f'] that is.
htab :: CharParser st Char
Match the tab ("\t") character.
lwsp :: CharParser st String
Match "linear white-space". That is any number of consecutive wsp, optionally followed by a crlf and (at least) one more wsp.
octet :: CharParser st Char
Match any character.
sp :: CharParser st Char
Match the space.
vchar :: CharParser st Char
Match any printable ASCII character. (The "v" stands for "visible".) That is any character in the decimal range of [33..126].
wsp :: CharParser st Char
Match either sp or htab.
Useful additions
quoted_pair :: CharParser st String
Match a "quoted pair". Any characters (excluding CR and LF) may be quoted.
quoted_string :: CharParser st String
Match a quoted string. The specials "\" and """ must be escaped inside a quoted string; CR and LF are not allowed at all.
Produced by Haddock version 0.8