pipes-binary-0.3.0.1: Encode and decode binary streams using the pipes and binary libraries.

Safe HaskellSafe-Inferred

Pipes.Binary

Contents

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 Iso' a b = forall f p. (Functor f, Profunctor p) => p b (f b) -> p a (f a)

Synopsis

Encoding

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

Convert a value to a byte stream.

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.

Explicit Put

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

Like encode, except this uses an explicit Put.

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) => Iso' (Producer ByteString m r) (Producer a m (Either (DecodingError, Producer ByteString m r) r))Source

An isomorphism between a stream of bytes and a stream of decoded values.

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) => Iso' (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

deConsumed :: !ByteOffset

Number of bytes consumed before the error

deMessage :: !String

Error message

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

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