
#14366: Type family equation refuses to unify wildcard type patterns -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Type checker) | Keywords: TypeFamilies, | Operating System: Unknown/Multiple TypeInType | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This typechecks: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} import Data.Kind import Data.Type.Equality type family Cast (e :: a :~: b) (x :: a) :: b where Cast Refl x = x }}} However, if you try to make the kinds `a` and `b` explicit arguments to `Cast`: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} import Data.Kind import Data.Type.Equality type family Cast (a :: Type) (b :: Type) (e :: a :~: b) (x :: a) :: b where Cast _ _ Refl x = x }}} Then GHC gets confused: {{{ GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ryanglscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:9:12: error: • Expected kind ‘_ :~: _1’, but ‘'Refl’ has kind ‘_ :~: _’ • In the third argument of ‘Cast’, namely ‘Refl’ In the type family declaration for ‘Cast’ | 9 | Cast _ _ Refl x = x | ^^^^ }}} A workaround is to explicitly write out what should be inferred by the underscores: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} import Data.Kind import Data.Type.Equality type family Cast (a :: Type) (b :: Type) (e :: a :~: b) (x :: a) :: b where Cast a a Refl x = x }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14366 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler