[Haskell-cafe] Explicit forall - Strange Error

Shayan Najd Javadipour sh.najd at gmail.com
Tue Jul 31 21:24:38 CEST 2012


If GHC handles the explicit "forall" in constructor "T1" in the same way as
it does for function "f", we have:

data T a where T1 :: (forall b. b -> b) -> Int -> T a


Which is totally fine! The main question is then why the "forall"s are
handled differently?

On Tue, Jul 31, 2012 at 9:07 PM, MigMit <miguelimo38 at yandex.ru> wrote:

> It really seems to me that the error message you've got explains
> everything quite clear.
>
> Отправлено с iPad
>
> 31.07.2012, в 22:59, Shayan Najd Javadipour <sh.najd at gmail.com>
> написал(а):
>
> 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
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120731/4e495b32/attachment.htm>


More information about the Haskell-Cafe mailing list