[Haskell-cafe] Explicit forall - Strange Error

Shayan Najd Javadipour sh.najd at gmail.com
Tue Jul 31 20:59:30 CEST 2012


Hi,

I wonder why the following code doesn't typecheck in GHC 7.4.1:

{-# LANGUAGE GADTs,RankNTypes #-}data T a where T1 :: (forall b. b ->
b) -> (forall a. Int -> T a)
{- Error:
Data constructor `T1' returns type `forall a. Int -> T a'
      instead of an instance of its parent type `T a'
    In the definition of data constructor `T1'
    In the data type declaration for `T'
Failed, modules loaded: none. -}
While:


{-# LANGUAGE GADTs,RankNTypes #-}
f :: (forall b. b -> b) -> (forall a. Int -> Maybe a)f = undefined
{-
ghci> :t f
f :: (forall b. b -> b) -> Int -> Maybe a
-}


Thanks,
 Shayan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120731/2d2229eb/attachment-0001.htm>


More information about the Haskell-Cafe mailing list