#3383: Confluent type instances confuse the solver
----------------------------------------------------+-----------------------
Reporter: desp | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
(Type checker)
Version: 6.10.3 | Severity: normal
Keywords: type family families instance instances | Testcase:
Os: Unknown/Multiple | Architecture:
Unknown/Multiple
----------------------------------------------------+-----------------------
While attempting to define integer arithmetic using type families, I
encountered a problem with the type checker failing to recognize
equivalent types:
{{{
{-# LANGUAGE EmptyDataDecls, TypeFamilies #-}
module WithBug where
data Z
data S a
data P a b
type family N a
type instance N (P Z a) = P Z a
type instance N (P a Z) = P a Z -- with bug
type instance N (P (S a) (S b)) = N (P a b)
}}}
{{{
$ ghci WithBug
*WithBug> :t (undefined :: N (P Z Z)) :: P Z Z
<interactive>:1:1:
Couldn't match expected type `P Z Z'
against inferred type `N (P Z Z)'
In the expression: (undefined :: N (P Z Z)) :: P Z Z
}}}
Rewriting the problematic instance fixed the problem:
{{{
{-# LANGUAGE EmptyDataDecls, TypeFamilies #-}
module WithoutBug where
data Z
data S a
data P a b
type family N a
type instance N (P Z a) = P Z a
type instance N (P (S a) Z) = P (S a) Z -- without bug
type instance N (P (S a) (S b)) = N (P a b)
}}}
{{{
$ ghci WithoutBug
*WithoutBug> :t (undefined :: N (P Z Z)) :: P Z Z
(undefined :: N (P Z Z)) :: P Z Z :: P Z Z
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3383>
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