
I've been working on a "ListT done right" for submission into `transformers`. I could split it off into its own package, but I would like to first run it by you all, particularly Ross, to see if this can be included this in `transformers` because I feel that `transformers` is where this belongs. I've lpasted the implementation here: http://lpaste.net/90890 I've written it to follow the spirit of the `transformers` library as closely as possible, both in API, documentation, and source code style. I'm fine with either replacing the old `ListT` implementation or providing both. I'll leave it to you guys to make the call on that. As long as the correct version is in `transformers` somewhere then I'm happy. If I *had* to pick a side, I suppose I would favor replacing the old one. Also, any suggestions for changes are welcome, particularly if they improve the likelihood of this getting into `transformers`.

ListT is a kind of delicate monad, because it has interesting control flow (arguably one is supposed to use LogicT for anything serious, since ). What makes this particular implementation "ListT done right?" Edward Excerpts from Gabriel Gonzalez's message of Sat Jul 13 20:47:02 -0700 2013:
I've been working on a "ListT done right" for submission into `transformers`. I could split it off into its own package, but I would like to first run it by you all, particularly Ross, to see if this can be included this in `transformers` because I feel that `transformers` is where this belongs.
I've lpasted the implementation here:
I've written it to follow the spirit of the `transformers` library as closely as possible, both in API, documentation, and source code style.
I'm fine with either replacing the old `ListT` implementation or providing both. I'll leave it to you guys to make the call on that. As long as the correct version is in `transformers` somewhere then I'm happy. If I *had* to pick a side, I suppose I would favor replacing the old one.
Also, any suggestions for changes are welcome, particularly if they improve the likelihood of this getting into `transformers`.

The problem with the existing ListT is it is often not a Monad.
Consider IO [Int]
To work with an infinite list you need to distribute an infinite number of
effects into the IO.
I personally would be slightly in favor adding "ListT done right" as a
separate monad, given that the existing one is still rather useful when you
want to use a small number of elements and aren't worried about
non-termination in the base monad, and in those limited circumstances it is
a heck of a lot easier to understand.
A longer summary of the issues with the existing ListT and the original
"ListT done right" proposal has been on the wiki for a long time:
http://www.haskell.org/haskellwiki/ListT_done_right
The main arguments against moving it into transformers / mtl. It _has_ been
around for a long time: it is annoyingly complicated to use and has been
packaged up several times in the meantime, and there are multiple similar
alternatives for specific domains that fill in for the weaknesses of even
this approach:
e.g. LogicT, Soutei's FStream, and to a lesser extent things like Luke
Palmer's Omega.
But for all that it is a more 'correct' ListT, hence my being weakly in
favor of finally putting it in a standard location.
-Edward
On Sun, Jul 14, 2013 at 2:59 AM, Edward Z. Yang
ListT is a kind of delicate monad, because it has interesting control flow (arguably one is supposed to use LogicT for anything serious, since ). What makes this particular implementation "ListT done right?"
Edward
Excerpts from Gabriel Gonzalez's message of Sat Jul 13 20:47:02 -0700 2013:
I've been working on a "ListT done right" for submission into `transformers`. I could split it off into its own package, but I would like to first run it by you all, particularly Ross, to see if this can be included this in `transformers` because I feel that `transformers` is where this belongs.
I've lpasted the implementation here:
I've written it to follow the spirit of the `transformers` library as closely as possible, both in API, documentation, and source code style.
I'm fine with either replacing the old `ListT` implementation or providing both. I'll leave it to you guys to make the call on that. As long as the correct version is in `transformers` somewhere then I'm happy. If I *had* to pick a side, I suppose I would favor replacing the old one.
Also, any suggestions for changes are welcome, particularly if they improve the likelihood of this getting into `transformers`.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sat, Jul 13, 2013 at 08:47:02PM -0700, Gabriel Gonzalez wrote:
I've been working on a "ListT done right" for submission into `transformers`. I could split it off into its own package, but I would like to first run it by you all, particularly Ross, to see if this can be included this in `transformers` because I feel that `transformers` is where this belongs.
I'm not sure. I'm inclined to think that the reason that ListT's violation of the monad laws upsets no-one is because no-one actually uses it. I don't think we should include the transformer just for the sake of having one. I've found myself using something like the new ListT before, but it's a bit awkward to have two new datatypes, and difficult to use existing list machinery with it, so I'm not sure it really pays off as an abstraction. Do we have compelling use cases for either the old or the new ListT? Is the old ListT used anywhere on Hackage? In lieu of these things, I might propose just removing it altogether.

On 07/14/2013 03:44 AM, Ben Millwood wrote:
On Sat, Jul 13, 2013 at 08:47:02PM -0700, Gabriel Gonzalez wrote:
I've been working on a "ListT done right" for submission into `transformers`. I could split it off into its own package, but I would like to first run it by you all, particularly Ross, to see if this can be included this in `transformers` because I feel that `transformers` is where this belongs.
I'm not sure. I'm inclined to think that the reason that ListT's violation of the monad laws upsets no-one is because no-one actually uses it. I don't think we should include the transformer just for the sake of having one.
This is a chicken-and-egg problem. Nobody uses it because it violates the laws and there is no good `ListT` implementation on Hackage. Also, I have two packages I want to release that do use `ListT`, which is the reason I am proposing this.
I've found myself using something like the new ListT before, but it's a bit awkward to have two new datatypes, and difficult to use existing list machinery with it, so I'm not sure it really pays off as an abstraction.
Do we have compelling use cases for either the old or the new ListT? Is the old ListT used anywhere on Hackage? In lieu of these things, I might propose just removing it altogether.
Here are some use cases I came up with that motivated me to fix this in the first place. First, a back-tracking effectful parser: -- 's' is the unconsumed input, 'm' is the base monad, 'r' is the parsed value newtype ParseT s m r = ParseT { unParseT :: StateT s (ListT m) r } deriving (Functor, Applicative, Monad, MonadPlus) instance MonadTrans (ParseT s) where lift = ParseT . lift . lift This is the effectful generalization of the backtracking Hutton-Meijer parser, typically define as: type ParseT s r = StateT s [] r ... except that the `ListT` version is a monad transformer so you can interleave effects. I use this to print debugging information while parsing (whenever `parsec` and `attoparsec` error messages are not sufficiently helpful). Another case is traversing a directory tree. You can see example code I've been writing up that traverses directory trees using `ListT` here: https://github.com/Gabriel439/Haskell-DirStream-Library/blob/master/DirStrea... You use it like this: recurse :: FilePath -> ListT SafeIO FilePath recurse path = do child <- contents path isVis <- visible child guard isVis isDir <- directory child return child <|> (guard isDir >> recurse child) This version is lazy and traverses the minimal number of directories to provide the number of demanded results. The old `ListT` would traverse the entire directory tree before providing even the first result. Edward raised another important point, which is how do you easily read out the result. In the case where you want to consume all the results you can use the `foreach` combinator, which I included in the code: foreach :: (Monad m) => ListT m a -> (a -> m b) -> m () In the case where you do not want to demand the result, you can convert the `ListT` to a `Producer` from `pipes`, using `fromListT`: fromListT :: (Monad m) => ListT m a -> Producer a m () Then you can use `pipes` combinators like `take` to only demand the first few elements of the list: -- Note that this is using the `pipes-4.0.0` API on Github import Pipes import qualified Pipes.Prelude as P exampleListT :: ListT IO String exampleProducer :: () -> Producer String IO () exampleProducer () = fromListT exampleListT main = runEffect $ (exampleProducer >-> P.take >-> P.stdout) () In fact, `ListT` is quite a nice fit for `pipes` because the `ListT` monad has an exact correspondence with one of the `pipes` categories (specifically the "respond" category): fromListT . (f >=> g) = (fromListT . f) />/ (fromListT . g) fromListT . return = respond Right now I have a `ListT` implementation in the `pipes` package, but I got several requests to move it into `transformers` because people felt that `ListT` should be even lower in the library hierarchy than `pipes`. I don't mind providing `ListT` in `pipes`, but it seems odd to tell people to use `pipes` for something as simple as `ListT` There is another important question that Edward didn't mention, but that is equally important: How do you easily build `ListT` computations? Again, `pipes` makes this very easy: toListT :: (Monad m) => Producer a m () -> ListT m a -- toListT . fromListT = id -- fromListT . toListT = id This allows people to assemble the `ListT` computation monadically as a `Producer`, then package it up as a `ListT` when they are done. Here's an example: exampleListT2 :: ListT IO Int exampleListT2 = toListT $ forM_ [1..3] $ \i -> do lift $ putStrLn $ "Selecting: " ++ show i respond i That creates a `ListT` computation that branches three times, printing the branch it choose before taking that branch. Then you can assemble these in the `ListT` monad: total :: ListT IO (Int, Int) total = do x <- exampleListT2 y <- exampleListT2 return (x, y) Here is some example output if that description is unclear:
main = foreach total print Selecting: 1 Selecting: 1 (1,1) Selecting: 2 (1,2) Selecting: 3 (1,3) Selecting: 2 Selecting: 1 (2,1) Selecting: 2 (2,2) Selecting: 3 (2,3) Selecting: 3 Selecting: 1 (3,1) Selecting: 2 (3,2) Selecting: 3 (3,3)
Anyway, I can certainly provide this in `pipes`, but I just wanted to give `transformers` a try first to see if you all were interested. I think many creative applications of `ListT` have been stymied simply because there is no high-quality `ListT` application on Hackage, but if `pipes` has to be the hiqh-quality `ListT` implementation then I am fine with that, too.

On Sun, Jul 14, 2013 at 07:37:21AM -0700, Gabriel Gonzalez wrote:
On 07/14/2013 03:44 AM, Ben Millwood wrote:
On Sat, Jul 13, 2013 at 08:47:02PM -0700, Gabriel Gonzalez wrote:
I've been working on a "ListT done right" for submission into `transformers`. I could split it off into its own package, but I would like to first run it by you all, particularly Ross, to see if this can be included this in `transformers` because I feel that `transformers` is where this belongs.
I'm not sure. I'm inclined to think that the reason that ListT's violation of the monad laws upsets no-one is because no-one actually uses it. I don't think we should include the transformer just for the sake of having one.
This is a chicken-and-egg problem. Nobody uses it because it violates the laws and there is no good `ListT` implementation on Hackage.
It seems there are 140 packages on hackage using ListT (which surprised me, given its flaws), so I don't think we can quickly remove it from transformers or re-implement it under the same name.
participants (5)
-
Ben Millwood
-
Edward Kmett
-
Edward Z. Yang
-
Gabriel Gonzalez
-
Ross Paterson