[GHC] #15507: Deriving with QuantifiedConstraints is unable to penetrate type families
GHC
ghc-devs at haskell.org
Sat Aug 11 20:18:47 UTC 2018
#15507: Deriving with QuantifiedConstraints is unable to penetrate type families
-------------------------------------+-------------------------------------
Reporter: isovector | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version:
Keywords: | Operating System: Unknown/Multiple
QuantifiedConstraints |
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I'd expect the following code to successfully derive a usable `Eq`
instance for `Foo`.
{{{#!hs
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module QuantifiedConstraints where
import Data.Functor.Identity
type family HKD f a where
HKD Identity a = a
HKD f a = f a
data Foo f = Foo
{ zoo :: HKD f Int
, zum :: HKD f Bool
}
deriving instance (forall a. Eq (HKD f a)) => Eq (Foo f)
}}}
However, it complains:
{{{
• Could not deduce (Eq (HKD f a))
from the context: forall a. Eq (HKD f a)
bound by an instance declaration:
forall (f :: * -> *). (forall a. Eq (HKD f a)) => Eq
(Foo f)
at /home/sandy/prj/book-of-
types/code/QuantifiedConstraints.hs:20:19-56
• In the ambiguity check for an instance declaration
To defer the ambiguity check to use sites, enable
AllowAmbiguousTypes
In the stand-alone deriving instance for
‘(forall a. Eq (HKD f a)) => Eq (Foo f)’
}}}
Adding -XAllowAmbiguousTypes doesn't fix the situation:
{{{
• Could not deduce (Eq (HKD f a))
arising from a use of ‘GHC.Classes.$dm/=’
from the context: forall a. Eq (HKD f a)
bound by the instance declaration
at /home/sandy/prj/book-of-
types/code/QuantifiedConstraints.hs:21:1-56
• In the expression: GHC.Classes.$dm/= @(Foo f)
In an equation for ‘/=’: (/=) = GHC.Classes.$dm/= @(Foo f)
When typechecking the code for ‘/=’
in a derived instance for ‘Eq (Foo f)’:
To see the code I am typechecking, use -ddump-deriv
In the instance declaration for ‘Eq (Foo f)’
}}}
and the result of -ddump-deriv:
{{{
==================== Derived instances ====================
Derived class instances:
instance (forall a.
GHC.Classes.Eq (QuantifiedConstraints.HKD f a)) =>
GHC.Classes.Eq (QuantifiedConstraints.Foo f) where
(GHC.Classes.==)
(QuantifiedConstraints.Foo a1_a6MW a2_a6MX)
(QuantifiedConstraints.Foo b1_a6MY b2_a6MZ)
= (((a1_a6MW GHC.Classes.== b1_a6MY))
GHC.Classes.&& ((a2_a6MX GHC.Classes.== b2_a6MZ)))
Derived type family instances:
==================== Filling in method body ====================
GHC.Classes.Eq [QuantifiedConstraints.Foo f_a6N0[ssk:1]]
GHC.Classes./= = GHC.Classes.$dm/=
@(QuantifiedConstraints.Foo f_a6N0[ssk:1])
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15507>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list