
#13931: GHC incorrectly considers type family instances conflicting? -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- 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): {{{#!hs {-# 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. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13931 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler