[Haskell-cafe] Explicit forall - Strange Error
Brandon Allbery
allbery.b at gmail.com
Tue Jul 31 21:28:35 CEST 2012
On Tue, Jul 31, 2012 at 2:59 PM, Shayan Najd Javadipour
<sh.najd at gmail.com>wrote:
> {-# 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'
>
>
This looks to me like other cases where GHC requires an exact type match
even though you used something equivalent. Similarly, for example, it
rejects (contrived example)
foo :: Num a => a -> a -> a
foo 0 0 = -1
foo = (+)
because the explicit arity of the cases must match exactly, even though
(+)'s type matches the required arity. I am under the impression that it's
difficult to make those kinds of things work nicely in the typechecker.
--
brandon s allbery allbery.b at gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120731/d15338d3/attachment.htm>
More information about the Haskell-Cafe
mailing list