#5120: inferred type of an implicit parameter rejected (associated type)
---------------------------+------------------------------------------------
Reporter: mikkonecny | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 7.0.3 | Keywords: associated type, implicit parameter
Testcase: | Blockedby:
Os: Linux | Blocking:
Architecture: x86 | Failure: None/Unknown
---------------------------+------------------------------------------------
The following module:
{{{
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Test where
class C t where
type TF t
ttt :: TF t -> t
b :: (C t, ?x :: TF t) => t
b = ttt ?x
}}}
compiles fine with ghc 6.12.3 but ghc 7.0.3 says:
{{{
Could not deduce (?x::TF t)
arising from a use of implicit parameter `?x'
from the context (C t, ?x::TF t)
bound by the type signature for b :: (C t, ?x::TF t) => t
at Test.hs:13:1-10
In the first argument of `ttt', namely `?x'
In the expression: ttt ?x
In an equation for `b': b = ttt ?x
}}}
Moreover, when I comment out the type declaration for b, ghc 7.0.3
compiles it and the inferred type for b is identical to the one that was
commented out:
{{{
*Test> :t b
b :: (C t, ?x::TF t) => t
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5120>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs