problems with impredicativity
wagnerdm at seas.upenn.edu
wagnerdm at seas.upenn.edu
Sat Nov 5 00:33:57 CET 2011
Quoting Wolfgang Jeltsch <g9ks157k at acme.softbase.org>:
> this code is accepted by GHC 7.0.4:
> <snip>
> However, this one isn?t:
>
>> {-# LANGUAGE ImpredicativeTypes #-}
>>
>> polyId :: (forall a. Maybe a) -> Maybe a
>> polyId x = x
>>
>> polyIdMap :: [forall a. Maybe a] -> [forall a. Maybe a]
>> polyIdMap xs = fmap polyId xs
>
> Is there a way to make it accepted?
Yep, fix the type signature. There is no type you can substitute for
"a" in "Maybe a" that results in "forall a. Maybe a". But GHC accepts
the same code with the following type signature, which should make
clear what I mean:
polyIdMap :: [forall a. Maybe a] -> [Maybe (forall a. a)]
~d
More information about the Glasgow-haskell-users
mailing list