Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- serialise :: (Serialise x, Monad m) => x -> Producer' ByteString m ()
- encode :: Monad m => Encoding -> Producer' ByteString m ()
- deserialise :: (MonadIO m, Serialise a) => Parser ByteString m (Either DeserialiseFailure (ByteOffset, a))
- decode :: MonadIO m => (forall s. Decoder s x) -> Parser ByteString m (Either DeserialiseFailure (ByteOffset, x))
Encoding
:: (Serialise x, Monad m) | |
=> x | |
-> Producer' ByteString m () |
Renders x
to a byte stream using its Serialise
instance.
:: Monad m | |
=> Encoding | |
-> Producer' ByteString m () |
Renders an Encoding
to a byte stream.
Decoding
:: (MonadIO m, Serialise a) | |
=> Parser ByteString m (Either DeserialiseFailure (ByteOffset, a)) |
Parses x
from a byte stream using its Serialise
instance.
Also returns the number of bytes consumed in order to to decode the value.
Implementation note: No, ideally this function shouldn't run in IO
. But
unfortunately, the underlying deserialiseIncremental
and its use of
ST
, which becomes both covariant and contravariant in
Parser
, make removing the IO
tricky. The only IO
this function
performs is stToIO
.
:: MonadIO m | |
=> (forall s. Decoder s x) | |
-> Parser ByteString m (Either DeserialiseFailure (ByteOffset, x)) |
Parses @x“ from a byte stream using the given Decoder
.
Also returns the number of bytes consumed in order to to decode the value.
Implementation note: No, ideally this function shouldn't run in IO
. But
unfortunately, the underlying deserialiseIncremental
and its use of
ST
, which becomes both covariant and contravariant in
Parser
, make removing the IO
tricky. The only IO
this function
performs is stToIO
.