[GHC] #15542: DuplicateRecordFields not honored within a data family?

GHC ghc-devs at haskell.org
Sun Aug 19 18:26:40 UTC 2018


#15542: DuplicateRecordFields not honored within a data family?
-------------------------------------+-------------------------------------
           Reporter:  michalrus      |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.4.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 I’m observing some weird behavior, which is probably closely related to
 issue #15149.

 The following minimized code does not compile on 8.2.1, 8.2.2, but it does
 compile on 8.4.3.

 However, in my original (non-free) codebase, this is reversed: 8.2.2
 compiles it just fine, and 8.4.3 fails with both errors per usage location
 at the same time:

 {{{
 src/.../Docs.hs:123:11: error:
     • Constructor ‘X'Y’ does not have the required strict field(s): z

 ...

 src/.../Docs.hs:123:11: error:
     • Constructor ‘X'Y’ does not have field ‘z’
 }}}

 I noticed, after updating the codebase’s compiler to 8.4.3.

 If the `z` field is renamed and unique, it compiles correctly.

 How can I go about debugging/minimizing this?

 This is the minimized code that works the other way round (OK on 8.4.3,
 fails on 8.2.2):

 {{{#!hs
 {-# LANGUAGE DuplicateRecordFields #-}
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE StrictData #-}

 module Main where

 data AB = A | B

 class SomeClass (ab :: AB) where
   data SomeData ab

 instance SomeClass 'A where
   data SomeData 'A = SomeData'A{someField :: Int} deriving Show

 instance SomeClass 'B where
   data SomeData 'B = SomeData'B{someField :: Int}

 main :: IO ()
 main = print SomeData'A{someField = 5}
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15542>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list