pipes-binary-0.4.3: Encode and decode binary streams using the pipes and binary libraries.
Safe HaskellNone
LanguageHaskell2010

Pipes.Binary

Description

pipes utilities for encoding and decoding values as byte streams

The tutorial at the bottom of this module illustrates how to use this library.

In this module, the following type synonym compatible with the lens, lens-family and lens-family-core libraries is used but not exported:

type Lens' a b = forall f . Functor f => (b -> f b) -> (a -> f a)
Synopsis

Encoding

encode :: (Monad m, Binary a) => a -> Proxy x' x () ByteString m () Source #

Convert a value to a byte stream.

encode :: (Monad m, Binary a) => a -> Producer' ByteString m ()

Keep in mind that a single encode value might be split into many ByteString chunks, that is, the lenght of the obtained Producer might be greater than 1.

Hint: You can easily turn this Producer' into a Pipe that encodes Binary instances as they flow downstream using:

for cat encode :: (Monad m, Binary a) => Pipe a ByteString m r

Explicit Put

encodePut :: Monad m => Put -> Proxy x' x () ByteString m () Source #

Like encode, except this uses an explicit Put.

encodePut :: (Monad m) => Put -> Producer' ByteString m ()

Decoding

decode :: (Monad m, Binary a) => Parser ByteString m (Either DecodingError a) Source #

Parse a value from a byte stream.

decoded :: (Monad m, Binary a) => Lens' (Producer ByteString m r) (Producer a m (Either (DecodingError, Producer ByteString m r) r)) Source #

Improper lens that turns a stream of bytes into a stream of decoded values.

By improper lens we mean that in practice you can't expect the Monad Morphism Laws to be true when using decoded with zoom.

zoom decoded (return r) /= return r
zoom decoded (m >>= f)  /= zoom decoded m >>= zoom decoded . f

Including lengths

decodeL :: (Monad m, Binary a) => Parser ByteString m (Either DecodingError (ByteOffset, a)) Source #

Like decode, but also returns the length of input consumed in order to to decode the value.

decodedL :: (Monad m, Binary a) => Lens' (Producer ByteString m r) (Producer (ByteOffset, a) m (Either (DecodingError, Producer ByteString m r) r)) Source #

Like decoded, except this tags each decoded value with the length of input consumed in order to decode it.

Explicit Get

decodeGet :: Monad m => Get a -> Parser ByteString m (Either DecodingError a) Source #

Like decode, except this requires an explicit Get instead of any Binary instance.

decodeGetL :: Monad m => Get a -> Parser ByteString m (Either DecodingError (ByteOffset, a)) Source #

Like decodeL, except this requires an explicit Get instead of any Binary instance.

Types

data DecodingError Source #

A Get decoding error, as provided by Fail.

Constructors

DecodingError 

Fields

Instances

Instances details
Eq DecodingError Source # 
Instance details

Defined in Pipes.Binary

Data DecodingError Source # 
Instance details

Defined in Pipes.Binary

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DecodingError -> c DecodingError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DecodingError #

toConstr :: DecodingError -> Constr #

dataTypeOf :: DecodingError -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DecodingError) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DecodingError) #

gmapT :: (forall b. Data b => b -> b) -> DecodingError -> DecodingError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DecodingError -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DecodingError -> r #

gmapQ :: (forall d. Data d => d -> u) -> DecodingError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DecodingError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DecodingError -> m DecodingError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DecodingError -> m DecodingError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DecodingError -> m DecodingError #

Read DecodingError Source # 
Instance details

Defined in Pipes.Binary

Show DecodingError Source # 
Instance details

Defined in Pipes.Binary

Generic DecodingError Source # 
Instance details

Defined in Pipes.Binary

Associated Types

type Rep DecodingError :: Type -> Type #

Exception DecodingError Source # 
Instance details

Defined in Pipes.Binary

Error DecodingError Source # 
Instance details

Defined in Pipes.Binary

type Rep DecodingError Source # 
Instance details

Defined in Pipes.Binary

type Rep DecodingError = D1 ('MetaData "DecodingError" "Pipes.Binary" "pipes-binary-0.4.3-HBC6Wyb25jwBqlUZ7vZ43r" 'False) (C1 ('MetaCons "DecodingError" 'PrefixI 'True) (S1 ('MetaSel ('Just "deConsumed") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 ByteOffset) :*: S1 ('MetaSel ('Just "deMessage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)))

Exports

The following types are re-exported from this module for your convenience:

From Data.Binary
Binary
From Data.Binary.Put
Put
From Data.Binary.Get
Get, ByteOffset
From Data.ByteString
ByteString
From Pipes.Parse
Parser

data Word #

A Word is an unsigned integral type, with the same size as Int.

Instances

Instances details
Bounded Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Eq Word 
Instance details

Defined in GHC.Classes

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Integral Word

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Data Word

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word #

toConstr :: Word -> Constr #

dataTypeOf :: Word -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) #

gmapT :: (forall b. Data b => b -> b) -> Word -> Word #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word #

Num Word

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Ord Word 
Instance details

Defined in GHC.Classes

Methods

compare :: Word -> Word -> Ordering #

(<) :: Word -> Word -> Bool #

(<=) :: Word -> Word -> Bool #

(>) :: Word -> Word -> Bool #

(>=) :: Word -> Word -> Bool #

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Read Word

Since: base-4.5.0.0

Instance details

Defined in GHC.Read

Real Word

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

toRational :: Word -> Rational #

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Ix Word

Since: base-4.6.0.0

Instance details

Defined in GHC.Ix

Methods

range :: (Word, Word) -> [Word] #

index :: (Word, Word) -> Word -> Int #

unsafeIndex :: (Word, Word) -> Word -> Int #

inRange :: (Word, Word) -> Word -> Bool #

rangeSize :: (Word, Word) -> Int #

unsafeRangeSize :: (Word, Word) -> Int #

Binary Word 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word -> Put #

get :: Get Word #

putList :: [Word] -> Put #

Hashable Word 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Lift Word 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word -> Q Exp #

liftTyped :: Word -> Q (TExp Word) #

IArray UArray Word 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word -> (i, i) #

numElements :: Ix i => UArray i Word -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word)] -> UArray i Word

unsafeAt :: Ix i => UArray i Word -> Int -> Word

unsafeReplace :: Ix i => UArray i Word -> [(Int, Word)] -> UArray i Word

unsafeAccum :: Ix i => (Word -> e' -> Word) -> UArray i Word -> [(Int, e')] -> UArray i Word

unsafeAccumArray :: Ix i => (Word -> e' -> Word) -> Word -> (i, i) -> [(Int, e')] -> UArray i Word

Generic1 (URec Word :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Word) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Word a -> Rep1 (URec Word) a #

to1 :: forall (a :: k0). Rep1 (URec Word) a -> URec Word a #

Foldable (UWord :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UWord m -> m #

foldMap :: Monoid m => (a -> m) -> UWord a -> m #

foldMap' :: Monoid m => (a -> m) -> UWord a -> m #

foldr :: (a -> b -> b) -> b -> UWord a -> b #

foldr' :: (a -> b -> b) -> b -> UWord a -> b #

foldl :: (b -> a -> b) -> b -> UWord a -> b #

foldl' :: (b -> a -> b) -> b -> UWord a -> b #

foldr1 :: (a -> a -> a) -> UWord a -> a #

foldl1 :: (a -> a -> a) -> UWord a -> a #

toList :: UWord a -> [a] #

null :: UWord a -> Bool #

length :: UWord a -> Int #

elem :: Eq a => a -> UWord a -> Bool #

maximum :: Ord a => UWord a -> a #

minimum :: Ord a => UWord a -> a #

sum :: Num a => UWord a -> a #

product :: Num a => UWord a -> a #

Traversable (UWord :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UWord a -> f (UWord b) #

sequenceA :: Applicative f => UWord (f a) -> f (UWord a) #

mapM :: Monad m => (a -> m b) -> UWord a -> m (UWord b) #

sequence :: Monad m => UWord (m a) -> m (UWord a) #

MArray (STUArray s) Word (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word -> ST s Int

newArray :: Ix i => (i, i) -> Word -> ST s (STUArray s i Word) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word)

unsafeRead :: Ix i => STUArray s i Word -> Int -> ST s Word

unsafeWrite :: Ix i => STUArray s i Word -> Int -> Word -> ST s ()

Functor (URec Word :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Eq (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Show (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Generic (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

data URec Word (p :: k)

Used for marking occurrences of Word#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Word (p :: k) = UWord {}
type Rep1 (URec Word :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec Word :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: k -> Type)))
type Rep (URec Word p) 
Instance details

Defined in GHC.Generics

type Rep (URec Word p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: Type -> Type)))

class Binary t where #

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.

Minimal complete definition

Nothing

Methods

put :: t -> Put #

Encode a value in the Put monad.

get :: Get t #

Decode a value in the Get monad

putList :: [t] -> Put #

Encode a list of values in the Put monad. The default implementation may be overridden to be more efficient but must still have the same encoding format.

Instances

Instances details
Binary Bool 
Instance details

Defined in Data.Binary.Class

Methods

put :: Bool -> Put #

get :: Get Bool #

putList :: [Bool] -> Put #

Binary Char 
Instance details

Defined in Data.Binary.Class

Methods

put :: Char -> Put #

get :: Get Char #

putList :: [Char] -> Put #

Binary Double 
Instance details

Defined in Data.Binary.Class

Methods

put :: Double -> Put #

get :: Get Double #

putList :: [Double] -> Put #

Binary Float 
Instance details

Defined in Data.Binary.Class

Methods

put :: Float -> Put #

get :: Get Float #

putList :: [Float] -> Put #

Binary Int 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int -> Put #

get :: Get Int #

putList :: [Int] -> Put #

Binary Int8 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int8 -> Put #

get :: Get Int8 #

putList :: [Int8] -> Put #

Binary Int16 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int16 -> Put #

get :: Get Int16 #

putList :: [Int16] -> Put #

Binary Int32 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int32 -> Put #

get :: Get Int32 #

putList :: [Int32] -> Put #

Binary Int64 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int64 -> Put #

get :: Get Int64 #

putList :: [Int64] -> Put #

Binary Integer 
Instance details

Defined in Data.Binary.Class

Methods

put :: Integer -> Put #

get :: Get Integer #

putList :: [Integer] -> Put #

Binary Natural

Since: binary-0.7.3.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Natural -> Put #

get :: Get Natural #

putList :: [Natural] -> Put #

Binary Ordering 
Instance details

Defined in Data.Binary.Class

Methods

put :: Ordering -> Put #

get :: Get Ordering #

putList :: [Ordering] -> Put #

Binary Word 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word -> Put #

get :: Get Word #

putList :: [Word] -> Put #

Binary Word8 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word8 -> Put #

get :: Get Word8 #

putList :: [Word8] -> Put #

Binary Word16 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word16 -> Put #

get :: Get Word16 #

putList :: [Word16] -> Put #

Binary Word32 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word32 -> Put #

get :: Get Word32 #

putList :: [Word32] -> Put #

Binary Word64 
Instance details

Defined in Data.Binary.Class

Methods

put :: Word64 -> Put #

get :: Get Word64 #

putList :: [Word64] -> Put #

Binary RuntimeRep

Since: binary-0.8.5.0

Instance details

Defined in Data.Binary.Class

Binary VecCount

Since: binary-0.8.5.0

Instance details

Defined in Data.Binary.Class

Methods

put :: VecCount -> Put #

get :: Get VecCount #

putList :: [VecCount] -> Put #

Binary VecElem

Since: binary-0.8.5.0

Instance details

Defined in Data.Binary.Class

Methods

put :: VecElem -> Put #

get :: Get VecElem #

putList :: [VecElem] -> Put #

Binary SomeTypeRep 
Instance details

Defined in Data.Binary.Class

Binary () 
Instance details

Defined in Data.Binary.Class

Methods

put :: () -> Put #

get :: Get () #

putList :: [()] -> Put #

Binary TyCon

Since: binary-0.8.5.0

Instance details

Defined in Data.Binary.Class

Methods

put :: TyCon -> Put #

get :: Get TyCon #

putList :: [TyCon] -> Put #

Binary KindRep

Since: binary-0.8.5.0

Instance details

Defined in Data.Binary.Class

Methods

put :: KindRep -> Put #

get :: Get KindRep #

putList :: [KindRep] -> Put #

Binary TypeLitSort

Since: binary-0.8.5.0

Instance details

Defined in Data.Binary.Class

Binary Void

Since: binary-0.8.0.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Void -> Put #

get :: Get Void #

putList :: [Void] -> Put #

Binary Version

Since: binary-0.8.0.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

Binary All

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: All -> Put #

get :: Get All #

putList :: [All] -> Put #

Binary Any

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Any -> Put #

get :: Get Any #

putList :: [Any] -> Put #

Binary Fingerprint

Since: binary-0.7.6.0

Instance details

Defined in Data.Binary.Class

Binary ShortByteString 
Instance details

Defined in Data.Binary.Class

Binary ByteString 
Instance details

Defined in Data.Binary.Class

Binary ByteString 
Instance details

Defined in Data.Binary.Class

Binary IntSet 
Instance details

Defined in Data.Binary.Class

Methods

put :: IntSet -> Put #

get :: Get IntSet #

putList :: [IntSet] -> Put #

Binary a => Binary [a] 
Instance details

Defined in Data.Binary.Class

Methods

put :: [a] -> Put #

get :: Get [a] #

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

Binary a => Binary (Maybe a) 
Instance details

Defined in Data.Binary.Class

Methods

put :: Maybe a -> Put #

get :: Get (Maybe a) #

putList :: [Maybe a] -> Put #

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

Defined in Data.Binary.Class

Methods

put :: Ratio a -> Put #

get :: Get (Ratio a) #

putList :: [Ratio a] -> Put #

Binary a => Binary (Complex a) 
Instance details

Defined in Data.Binary.Class

Methods

put :: Complex a -> Put #

get :: Get (Complex a) #

putList :: [Complex a] -> Put #

Binary a => Binary (Min a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Min a -> Put #

get :: Get (Min a) #

putList :: [Min a] -> Put #

Binary a => Binary (Max a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Max a -> Put #

get :: Get (Max a) #

putList :: [Max a] -> Put #

Binary a => Binary (First a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: First a -> Put #

get :: Get (First a) #

putList :: [First a] -> Put #

Binary a => Binary (Last a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Last a -> Put #

get :: Get (Last a) #

putList :: [Last a] -> Put #

Binary m => Binary (WrappedMonoid m)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Binary a => Binary (Option a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Option a -> Put #

get :: Get (Option a) #

putList :: [Option a] -> Put #

Binary a => Binary (Identity a) 
Instance details

Defined in Data.Binary.Class

Methods

put :: Identity a -> Put #

get :: Get (Identity a) #

putList :: [Identity a] -> Put #

Binary a => Binary (First a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: First a -> Put #

get :: Get (First a) #

putList :: [First a] -> Put #

Binary a => Binary (Last a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Last a -> Put #

get :: Get (Last a) #

putList :: [Last a] -> Put #

Binary a => Binary (Dual a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Dual a -> Put #

get :: Get (Dual a) #

putList :: [Dual a] -> Put #

Binary a => Binary (Sum a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Sum a -> Put #

get :: Get (Sum a) #

putList :: [Sum a] -> Put #

Binary a => Binary (Product a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Product a -> Put #

get :: Get (Product a) #

putList :: [Product a] -> Put #

Binary a => Binary (NonEmpty a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: NonEmpty a -> Put #

get :: Get (NonEmpty a) #

putList :: [NonEmpty a] -> Put #

Binary e => Binary (IntMap e) 
Instance details

Defined in Data.Binary.Class

Methods

put :: IntMap e -> Put #

get :: Get (IntMap e) #

putList :: [IntMap e] -> Put #

Binary e => Binary (Tree e) 
Instance details

Defined in Data.Binary.Class

Methods

put :: Tree e -> Put #

get :: Get (Tree e) #

putList :: [Tree e] -> Put #

Binary e => Binary (Seq e) 
Instance details

Defined in Data.Binary.Class

Methods

put :: Seq e -> Put #

get :: Get (Seq e) #

putList :: [Seq e] -> Put #

Binary a => Binary (Set a) 
Instance details

Defined in Data.Binary.Class

Methods

put :: Set a -> Put #

get :: Get (Set a) #

putList :: [Set a] -> Put #

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

Defined in Data.Binary.Class

Methods

put :: Either a b -> Put #

get :: Get (Either a b) #

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

Typeable a => Binary (TypeRep a) 
Instance details

Defined in Data.Binary.Class

Methods

put :: TypeRep a -> Put #

get :: Get (TypeRep a) #

putList :: [TypeRep a] -> Put #

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

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

Methods

put :: Array i e -> Put #

get :: Get (Array i e) #

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

Binary (Fixed a)

Since: binary-0.8.0.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Fixed a -> Put #

get :: Get (Fixed a) #

putList :: [Fixed a] -> Put #

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

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Arg a b -> Put #

get :: Get (Arg a b) #

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

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

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

Methods

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

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

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

Binary (f a) => Binary (Alt f a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Alt f a -> Put #

get :: Get (Alt f a) #

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

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

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

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) 
Instance details

Defined in Data.Binary.Class

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 #

type Put = PutM () #

Put merely lifts Builder into a Writer monad, applied to ().

data Get a #

Instances

Instances details
Monad Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

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

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

return :: a -> Get a #

Functor Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

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

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

MonadFail Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

fail :: String -> Get a #

Applicative Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

pure :: a -> Get a #

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

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

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

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

Alternative Get

Since: binary-0.7.0.0

Instance details

Defined in Data.Binary.Get.Internal

Methods

empty :: Get a #

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

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

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

MonadPlus Get

Since: binary-0.7.1.0

Instance details

Defined in Data.Binary.Get.Internal

Methods

mzero :: Get a #

mplus :: Get a -> Get a -> Get a #

type ByteOffset = Int64 #

An offset, counted in bytes.

data Get a #

Instances

Instances details
Monad Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

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

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

return :: a -> Get a #

Functor Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

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

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

MonadFail Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

fail :: String -> Get a #

Applicative Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

pure :: a -> Get a #

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

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

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

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

Alternative Get

Since: binary-0.7.0.0

Instance details

Defined in Data.Binary.Get.Internal

Methods

empty :: Get a #

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

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

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

MonadPlus Get

Since: binary-0.7.1.0

Instance details

Defined in Data.Binary.Get.Internal

Methods

mzero :: Get a #

mplus :: Get a -> Get a -> Get a #

type Put = PutM () #

Put merely lifts Builder into a Writer monad, applied to ().

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Data ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

IsString ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Binary ByteString 
Instance details

Defined in Data.Binary.Class

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

type Parser a (m :: Type -> Type) r = forall x. StateT (Producer a m x) m r #

A Parser is an action that reads from and writes to a stored Producer

Tutorial

Use encode to convert values to byte streams

-- example.hs

import Pipes
import qualified Pipes.Prelude as P
import Pipes.Binary

readInts :: Int -> Producer Int IO ()
readInts n = P.readLn >-> P.take n

encodedValues :: Producer ByteString IO ()
encodedValues = do
    for (readInts 3) encode  -- Encode 3 Ints read from user input
    encode 'C'               -- Encode a 'Char'
    encode True              -- Encode a 'Bool'

Use decode to parse a single decoded value or decoded to access a stream of decoded values:

-- example.hs

import Data.ByteString (ByteString)
import Pipes.Parse
import Prelude hiding (splitAt)

-- We need to import 'zoom', which can be found in many packages and all work
-- equally fine for our purposes. Read "Pipes.Parse.Tutorial" for details.
--
-- * From the package @lens-family-core@: 'Lens.Family.State.Strict.zoom'
-- * From the package @lens-family@:      'Lens.Family2.State.Strict.zoom'
-- * From the package @lens@:             'Control.Lens.Zoom.zoom'
import Lens.Family.State.Strict (zoom)

decoder :: Parser ByteString IO ()
decoder = do
    xs <- zoom (decoded . splitAt 3) drawAll      -- Decode up to three 'Int's
    lift $ print (xs :: [Int])
    y  <- decode                                  -- Decode a single 'Char'
    lift $ print (y :: Either DecodingError Char)
    z  <- zoom decoded draw                       -- Same as 'decode', but
    lift $ print (z :: Maybe Bool)                -- with a 'Maybe'

main = evalStateT decoder encodedValues

Here are some example inputs:

$ ./example
1<Enter>
2<Enter>
3<Enter>
[1,2,3]
Right 'C'
Just True
$ ./example
<Ctrl-D>
[]
Right 'C'
Just True