[GHC] #14347: Top-level RecordWildCards no longer working.

GHC ghc-devs at haskell.org
Thu Oct 12 16:43:08 UTC 2017


#14347: Top-level RecordWildCards no longer working.
-------------------------------------+-------------------------------------
           Reporter:  Fuuzetsu       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           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:
-------------------------------------+-------------------------------------
 {{{#!hs
 $ ghc -fforce-recomp /tmp/Damn.hs /tmp/T.hs
 [1 of 2] Compiling Damn             ( /tmp/Damn.hs, /tmp/Damn.o )
 [2 of 2] Compiling T                ( /tmp/T.hs, /tmp/T.o )

 /tmp/T.hs:7:5: warning: [-Wmissing-fields]
     • Fields of ‘D.D’ not initialised: x, y
     • In the expression: D.D {..}
       In an equation for ‘d’: d = D.D {..}
   |
 7 | d = D.D {..}
   |     ^^^^^^^^

 $ cat /tmp/Damn.hs /tmp/T.hs
 module Damn (D(..)) where

 data D = D { x :: Int, y :: () }
 {-# LANGUAGE RecordWildCards #-}
 module T where

 import qualified Damn as D

 d :: D.D
 d = D.D {..}

 x :: Int
 x = 7

 y :: ()
 y = ()

 $ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 8.2.1

 }}}

 Meanwhile on 8.0

 {{{#!hs
 $ ghc -Wall -fforce-recomp /tmp/Damn.hs /tmp/T.hs
 [1 of 2] Compiling Damn             ( /tmp/Damn.hs, /tmp/Damn.o )
 [2 of 2] Compiling T                ( /tmp/T.hs, /tmp/T.o )

 $ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 8.0.2
 }}}

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


More information about the ghc-tickets mailing list