
#11207: GHC cannot infer injectivity on type family operating on GHC.TypeLits' Nat, but can for equivalent type family operating on user-defined Nat kind -------------------------------------+------------------------------------- Reporter: duairc | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following does not work: {{{#!hs {-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TypeOperators, UndecidableInstances #-} import GHC.TypeLits (Nat, type (-)) type family Replicate (n :: Nat) (a :: k) = (r :: [k]) | r -> n where Replicate 0 a = '[] Replicate n a = a ': Replicate (n - 1) a }}} It fails to compile with the following error: {{{ error: • Type family equation violates injectivity annotation. Type variable ‘n’ cannot be inferred from the right-hand side. In the type family equation: forall (k :: BOX) (n :: Nat) (a :: k). Replicate n a = a : Replicate (n - 1) a • In the equations for closed type family ‘Replicate’ In the type family declaration for ‘Replicate’ Failed, modules loaded: none. }}} However, the following does: {{{#!hs {-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TypeOperators, UndecidableInstances #-} data Nat = Zero | Succ Nat type family Replicate (n :: Nat) (a :: k) = (r :: [k]) | r -> n where Replicate Zero a = '[] Replicate (Succ n) a = a ': Replicate n a }}} Sure GHC.TypeLits' built-in Nat type is isomorphic to the one defined above, and thus GHC should be able to infer injectivity for Replicate? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11207 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler