Proposal: Deprecate ExistentialQuantification

Sittampalam, Ganesh ganesh.sittampalam at credit-suisse.com
Thu Jul 23 12:36:00 EDT 2009


One can use the following style of GADT definition, which avoids the
type variables in the declaration:

{-# LANGUAGE GADTs, KindSignatures #-}
module GADT where

data Foo :: * -> * where
  Foo :: Int -> Foo Int

Iavor Diatchki wrote:
> Hello,
> 
> Sorry for responding so late---I just saw the thread.  I don't think
> that we should deprecate the usual way to define existentials.  While
> the GADT syntax is nice in some cases, there are also examples when
> it is quite verbose. For example, there is a lot of repetition in
> datatypes that have many constructors, especially if the datatype has
> parameters and a slightly longer name.  Furthermore, I find the type
> variables in the declaration of the type quite confusing because they
> have no relation to the type variables in the constructors.  Finally,
> there is quite a lot of literature about the semantics of existential
> types, while the semantics of GADTs seems quite complex, so it seems
> a bit risky to mix up the two.          
> 
> -Iavor
> 
> 
> 
> 
> 
> On Thu, Jul 23, 2009 at 2:47 PM, Niklas
> Broberg<niklas.broberg at gmail.com> wrote: 
>>> Discussion period: 2 weeks
>> 
>> Returning to this discussion, I'm surprised that so few people have
>> actually commented yea or nay. Seems to me though that...
>> * Some people are clearly in favor of a move in this direction, as
>> seen both by their replies here and discussion over other channels.
>> * Others are wary of deprecating anything of this magnitude for
>> practical reasons. 
>> * No one has commented in true support of the classic existential
>> syntax, only wanting to keep it for "legacy" reasons.
>> 
>> I'm in no particular hurry to see this deprecation implemented, and I
>> certainly understand the practical concerns, but I would still very
>> much like us to make a statement that this is the direction we intend
>> to go in the longer run. I'm not sure what the best procedure for
>> doing so would be, but some sort of soft deprecation seems
>> reasonable to me. 
>> 
>> Further thoughts?
>> 
>> Cheers,
>> 
>> /Niklas
>> _______________________________________________
>> Haskell-prime mailing list
>> Haskell-prime at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-prime
>> 
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


=============================================================================== 
 Please access the attached hyperlink for an important electronic communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 =============================================================================== 
 


More information about the Haskell-prime mailing list