Implicit 'forall' in data declarations
Sebastian Fischer
fischer at nii.ac.jp
Fri Oct 15 21:09:38 EDT 2010
Hello,
GHC 6.12.3 allows to omit the explicit quantification of
higher-rank type variables using 'forall' in data types if they
appear in a type class context
{-# LANGUAGE RankNTypes #-}
data Foo = Foo (Eq a => a)
Is this implicit introduction of 'forall' intended? If it is, why
does it not work in function types? The following is not accepted
by my GHC:
bar :: Eq b => (Eq a => a) -> b
bar x = x
The error message is
All of the type variables in the constraint `Eq a'
are already in scope (at least one must be universally quantified
here)
(Use -XFlexibleContexts to lift this restriction)
Using `FlexibleContexts` the signature of `bar` seems to be
interpreted as
bar :: (Eq b, Eq a) => a -> b
because then the error becomes
Couldn't match expected type `b' against inferred type `a'
So unlike in data-type declarations, a 'forall' in a function type
must be written explicitly even if the quantified variable appears in
a local type class constraint.
bar :: Eq b => (forall a . Eq a => a) -> b
bar x = x
I have not yet installed GHC 7. Is this inconsistency between data and
function declarations intended or has it been changed in the new type
checker?
Sebastian
More information about the Glasgow-haskell-users
mailing list