Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- encode :: (Monad m, Binary a) => a -> Proxy x' x () ByteString m ()
- encodePut :: Monad m => Put -> Proxy x' x () ByteString m ()
- decode :: (Monad m, Binary a) => Parser ByteString m (Either DecodingError a)
- decoded :: (Monad m, Binary a) => Lens' (Producer ByteString m r) (Producer a m (Either (DecodingError, Producer ByteString m r) r))
- decodeL :: (Monad m, Binary a) => Parser ByteString m (Either DecodingError (ByteOffset, a))
- decodedL :: (Monad m, Binary a) => Lens' (Producer ByteString m r) (Producer (ByteOffset, a) m (Either (DecodingError, Producer ByteString m r) r))
- decodeGet :: Monad m => Get a -> Parser ByteString m (Either DecodingError a)
- decodeGetL :: Monad m => Get a -> Parser ByteString m (Either DecodingError (ByteOffset, a))
- data DecodingError = DecodingError {
- deConsumed :: !ByteOffset
- deMessage :: !String
- data Word
- class Binary t where
- type Put = PutM ()
- data Get a
- type ByteOffset = Int64
- data Get a
- type Put = PutM ()
- data ByteString
- type Parser a (m :: Type -> Type) r = forall x. StateT (Producer a m x) m r
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
aByteString
m r
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) => Lens' (Producer ByteString m r) (Producer a m (Either (DecodingError, Producer ByteString m r) r)) Source #
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 #
decodeGetL :: Monad m => Get a -> Parser ByteString m (Either DecodingError (ByteOffset, a)) Source #
Types
data DecodingError Source #
DecodingError | |
|
Instances
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
Instances
Bounded Word | Since: base-2.1 |
Enum Word | Since: base-2.1 |
Eq Word | |
Integral Word | Since: base-2.1 |
Data Word | Since: base-4.0.0.0 |
Defined in Data.Data 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 # 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 |
Ord Word | |
Read Word | Since: base-4.5.0.0 |
Real Word | Since: base-2.1 |
Defined in GHC.Real toRational :: Word -> Rational # | |
Show Word | Since: base-2.1 |
Ix Word | Since: base-4.6.0.0 |
Binary Word | |
Hashable Word | |
Defined in Data.Hashable.Class | |
Lift Word | |
IArray UArray Word | |
Defined in Data.Array.Base 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 |
Foldable (UWord :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 # elem :: Eq a => a -> UWord a -> Bool # maximum :: Ord a => UWord a -> a # minimum :: Ord a => UWord a -> a # | |
Traversable (UWord :: Type -> Type) | Since: base-4.9.0.0 |
MArray (STUArray s) Word (ST s) | |
Defined in Data.Array.Base 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 |
Eq (URec Word p) | Since: base-4.9.0.0 |
Ord (URec Word p) | Since: base-4.9.0.0 |
Show (URec Word p) | Since: base-4.9.0.0 |
Generic (URec Word p) | Since: base-4.9.0.0 |
data URec Word (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Word :: k -> Type) | |
Defined in GHC.Generics | |
type Rep (URec Word p) | |
Defined in GHC.Generics |
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.
Nothing
Encode a value in the Put monad.
Decode a value in the Get monad
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
Binary Bool | |
Binary Char | |
Binary Double | |
Binary Float | |
Binary Int | |
Binary Int8 | |
Binary Int16 | |
Binary Int32 | |
Binary Int64 | |
Binary Integer | |
Binary Natural | Since: binary-0.7.3.0 |
Binary Ordering | |
Binary Word | |
Binary Word8 | |
Binary Word16 | |
Binary Word32 | |
Binary Word64 | |
Binary RuntimeRep | Since: binary-0.8.5.0 |
Defined in Data.Binary.Class | |
Binary VecCount | Since: binary-0.8.5.0 |
Binary VecElem | Since: binary-0.8.5.0 |
Binary SomeTypeRep | |
Defined in Data.Binary.Class | |
Binary () | |
Binary TyCon | Since: binary-0.8.5.0 |
Binary KindRep | Since: binary-0.8.5.0 |
Binary TypeLitSort | Since: binary-0.8.5.0 |
Defined in Data.Binary.Class | |
Binary Void | Since: binary-0.8.0.0 |
Binary Version | Since: binary-0.8.0.0 |
Binary All | Since: binary-0.8.4.0 |
Binary Any | Since: binary-0.8.4.0 |
Binary Fingerprint | Since: binary-0.7.6.0 |
Defined in Data.Binary.Class | |
Binary ShortByteString | |
Defined in Data.Binary.Class | |
Binary ByteString | |
Defined in Data.Binary.Class | |
Binary ByteString | |
Defined in Data.Binary.Class | |
Binary IntSet | |
Binary a => Binary [a] | |
Binary a => Binary (Maybe a) | |
(Binary a, Integral a) => Binary (Ratio a) | |
Binary a => Binary (Complex a) | |
Binary a => Binary (Min a) | Since: binary-0.8.4.0 |
Binary a => Binary (Max a) | Since: binary-0.8.4.0 |
Binary a => Binary (First a) | Since: binary-0.8.4.0 |
Binary a => Binary (Last a) | Since: binary-0.8.4.0 |
Binary m => Binary (WrappedMonoid m) | Since: binary-0.8.4.0 |
Defined in Data.Binary.Class | |
Binary a => Binary (Option a) | Since: binary-0.8.4.0 |
Binary a => Binary (Identity a) | |
Binary a => Binary (First a) | Since: binary-0.8.4.0 |
Binary a => Binary (Last a) | Since: binary-0.8.4.0 |
Binary a => Binary (Dual a) | Since: binary-0.8.4.0 |
Binary a => Binary (Sum a) | Since: binary-0.8.4.0 |
Binary a => Binary (Product a) | Since: binary-0.8.4.0 |
Binary a => Binary (NonEmpty a) | Since: binary-0.8.4.0 |
Binary e => Binary (IntMap e) | |
Binary e => Binary (Tree e) | |
Binary e => Binary (Seq e) | |
Binary a => Binary (Set a) | |
(Binary a, Binary b) => Binary (Either a b) | |
Typeable a => Binary (TypeRep a) | |
(Binary a, Binary b) => Binary (a, b) | |
(Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) | |
(Binary i, Ix i, Binary e) => Binary (Array i e) | |
Binary (Fixed a) | Since: binary-0.8.0.0 |
(Binary a, Binary b) => Binary (Arg a b) | Since: binary-0.8.4.0 |
(Binary k, Binary e) => Binary (Map k e) | |
(Binary a, Binary b, Binary c) => Binary (a, b, c) | |
Binary (f a) => Binary (Alt f a) | Since: binary-0.8.4.0 |
(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) | |
(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) | |
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a, b, c, d, e, f) | |
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a, b, c, d, e, f, g) | |
(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) | |
(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) | |
(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) | |
Instances
Monad Get | |
Functor Get | |
MonadFail Get | |
Defined in Data.Binary.Get.Internal | |
Applicative Get | |
Alternative Get | Since: binary-0.7.0.0 |
MonadPlus Get | Since: binary-0.7.1.0 |
type ByteOffset = Int64 #
An offset, counted in bytes.
Instances
Monad Get | |
Functor Get | |
MonadFail Get | |
Defined in Data.Binary.Get.Internal | |
Applicative Get | |
Alternative Get | Since: binary-0.7.0.0 |
MonadPlus Get | Since: binary-0.7.1.0 |
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
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