Yes. There is a significant difference in both the internal
representation and the high level representation. ExistsEq is a
structure with two internal fields the dictionary and the function,
while the RankNEq has only one field. As Andreas Rossberg noted
ExistsEq is useless without extra fields. Here is an example which
might be more useful:

data Exists = Eq a => Exists (a -> a) a a

next :: Exists -> Maybe Exists
next (Exists f x y)
   | x == y     = Nothing
   | otherwise = Just (Exists f (f x) y)

Note that the only functions which I can apply over type 'a' are (==) and f.

Cheers,
  Krasimir

On 4/27/05, Andre Pang <[EMAIL PROTECTED]> wrote:
> On 27/04/2005, at 9:26 PM, Krasimir Angelov wrote:
> 
> > 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).
> 
> Thanks Krasimir and Tomasz for that clarification.  Unfortunately, I'm
> still a bit confused :).  Krasimir, from what you say, this sounds like
> a big difference in implementation, but from a Haskell
> (non-type-wizard) user's point of view, is there a practical difference
> between the two?  I can't think of a situation where
> rank-N/existentials couldn't be substituted for the other ...
> 
> 
> --
> % Andre Pang : trust.in.love.to.save  <http://www.algorithm.com.au/>
> 
>
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to