Portability | unknown |
---|---|
Stability | experimental |
Maintainer | bos@serpentine.com |
Simple, efficient parser combinators for lazy ByteString
strings, loosely based on Text.ParserCombinators.Parsec
.
- type ParseError = String
- data Parser a
- parse :: Parser a -> ByteString -> (ByteString, Either ParseError a)
- parseAt :: Parser a -> ByteString -> Int64 -> (ByteString, Either ParseError (a, Int64))
- parseTest :: Show a => Parser a -> ByteString -> IO ()
- subParse :: Parser a -> ByteString -> Parser a
- (<?>) :: Parser a -> String -> Parser a
- try :: Parser a -> Parser a
- choice :: [Parser a] -> Parser a
- manyTill :: Parser a -> Parser b -> Parser [a]
- eof :: Parser ()
- notFollowedBy :: Parser a -> Parser ()
- skipMany :: Parser a -> Parser ()
- skipMany1 :: Parser a -> Parser ()
- count :: Int -> Parser a -> Parser [a]
- lookAhead :: Parser a -> Parser a
- peek :: Parser a -> Parser (Maybe a)
- sepBy :: Parser a -> Parser s -> Parser [a]
- sepBy1 :: Parser a -> Parser s -> Parser [a]
- satisfy :: (Word8 -> Bool) -> Parser Word8
- anyWord8 :: Parser Word8
- word8 :: Word8 -> Parser Word8
- notWord8 :: Word8 -> Parser Word8
- string :: ByteString -> Parser ByteString
- stringTransform :: (ByteString -> ByteString) -> ByteString -> Parser ByteString
- eitherP :: Parser a -> Parser b -> Parser (Either a b)
- eitherF :: Parser a -> Parser (Either (ByteString, [String]) a)
- err :: [String] -> Parser a
- getInput :: Parser ByteString
- getConsumed :: Parser Int64
- takeWhile :: (Word8 -> Bool) -> Parser ByteString
- takeWhile1 :: (Word8 -> Bool) -> Parser ByteString
- takeTill :: (Word8 -> Bool) -> Parser ByteString
- takeAll :: Parser ByteString
- skipWhile :: (Word8 -> Bool) -> Parser ()
- notEmpty :: Parser ByteString -> Parser ByteString
- match :: Parser a -> Parser ByteString
Parser
type ParseError = StringSource
Running parsers
parse :: Parser a -> ByteString -> (ByteString, Either ParseError a)Source
Run a parser.
parseAt :: Parser a -> ByteString -> Int64 -> (ByteString, Either ParseError (a, Int64))Source
subParse :: Parser a -> ByteString -> Parser aSource
Combinators
Things vaguely like those in Parsec.Combinator
(and Parsec.Prim
)
notFollowedBy :: Parser a -> Parser ()Source
count :: Int -> Parser a -> Parser [a]Source
Apply the given parser repeatedly, returning every parse result.
Things like in Parsec.Char
string :: ByteString -> Parser ByteStringSource
Satisfy a literal string.
stringTransform :: (ByteString -> ByteString) -> ByteString -> Parser ByteStringSource
Satisfy a literal string, after applying a transformation to both it and the matching text.
Parser converters.
Miscellaneous functions.
getInput :: Parser ByteStringSource
Get remaining input.
getConsumed :: Parser Int64Source
Get number of bytes consumed so far.
takeWhile :: (Word8 -> Bool) -> Parser ByteStringSource
Consume characters while the predicate is true.
takeWhile1 :: (Word8 -> Bool) -> Parser ByteStringSource
notEmpty :: Parser ByteString -> Parser ByteStringSource
Test that a parser returned a non-null ByteString.
match :: Parser a -> Parser ByteStringSource
Parse some input with the given parser and return that input without copying it.