Drastic Prelude changes imminent

Austin Seipp austin at well-typed.com
Sun Feb 1 20:25:45 UTC 2015


>   - 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.
>
Monoid in Prelude is a result of the AMP, and that's not going to change
without breaking code even more, or introducing orphans. Neither of these
are going to happen: BBP has nothing to do with it.


> 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.
>
I understand why you feel that way, but it's simply impossible to do in any
scalable or sensible way in general. Why do we need a unanimous vote here?
Or, by this reasoning, when would we *not* need a unanimous vote?

Even 80% in agreement is literally a supermajority beyond what you need in
almost any liberal democracy in the world to affect change, for example. If
we set our standards that high, it's not only slightly ridiculous, it's
tantamount to making sure nothing ever changes.

Pleasing all the people all the time is just never going to be possible.


> -Iavor
> I happen to support the vast majority of my packages for 3 major GHC
> releases, not just platforms, and for the current stackage build as well.
>
> The idea that we can't personally benefit from things for ~3 years because
> we happen to have packages with long support cycles leads to a fallacy by
> which by induction no progress can ever be made to benefit the larger pool
> of Haskell users we will have in the future because we can never pay a
> price in the short term to benefit them.
>
> Regarding Foldable, there is a chain of reasoning that begins with
> accepting the Applicative-Monad Proposal:
>
> Once we accept Applicative as a superclass of Monad then mapM is _never_
> the right abstraction.
>
> Why?
>
> mapM is needlessly constrained to Monad, so you really start needing the
> ability to traverse with Applicative.
>
> mapM actively gets in the way of making code work with the reduced
> Applicative constraints that are possible post AMP.
>
> Dead End #1. We can't just generalize the signature of mapM in a way that
> makes mapM work with Applicative without a whole host of other issues.
> (mapM is a member of the Traversable class alongside traverse, there exists
> a corner case where Traversable.mapM can have better termination behavior
> on a weirdly designed container, so having Prelude mapM and
> Traversable.mapM generalized differently would be bad.)
>
> Dead End #2. To go the other way and put in a monomorphized traverse into
> Prelude would break insane amounts of code across the entire ecosystem.
>
> To expose traverse is to expose Traversable.
>
> Exposing Traversable from the Prelude then really wants to drag in the
> superclasses of Traversable lest you have a class that is exposed in the
> Prelude with a superclass you can't define.
>
> Dead End #3. We could have added Applicative as a superclass of Monad
> without adding it to the Prelude, but it would have been a bad way to
> proceed. Now users who want to either benefit from the change or define a
> Monad, ever, would have to add an extra import Control.Applicative line,
> what is the probem. This is the same argument against forcing Foldable into
> hiding while possibly exposing Traversable, just mutatis mutandis for
> Foldable/Applicative and Traversable/Monad.
>
> Consequently, exposing the pieces you need to define classes that are
> exposed through Prelude seems to be the direction that in the long term is
> the most defensible in terms of how to explain the state of the world to
> newcomers, once we get the hurdle of transition.
>
> The current state of affairs was quite eloquently summarized by this
> transcript from Nick Partridge about the process of describing the AMP to
> his coworkers:
>
>
> 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.
>
> On Sat, Jan 31, 2015 at 12:59 PM, Johan Tibell <johan.tibell at gmail.com
> <javascript:_e(%7B%7D,'cvml','johan.tibell at gmail.com');>> wrote:
>
>> 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 F
>>
>> The 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
>>     #else
>>     import Data.Foldable (...)
>>     import Prelude hiding (...)  -- the same
>>     #endif
>>
>> Which is terrible. Alternatively I can write
>>
>>     import qualified Data.Foldable as F
>>
>> but 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
>>
>>
>>
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> <javascript:_e(%7B%7D,'cvml','Libraries at haskell.org');>
> http://www.haskell.org/mailman/listinfo/libraries
>
>

-- 
Regards,

Austin Seipp, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20150201/6c7697a5/attachment-0001.html>


More information about the Libraries mailing list