Conduit experiment: Is this correct?

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/

2012/2/3 Ertugrul Söylemez
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

2012/2/3 Michael Snoyman
2012/2/3 Ertugrul Söylemez
: 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.
Since Sink works in a CPS fashion, by which i mean every step it return a new push close pair, i think it can be used multiple time.
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

Michael Snoyman
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:
[...]
Thanks a lot. This conduit world is really new to me and feels a bit
more complicated than enumerators, but at least I seem to be getting the
right intuition.
Greets,
Ertugrul
--
Key-ID: E5DD8D11 "Ertugrul Soeylemez

Ertugrul Söylemez wrote:
Thanks a lot. This conduit world is really new to me and feels a bit more complicated than enumerators, but at least I seem to be getting the right intuition.
I can assure you that while this may be true for simple cases, it most definitely is not true for at least one more complex case. I have a hackage package http-proxy which initially used Enumerator and now uses Conduit. The Enumerator version was extremely difficult to figure out and eventually required a function like this: enumIteratee :: MonadIO m => Int64 -> (Int -> Iteratee ByteString m ByteString) -> Enumerator ByteString (Iteratee ByteString m) c with an Iteratee nested inside an Enumerator. The Conduit version was much easier to put together because conduits seem to compose much more naturally. IMO, Conduit is a significant improvement over Enumerator but a better solution may still exist (I'm interested in seeing how Pipes work out). Cheers, Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

Michael Snoyman
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:
I think I'm getting the conduit stuff, at least on a high level. As a
little exercise I have ported a simplified variant of the 'netlines'
enumerator to the conduit library. This is the code:
import qualified Data.ByteString as B
netLine :: (Resource m) => Int -> Sink B.ByteString m B.ByteString
netLine n0 = sinkState (n0, B.empty) push (return . snd)
where
push (n, str') dstr' =
return $
case B.elemIndex 10 dstr' of
Nothing ->
let dstr = B.take n dstr'
str = B.append str' dstr
in str `seq` StateProcessing (n - B.length dstr, str)
Just i ->
let (pfx, sfx) = B.splitAt i dstr'
str = B.append str' (B.take n pfx)
in str `seq` StateDone (Just . B.copy $ B.tail sfx) str
netLines :: (Resource m) => Int -> Conduit B.ByteString m B.ByteString
netLines n = sequenceSink () (\s -> fmap (\ln -> Emit s [ln]) (netLine n))
It reads a 256 MiB file with random data in 1.3 seconds and runs in
constant memory for infinite lines. This is reassuring.
But anyway, is this the proper/idiomatic way to do it, or would you go
for a different direction?
Greets,
Ertugrul
--
Key-ID: E5DD8D11 "Ertugrul Soeylemez

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
2012/2/3 Ertugrul Söylemez
: 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
participants (5)
-
Erik de Castro Lopo
-
Ertugrul Söylemez
-
Felipe Almeida Lessa
-
Michael Snoyman
-
yi huang