| Copyright | Soostone Inc, Winterland |
|---|---|
| License | BSD3 |
| Maintainer | Michael Xavier, Winterland |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
System.IO.Streams.Cereal
Description
Use cereal to encode/decode io-streams.
- getFromStream :: Get r -> InputStream ByteString -> IO (Maybe r)
- putToStream :: Put -> OutputStream ByteString -> IO ()
- getInputStream :: Get r -> InputStream ByteString -> IO (InputStream r)
- decodeInputStream :: Serialize r => InputStream ByteString -> IO (InputStream r)
- putInputStream :: Putter r -> InputStream r -> IO (InputStream ByteString)
- encodeInputStream :: Serialize r => InputStream r -> IO (InputStream ByteString)
- putOutputStream :: Putter r -> OutputStream ByteString -> IO (OutputStream r)
- encodeOutputStream :: Serialize r => OutputStream ByteString -> IO (OutputStream r)
- data DecodeException = DecodeException String
single element encode/decode
getFromStream :: Get r -> InputStream ByteString -> IO (Maybe r) Source #
Take a Get and an InputStream and decode a
value. Consumes only as much input as necessary to decode the
value. Unconsumed input will be unread. If there is
an error while deserializing, a DecodeException is thrown, and
unconsumed part will be unread. To simplify upstream generation,
all empty ByteString will be filtered out and not passed to cereal,
only EOFs/Nothing will close a cereal decoder.
Examples:
>>>import qualified System.IO.Streams as Streams>>>getFromStream (get :: Get String) =<< Streams.fromByteString (Data.ByteString.drop 1 $ runPut $ put "encode me")*** Exception: System.IO.Streams.Cereal: cereal decode exception: too few bytes From: demandInput
putToStream :: Put -> OutputStream ByteString -> IO () Source #
write a Put to an OutputStream
InputStream encode/decode
getInputStream :: Get r -> InputStream ByteString -> IO (InputStream r) Source #
Convert a stream of individual encoded ByteStrings to a stream
of Results. Throws a DecodeException on error.
Example:
>>>Streams.toList =<< getInputStream (get :: Get String) =<< Streams.fromList (map (runPut . put) ["foo", "bar"])["foo","bar"]
decodeInputStream :: Serialize r => InputStream ByteString -> IO (InputStream r) Source #
typeclass version of getInputStream
putInputStream :: Putter r -> InputStream r -> IO (InputStream ByteString) Source #
Convert a stream of serializable objects into a stream of
individual ByteStrings with a Putter, while most of the time
these function are not needed, they can be used in round-trip test.
Example:
>>>Streams.toList =<< getInputStream (get :: Get String) =<< encodeInputStream =<< Streams.fromList ["foo","bar"]["foo","bar"]
encodeInputStream :: Serialize r => InputStream r -> IO (InputStream ByteString) Source #
typeclass version of putInputStream
OutputStream encode
putOutputStream :: Putter r -> OutputStream ByteString -> IO (OutputStream r) Source #
create an OutputStream of serializable values from an OutputStream
of bytestrings with a Putter.
encodeOutputStream :: Serialize r => OutputStream ByteString -> IO (OutputStream r) Source #
typeclass version of putOutputStream