problems with impredicativity
Wolfgang Jeltsch
g9ks157k at acme.softbase.org
Fri Nov 4 23:12:55 CET 2011
Hello,
this code is accepted by GHC 7.0.4:
> {-# LANGUAGE ImpredicativeTypes #-}
>
> polyId :: (forall a. a) -> a
> polyId x = x
>
> polyIdMap :: [forall a. a] -> [forall a. a]
> polyIdMap xs = fmap polyId xs
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?
Best wishes,
Wolfgang
More information about the Glasgow-haskell-users
mailing list