[Haskell-cafe] Conduit experiment: Is this correct?

Ertugrul Söylemez es at ertes.de
Fri Feb 3 14:21:56 CET 2012


Hello there,

I'm trying to build a server for testing the conduit and network-conduit
packages.  As a contrived example the goal is to pick the first three
lines from the client and send them back without the line feeds.  After
that, I'd like to switch to a simple echo server.  This is the code:

    module Main where

    import Data.Conduit
    import Data.Conduit.Binary as Cb
    import Data.Conduit.List as Cl
    import Data.Conduit.Network

    handleClient :: Application
    handleClient src snk =
        src $$ do
            (Cb.lines =$= Cl.isolate 3) =$ snk
            snk

    main :: IO ()
    main = runTCPServer (ServerSettings 4000 Nothing) handleClient

I'm not sure whether it is correct to use the 'snk' sink multiple times,
and intuitively I'd say that this is wrong.  What would be the proper
way to do this?


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120203/2586e708/attachment.pgp>


More information about the Haskell-Cafe mailing list