Safe Haskell | None |
---|---|
Language | Haskell98 |
This module provide different utility functions that allow to use safe higher level usage.
Conduit pairs allow creation of an internal datastructure that acts as a bridge, and provides input and output conduits. The structure itself is hidden internally and can't be used directly, this provide an additional safeness.
In order to create a bridge from your own datastructures you need to do the following:
- Make it an instance of
UnboundedStream
orBoundedStream
depending on it's properties:
instance BoundedStream (Proxy2 TBMQueue) TBMQueue where mkBStream _ i = atomically $ newTBMQueue i
- Add
IsConduit
instance.
instance MonadIO m => IsConduit m TBMQueue where mkSource = sourceTBMQueue mkSink = flip sinkTBMQueue True
- Use "pair" or "pairBounded" to create a bridge. Because bridge data structure is hidden and not seen in parameters, we need proxy type to help compiler to choose type, we use Proxy2 for that.
pairTBMQueue = pairBounded (proxy2 :: Proxy2 TBMQueue a)
- Now we can create a pair of conduits:
(src, snk) <- pairTBMQueue 32 Control.Concurrent.Async.concurrently (sender src) (receviver snk)
As channel is not visible we can close it or send additional messages bypassing conduit code.
This package provides predefined pairs for all STM types that are used in the package.
Synopsis
- pairBounded :: (MonadIO m, IsConduit m o, BoundedStream i o) => i a -> Int -> m (ConduitT () a m (), ConduitT a Void m ())
- pair :: (MonadIO m, IsConduit m o, UnboundedStream i o) => i a -> m (ConduitT () a m (), ConduitT a Void m ())
- class UnboundedStream i o | i -> o where
- class BoundedStream i o | i -> o where
- class MonadIO m => IsConduit m (x :: * -> *) where
- data Proxy2 (a :: * -> *) b
- proxy2 :: Proxy2 a b
- pairTQueue :: MonadIO m => m (ConduitT () a m (), ConduitT a Void m ())
- pairTMQueue :: MonadIO m => m (ConduitT () a m (), ConduitT a Void m ())
- pairTMChan :: MonadIO m => m (ConduitT () a m (), ConduitT a Void m ())
- pairTBQueue :: MonadIO m => Int -> m (ConduitT () a m (), ConduitT a Void m ())
- pairTBMQueue :: MonadIO m => Int -> m (ConduitT () a m (), ConduitT a Void m ())
- pairTBMChan :: MonadIO m => Int -> m (ConduitT () a m (), ConduitT a Void m ())
Conduit pairs
Low level functions
:: (MonadIO m, IsConduit m o, BoundedStream i o) | |
=> i a | Type description. |
-> Int | Conduit size. |
-> m (ConduitT () a m (), ConduitT a Void m ()) |
Create bounded conduit pair, see BoundedStream class description.
:: (MonadIO m, IsConduit m o, UnboundedStream i o) | |
=> i a | Type description. |
-> m (ConduitT () a m (), ConduitT a Void m ()) |
Create unbounded pair, see UnboundedStream class description.
Classes
class UnboundedStream i o | i -> o where Source #
Class for structures that can handle unbounded stream of values. Such streams break conduit assumptions that constant memory will be used, because if receiver is slower then sender than values will be accumulated.
class BoundedStream i o | i -> o where Source #
Class for structures that can handle bounded stream of values i.e.
there is exists Int
value that sets an upper limit on the number
of values that can be handled by structure. Exact meaning of this
limit may depend on the carrier type.
class MonadIO m => IsConduit m (x :: * -> *) where Source #
Class that describes how we can make conduit out of the carrier value.
Types
data Proxy2 (a :: * -> *) b Source #
Proxy type that can be used to create opaque values.
This proxy type is required because pair hides internal data structure and proxy is used to help compiler infer internal type.
Instances
Specialized functions
List of specialized functions, that can create a bridges over STM types, where *B* stands for bounded *M* stands for closable. If data structure is not closable then there is no way to notify receiver side that bridge is closed, so it's possible to use it only in infinite streams of when some other mechanism of notification is used.