[GHC] #10338: GHC Forgets Constraints
GHC
ghc-devs at haskell.org
Tue Apr 21 13:49:49 UTC 2015
#10338: GHC Forgets Constraints
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
This is possibly fixed by #10195, but I don't have a convenient means of
testing it. At any rate, this testcase is considerably simpler than the
one in #10195.
{{{#!hs
{-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs, MultiParamTypeClasses
#-}
type family F r
class (Functor t) => T t r where
fromScalar :: r -> t r
data Foo t r where
Foo :: t (F r) -> Foo t r
Scalar :: r -> Foo t r
toF :: r -> F r
toF = undefined
convert :: (T t (F r))
=> Foo t r -> Foo t r
convert (Scalar c) =
let fromScalar' = fromScalar
in Foo $ fromScalar' $ toF c
}}}
This code compiles with GHC 7.8.4.
When I add a generic instance for `T` (which requires
`FlexibleInstances`): `instance (Functor t, Num r) => T t r`
GHC complains:
{{{#!hs
Could not deduce (Num (F r)) arising from a use of ‘fromScalar’
from the context (T t (F r))
bound by the type signature for
convert :: (T t (F r)) => Foo t r -> Foo t r
at Main.hs:(17,12)-(18,23)
In the expression: fromScalar
In an equation for ‘fromScalar'’: fromScalar' = fromScalar
In the expression:
let fromScalar' = fromScalar in Foo $ fromScalar' $ toF c
}}}
Of course the problem can be fixed by adding a type signature to
`fromScalar` and adding `ScopedTypeVariables`:
{{{#!hs
convert :: forall t r . (T t (F r))
=> Foo t r -> Foo t r
convert (Scalar c) =
let fromScalar' = fromScalar :: F r -> t (F r)
in Foo $ fromScalar' $ toF c
}}}
Like #10195, this is triggered when a generic instance is in scope. The
(main) problem of course is that GHC tries to match the generic instance
instead of using the `T (F r)` constraint supplied by `convert`.
A secondary issue is that I think the example should have the same
behavior pre- and post-instance, i.e either both should compile or both
should not compile. I'm not sure if a monomorphism restriction is actually
being triggered here or if that's just a red herring.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10338>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list