[GHC] #8030: FlexibleContexts PolyKinds Type Families bug

#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

#8030: FlexibleContexts PolyKinds Type Families bug ---------------------------------+------------------------------------------ Reporter: wvv | Owner: Type: bug | Status: closed Priority: normal | Component: Compiler Version: 7.6.3 | Resolution: invalid Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: GHC rejects valid program Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by goldfire): * status: new => closed * resolution: => invalid Comment: This looks like correct behavior to me. The problem is that the type signatures for `mempty` and `mappend` are inherently ambiguous. Because GHC cannot know whether `Pr` is injective, there is no way to get the identity of the type `a` from the identity of `Pr a`. Thus, all uses of `mempty` and `mappend` will be ambiguous. This ambiguity is what is causing the error you see. It's possible that the definitions of `mempty` and `mappend` as given should be rejected, but the error you're seeing looks correct to me. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8030#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC