Regression in the typechecker in GHC 7.8.2
Simon Peyton Jones
simonpj at microsoft.com
Mon Jun 16 12:59:30 UTC 2014
Copying ghc-devs. Oleg says:
| Sorry for reporting a problem via e-mail. It seems track no
| longer accepts anonymous (guest) submissions. When I tried to register
| the account I was told that my submission is a spam. The tracker is
| really well protected.
Can anyone help him? I'll open a ticket.
Simon
| -----Original Message-----
| From: oleg at okmij.org [mailto:oleg at okmij.org]
| Sent: 16 June 2014 11:46
| To: Simon Peyton Jones
| Subject: Regression in the typechecker in GHC 7.8.2
|
|
| Hello!
|
| Sorry for reporting a problem via e-mail. It seems track no
| longer accepts anonymous (guest) submissions. When I tried to register
| the account I was told that my submission is a spam. The tracker is
| really well protected.
|
| Here is the problem: what used to type check in GHC 7.4.1 (and I think
| in 7.6.2, although I no longer have access to that version) fails in GHC
| 7.8.2.
|
| The following program type-checks with GHC 7.4.1 and GHC 7.8.2:
|
| {-# LANGUAGE RankNTypes #-}
| {-# LANGUAGE TypeFamilies #-}
|
| module T where
|
| foo :: (forall f g. (Functor f) => f a -> f b) -> [a] -> [b]
| -- foo :: (forall f g. (Functor f, g ~ f) => g a -> g b) -> [a] -> [b]
| foo tr x = tr x
|
| t = foo (fmap not) [True]
|
| The following code (which differs only in the signature of foo)
|
| {-# LANGUAGE RankNTypes #-}
| {-# LANGUAGE TypeFamilies #-}
|
| module T where
|
| -- foo :: (forall f g. (Functor f) => f a -> f b) -> [a] -> [b] foo ::
| (forall f g. (Functor f, g ~ f) => g a -> g b) -> [a] -> [b] foo tr x =
| tr x
|
| t = foo (fmap not) [True]
|
|
| type-checks with 7.4.1 but not with 7.8.2. The latter reports the error
|
| Couldn't match type `b' with `Bool'
| `b' is untouchable
| inside the constraints (Functor f, g ~ f)
| bound by a type expected by the context:
| (Functor f, g ~ f) => g Bool -> g b
| at /tmp/t.hs:12:5-25
| `b' is a rigid type variable bound by
| the inferred type of t :: [b] at /tmp/t.hs:12:1
| Expected type: Bool -> b
| Actual type: Bool -> Bool
| Relevant bindings include t :: [b] (bound at /tmp/t.hs:12:1)
| In the first argument of `fmap', namely `not'
| In the first argument of `foo', namely `(fmap not)'
|
| Giving t the type signature [Bool] fixes the problem. Alas, I come
| across the similar untouchable error in situations where giving the type
| signature is quite difficult (in local bindings, with quite large
| types).
|
| Sorry again for the off-line report,
| Oleg
More information about the ghc-devs
mailing list