I thought about it a bit more. The problem would actually be *very* easy to solve if conduit exported one extra function: a connect function that returned a Sink instead of running it. Then you could do:
bsrc <- bufferSource src sink2 <- (bsrc $= Cb.lines $= Cl.isolate 3) `connectReturnSink` snk bsrc $$ sink2 That might be generally useful in other places as well, I'm not sure. Michael 2012/2/3 Michael Snoyman <mich...@snoyman.com>: > 2012/2/3 Ertugrul Söylemez <e...@ertes.de>: >> 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 > > In this particular case, it will work due to the implementation of > snk. In general, however, you're correct: you should not use the same > sink twice. > > I haven't thought about it much yet, but my initial recommendation > would be to create a new Conduit using SequencedSink, which takes the > three lines and then switches over to a passthrough conduit. The > result looks like this: > > > 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 $$ myConduit =$ snk > > main :: IO () > main = runTCPServer (ServerSettings 4000 Nothing) handleClient > > myConduit = > sequenceSink 3 go > where > go 0 = return $ StartConduit $ Cl.map id > go count = do > mx <- Cb.lines =$ Cl.head > case mx of > Nothing -> return Stop > Just x -> return $ Emit (count - 1) [x] > > Michael _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe