Hello,
I think that "dead end #3" is the right choice, and keep Foldable etc. in their own modules. We have a module system, we should use it. In general, I think if we are to "burn bridges" it should be by moving things out of the Prelude, not adding more abstractions there.
For the sake of concreteness, here are some of the things I don't like about the current design:
- the design of 'Foldable'. When you ask GHCi about what are the members of the class, you are presented with a long list of more or less random methods. This does not seem like a clean abstraction (e.g., why are 'sum' and 'product' there??).
- the 'Monoid' class. Monoids are a useful abstraction, but encoding them as a Haskell class is very much a compromise (in my mind, anyway). Keeping them in their own module seems like a good idea.
- the state of Data.List: I generally prefer that, when possible, a datatype should provide non-overloaded access to its functionality, and in addition, there can be instances to expose the same functionality via an overloaded API.
Of course, I can generally work around all of those, so not a big deal. However, it'd be nice if we could come up with a design that, more or less, the whole community thinks is a good one.
-Iavor
In a conversation with co-workers about these changes, I fired up a ghci session to show the difference betweenmapM and traverse and what it would mean to generalize the functions in Prelude, and how traverse was just a more general mapM.
Here is how that went down:
> :i traverse
Top level:
    Not in scope: ‘traverse’
    Perhaps you meant ‘reverse’ (imported from Prelude)
Ah, of course. I forgot the import.
> import Data.Traversable
> :i traverse
class (Functor t, Data.Foldable.Foldable t) =>
      Traversable (t :: * -> *) where
  traverse ::
    Control.Applicative.Applicative f => (a -> f b) -> t a -> f (t b)
  ...
    -- Defined in ‘Data.Traversable’
Great. Now let's look at mapM:
> :i mapM
Top level:
    Ambiguous occurrence ‘mapM’
    It could refer to either ‘Data.Traversable.mapM’,
                             imported from ‘Data.Traversable’
                          or ‘Prelude.mapM’,
                             imported from ‘Prelude’ (and originally defined in ‘Control.Monad’)
Oh. Okay we'll check out the one in Prelude by prefixing it.
> :i Prelude.mapM
Prelude.mapM :: Monad m => (a -> m b) -> [a] -> m [b]
    -- Defined in ‘Control.Monad’
> :t traverse
traverse
  :: (Traversable t, Control.Applicative.Applicative f) =>
     (a -> f b) -> t a -> f (t b)
Now let's specialise traverse for Monad and List, to show that it's equivalent.
> :t (traverse :: Monad m => (a -> m b) -> [a] -> m [b])
<interactive>:1:2:
    Could not deduce (Control.Applicative.Applicative m1)
      arising from a use of ‘traverse’
    from the context (Monad m)
      bound by the inferred type of
               it :: Monad m => (a -> m b) -> [a] -> m [b]
      at Top level
    or from (Monad m1)
      bound by an expression type signature:
                 Monad m1 => (a1 -> m1 b1) -> [a1] -> m1 [b1]
      at <interactive>:1:2-50
    Possible fix:
      add (Control.Applicative.Applicative m1) to the context of
        an expression type signature:
          Monad m1 => (a1 -> m1 b1) -> [a1] -> m1 [b1]
        or the inferred type of it :: Monad m => (a -> m b) -> [a] -> m [b]
    In the expression:
      (traverse :: Monad m => (a -> m b) -> [a] -> m [b])
Curses! Looking forward to AMP. Insert explanation about how Applicative should be a superclass of Monad. Pretend that it really is. Wave hands about.
> :t (traverse :: Applicative m => (a -> m b) -> [a] -> m [b])
<interactive>:1:14:
    Not in scope: type constructor or class ‘Applicative’
Okay this is getting silly.
> import Control.Applicative
> :t (traverse :: Applicative m => (a -> m b) -> [a] -> m [b])
(traverse :: Applicative m => (a -> m b) -> [a] -> m [b])
  :: Applicative m => (a -> m b) -> [a] -> m [b]
This is really really common teaching/learning scenario using the current state of the Prelude.
I re-read the goals* of the proposal: https://wiki.haskell.org/Foldable_Traversable_In_Prelude"One goal here is that people should be able to use methods from these modules without the need of a qualified import -- i.e. to prevent clash in the namespace, by resolving such in favor of the more generalized versions. Additionally, there are some new methods added to the Foldable class because it seems to be the "right" thing."Before FTP, I would have to write this to use Foldable/Traversable:import qualified Data.Foldable as FThe import is qualified as to not collide with the Prelude.If I have code that needs to be compatible with more than one GHC release (I typically need compatibility with the last 3 major releases), what do I have to write post-FTP? Since I cannot rely on the Prelude being generalized (because I might be compiling with a pre-FTP compiler) I need to either write:#if MIN_VERSION_base(x,y,z)-- Get Foldable etc from Prelude#elseimport Data.Foldable (...)import Prelude hiding (...) -- the same#endifWhich is terrible. Alternatively I can writeimport qualified Data.Foldable as Fbut now nothing is gained over the pre-FTP state. Only after 3+ years (at the current GHC release phase) I can drop that one extra import. One out of perhaps 20. That seems quite a small gain given that we will then have made Data.List a very confusing module (it's essentially Data.Foldable under a different name), broken some code due to added type ambiguity, and also removed one of the simpler ways to remove that ambiguity, which would have been to import one of the monomorphic list functions that no longer exist.* People tell me that there are other goals, but they aren't really stated clearly anywhere.-- Johan