streaming-binary-0.3.0.1: Streaming interface to binary.

Safe HaskellNone
LanguageHaskell2010

Streaming.Binary

Description

This module implements a method to ingest a sequence of Data.Binary encoded records using bounded memory. Minimal example:

{-# LANGUAGE TypeApplications #-}

import Data.Function ((&))
import qualified Data.ByteString.Streaming as Q
import Streaming
import Streaming.Binary
import qualified Streaming.Prelude as S

-- Interpret all bytes on stdin as a sequence of integers.
-- Print them on-the-fly on stdout.
main = Q.getContents & decoded @Int & S.print

Synopsis

Documentation

decode :: (Binary a, Monad m) => ByteString m r -> m (ByteString m r, Int64, Either String a) Source #

Decode a single element from a streaming bytestring. Returns any leftover input, the number of bytes consumed, and either an error string or the element if decoding succeeded.

decodeWith :: Monad m => Get a -> ByteString m r -> m (ByteString m r, Int64, Either String a) Source #

Like decode, but with an explicitly provided decoder.

decoded :: (Binary a, Monad m) => ByteString m r -> Stream (Of a) m (ByteString m r, Int64, Either String r) Source #

Decode a sequence of elements from a streaming bytestring. Returns any leftover input, the number of bytes consumed, and either an error string or the return value if there were no errors. Decoding stops at the first error.

decodedWith :: Monad m => Get a -> ByteString m r -> Stream (Of a) m (ByteString m r, Int64, Either String r) Source #

Like decoded, but with an explicitly provided decoder.

encode :: (Binary a, MonadIO m) => a -> ByteString m () Source #

Encode a single element.

encodeWith :: MonadIO m => (a -> Put) -> a -> ByteString m () Source #

Like encode, but with an explicitly provided encoder.

encoded :: (Binary a, MonadIO m) => Stream (Of a) IO () -> ByteString m () Source #

Encode a stream of elements to a streaming bytestring.

encodedWith :: MonadIO m => (a -> Put) -> Stream (Of a) IO () -> ByteString m () Source #

Like encoded, but with an explicitly provided encoder.