quiver-binary-0.1.1.1: Binary serialisation support for Quivers

Copyright(c) Ivan Lazar Miljenovic
LicenseMIT
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Control.Quiver.Binary

Contents

Description

This module provides functions for encoding/decoding values within a Quiver.

For any I/O operations, use the functions provided by the quiver-bytestring package.

Synopsis

Simple encoding/decoding

spput :: Binary a => SConsumer a PutM e Source #

Encode all values.

spget :: Binary a => SProducer a Get e Source #

Decode all values.

Conversions to/from ByteStrings

spdecode :: (Binary a, Monad m) => SP ByteString a m String Source #

Decode all values from the provided stream of strict ByteStrings. Note that the error message does not return the ByteOffset from the Decoder as it will probably not match the actual location of the source ByteString.

spdecodeL :: forall a m. (Binary a, Monad m) => SP ByteString a m String Source #

Decode all values from the provided stream of lazy ByteStrings. Note that the error message does not return the ByteOffset from the Decoder as it will probably not match the actual location of the source ByteString.

spencode :: (Binary a, Functor m) => SP a ByteString m () Source #

Encode all values to a stream of strict ByteStrings.

spencodeL :: Binary a => SP a ByteString m () Source #

Encode all values to a stream of lazy ByteStrings.

Re-exports

class Binary t #

The Binary class provides put and get, methods to encode and decode a Haskell value to a lazy ByteString. It mirrors the Read and Show classes for textual representation of Haskell types, and is suitable for serialising Haskell values to disk, over the network.

For decoding and generating simple external binary formats (e.g. C structures), Binary may be used, but in general is not suitable for complex protocols. Instead use the Put and Get primitives directly.

Instances of Binary should satisfy the following property:

decode . encode == id

That is, the get and put methods should be the inverse of each other. A range of instances are provided for basic Haskell types.

Instances

Binary Bool 

Methods

put :: Bool -> Put #

get :: Get Bool #

putList :: [Bool] -> Put #

Binary Char 

Methods

put :: Char -> Put #

get :: Get Char #

putList :: [Char] -> Put #

Binary Double 

Methods

put :: Double -> Put #

get :: Get Double #

putList :: [Double] -> Put #

Binary Float 

Methods

put :: Float -> Put #

get :: Get Float #

putList :: [Float] -> Put #

Binary Int 

Methods

put :: Int -> Put #

get :: Get Int #

putList :: [Int] -> Put #

Binary Int8 

Methods

put :: Int8 -> Put #

get :: Get Int8 #

putList :: [Int8] -> Put #

Binary Int16 

Methods

put :: Int16 -> Put #

get :: Get Int16 #

putList :: [Int16] -> Put #

Binary Int32 

Methods

put :: Int32 -> Put #

get :: Get Int32 #

putList :: [Int32] -> Put #

Binary Int64 

Methods

put :: Int64 -> Put #

get :: Get Int64 #

putList :: [Int64] -> Put #

Binary Integer 

Methods

put :: Integer -> Put #

get :: Get Integer #

putList :: [Integer] -> Put #

Binary Ordering 

Methods

put :: Ordering -> Put #

get :: Get Ordering #

putList :: [Ordering] -> Put #

Binary Word 

Methods

put :: Word -> Put #

get :: Get Word #

putList :: [Word] -> Put #

Binary Word8 

Methods

put :: Word8 -> Put #

get :: Get Word8 #

putList :: [Word8] -> Put #

Binary Word16 

Methods

put :: Word16 -> Put #

get :: Get Word16 #

putList :: [Word16] -> Put #

Binary Word32 

Methods

put :: Word32 -> Put #

get :: Get Word32 #

putList :: [Word32] -> Put #

Binary Word64 

Methods

put :: Word64 -> Put #

get :: Get Word64 #

putList :: [Word64] -> Put #

Binary () 

Methods

put :: () -> Put #

get :: Get () #

putList :: [()] -> Put #

Binary Natural

Since: 0.7.3.0

Methods

put :: Natural -> Put #

get :: Get Natural #

putList :: [Natural] -> Put #

Binary Void

Since: 0.8.0.0

Methods

put :: Void -> Put #

get :: Get Void #

putList :: [Void] -> Put #

Binary Version

Since: 0.8.0.0

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

Binary Fingerprint

Since: 0.7.6.0

Binary ShortByteString 
Binary ByteString 
Binary ByteString 
Binary IntSet 

Methods

put :: IntSet -> Put #

get :: Get IntSet #

putList :: [IntSet] -> Put #

Binary a => Binary [a] 

Methods

put :: [a] -> Put #

get :: Get [a] #

putList :: [[a]] -> Put #

Binary a => Binary (Maybe a) 

Methods

put :: Maybe a -> Put #

get :: Get (Maybe a) #

putList :: [Maybe a] -> Put #

(Binary a, Integral a) => Binary (Ratio a) 

Methods

put :: Ratio a -> Put #

get :: Get (Ratio a) #

putList :: [Ratio a] -> Put #

Binary (Fixed a)

Since: 0.8.0.0

Methods

put :: Fixed a -> Put #

get :: Get (Fixed a) #

putList :: [Fixed a] -> Put #

Binary a => Binary (Complex a) 

Methods

put :: Complex a -> Put #

get :: Get (Complex a) #

putList :: [Complex a] -> Put #

Binary e => Binary (IntMap e) 

Methods

put :: IntMap e -> Put #

get :: Get (IntMap e) #

putList :: [IntMap e] -> Put #

Binary e => Binary (Tree e) 

Methods

put :: Tree e -> Put #

get :: Get (Tree e) #

putList :: [Tree e] -> Put #

Binary e => Binary (Seq e) 

Methods

put :: Seq e -> Put #

get :: Get (Seq e) #

putList :: [Seq e] -> Put #

Binary a => Binary (Set a) 

Methods

put :: Set a -> Put #

get :: Get (Set a) #

putList :: [Set a] -> Put #

(Binary a, Binary b) => Binary (Either a b) 

Methods

put :: Either a b -> Put #

get :: Get (Either a b) #

putList :: [Either a b] -> Put #

(Binary a, Binary b) => Binary (a, b) 

Methods

put :: (a, b) -> Put #

get :: Get (a, b) #

putList :: [(a, b)] -> Put #

(Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) 

Methods

put :: UArray i e -> Put #

get :: Get (UArray i e) #

putList :: [UArray i e] -> Put #

(Binary i, Ix i, Binary e) => Binary (Array i e) 

Methods

put :: Array i e -> Put #

get :: Get (Array i e) #

putList :: [Array i e] -> Put #

(Binary k, Binary e) => Binary (Map k e) 

Methods

put :: Map k e -> Put #

get :: Get (Map k e) #

putList :: [Map k e] -> Put #

(Binary a, Binary b, Binary c) => Binary (a, b, c) 

Methods

put :: (a, b, c) -> Put #

get :: Get (a, b, c) #

putList :: [(a, b, c)] -> Put #

(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) 

Methods

put :: (a, b, c, d) -> Put #

get :: Get (a, b, c, d) #

putList :: [(a, b, c, d)] -> Put #

(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) 

Methods

put :: (a, b, c, d, e) -> Put #

get :: Get (a, b, c, d, e) #

putList :: [(a, b, c, d, e)] -> Put #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a, b, c, d, e, f) 

Methods

put :: (a, b, c, d, e, f) -> Put #

get :: Get (a, b, c, d, e, f) #

putList :: [(a, b, c, d, e, f)] -> Put #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a, b, c, d, e, f, g) 

Methods

put :: (a, b, c, d, e, f, g) -> Put #

get :: Get (a, b, c, d, e, f, g) #

putList :: [(a, b, c, d, e, f, g)] -> Put #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h) => Binary (a, b, c, d, e, f, g, h) 

Methods

put :: (a, b, c, d, e, f, g, h) -> Put #

get :: Get (a, b, c, d, e, f, g, h) #

putList :: [(a, b, c, d, e, f, g, h)] -> Put #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i) => Binary (a, b, c, d, e, f, g, h, i) 

Methods

put :: (a, b, c, d, e, f, g, h, i) -> Put #

get :: Get (a, b, c, d, e, f, g, h, i) #

putList :: [(a, b, c, d, e, f, g, h, i)] -> Put #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i, Binary j) => Binary (a, b, c, d, e, f, g, h, i, j) 

Methods

put :: (a, b, c, d, e, f, g, h, i, j) -> Put #

get :: Get (a, b, c, d, e, f, g, h, i, j) #

putList :: [(a, b, c, d, e, f, g, h, i, j)] -> Put #