[Haskell-cafe] Combining pool and Conduit

Pieter Laeremans pieter at laeremans.org
Mon Aug 7 19:02:55 UTC 2017


Thans a lot!

Pieter Laeremans

> On 7 Aug 2017, at 20:15, Michael Snoyman <michael at snoyman.com> wrote:
> 
> Because ConduitM is based on continuations, you can't safely acquire resources inside of it. In order to make safe allocations, you need to use ResourceT. I wrote a blog post two months ago with a lot more information on ResourceT:
> 
> https://www.fpcomplete.com/blog/2017/06/understanding-resourcet
> 
> Because of this, you cannot use `withResource`. The error message you're getting is confusing, but this is where it's coming from: because of its continuations, ConduitM cannot provide a MonadBaseControl instance. Instead, you'll need to use the `takeResource` and either `destroyResource` or `putResource` functions, plus something like `bracketP` or `allocate`.
> 
>> On Mon, Aug 7, 2017 at 3:57 PM, Pieter Laeremans <pieter at laeremans.org> wrote:
>> Hello,
>> 
>> I would like to combine a "Connection Pool" with the conduit library.
>> 
>> I have an application were a stream of results from a web api needs to
>> be analysed and stored in a database.
>> Since the analysis is composed of different parts, I combine some parts
>> together ( .|)
>> 
>> Some of those parts need a database connection to do their work.
>> Initially I created a Connection and passed it around to each part that
>> needed it, this is sub-optimal. So I wanted to try the "resource-pool"
>> library to address this problem.
>> (https://hackage.haskell.org/package/resource-pool)
>> 
>> So instead of a Connection I pass around a (Pool Connection) But I run
>> into problems , and I don't know how to fix them.
>> 
>> Here is a simple snippet of code that demonstrates the problem:
>> 
>> 
>> -------------------------------------------
>> {-# LANGUAGE RankNTypes #-}
>> 
>> module Lib where
>> 
>> import Data.Pool
>> import Database.HDBC
>> import Database.HDBC.ODBC
>> import Data.Conduit
>> import Conduit
>> 
>> createConnectionPool :: Pool Connection
>> createConnectionPool = undefined
>> 
>> processFoo :: Pool Connection -> Consumer String IO ()
>> processFoo pool = withResource pool $ \conn -> do
>>                                                  mapM_C print
>> 
>> -------------------------
>> 
>> I can not get this to compile:
>> 
>> src/Lib.hs:15:19: error:
>>     • No instance for (MonadBaseControl IO (ConduitM String o IO))
>>         arising from a use of ‘withResource’
>>     • In the expression: withResource pool
>>       In the expression:
>>         withResource pool $ \ conn -> do { mapM_C print }
>>       In an equation for ‘processFoo’:
>>           processFoo pool = withResource pool $ \ conn -> do { mapM_C
>>           print }
>> 
>> But I have no Idea how to tackle this problem.  Any suggestions ?
>> 
>> Thanks,
>> 
>> Pieter
>> 
>> --
>>   Pieter Laeremans
>>   pieter at laeremans.org
>> _______________________________________________
>> 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.
> 
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170807/1084ba79/attachment.html>


More information about the Haskell-Cafe mailing list