[GHC] #9245: In absence of recursive imports, hs-boot files not checked for consistency
GHC
ghc-devs at haskell.org
Sat Jun 28 10:40:04 UTC 2014
#9245: In absence of recursive imports, hs-boot files not checked for consistency
---------------------------------------+-----------------------------------
Reporter: ezyang | Owner: ezyang
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time crash | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
---------------------------------------+-----------------------------------
Description changed by ezyang:
Old description:
> Example:
>
> B.hs-boot
> {{{
> module B where
> b :: Bool
> }}}
>
> A.hs
> {{{
> module A where
> import {-# SOURCE #-} B
> a = b
> }}}
>
> B.hs
> {{{
> module B where
> }}}
>
> Main.hs
> {{{
> import A
> main = print a
> }}}
>
> Compilation:
>
> {{{
> ghc -c B.hs-boot
> ghc -c A.hs
> ghc -c B.hs
> ghc -c Main.hs
> ghc -o main A.o B.o Main.o
> }}}
>
> Error:
> {{{A.o:(.text+0x79): undefined reference to `B_b_closure'
> A.o: In function `A_a_srt':
> (.data+0x0): undefined reference to `B_b_closure'
> collect2: error: ld returned 1 exit status
> }}}
>
> The culprit seems to be this code:
>
> {{{
> -- OK, so we're in one-shot mode.
> -- In that case, we're read all the direct imports by now,
> -- so eps_is_boot will record if any of our imports mention us by
> -- way of hi-boot file
> { eps <- getEps
> ; case lookupUFM (eps_is_boot eps) (moduleName mod) of {
> Nothing -> return emptyModDetails ; -- The typical case
>
> Just (_, False) -> failWithTc moduleLoop ;
> -- Someone below us imported us!
> -- This is a loop with no hi-boot in the way
>
> Just (_mod, True) -> -- There's a hi-boot interface
> below us
> }}}
>
> but I am not 100% sure what the correct new logic is yet.
New description:
Example:
B.hs-boot
{{{
module B where
b :: Bool
}}}
A.hs
{{{
module A where
import {-# SOURCE #-} B
a = b
}}}
B.hs
{{{
module B where
}}}
Main.hs
{{{
import A
main = print a
}}}
Compilation:
{{{
ghc -c B.hs-boot
ghc -c A.hs
ghc -c B.hs
ghc -c Main.hs
ghc -o main A.o B.o Main.o
}}}
Error:
{{{
A.o:(.text+0x79): undefined reference to `B_b_closure'
A.o: In function `A_a_srt':
(.data+0x0): undefined reference to `B_b_closure'
collect2: error: ld returned 1 exit status
}}}
The culprit seems to be this code:
{{{
-- OK, so we're in one-shot mode.
-- In that case, we're read all the direct imports by now,
-- so eps_is_boot will record if any of our imports mention us by
-- way of hi-boot file
{ eps <- getEps
; case lookupUFM (eps_is_boot eps) (moduleName mod) of {
Nothing -> return emptyModDetails ; -- The typical case
Just (_, False) -> failWithTc moduleLoop ;
-- Someone below us imported us!
-- This is a loop with no hi-boot in the way
Just (_mod, True) -> -- There's a hi-boot interface
below us
}}}
but I am not 100% sure what the correct new logic is yet.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9245#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list