[Haskell] Rank-N types vs existential types

Krasimir Angelov kr.angelov at gmail.com
Wed Apr 27 07:26:54 EDT 2005


RankN and Exists are completelly different. The types of RankNEq and
ExistsEq constructors are:

RankNEq :: (forall a. Eq a => a -> a -> Bool) -> RankN
ExistsEq :: forall a. Eq a => (a -> a -> Bool) -> Exists

i.e. RankNEq requires one argument, which is a polymorfic function
that have to be applied to Eq dictonary. ExistsEq have two arguments:
an Eq dictonary and function of type (a -> a -> Bool).

Cheers,
  Krasimir

On 4/27/05, Andre Pang <ozone at algorithm.com.au> wrote:
> Hi all,
> 
> Let's say I have the following two data types:
> 
> > {-# OPTIONS_GHC -fglasgow-exts #-}
> >
> > module RankNVsExists where
> >
> > data RankN  = RankNEq (forall a. Eq a => a -> a -> Bool)
> >             | RankNOrd (forall a. Ord a => a -> a -> Bool)
> >
> > data Exists = forall a. Eq a => ExistsEq (a -> a -> Bool)
> >             | forall a. Ord a => ExistsOrd (a -> a -> Bool)
> 
> So, the RankN type uses rank-2 polymorphism to "hide" the expression
> inside the type, whereas the Exists type uses existentially quantified
> types instead.  The two seem pretty equivalent to me, since the data
> constructors have the same type.  However, I can't help but feel that
> I'm missing something fundamental about a difference between them.  Are
> the two completely isomorphic?  Is there some advantage or disadvantage
> to using one over the other?
> 
> --
> % Andre Pang : trust.in.love.to.save  <http://www.algorithm.com.au/>
> 
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>


More information about the Haskell mailing list