
#8030: FlexibleContexts PolyKinds Type Families bug --------------------------------------+------------------------------------- Reporter: wvv | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: GHC rejects valid program | Blockedby: Blocking: | Related: --------------------------------------+------------------------------------- A bug with TypeFamilies + FlexibleContexts + PolyKinds {{{ {-# LANGUAGE PolyKinds, FlexibleContexts, TypeFamilies #-} class Monoid (a :: k) where type Pr a :: * mempty :: Pr a mappend :: Pr a -> Pr a -> Pr a instance Monoid [b] where type Pr [b] = [b] mempty = [] mappend = (++) }}} This is compilable. But this is not: {{{ t :: (Monoid [b]) => b -> [b] t b = [b] `mappend` mempty }}} {{{ Could not deduce ([b] ~ Pr k0 a0) from the context (Monoid * [b]) bound by the type signature for t :: Monoid * [b] => b -> [b] at t.hs:26:6-29 The type variables `k0', `a0' are ambiguous Possible fix: add a type signature that fixes these type variable(s) In the expression: [b] `mappend` mempty In an equation for `t': t b = [b] `mappend` mempty Could not deduce (Pr k1 a1 ~ [b]) from the context (Monoid * [b]) bound by the type signature for t :: Monoid * [b] => b -> [b] at test4.hs:26:6-29 The type variables `k1', `a1' are ambiguous Possible fix: add a type signature that fixes these type variable(s) Expected type: Pr k0 a0 Actual type: Pr k1 a1 In the second argument of `mappend', namely `mempty' In the expression: [b] `mappend` mempty In an equation for `t': t b = [b] `mappend` mempty }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8030 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler