Copyright | Petter Bergman, Winterland |
---|---|
License | BSD3 |
Maintainer | Winterland |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
System.IO.Streams.Binary
Description
Use binary to encode/decode io-streams.
- getFromStream :: Get a -> InputStream ByteString -> IO (Maybe a)
- decodeFromStream :: Binary a => InputStream ByteString -> IO (Maybe a)
- putToStream :: Binary a => Maybe a -> OutputStream ByteString -> IO ()
- getInputStream :: Get a -> InputStream ByteString -> IO (InputStream a)
- decodeInputStream :: Binary a => InputStream ByteString -> IO (InputStream a)
- putOutputStream :: (a -> Put) -> OutputStream ByteString -> IO (OutputStream a)
- encodeOutputStream :: Binary a => OutputStream ByteString -> IO (OutputStream a)
- data DecodeException = DecodeException ByteString ByteOffset String
single element encode/decode
getFromStream :: Get a -> InputStream ByteString -> IO (Maybe a) 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. binary decoder use Nothing
to indicate input end, so EOFs/Nothing will close a binary decoder.
Examples:
>>>
import qualified System.IO.Streams as Streams
>>>
getFromStream (get :: Get String) =<< Streams.fromLazyByteString (Data.ByteString.Lazy.drop 1 $ runPut $ put "encode me")
*** Exception: System.IO.Streams.Binary: binary decode exception: offset 16, "not enough bytes"
decodeFromStream :: Binary a => InputStream ByteString -> IO (Maybe a) Source
typeclass version of getFromStream
putToStream :: Binary a => Maybe a -> OutputStream ByteString -> IO () Source
Write an instance of Binary
to an OutputStream
.
InputStream
encode/decode
getInputStream :: Get a -> InputStream ByteString -> IO (InputStream a) Source
Convert a stream of individual encoded ByteString
s to a stream
of Results. Throws a DecodeException
on error.
decodeInputStream :: Binary a => InputStream ByteString -> IO (InputStream a) Source
typeclass version of getInputStream
OutputStream
encode
putOutputStream :: (a -> Put) -> OutputStream ByteString -> IO (OutputStream a) Source
create an OutputStream
of serializable values from an OutputStream
of bytestrings with a Putter
.
encodeOutputStream :: Binary a => OutputStream ByteString -> IO (OutputStream a) Source
typeclass version of putOutputStream
exception type
data DecodeException Source
An Exception raised when binary decoding fails.
it contains offset information where cereal don't.
Constructors
DecodeException ByteString ByteOffset String |
Instances