Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Niklas Broberg
Hi all,

Following the discussion on the use of 'forall' and extensions that
use it [1], I would hereby like to propose that the
ExistentialQuantification extension is deprecated.

My rationale is as follows. With the introduction of GADTs, we now
have two ways to write datatype declarations, the old simple way and
the GADTs way. The GADTs way fits better syntactically with Haskell's
other syntactic constructs, in all ways. The general style is
(somewhat simplified) keyword type 'where' decls, where keyword can
in Haskell 98 be class or instance, but with GADTs also data. The old
simple way of defining data types is the odd one out. It certainly has
its uses though, in particular when defining some simple (but possibly
large) enum-like datatype (like cabal's Extension type incidentally),
then it obviously becomes tedious to have to restate the trivial type
signature for each constructor.

Using GADTs style syntax it is possible to allow constructors with
existentially quantified arguments with *no additional syntax needed*.
It follows nicely from the standard syntax for type signature
declarations (assuming explicit foralls), e.g. the following normal
datatype declaration

  data Foo =
forall a . Show a = Foo a

which uses ExistentialQuantification syntax, could be written as

  data Foo where
Foo :: forall a . Show a = a - Foo

which is syntactically just a normal type signature.

The upside of deprecating ExistentialQuantification is thus that we
keep the syntax cleaner, and we keep the old style of datatype
declarations simple (as it should be, IMO). Anything fancier can use
the GADTs syntax, which anyone that uses something fancier should be
acquainted with anyway.

The downside is that we lose one level of granularity in the type
system. GADTs enables a lot more semantic possibilities for
constructors than ExistentialQuantification does, and baking the
latter into the former means we have no way of specifying that we
*only* want to use the capabilities of ExistentialQuantification.

My own take on that is that what we have now is a wart that should be
removed, and that if we think that the latter is a problem then the
way to go would be to split the monolithic GADTs extension into
several semantic levels. There is of course also the downside that we
break existing code, but that's a standard problem with improvement
through deprecation which I will pay no mind.


Discussion period: 2 weeks

Cheers,

/Niklas

[1] http://www.haskell.org/pipermail/glasgow-haskell-users/2009-June/017432.html
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: group keyword with TransformListComp

2009-06-27 Thread Max Bolingbroke
Hi,

I agree this is annoying. It was hard to find syntax which was both
meaningful and currently unused, so we settled on this instead. As
Simon says, suggestions are welcome!

Note that group *should* be parsed as a special id, so you can still
import D.L qualified and then use dot notation to access the function.

Cheers,
Max

2009/6/21 Neil Mitchell ndmitch...@gmail.com:
 Hi,

 The TransformListComp extension makes group a keyword. Unfortunately
 group is a useful function, and is even in Data.List. Thus,
 Data.List.group and TransformListComp are incompatible. This seems a
 very painful concession to give up a nice function name for a new
 extension. Is this intentional? Here's an example:

 $ cat GroupKeyword.hs
 {-# LANGUAGE TransformListComp #-}
 module GroupKeyword where

 a = map head $ group $ sort [1..100]
 $ ghci GroupKeyword.hs
 GHCi, version 6.10.2: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling GroupKeyword     ( GroupKeyword.hs, interpreted )

 GroupKeyword.hs:4:15: parse error on input `group'
 Failed, modules loaded: none.
 Prelude

 There are some places I'd like to use TransformListComp, but I often
 want to use group in the same module.

 Thanks

 Neil

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Antoine Latter
On Sat, Jun 27, 2009 at 5:44 AM, Niklas Brobergniklas.brob...@gmail.com wrote:
 Hi all,

 Following the discussion on the use of 'forall' and extensions that
 use it [1], I would hereby like to propose that the
 ExistentialQuantification extension is deprecated.

 My rationale is as follows. With the introduction of GADTs, we now
 have two ways to write datatype declarations, the old simple way and
 the GADTs way. The GADTs way fits better syntactically with Haskell's
 other syntactic constructs, in all ways. The general style is
 (somewhat simplified) keyword type 'where' decls, where keyword can
 in Haskell 98 be class or instance, but with GADTs also data. The old
 simple way of defining data types is the odd one out. It certainly has
 its uses though, in particular when defining some simple (but possibly
 large) enum-like datatype (like cabal's Extension type incidentally),
 then it obviously becomes tedious to have to restate the trivial type
 signature for each constructor.

How does the support of the extensions differ between existing implementations?

Antoine
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Isaac Dupree

Niklas Broberg wrote:

  data Foo =
forall a . Show a = Foo a

which uses ExistentialQuantification syntax, could be written as

  data Foo where
Foo :: forall a . Show a = a - Foo



The downside is that we lose one level of granularity in the type
system. GADTs enables a lot more semantic possibilities for
constructors than ExistentialQuantification does, and baking the
latter into the former means we have no way of specifying that we
*only* want to use the capabilities of ExistentialQuantification.


Is it easy algorithmically to look at a GADT and decide whether it has 
only ExistentialQuantification features?  After all, IIRC, hugs and nhc 
support ExistentialQuantification but their type systems might not be up 
to the full generality of GADTs.  (GHC's wasn't even quite up to it for 
quite a long time until around 6.8, when we finally got it right.)


-Isaac
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Malcolm Wallace

I would hereby like to propose that the
ExistentialQuantification extension is deprecated.


It is worth pointing out that all current Haskell implementations (to  
my knowledge) have ExistentialQuantification, whilst there is only one  
Haskell implementation that has the proposed replacement feature, GADTs.


Of course, that in itself is not an argument to avoid desirable change  
to the language, but it is one factor to consider.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Niklas Broberg
 I would hereby like to propose that the
 ExistentialQuantification extension is deprecated.

 It is worth pointing out that all current Haskell implementations (to my
 knowledge) have ExistentialQuantification, whilst there is only one Haskell
 implementation that has the proposed replacement feature, GADTs.

 Of course, that in itself is not an argument to avoid desirable change to
 the language, but it is one factor to consider.

The tongue-in-cheek response is that it should be a factor to consider
only for how long a deprecation period we want... ;-)

Seriously though, it's of course a consideration that should be made.
It also ties back to the problem of the monolithic GADTs extension,
which isn't trivial to implement in other tools - but the
ExistentialQuantification *subset* of GADTs should be easy, for any
implementation that already supports the current
ExistentialQuantification extension, since then it's just a syntactic
issue.

So might as well bite that bullet then, what if we did the following
split, in the spirit of the various increasing power of the extensions
that enable forall-quantified types ((ExplicitForall =)
PolymorphicComponents = Rank2Types = RankNTypes):

* NewConstructorSyntax: Lets the programmer write data types using the
GADTs *syntax*, but doesn't add any type-level power (and no forall
syntax). Could probably use a better name (bikeshed warning).

* ExistentialQuantification: Implies NewConstructorSyntax (and
ExplicitForall). Let's the programmer use existentially quantified
arguments to constructors when using the GADTs syntax. Still requires
all constructors to have the same type, which is the one given in the
header.

* GADTs: Implies ExistentialQuantification. Let's the programmer use
the full type-level power of GADTs.

It might make sense to merge NewConstructorSyntax and
ExistentialQuantification, though I'm not sure naming that merge
ExistentialQuantification would be accurate (naming is the bikeshed
though). Personally I would prefer the full 3-way split, to keep a
clean separation between syntactic and semantic extensions, but it's a
rather weak preference.

If we had something like this split, implementations that already
support ExistentialQuantification at the type level would only need
to change their parsers in a simple way (nothing hard, trust me), and
add what should be a simple check that the constructors all have the
declared type.

Would that be preferable?

Cheers,

/Niklas
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Brandon S. Allbery KF8NH

On Jun 27, 2009, at 15:37 , Niklas Broberg wrote:

* NewConstructorSyntax: Lets the programmer write data types using the
GADTs *syntax*, but doesn't add any type-level power (and no forall
syntax). Could probably use a better name (bikeshed warning).


GeneralizedTypeSyntax occurs to me.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users