(New to Conduits) mixing lazy lists and Conduits?

Suppose I’m writing some code using Conduits, but need to use some old function f::[a]->[b] (defined in a library somewhere) that transforms a lazy list. Is there a way of turning f into a Conduit without ending up with all of the list being in memory? ie something that looks like toConduit:: ([a]->[b]) -> ConduitT a b m () I’ve got nowhere with Hoogle or Hayoo -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On 06/21/2018 05:13 AM, Jon Fairbairn wrote:
Suppose I’m writing some code using Conduits, but need to use some old function f::[a]->[b] (defined in a library somewhere) that transforms a lazy list.
Is there a way of turning f into a Conduit without ending up with all of the list being in memory?
Constructing a list in such a streaming fashion only seems possible with unsafePerformIO trickery: define the input list lazily by reading a mutable reference, which gets populated whenever the conduit 'await's a new value. Li-yao

You can use Data.Conduit.Lazy for this.
https://www.stackage.org/haddock/lts-11.14/conduit-extra-1.3.0/Data-Conduit-...
On Thu, Jun 21, 2018, 12:13 PM Jon Fairbairn
Suppose I’m writing some code using Conduits, but need to use some old function f::[a]->[b] (defined in a library somewhere) that transforms a lazy list.
Is there a way of turning f into a Conduit without ending up with all of the list being in memory? ie something that looks like
toConduit:: ([a]->[b]) -> ConduitT a b m ()
I’ve got nowhere with Hoogle or Hayoo -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Michael Snoyman
You can use Data.Conduit.Lazy for this.
Thanks. Not as straightforward as I had hoped, but I can see why. On a different note, still attempting to learn, I am trying to use Network.Wai.Conduit with a conduit that has effects (ie involves sourceFile), and so lives in (ResourceT IO). eg example:: ConduitT i (Flush Builder) (ResourceT IO) () Now, responseSource expects IO, not ResourceT IO, so I don’t think I can use that, so I wrote this:
responseSourceRes status headers res_conduit = responseStream status200 headers (\send flush -> runConduitRes $ res_conduit .| mapM_ (\e->lift $ case e of Chunk c -> send c Flush -> flush ))
which runs, but (rather to my surprise) doesn’t produce output (not even headers) until all the effects have completed. That gives rise to two questions: Why does that not stream output? What should I do instead? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

I'd have to see a complete repro to know why the program in question
doesn't stream. But I _can_ explain how best to do something like this.
To frame this: why is something like ResourceT needed here? The issue is we
want to ensure exception safety around the open file handle, and guarantee
that the handle is closed regardless of any exceptions being thrown.
ResourceT solves this problem by letting you register cleanup actions. This
allows for solving some really complicated dynamic allocation problems, but
for most cases it's overkill. Instead, a simple use of the bracket pattern
is sufficient. You can do that with `withSourceFile`:
```
#!/usr/bin/env stack
-- stack --resolver lts-11.10 script
import Network.Wai
import Network.Wai.Handler.Warp
import Network.Wai.Conduit
import Network.HTTP.Types
import Conduit
import Data.ByteString.Builder (byteString)
main :: IO ()
main = run 3000 app
app :: Application
app _req respond =
withSourceFile "Main.hs" $ \src ->
respond $ responseSource status200 []
$ src .| mapC (Chunk . byteString)
```
You can also do this by sticking with ResourceT, which requires jumping
through some hoops with monad transformers to ensure the original ResourceT
context is used. I don't recommend this approach unless you really need it:
it's complicated, and slightly slower than the above. But in case you're
curious:
```
#!/usr/bin/env stack
-- stack --resolver lts-11.10 script
import Network.Wai
import Network.Wai.Handler.Warp
import Network.Wai.Conduit
import Network.HTTP.Types
import Conduit
import Data.ByteString.Builder (byteString)
import Control.Monad.Trans.Resource
main :: IO ()
main = run 3000 app
app :: Application
app _req respond =
runResourceT $ withInternalState $ \is ->
respond $ responseSource status200 [] $
transPipe (`runInternalState` is) (sourceFile "Main.hs") .|
mapC (Chunk . byteString)
```
On Fri, Jun 29, 2018 at 12:05 AM Jon Fairbairn
Michael Snoyman
writes: You can use Data.Conduit.Lazy for this.
Thanks. Not as straightforward as I had hoped, but I can see why.
On a different note, still attempting to learn, I am trying to use Network.Wai.Conduit with a conduit that has effects (ie involves sourceFile), and so lives in (ResourceT IO). eg
example:: ConduitT i (Flush Builder) (ResourceT IO) ()
Now, responseSource expects IO, not ResourceT IO, so I don’t think I can use that, so I wrote this:
responseSourceRes status headers res_conduit = responseStream status200 headers (\send flush -> runConduitRes $ res_conduit .| mapM_ (\e->lift $ case e of Chunk c -> send c Flush -> flush ))
which runs, but (rather to my surprise) doesn’t produce output (not even headers) until all the effects have completed. That gives rise to two questions:
Why does that not stream output? What should I do instead?
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Michael Snoyman
I'd have to see a complete repro to know why the program in question doesn't stream.
Thanks. Here’s a fairly small example ``` module Main where import Prelude hiding (mapM_) import Conduit import Data.Conduit.List (mapM_) import System.FilePath import Data.ByteString.UTF8 import Data.Binary.Builder import GHC.IO.Exception (IOException) import Network.Wai.Handler.FastCGI (run) import Network.Wai.Conduit (Application, responseStream) import Network.HTTP.Types.Status import Network.HTTP.Types.Header data_directory = "./test-data/" main = run $ app app:: Application app request respond = do respond $ responseSourceRes status200 [(hContentType, fromString "text/plain; charset=UTF-8")] $ do yieldCBS "\nBEGIN\n" yield Flush wrapSourceFile $ data_directory > "file1" wrapSourceFile $ data_directory > "a_pipe" yieldCBS "END\n" yield Flush wrapSourceFile:: (MonadUnliftIO m, MonadResource m) => FilePath -> ConduitM a (Flush Builder) m () wrapSourceFile path = do yieldCBS ("\n" ++ path ++ ":\n") catchC (sourceFile path .| mapC (Chunk . fromByteString)) (\e -> yieldCBS $ "Error: " ++ show (e::IOException) ++ "\n") yieldCBS "\n" yield Flush yieldCBS:: Monad m => String -> ConduitT i (Flush Builder) m () yieldCBS = yield . Chunk . fromByteString . fromString responseSourceRes status headers res_conduit = responseStream status200 headers (\send flush -> runConduitRes $ res_conduit .| mapM_ (\e->liftIO $ case e of Chunk c -> send c Flush -> flush )) ``` The various flushes in there were attempts to make something come out.
But I _can_ explain how best to do something like this.
To frame this: why is something like ResourceT needed here? The issue is we want to ensure exception safety around the open file handle, and guarantee that the handle is closed regardless of any exceptions being thrown. ResourceT solves this problem by letting you register cleanup actions. This allows for solving some really complicated dynamic allocation problems, but for most cases it's overkill. Instead, a simple use of the bracket pattern is sufficient. You can do that with `withSourceFile`:
``` #!/usr/bin/env stack -- stack --resolver lts-11.10 script import Network.Wai import Network.Wai.Handler.Warp import Network.Wai.Conduit import Network.HTTP.Types import Conduit import Data.ByteString.Builder (byteString)
main :: IO () main = run 3000 app
app :: Application app _req respond = withSourceFile "Main.hs" $ \src -> respond $ responseSource status200 [] $ src .| mapC (Chunk . byteString)
I don’t think that will work for what I’m trying to do as the decision to open which file is made within the conduit.
You can also do this by sticking with ResourceT, which requires jumping through some hoops with monad transformers to ensure the original ResourceT context is used. I don't recommend this approach unless you really need it: it's complicated, and slightly slower than the above. But in case you're curious:
Thanks. I think that may be what I want, but it’ll take a while to digest -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

I'm not set up to run a FastCGI script easily on my system, but replacing
your example with Warp as the handler works just fine on my machine.
On Fri, Jun 29, 2018 at 12:41 PM Jon Fairbairn
Michael Snoyman
writes: I'd have to see a complete repro to know why the program in question doesn't stream.
Thanks. Here’s a fairly small example
``` module Main where
import Prelude hiding (mapM_) import Conduit import Data.Conduit.List (mapM_) import System.FilePath import Data.ByteString.UTF8 import Data.Binary.Builder import GHC.IO.Exception (IOException)
import Network.Wai.Handler.FastCGI (run) import Network.Wai.Conduit (Application, responseStream) import Network.HTTP.Types.Status import Network.HTTP.Types.Header
data_directory = "./test-data/"
main = run $ app
app:: Application app request respond = do respond $ responseSourceRes status200 [(hContentType, fromString "text/plain; charset=UTF-8")] $ do yieldCBS "\nBEGIN\n" yield Flush wrapSourceFile $ data_directory > "file1" wrapSourceFile $ data_directory > "a_pipe" yieldCBS "END\n" yield Flush
wrapSourceFile:: (MonadUnliftIO m, MonadResource m) => FilePath -> ConduitM a (Flush Builder) m () wrapSourceFile path = do yieldCBS ("\n" ++ path ++ ":\n") catchC (sourceFile path .| mapC (Chunk . fromByteString)) (\e -> yieldCBS $ "Error: " ++ show (e::IOException) ++ "\n") yieldCBS "\n" yield Flush
yieldCBS:: Monad m => String -> ConduitT i (Flush Builder) m () yieldCBS = yield . Chunk . fromByteString . fromString
responseSourceRes status headers res_conduit = responseStream status200 headers (\send flush -> runConduitRes $ res_conduit .| mapM_ (\e->liftIO $ case e of Chunk c -> send c Flush -> flush ))
```
The various flushes in there were attempts to make something come out.
But I _can_ explain how best to do something like this.
To frame this: why is something like ResourceT needed here? The issue is we want to ensure exception safety around the open file handle, and guarantee that the handle is closed regardless of any exceptions being thrown. ResourceT solves this problem by letting you register cleanup actions. This allows for solving some really complicated dynamic allocation problems, but for most cases it's overkill. Instead, a simple use of the bracket pattern is sufficient. You can do that with `withSourceFile`:
``` #!/usr/bin/env stack -- stack --resolver lts-11.10 script import Network.Wai import Network.Wai.Handler.Warp import Network.Wai.Conduit import Network.HTTP.Types import Conduit import Data.ByteString.Builder (byteString)
main :: IO () main = run 3000 app
app :: Application app _req respond = withSourceFile "Main.hs" $ \src -> respond $ responseSource status200 [] $ src .| mapC (Chunk . byteString)
I don’t think that will work for what I’m trying to do as the decision to open which file is made within the conduit.
You can also do this by sticking with ResourceT, which requires jumping through some hoops with monad transformers to ensure the original ResourceT context is used. I don't recommend this approach unless you really need it: it's complicated, and slightly slower than the above. But in case you're curious:
Thanks. I think that may be what I want, but it’ll take a while to digest
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Michael Snoyman
I'm not set up to run a FastCGI script easily on my system, but replacing your example with Warp as the handler works just fine on my machine.
You beat me to it. I have been away from my machine and was part way through testing that when your message arrived. My original version works here too with warp, but not with FastCGI, so it’s something to do with using FastCGI. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
participants (3)
-
Jon Fairbairn
-
Li-yao Xia
-
Michael Snoyman