[Haskell-cafe] Conduit Error Output: Control.Monad.Trans.Resource.stateCleanup

Michael Snoyman michael at snoyman.com
Tue Feb 21 06:40:56 CET 2012


On Tue, Feb 21, 2012 at 5:46 AM, Lyndon Maydwell <maydwell at gmail.com> wrote:
> Hi Michael, Café.
>
> I'm writing some code using the conduit library and am encountering
> the following error output (while the program appears to function
> correctly) when using Data.Conduit.Lazy.
>
> The error given is:
>
>> profile_simple_test_data: Control.Monad.Trans.Resource.stateCleanup: There is a bug in the implementation. The mutable state is being accessed after cleanup. Please contact the maintainers.
>
> A reduced code snippet that generates this error is (also attached):
>
>> import Control.Monad
>> import System.Environment
>> import Control.Monad.IO.Class (liftIO)
>> import System.IO
>> import Data.Conduit.Lazy
>> import Data.List (sort)
>>
>> import Data.Conduit
>>
>> import Prelude hiding (map)
>>
>> main = getArgs >>= process
>>
>> process args = mapM_ sorted args
>>
>> sorted x = runResourceT (lazyConsume $ sourceFeed x) >>= (mapM_ print . id)
>>
>> sourceFeed :: ResourceIO m => FilePath -> Source m String
>> sourceFeed file = sourceIO
>>     (openFile file ReadMode)
>>     hClose
>>     (\h -> liftIO $ do
>>         eof <- hIsEOF h
>>         if eof
>>             then return IOClosed
>>             else fmap IOOpen $ hGetLine h)
>
> when run over any text file.
>
> I may be doing something inconsistent with the correct use of sourceIO
> or lazyConsume, however, I tried to follow the example at
> http://www.yesodweb.com/home/snoyberg/blogs/conduit/conduit/source/source.ditamap?nav=nav-2
> as closely as possible.
>
> Is this a bug, or simply an incorrect use of Conduit?

I haven't fully debugged this yet. There's certainly a bug in the
implementation of ResourceT, but the sample program is also wrong. You
can't pass the result from a call to lazyConsume outside the scope of
its ResourceT; the correct way to write sorted would be:

    sorted x = runResourceT $ lazyConsume (sourceFeed x) >>= mapM_
(liftIO . print)

My guess is that this is a fallout from the transition away from
mutable variables: lazyConsume no longer has any way of knowing that
its ResourceT has already been terminated. Perhaps a simple solution
would be to expose a primitive that checks if the ResourceT block has
already been finalized.

Michael



More information about the Haskell-Cafe mailing list