[GHC] #10009: type inference regression when faking injective type families
GHC
ghc-devs at haskell.org
Tue Jun 2 21:54:21 UTC 2015
#10009: type inference regression when faking injective type families
-------------------------------------+-------------------------------------
Reporter: aavogt | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.10.2
Component: Compiler (Type | Version: 7.10.1-rc1
checker) | Keywords:
Resolution: | Architecture:
Operating System: Unknown/Multiple | Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | Blocking:
Blocked By: | Differential Revisions:
Related Tickets: #10226 |
-------------------------------------+-------------------------------------
Comment (by jeltsch):
I have an issue with GHC 7.10.1, which is probably rooted in the same bug.
The following code is accepted by GHC 7.8.3, but not 7.10.1:
{{{
{-# LANGUAGE TypeFamilies #-}
type family F a :: *
type family G b :: *
x :: G (F a) ~ a => F a
x = undefined
}}}
GHC 7.10.1 gives the following error message:
{{{
Could not deduce (F a0 ~ F a)
from the context (G (F a) ~ a)
bound by the type signature for x :: (G (F a) ~ a) => F a
at Test.hs:7:6-23
NB: ‘F’ is a type function, and may not be injective
The type variable ‘a0’ is ambiguous
In the ambiguity check for the type signature for ‘x’:
x :: forall a. (G (F a) ~ a) => F a
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
In the type signature for ‘x’: x :: G (F a) ~ a => F a
}}}
Is this code accepted by GHC HEAD?
I came across this problem when trying to recompile the `incremental-
computing` package with GHC 7.10.1. Since this issue breaks `incremental-
computing` in a nontrivial way, I would be ''extremely'' happy if the fix
of this bug would make it into GHC 7.10.2.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10009#comment:29>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list