Drastic Prelude changes imminent

Simon Marlow marlowsd at gmail.com
Tue Jan 27 17:30:58 UTC 2015


On 27/01/2015 10:32, Augustsson, Lennart wrote:
> Proposal 1:
>
> *    Add a new pragma
>
>          {-# LANGUAGE Prelude=AlternativePrelude #-}

As I mentioned to Simon PJ, I don't think this is the best way to solve 
the problem, because adding a new extension brings new 
backwards-compatibility issues on top of the ones we're trying to solve. 
  Users will need to employ flags in their .cabal file, or #ifdefs in 
their source code, to account for the fact that only GHC 7.10 supports 
the new option.

Furthermore, every GHC version already has the necessary functionality 
to do this, so we don't need to add a new flag.  You can either (a) use 
{-# LANGUAGE NoImplicitPrelude #-} together with import MyPrelude, or 
(b) use import Prelude (); import MyPrelude.  Slightly more characters, 
but entirely backwards-compatible - I think that's a worthy tradeoff.

FWIW, I agreed with Neil when he brought up the issue of the new Prelude 
changes a while ago.

Cheers,
Simon






>        *   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.
>
> *    The question becomes "what is the default".
>
> Proposal 2:
>
> *    Make the default be the old rather than the new.
>
>        *   Altering the default Prelude API should be done slowly, with
> lots of warning; because all users get it willy-nilly.
>
>        *   Unlike AMP, the change is controversial (clearly).
>
>        *   Easier to make changes to New Prelude if it isn't the default.
>
> That's it.
>
> Discussing the BBP proposal we also came up with a number of technical
> questions:
>
> 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?
>
> 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'?
>
> 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
>
>    -- Lennart
>
>
> This email and any attachments are confidential and may also be
> privileged. If you are not the intended recipient, please delete all
> copies and notify the sender immediately. You may wish to refer to the
> incorporation details of Standard Chartered PLC, Standard Chartered Bank
> and their subsidiaries at
> http://www.standardchartered.com/en/incorporation-details.html
>
> Insofar as this communication contains any market commentary, the market
> commentary has been prepared by a sales and/or trading desk of Standard
> Chartered Bank or its affiliate. It is not and does not constitute
> research material, independent research, recommendation or financial
> advice. Any market commentary is for information purpose only and shall
> not be relied for any other purpose, and is subject to the relevant
> disclaimers available at
> http://wholesalebanking.standardchartered.com/en/utility/Pages/d-mkt.aspx.
>
> Please visit
> http://wholesalebanking.standardchartered.com/en/capabilities/financialmarkets/Pages/doddfrankdisclosures.aspx
> for important information with respect to derivative products.
>
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>


More information about the Libraries mailing list