iteratee (was: Could iteratee depend on mtl instead of transformers?)

Valery V. Vorotyntsev valery.vv at gmail.com
Wed Nov 18 05:42:19 EST 2009


>> Valery V. Vorotyntsev wrote:
>>
>>> Thus, the question is: are there any transformers-specific features
>>> iteratee package needs, or can it just go with mtl?


> Henning Thielemann wrote:
>
>> The question is, whether Iteratee needs functions of MTL that transformers
>> does not provide? 'Transformers' is the more basic package, entirely
>> Haskell 98, thus should be prefered. It is however sad, that Transformers
>> cannot easily be used with GHCi in parallel with MTL installed. I was
>> always against that ... Renaming Control.Monad.Trans and
>> Control.Monad.Identity to something else would solve the conflict. I'm
>> also not happy, that you have to choose between monads-fd and monads-tf. I
>> think it would be better to be able to have both type class approaches.


John Lato wrote:

> Iteratee does not need any MTL functions that transformers does not
> provide.  It does the following:
>
> 1) implement instances of MonadTrans and MonadIO
> 2) uses lift and liftIO (polymorphically)
>
> There's no technical reason iteratee couldn't use mtl, and as Erik
> mentions, if you change the dependency it works just fine.  For
> myself, I can be swayed by user demand, although I'd like to see the
> outcome of this discussion before committing to any changes.


I for one have no demand any more. I'm doing fine with the following
lines in module:

    {-# LANGUAGE PackageImports #-}
    -- ...
    import "transformers" Control.Monad.Trans

> In all honesty, I never thought iteratee would generate enough
> interest for this to matter.  It's not a particularly popular
> package.

I thought it was. :)

  http://comonad.com/reader/2009/iteratees-parsec-and-monoid/
  http://therning.org/magnus/archives/735
  http://stackoverflow.com/questions/1319705
  http://www.johantibell.com/Left_fold_enumerators.pdf

-- 
vvv


More information about the Libraries mailing list