Haskell platform proposal: split package

Brent Yorgey byorgey at seas.upenn.edu
Sat Jul 21 02:34:46 CEST 2012


On Fri, Jul 20, 2012 at 11:25:47PM +0200, Henning Thielemann wrote:
> 
> On Fri, 20 Jul 2012, Brent Yorgey wrote:
> 
> >Use of GHC.Exts
> >---------------
> >
> >At the request of a user, the 0.1.4.3 release switched from defining
> >its own version of the standard 'build' function, to importing it from
> >GHC.Exts.  This allows GHC to do more optimization, resulting in
> >reported speedups to uses of splitEvery, splitPlaces, and
> >splitPlacesBlanks.  However, this makes the library GHC-specific.  If
> >any reviewers think this is an issue I would be willing to go back to
> >defining build by hand, or use CPP macros to select between build
> >implementations based on the compiler.
> 
> You could provide two private modules with the same name in different
> directories, one that re-exports 'build' from GHC.Exts and one with a
> custom definition of 'build' for non-GHC compilers. Then set
> 'Hs-Source-Dirs' in Cabal according to the impl(ghc). No CPP needed,
> only Cabal. One could even think of a separate package for this
> purpose.

Ah, this is a good idea.  I'd still like to hear from other reviewers
whether they think it is worth the trouble.  To what extent should the
Haskell Platform try to be compiler-agnostic (even though it includes
GHC)?

> The only type extension you use, is GADTs, right? It looks like you
> use it for an Eq constraint in Delimiter/DelimSublist. That is, you
> actually need only ExistentialQuantification. Is it necessary?

You are right, actually, only ExistentialQuantification is necessary,
as long as we also stop using GADT syntax.  I didn't realize before
that this syntax is accepted:

  {-# LANGUAGE ExistentialQuantification #-}

  data Delimiter a =         DelimEltPred (a -> Bool)
		   | Eq a => DelimSublist [a]

I do agree that this is a bit weird, what's going on here is not
exactly existential quantification.  But in any case the
ExistentialQuantification extension turns on this ability to embed
class constraints in data constructors -- at least in GHC.  I am happy
to make this change, but I guess it again raises the issue
GHC-specificity.

As to whether there is a way to do this without using
ExistentialQuantification, I don't see an obvious solution (though
there probably is one).  The issue is that we certainly don't want to
require an (Eq a) constraint when using a predicate, but we need one
when matching sublists.  I'm open to suggestions.

-Brent



More information about the Libraries mailing list