[GHC] #12993: GHC 8.0.2-rc2 template Haskell interface file issue
GHC
ghc-devs at haskell.org
Wed Aug 2 19:34:08 UTC 2017
#12993: GHC 8.0.2-rc2 template Haskell interface file issue
-------------------------------------+-------------------------------------
Reporter: glguy | Owner: (none)
Type: bug | Status: closed
Priority: highest | Milestone: 8.0.2
Component: Template Haskell | Version: 8.0.2-rc2
Resolution: fixed | Keywords:
Operating System: MacOS X | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by niteria):
I just run into this in our `ghc-8.0.2-facebook` branch (we cut from
ghc-8.0 before the revert happened).
It reproduces in an interesting way with `haddock` +
`DuplicateRecordFields`:
{{{
$ cat A.hs Main.hs; haddock A.hs Main.hs
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE DuplicateRecordFields #-}
module A where
data A = A {
func :: Int -> Int
}
a :: A
a = A { func = (*2) }
module Main where
import A
main :: IO ()
main = print (func a 10)
Haddock coverage:
0% ( 0 / 3) in 'A'
Missing documentation for:
Module header
A (A.hs:4)
a (A.hs:8)
Main.hs:6:15: error:
• Can't find interface-file declaration for variable A.$sel:func:A
Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the error
• In the first argument of ‘print’, namely ‘(func a 10)’
In the expression: print (func a 10)
In an equation for ‘main’: main = print (func a 10)
|
6 | main = print (func a 10)
|
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12993#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list