Safe Haskell | None |
---|---|
Language | Haskell2010 |
Read and write values of types that implement Binary
.
Synopsis
- data ReaderError = ReaderGetError {}
- newtype Reader m = Reader {}
- newReader :: (MonadConc m, MonadIO m) => Handle -> m (Reader m)
- newReaderWith :: MonadConc m => m ByteString -> m (Reader m)
- mapReader :: (forall a. m a -> n a) -> Reader m -> Reader n
- newtype Writer m = Writer {}
- newWriter :: MonadIO m => Handle -> Writer m
- newWriterWith :: Functor m => (ByteString -> m ()) -> Writer m
- mapWriter :: (forall x. m x -> n x) -> Writer m -> Writer n
- newPipe :: (MonadConc m, MonadIO m) => m (Reader m, Writer m)
- data Duplex m = Duplex {
- duplexWriter :: Writer m
- duplexReader :: Reader m
- newDuplex :: (MonadConc m, MonadIO m) => Handle -> m (Duplex m)
- newDuplexWith :: MonadConc m => m ByteString -> (ByteString -> m ()) -> m (Duplex m)
- mapDuplex :: (forall a. m a -> n a) -> Duplex m -> Duplex n
- class CanGet r m where
- read :: (CanGet r m, Binary a) => r -> m a
- isEmpty :: CanGet r m => r -> m Bool
- class CanPut w m where
- write :: (CanPut w m, Binary a) => w -> a -> m ()
Reader
data ReaderError Source #
An error that can occur during reading
Since: 0.4.0
ReaderGetError | Error from the |
|
Instances
Show ReaderError Source # | |
Defined in Data.Binary.IO.Lifted showsPrec :: Int -> ReaderError -> ShowS # show :: ReaderError -> String # showList :: [ReaderError] -> ShowS # | |
Exception ReaderError Source # | |
Defined in Data.Binary.IO.Lifted |
Since: 0.4.0
Create a new reader.
Inherits properties from newReaderWith
.
Other threads reading from the Handle
will interfere with read operations of the Reader
.
However, the Reader
itself is thread-safe and can be utilized concurrently.
The given Handle
will be swiched to binary mode via hSetBinaryMode
.
Since: 0.4.0
:: MonadConc m | |
=> m ByteString | Chunk provider |
-> m (Reader m) |
Create a new Reader
using an action that provides the chunks.
The chunk producers indicates the end of the stream by returning an empty
ByteString
.
Reading using the Reader
may throw ReaderError
.
The internal position of the Reader
is not advanced when it throws an exception during reading.
This has the consequence that if you're trying to read with the same faulty Get
operation multiple times, you will always receive an exception.
The Reader
is safe to use concurrently.
Since: 0.4.0
mapReader :: (forall a. m a -> n a) -> Reader m -> Reader n Source #
Transform the underlying functor.
Since: 0.4.0
Writer
Since: 0.4.0
:: Functor m | |
=> (ByteString -> m ()) | Chunk writer |
-> Writer m |
Create a writer using a function that handles the output chunks.
Since: 0.4.0
mapWriter :: (forall x. m x -> n x) -> Writer m -> Writer n Source #
Transform the underlying functor.
Since: 0.4.0
Pipe
Duplex
Duplex | |
|
:: MonadConc m | |
=> m ByteString | Input chunk producer for |
-> (ByteString -> m ()) | Chunk writer for |
-> m (Duplex m) |
Combines newReaderWith
and newWriterWith
.
Since: 0.4.0
mapDuplex :: (forall a. m a -> n a) -> Duplex m -> Duplex n Source #
Transform the underlying functor.
Since: 0.4.0
Classes
class CanGet r m where Source #
r
can execute Get
operations in m
Since: 0.4.0
Read something from r
. Inherits properties from runGet
.
Since: 0.4.0
Check if there is no more input to consume. This function may block. All properties of runGet
apply to this function as well.
Since: 0.4.0