[GHC] #10808: Odd interaction between record update and type families
GHC
ghc-devs at haskell.org
Sat Aug 29 03:17:35 UTC 2015
#10808: Odd interaction between record update and type families
-------------------------------------+-------------------------------------
Reporter: diatchki | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Revisions: |
-------------------------------------+-------------------------------------
Consider the following example
{{{#!hs
{-# LANGUAGE TypeFamilies #-}
type family F a
type family G a
data T1
type instance F T1 = Char
type instance G T1 = Int
data T2
type instance F T2 = Bool
type instance G T2 = Int
data R a = R { x :: F a, y :: G a }
r1 :: R T1
r1 = R { x = 'a', y = 2 }
r2 :: R T2
r2 = r1 { x = True } -- error: Cannot match T1 with T2
r3 :: R T2
r3 = r1 { x = True, y = y r1 } -- OK
}}}
The error for `r2` is odd because types `R T1` and `R T2` differ only in
the type of `x`, so if we start with a value of type `R T1`, and update
the field where the types differ, we should end up with a valid value of
type `R T2`.
The fact that `r2` is OK is demonstrated by `r3` where we update the other
field with its own value, and now the type checker is happy.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10808>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list