conduit-network-stream-0.2: A base layer for network protocols using Conduits

Stabilityexperimental
MaintainerNils Schweinsberg <mail@nils.cc>
Safe HaskellNone

Data.Conduit.Network.Stream

Contents

Description

Easy to use network streaming with conduits. This library properly encodes conduit blocks over a network connection such that

It also supports sending and receiving of custom data types via the Sendable and Receivable instances.

A simple server/client example (using -XOverloadedStrings):

 import           Control.Monad.Trans
 import qualified Data.ByteString             as Strict
 import qualified Data.ByteString.Lazy        as Lazy
 import           Data.Conduit
 import qualified Data.Conduit.List           as CL
 import           Data.Conduit.Network
 import           Data.Conduit.Network.Stream

 client :: IO ()
 client = runResourceT $ runTCPClient (clientSettings ..) $ \appData -> do       

     streamData <- toStreamData appData

     send streamData $ mapM_ yield (["ab", "cd", "ef"] :: [Strict.ByteString])
     send streamData $ mapM_ yield (["123", "456"]     :: [Strict.ByteString])

     closeStream streamData

 server :: IO ()
 server = runResourceT $ runTCPServer (serverSettings ..) $ \appData -> do

     streamData <- toStreamData appData

     bs  <- receive streamData $ CL.consume
     liftIO $ print (bs  :: [Lazy.ByteString])

     bs' <- receive streamData $ CL.consume
     liftIO $ print (bs' :: [Lazy.ByteString])
 
     closeStream streamData

Synopsis

Network streams

closeStream :: MonadResource m => StreamData m -> m ()Source

Close current stream. In order to guarantee process resource finalization, you must use this operator after using receive.

Sending

send :: (Monad m, Sendable m a) => StreamData m -> Source m a -> m ()Source

Send one conduit block.

class Sendable m a whereSource

To define your own Sendable instances, reuse the instances for strict and lazy bytestrings, for example for Data.Text:

 instance (Monad m, Sendable m Data.ByteString.ByteString) => Sendable m Text where
     encode = Data.Conduit.List.map encodeUtf8 =$= encode

Methods

encode :: Conduit a m EncodedBSSource

encode is called before sending out conduit block elements. Each element has to be encoded either as strict ByteString or as lazy ByteString with a known length.

Instances

Monad m => Sendable m ByteString

Instance for lazy bytestrings which calculates the length of the ByteString before calling the (Int, Data.ByteString.Lazy.ByteString) instance of Sendable.

Monad m => Sendable m ByteString

Instance for strict bytestrings, using a specialized version of encode.

Monad m => Sendable m (Int, ByteString)

Instance for lazy bytestrings with a known length, using a specialized version of encode.

data EncodedBS Source

Newtype for properly encoded bytestrings.

Receiving

receive :: (MonadResource m, Receivable a m) => StreamData m -> Sink a m b -> m bSource

Receive the next conduit block. Might fail with the ClosedStream exception if used on a stream that has been closed by closeStream.

class Receivable a m whereSource

decode is used after receiving the individual conduit block elements. It is therefore not necessary to reuse other decode instances (in contrast to Sendable instance definitions).

Instances

Monad m => Receivable ByteString m

For lazy bytestrings, decode is the identity conduit.

Monad m => Receivable ByteString m

Instance for strict bytestrings. Note that this uses toStrict for the conversion from lazy bytestrings, which is rather expensive. Try to use lazy bytestrings if possible.

Bi-directional conversations

streamSink :: (Monad m, Sendable m a) => StreamData m -> Sink a m ()Source

For bi-directional conversations you sometimes need the sink of the current stream, since you can't use send within another receive.

A simple example:

 receive streamData $
     myConduit =$ streamSink streamData

Note, that each streamSink marks its own conduit block. If you want to sink single block elements, use withElementSink instead.

withElementSink :: (Monad m, Sendable m a) => StreamData m -> (Sink a m () -> Sink b m c) -> Sink b m cSource

Sink single elements inside the same conduit block. Example:

 receive streamData $ withElementSink $ \sinkElem -> do
     yield singleElem =$ sinkElem
     mapM_ yield moreElems =$ sinkElem