#2569: Inferred type not accepted by compiler
------------------------+---------------------------------------------------
Reporter: ajd | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 6.9 | Severity: normal
Keywords: | Testcase:
Architecture: Unknown | Os: Unknown
------------------------+---------------------------------------------------
{{{ ghc --version: The Glorious Glasgow Haskell Compilation System,
version 6.9.20080825 }}}
A.hs:
{{{
{-# LANGUAGE TypeFamilies #-}
module A
where
data H a = A a | B a deriving Eq
class PL p
class PE a where
type P a :: *
instance PE [a] where
type P [a] = H a
instance PL (H a)
foo :: PE a => [P a] -> [P a] -> (([P a], [P a]),([P a],[P a]))
foo pa pb = ((pa, pa), (pb, pb))
-- bar :: (PE a) => [P a] -> [P a] -> Either ([P a], [P a]) [P a]
bar pa pb
= let _ = foo pa pb
in case True of
True -> Right pa
False -> Left (pa, pb)
}}}
Load the above module into GHCi.
{{{
*A> :t bar
bar :: (PE a) => [P a] -> [P a] -> Either ([P a], [P a]) [P a]
}}}
However, if we uncomment bar's type signature (which is ''exactly'' the
same as the one printed by GHCi), we get a type error:
{{{
[1 of 1] Compiling A ( A.hs, interpreted )
A.hs:23:16:
Couldn't match expected type `P a' against inferred type `P a1'
Expected type: [P a]
Inferred type: [P a1]
In the first argument of `foo', namely `pa'
In the expression: foo pa pb
Failed, modules loaded: none.
}}}
I'm not all that familiar with type families, but I'm pretty sure that
when GHCi prints a type, we ought to be able to specify that type and the
module ought to compile...
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2569>
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