Network.HTTP.Lucu.Parser
Description
Yet another parser combinator. This is mostly a subset of Text.ParserCombinators.Parsec but there are some differences:
- This parser works on
Data.ByteString.Base.LazyByteString
instead ofString
. - Backtracking is the only possible behavior so there is no "try" action.
- On success, the remaining string is returned as well as the parser result.
- You can choose whether to treat reaching EOF (trying to eat one more letter at the end of string) a fatal error or to treat it a normal failure. If a fatal error occurs, the entire parsing process immediately fails without trying any backtracks. The default behavior is to treat EOF fatal.
In general, you don't have to use this module directly.
- data Parser a
- data ParserResult a
- = Success !a
- | IllegalInput
- | ReachedEOF
- failP :: Parser a
- parse :: Parser a -> ByteString -> (#ParserResult a, ByteString#)
- parseStr :: Parser a -> String -> (#ParserResult a, ByteString#)
- anyChar :: Parser Char
- eof :: Parser ()
- allowEOF :: Parser a -> Parser a
- satisfy :: (Char -> Bool) -> Parser Char
- char :: Char -> Parser Char
- string :: String -> Parser String
- (<|>) :: Parser a -> Parser a -> Parser a
- choice :: [Parser a] -> Parser a
- oneOf :: [Char] -> Parser Char
- digit :: Parser Char
- hexDigit :: Parser Char
- notFollowedBy :: Parser a -> Parser ()
- many :: forall a. Parser a -> Parser [a]
- manyChar :: Parser Char -> Parser ByteString
- many1 :: Parser a -> Parser [a]
- count :: Int -> Parser a -> Parser [a]
- option :: a -> Parser a -> Parser a
- sepBy :: Parser a -> Parser sep -> Parser [a]
- sepBy1 :: Parser a -> Parser sep -> Parser [a]
- sp :: Parser Char
- ht :: Parser Char
- crlf :: Parser String
Documentation
is obviously a parser which parses and returns Parser
aa
.
data ParserResult a Source
Constructors
Success !a | |
IllegalInput | |
ReachedEOF |
Instances
Eq a => Eq (ParserResult a) | |
Show a => Show (ParserResult a) |
parse :: Parser a -> ByteString -> (#ParserResult a, ByteString#)Source
parses parse
p bstrbstr
with p
and returns (# result,
remaining #)
.
parseStr :: Parser a -> String -> (#ParserResult a, ByteString#)Source
packs parseStr
p strstr
and parses it.
(<|>) :: Parser a -> Parser a -> Parser aSource
This is the backtracking alternation. There is no non-backtracking equivalent.
notFollowedBy :: Parser a -> Parser ()Source