Drastic Prelude changes imminent

Edward Kmett ekmett at gmail.com
Tue Jan 27 18:33:22 UTC 2015


On Tue, Jan 27, 2015 at 5:32 AM, Augustsson, Lennart <
Lennart.Augustsson at sc.com> wrote:

>  The next version (7.10) of GHC is slated to have a drastically changed
> Prelude.
>
> This message is very late in the release process, but I would urge caution
> before changing.
>
>
>
> The changes are (aptly) named the Burning Bridges Proposal (BBP).
>
> Even though the work has been going on for a while, it seems that this
>
> change is coming as a surprise to many people (including Simon Peyton
>
> Jones).  In summary, it generalizes many list operation, e.g., foldr,
>
> to be overloaded.
>
>
>
> There is much to welcome in BBP, but changing the Prelude cannot be
>
> done lightly since it really is like changing the language.
>
> So I think it's really important for a large number of people to be able to
>
> try out such changes before they come into effect, and to have time
>
> to let the changes stabilize (you rarely get it right the first time).
>
>
>
> I've discussed this with a number of people, including Simon PJ, and
>
> we have concrete proposals.
>
>
>
> Proposal 1:
>
> *    Add a new pragma
>
>         {-# LANGUAGE Prelude=AlternativePrelude #-}
>
>       *   This is a new feature, but it is easy and low-risk to implement.
>
>       *   Which Prelude you use really is a language choice; appropriate
> for a LANGUAGE pragma.
>
>       *   Semantics is name-space only: import Prelude (); import
> AlternativePrelude
>
>       *   No effect on desugaring or typing of built-in syntax (list
> comprehensions, do-notation etc).
>
*    Ship with both old and new prelude.
>
*    So now old and new behaviour are easy to achieve, in the module or in
> a .cabal file.
>
>

This actually *doesn't work*. We seriously considered it, but the effects
have knock-on consequences that go far beyond the Prelude itself.

Control.Monad for instance re-exports `mapM`

Data.List re-exports most of the folds.

`mtl` re-exports the monad combinators as well, etc.

The list goes on and on.

We made a serious go at trying this proposal before we abandoned it as
unworkable, because of the re-export issue.

import Data.List

would have to collide or not collide with Prelude types based on whether or
not the Prelude was being used or this alternate Prelude.

import Control.Monad
import Data.Foldable
import Data.Traversable

etc.

the list goes on.

Under the scheme we've adopted all of these work unconditionally.

Q1
>
> An alternative to Foldable would be
>
>   class Enumerable t where
>
>     toList :: t a -> [a]   -- Implementations should use 'build'
>
> Is Foldable more general (or efficient) than a Enumerable class, plus
> fusion?
>
>
This is insufficient in a lazy language, it forces all folds to be
left-biased, and introduces bottoms that do not exist in a foldMap based
Foldable.

class Foldable f where
  foldMap :: Monoid m => (a -> m) -> f a -> m

on the other hand would be a very serious candidate for a minimalist
Foldable, but then we run afoul of Q2.


>  Consider a new data type X a.  I write
>
>      foldX :: (a -> b -> b) -> b -> X a -> b
>
>      foldX = ...lots of code...
>
>
>
>      toList :: X a -> [a]  {-# INLINE toList #-}
>
>      toList x = build (\c n. foldX c n x)
>
>
>
> So now toList is small and easy to inline.  Every good list consumer of a
> call to toList will turn into a call to foldX, which is what we want.
>
>
>
> Q2
>
> What are the criteria for being in Foldable?
>
> For instance, why are 'sum', 'product' in Foldable, but not 'and', 'or'?
>
>
sum and product went into Foldable because Prelude.sum and
Data.Foldable.sum folded in opposite directions.

and/or didn't have this problem.

For any new data type, defining foldMap alone is sufficient.

For [] on the other hand we decided that expanding Foldable to avoid
silently changing the semantics of all Haskell programs ever written was
the lesser of two evils.

It was considered _by far_ the lesser of evils to expand the class to
enable it to duplicate existing semantics where possible rather than
silently change the semantics of which way folks code associated for all
Haskell programs ever written.

Q3
>
> What's the relationship of Foldable to GHC.Exts.IsList?
>
> Which also has toList, fromList, and does work with ByteString.
>
> *  For example, could we use IsList instead of Foldable?
>
>     Specifically, Foldable does not use its potential power to apply the
> type constructor t to different arguments.  (Unlike Traversable which does.)
>
>         foldr :: IsList l => (Item l->b->b) -> b -> l -> b
>
>
Because IsList includes both fromList and toList, _and_ is over an argument
of kind * not an argument of kind * -> *, IsList has no connection to
Foldable.

At best what you can say is that the toList for Data.Foldable and the
toList for IsList should yield the same answer if you want to be sensible,
but remember IsList is on a different kind entirely, and there are usecases
that require it to have that kind.

-Edward
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20150127/fc41909f/attachment-0001.html>


More information about the Libraries mailing list