conduit icon indicating copy to clipboard operation
conduit copied to clipboard

Accumulate ByteStrings into single result

Open emlautarom1 opened this issue 2 years ago • 3 comments

I have the following scenario: I have a server that on any response returns a ByteString which can be very long. On the client side, every now and then I perform a request to the server and I expect to get the full ByteString. The code is as follows:

-- Server.hs
module Server where

main = do
  let settings = serverSettings 80 "127.0.0.1"
  runTCPServer settings $ \appData -> do
    void $
      runConduitRes $
        appSource appData .| handler .| appSink appData

handler :: Monad m => ConduitT ByteString ByteString m ()
handler = awaitForever (const $ yield veryLongString)

-- Client.hs
module Client where

main = do
  let settings = clientSettings 80 "127.0.0.1"
  result <- runTCPClient settings $ \appData -> do
      runConduit $ yield "request" .| appSink appData
      runConduit $ appSource appData .| ??? -- What to use here to "accumulate all ByteStrings"?

  print result

Now, if I replace ??? with headC, as long as the ByteString that the server sends is not too long everything works just fine, but if it happens to be long enough I only get part of it.

Ideally I would accumulate all ByteStrings until the server stops sending them. In other issues it's mentioned that I should use Builders for this task, but I'm not quite sure how to get that working, so I would appreciate any suggestions.

emlautarom1 avatar May 15 '22 16:05 emlautarom1

I found that I can do the following:

-- Client.hs
module Client where

main = do
  let settings = clientSettings 80 "127.0.0.1"
  result <- runTCPClient settings $ \appData -> do
      runConduit $ yield "request" .| appSink appData
      lazy <- runConduit $ appSource appData .| mapC Builder.byteString .| sinkLazyBuilder
      return $ toStrict lazy

  print result

Now I get a single value from runConduit, but this program hangs forever. I assume that it waits forever for more ByteStrings (which will never arrive).

emlautarom1 avatar May 15 '22 17:05 emlautarom1

In order to make a system like this work, you need to do something like:

  • Have the sending side close its send socket to let the receiving side no there's no more data
  • Indicate at the beginning of the message how many bytes are coming
  • Have some kind of termination signal within the stream

snoyberg avatar May 16 '22 10:05 snoyberg

What I ended up doing is the following:

-- Server.hs
module Server where

main = do
  let settings = serverSettings 80 "127.0.0.1"
  runTCPServer settings $ \appData -> do
    void $
      runConduitRes $
        appSource appData .| handler .| appSink appData

handler :: Monad m => ConduitT ByteString ByteString m ()
handler = whenJustM await (const $ yield veryLongString)

-- Client.hs
module Client where

main = do
  let settings = clientSettings 80 "127.0.0.1"
  result <- runTCPClient settings $ \appData -> do
      runConduit $ yield "request" .| appSink appData
      runConduit $ appSource appData .| foldC

  print result

With this, the server will get only the first message with await and then close the connection. I'm not quite satisfied with this solution but it works for my use case. As for the client, I'm not sure if there's a performance degradation on using a single foldC instead of builders, but again, for my use case it seems to be fine.

emlautarom1 avatar May 16 '22 12:05 emlautarom1