GHC incorrectly considers type family instances conflicting?
I asked this on stackoverflow first https://stackoverflow.com/questions/44958114/why-these-type-family-instances-conflicting
I'm using GHC-8.0.1. This code (requires singletons lib):
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
import Data.Singletons
type family MkCtx (kx :: Type) (kc :: Type) (c :: kc) (x :: kx) :: Constraint
type instance MkCtx kx (kx ~> Constraint) c x = Apply c x
type instance MkCtx kx (kx -> Constraint) c x = c x
with the message:
Conflicting family instance declarations:
forall kx (x :: kx) (c :: kx ~> Constraint).
MkCtx kx (kx ~> Constraint) c x = Apply c x
forall kx (x :: kx) (c :: kx -> Constraint).
MkCtx kx (kx -> Constraint) c x = c x
Why GHC considers these instances conflicting? I don't see how they overlap.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |