
#11324: Missing Kind Inference -------------------------------------+------------------------------------- Reporter: crockeea | 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 example doesn't compile, but I expected it to. {{{ {-# LANGUAGE RankNTypes, ConstraintKinds, ScopedTypeVariables, KindSignatures, PolyKinds, DataKinds, FlexibleInstances, UndecidableInstances, TypeFamilies #-} module Test where data Proxy a data Tagged t s = Tag s type family CharOf fp :: k class Reflects (a :: k) where value :: Proxy a instance Reflects (a :: Bool) type MyConstraint (x :: Bool) = (x~x) foo :: forall fp . (MyConstraint (CharOf fp)) => Tagged fp Int foo= let x = value::Proxy (CharOf fp) in Tag 2 }}} The error in 7.10.2 (unable to test with HEAD) is `Could not deduce (Reflects k (CharOf k fp)) arising from a use of ‘value’`, basically that it was unable to figure out the kind of `CharOf fp`. I think GHC should know the kind from the constraint on `foo`. I've found two workarounds: {{{ foo :: forall fp . (MyConstraint (CharOf fp)) => Tagged fp Int foo= let x = value::Proxy (CharOf fp :: Bin) in Tag 2 }}} and {{{ foo :: forall fp x . (MyConstraint x, x~CharOf fp) => Tagged fp Int foo= let x = value::Proxy x in Tag 2 }}} but both seem unnecessary. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11324 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler