HCodecs-0.5.1: A library to read, write and manipulate MIDI, WAVE, and SoundFont2 files.

CopyrightLennart Kolmodin George Giorgidze
LicenseBSD3
MaintainerGeorge Giorgidze <http://cs.nott.ac.uk/~ggg/>
Stabilityexperimental
PortabilityPortable
Safe HaskellNone
LanguageHaskell98

Codec.ByteString.Parser

Contents

Description

A monad for efficiently building structures from encoded lazy ByteStrings.

Synopsis

The Parser type

data Parser a Source #

The Get monad is just a State monad carrying around the input ByteString

Instances

Monad Parser Source # 

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Applicative Parser Source # 

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Alternative Parser Source # 

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser Source # 

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

runParser :: Parser a -> ByteString -> Either String a Source #

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

expect :: (Show a, Eq a) => (a -> Bool) -> Parser a -> Parser a Source #

skip :: Word64 -> Parser () Source #

Skip ahead n bytes. Fails if fewer than n bytes are available.

lookAhead :: Parser a -> Parser a Source #

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

bytesRead :: Parser Int64 Source #

Get the total number of bytes read to this point.

getBytes :: Int -> Parser ByteString Source #

Pull n bytes from the input, as a strict ByteString.

remaining :: Parser Int64 Source #

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.

isEmpty :: Parser Bool Source #

Test whether all input has been consumed, i.e. there are no remaining unparsed bytes.

Parsing particular types

getWord8 :: Parser Word8 Source #

Read a Word8 from the monad state

ByteStrings

getByteString :: Int -> Parser ByteString Source #

An efficient get method for strict ByteStrings. Fails if fewer than n bytes are left in the input.

getLazyByteString :: Int64 -> Parser ByteString Source #

An efficient get method for lazy ByteStrings. Does not fail if fewer than n bytes are left in the input.

getLazyByteStringNul :: Parser ByteString Source #

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 ByteString Source #

Get the remaining bytes as a lazy ByteString

Big-endian reads

getWord16be :: Parser Word16 Source #

Read a Word16 in big endian format

getWord24be :: Parser Word32 Source #

Read a 24 bit word into Word32 in big endian format

getWord32be :: Parser Word32 Source #

Read a Word32 in big endian format

getWord64be :: Parser Word64 Source #

Read a Word64 in big endian format

Little-endian reads

getWord16le :: Parser Word16 Source #

Read a Word16 in little endian format

getWord32le :: Parser Word32 Source #

Read a Word32 in little endian format

getWord64le :: Parser Word64 Source #

Read a Word64 in little endian format

Host-endian, unaligned reads

getWordHost :: Parser Word Source #

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 Word16 Source #

O(1). Read a 2 byte Word16 in native host order and host endianness.

getWord32host :: Parser Word32 Source #

O(1). Read a Word32 in native host order and host endianness.

getWord64host :: Parser Word64 Source #

O(1). Read a Word64 in native host order and host endianess.