[GHC] #9227: Coverage Condition cannot be turned off
GHC
ghc-devs at haskell.org
Mon Jun 23 08:37:09 UTC 2014
#9227: Coverage Condition cannot be turned off
------------------------------------+-------------------------------------
Reporter: augustss | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Keywords: | Operating System: Unknown/Multiple
Architecture: Unknown/Multiple | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------------+-------------------------------------
Compile this program
{{{
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
module Bug1 where
class C a b | a -> b
data A a = A
data B a = B
instance C (A a) (B b)
}}}
and observe the error message
{{{
Bug1.hs:9:10:
Illegal instance declaration for `C (A a) (B b)'
The coverage condition fails in class `C'
for functional dependency: `a -> b'
Reason: lhs type `A a' does not determine rhs type `B b'
In the instance declaration for `C (A a) (B b)'
}}}
Then read manual, sec 7.6.3.3:
{{{
Both the Paterson Conditions and the Coverage Condition are lifted if you
give the -XUndecidableInstances flag
}}}
Compile again with -XUndecidableInstances. Observe the exact same error
message.
Either the compiler or the documentation is wrong. I certainly hope it is
the compiler, because it worked in 7.6 and was quite useful.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9227>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list