Portability | Portable |
---|---|
Stability | experimental |
Maintainer | George Giorgidze <http://cs.nott.ac.uk/~ggg/> |
Safe Haskell | None |
A monad for efficiently building structures from encoded lazy ByteStrings.
- data Parser a
- runParser :: Parser a -> ByteString -> Either String a
- runParserState :: Parser a -> ByteString -> Int64 -> Either String (a, ByteString, Int64)
- choice :: [Parser a] -> Parser a
- expect :: (Show a, Eq a) => (a -> Bool) -> Parser a -> Parser a
- skip :: Word64 -> Parser ()
- lookAhead :: Parser a -> Parser a
- lookAheadM :: Parser (Maybe a) -> Parser (Maybe a)
- lookAheadE :: Parser (Either a b) -> Parser (Either a b)
- bytesRead :: Parser Int64
- getBytes :: Int -> Parser ByteString
- remaining :: Parser Int64
- isEmpty :: Parser Bool
- satisfy :: (Word8 -> Bool) -> Parser Word8
- getString :: Int -> Parser String
- getStringNul :: Parser String
- string :: String -> Parser String
- getWord8 :: Parser Word8
- getInt8 :: Parser Int8
- word8 :: Word8 -> Parser Word8
- int8 :: Int8 -> Parser Int8
- getByteString :: Int -> Parser ByteString
- getLazyByteString :: Int64 -> Parser ByteString
- getLazyByteStringNul :: Parser ByteString
- getRemainingLazyByteString :: Parser ByteString
- getWord16be :: Parser Word16
- word16be :: Word16 -> Parser Word16
- getWord24be :: Parser Word32
- word24be :: Word32 -> Parser Word32
- getWord32be :: Parser Word32
- word32be :: Word32 -> Parser Word32
- getWord64be :: Parser Word64
- word64be :: Word64 -> Parser Word64
- getInt16be :: Parser Int16
- int16be :: Int16 -> Parser Int16
- getInt32be :: Parser Int32
- int32be :: Int32 -> Parser Int32
- getInt64be :: Parser Int64
- int64be :: Int64 -> Parser Int64
- getWord16le :: Parser Word16
- word16le :: Word16 -> Parser Word16
- getWord24le :: Parser Word32
- word24le :: Word32 -> Parser Word32
- getWord32le :: Parser Word32
- word32le :: Word32 -> Parser Word32
- getWord64le :: Parser Word64
- word64le :: Word64 -> Parser Word64
- getInt16le :: Parser Int16
- int16le :: Int16 -> Parser Int16
- getInt32le :: Parser Int32
- int32le :: Int32 -> Parser Int32
- getInt64le :: Parser Int64
- int64le :: Int64 -> Parser Int64
- getWordHost :: Parser Word
- wordHost :: Word -> Parser Word
- getWord16host :: Parser Word16
- word16host :: Word16 -> Parser Word16
- getWord32host :: Parser Word32
- word32host :: Word32 -> Parser Word32
- getWord64host :: Parser Word64
- word64host :: Word64 -> Parser Word64
- getVarLenBe :: Parser Word64
- varLenBe :: Word64 -> Parser Word64
- getVarLenLe :: Parser Word64
- varLenLe :: Word64 -> Parser Word64
The Parser type
The Get monad is just a State monad carrying around the input ByteString
runParser :: Parser a -> ByteString -> Either String aSource
Run the Get monad applies a get
-based parser on the input ByteString
runParserState :: Parser a -> ByteString -> Int64 -> Either String (a, ByteString, Int64)Source
Run the Get monad applies a get
-based parser on the input
ByteString. Additional to the result of get it returns the number of
consumed bytes and the rest of the input.
Parsing
lookAhead :: Parser a -> Parser aSource
Run ga
, but return without consuming its input.
Fails if ga
fails.
lookAheadM :: Parser (Maybe a) -> Parser (Maybe a)Source
Like lookAhead
, but consume the input if gma
returns 'Just _'.
Fails if gma
fails.
lookAheadE :: Parser (Either a b) -> Parser (Either a b)Source
Like lookAhead
, but consume the input if gea
returns 'Right _'.
Fails if gea
fails.
Utility
getBytes :: Int -> Parser ByteStringSource
Pull n
bytes from the input, as a strict ByteString.
remaining :: Parser Int64Source
Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed. Note that this forces the rest of the input.
Test whether all input has been consumed, i.e. there are no remaining unparsed bytes.
Parsing particular types
ByteStrings
getByteString :: Int -> Parser ByteStringSource
An efficient get
method for strict ByteStrings. Fails if fewer
than n
bytes are left in the input.
getLazyByteString :: Int64 -> Parser ByteStringSource
An efficient get
method for lazy ByteStrings. Does not fail if fewer than
n
bytes are left in the input.
getLazyByteStringNul :: Parser ByteStringSource
Get a lazy ByteString that is terminated with a NUL byte. Fails if it reaches the end of input without hitting a NUL.
getRemainingLazyByteString :: Parser ByteStringSource
Get the remaining bytes as a lazy ByteString
Big-endian reads
getWord16be :: Parser Word16Source
Read a Word16 in big endian format
getWord24be :: Parser Word32Source
Read a 24 bit word into Word32 in big endian format
getWord32be :: Parser Word32Source
Read a Word32 in big endian format
getWord64be :: Parser Word64Source
Read a Word64 in big endian format
Little-endian reads
getWord16le :: Parser Word16Source
Read a Word16 in little endian format
getWord32le :: Parser Word32Source
Read a Word32 in little endian format
getWord64le :: Parser Word64Source
Read a Word64 in little endian format
Host-endian, unaligned reads
getWordHost :: Parser WordSource
O(1). Read a single native machine word. The word is read in host order, host endian form, for the machine you're on. On a 64 bit machine the Word is an 8 byte value, on a 32 bit machine, 4 bytes.
getWord16host :: Parser Word16Source
O(1). Read a 2 byte Word16 in native host order and host endianness.
word16host :: Word16 -> Parser Word16Source
getWord32host :: Parser Word32Source
O(1). Read a Word32 in native host order and host endianness.
word32host :: Word32 -> Parser Word32Source
getWord64host :: Parser Word64Source
O(1). Read a Word64 in native host order and host endianess.
word64host :: Word64 -> Parser Word64Source