
#12919: Equality not used for substitution -------------------------------------+------------------------------------- Reporter: int-index | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | 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: -------------------------------------+------------------------------------- This code {{{ {-# LANGUAGE TypeInType, TypeFamilies, GADTs, ConstraintKinds #-} import Data.Kind data N = Z data V :: N -> Type where VZ :: V Z type family VC (n :: N) :: Type where VC Z = Type type family VF (xs :: V n) (f :: VC n) :: Type where VF VZ f = f data Dict c where Dict :: c => Dict c prop :: xs ~ VZ => Dict (VF xs f ~ f) prop = Dict }}} fails with this error: {{{ Op.hs:20:8: error: • Couldn't match type ‘f’ with ‘VF 'VZ f’ arising from a use of ‘Dict’ ‘f’ is a rigid type variable bound by the type signature for: prop :: forall (xs :: V 'Z) f. xs ~ 'VZ => Dict VF xs f ~ f at Op.hs:19:9 • In the expression: Dict In an equation for ‘prop’: prop = Dict • Relevant bindings include prop :: Dict VF xs f ~ f (bound at Op.hs:20:1) }}} However, if I substitute `xs` with `VZ` (by hand) in the type of `prop`, it compiles. Can be reproduced with GHC 8.0.1 but not HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12919 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler