Lucu-0.3.2: HTTP Daemonic LibrarySource codeContentsIndex
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 of String.
  • 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.

Synopsis
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 :: Parser a -> Parser [a]
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
data Parser a Source
Parser a is obviously a parser which parses and returns a.
show/hide Instances
data ParserResult a Source
Constructors
Success !a
IllegalInput
ReachedEOF
show/hide Instances
failP :: Parser aSource
failP is just a synonym for fail undefined.
parse :: Parser a -> ByteString -> (#ParserResult a, ByteString#)Source
parse p bstr parses bstr with p and returns (# result, remaining #).
parseStr :: Parser a -> String -> (#ParserResult a, ByteString#)Source
parseStr p str packs str and parses it.
anyChar :: Parser CharSource
eof :: Parser ()Source
allowEOF :: Parser a -> Parser aSource
allowEOF p makes p treat reaching EOF a normal failure.
satisfy :: (Char -> Bool) -> Parser CharSource
char :: Char -> Parser CharSource
string :: String -> Parser StringSource
(<|>) :: Parser a -> Parser a -> Parser aSource
This is the backtracking alternation. There is no non-backtracking equivalent.
choice :: [Parser a] -> Parser aSource
oneOf :: [Char] -> Parser CharSource
digit :: Parser CharSource
hexDigit :: Parser CharSource
notFollowedBy :: Parser a -> Parser ()Source
many :: Parser a -> Parser [a]Source
many1 :: Parser a -> Parser [a]Source
count :: Int -> Parser a -> Parser [a]Source
option :: a -> Parser a -> Parser aSource
sepBy :: Parser a -> Parser sep -> Parser [a]Source
sepBy1 :: Parser a -> Parser sep -> Parser [a]Source
sp :: Parser CharSource
ht :: Parser CharSource
crlf :: Parser StringSource
Produced by Haddock version 2.4.2