[Haskell-cafe] Re: Existencial quantification and polymorphic
datatypes (actually, components...)
Gleb Alexeyev
gleb.alexeev at gmail.com
Tue Jan 20 12:19:35 EST 2009
I just thought that the shorter explanation could do better: the
difference is in the types of the constructor functions.
Code:
> {-# LANGUAGE ExistentialQuantification #-}
> {-# LANGUAGE RankNTypes #-}
> data SomeNum1 = forall a. SN1 a
> data SomeNum2 = SN2 (forall a. a)
ghci session:
*Main> :t SN1
SN1 :: a -> SomeNum1
*Main> :t SN2
SN2 :: (forall a. a) -> SomeNum2
This is not the whole story, types of the bound variables you get on
pattern matching differ too, but this makes the short explanation a bit
longer :).
More information about the Haskell-Cafe
mailing list