| Copyright | Bryan O'Sullivan 2007-2015 Winterland 2016 | 
|---|---|
| License | BSD3 | 
| Maintainer | drkoster@qq.com | 
| Stability | experimental | 
| Portability | unknown | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.Binary.Parser.Word8
Description
Simple, efficient combinator parsing for ByteString strings.
Synopsis
- peekMaybe :: Get (Maybe Word8)
- peek :: Get Word8
- satisfy :: (Word8 -> Bool) -> Get Word8
- satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Get a
- word8 :: Word8 -> Get ()
- anyWord8 :: Get Word8
- skipWord8 :: (Word8 -> Bool) -> Get ()
- skipN :: Int -> Get ()
- takeTill :: (Word8 -> Bool) -> Get ByteString
- takeWhile :: (Word8 -> Bool) -> Get ByteString
- takeWhile1 :: (Word8 -> Bool) -> Get ByteString
- skipWhile :: (Word8 -> Bool) -> Get ()
- skipSpaces :: Get ()
- string :: ByteString -> Get ()
- scan :: s -> (s -> Word8 -> Maybe s) -> Get ByteString
- scanChunks :: s -> Consume s -> Get ByteString
- isSpace :: Word8 -> Bool
- isDigit :: Word8 -> Bool
- isHexDigit :: Word8 -> Bool
- isHorizontalSpace :: Word8 -> Bool
- isEndOfLine :: Word8 -> Bool
- endOfLine :: Get ()
Documentation
peekMaybe :: Get (Maybe Word8) Source #
Match any byte, to perform lookahead. Returns Nothing if end of
 input has been reached. Does not consume any input.
Match any byte, to perform lookahead. Does not consume any input, but will fail if end of input has been reached.
satisfy :: (Word8 -> Bool) -> Get Word8 Source #
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 w = w >= 48 && w <= 57satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Get a Source #
The parser satisfyWith f p transforms a byte, and succeeds if
 the predicate p returns True on the transformed value. The
 parser returns the transformed byte that was parsed.
skipWord8 :: (Word8 -> Bool) -> Get () Source #
The parser skipWord8 p succeeds for any byte for which the predicate p returns True.
skipN :: Int -> Get () Source #
This is a faster version of skip for small N (smaller than chunk size).
takeTill :: (Word8 -> Bool) -> Get ByteString Source #
Consume input as long as the predicate returns False or reach the end of input,
 and return the consumed input.
takeWhile :: (Word8 -> Bool) -> Get ByteString Source #
Consume input as long as the predicate returns True or reach the end of input,
 and return the consumed input.
takeWhile1 :: (Word8 -> Bool) -> Get ByteString Source #
skipWhile :: (Word8 -> Bool) -> Get () Source #
Skip past input for as long as the predicate returns True.
skipSpaces :: Get () Source #
Skip over white space using isSpace.
string :: ByteString -> Get () Source #
string s parses a sequence of bytes that identically match s.
scan :: s -> (s -> Word8 -> Maybe s) -> Get ByteString Source #
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.
scanChunks :: s -> Consume s -> Get ByteString Source #
Similar to scan, but working on ByteString chunks, The predicate
 consumes a ByteString chunk and transforms a state argument,
 and each transformed state is passed to successive invocations of
 the predicate on each chunk of the input until one chunk got splited to
 Right (ByteString, ByteString) or the input ends.
isSpace :: Word8 -> Bool Source #
Fast Word8 predicate for matching ASCII space characters
isSpace w = w == 32 || w - 9 <= 4
isHexDigit :: Word8 -> Bool Source #
Hex digit predicate.
isHorizontalSpace :: Word8 -> Bool Source #
A predicate that matches either a space ' ' or horizontal tab
 '\t' character.
isEndOfLine :: Word8 -> Bool Source #
A predicate that matches either a carriage return '\r' or
 newline '\n' character.