[GHC] #9176: GHC not generating dyn_hi files
GHC
ghc-devs at haskell.org
Thu Jul 3 23:27:11 UTC 2014
#9176: GHC not generating dyn_hi files
-----------------------------+----------------------------------
Reporter: heatsink | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: | Keywords: dynamic
Operating System: MacOS X | Architecture: x86_64 (amd64)
Type of failure: Other | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-----------------------------+----------------------------------
Description changed by heatsink:
Old description:
> In some situations, GHC terminates successfully and generates a `dyn_o`
> file, but no `dyn_hi` file. As a result, a package that contains a
> library seems to build successfully, but fails to install. I narrowed
> the problem down to the following test case. I compile it with `ghc
> --make -shared -dynamic-too Foo`. It seems to be Parsec-related, but I
> don't know how to trace it further.
>
> {{{
> module Foo where
> import Text.ParserCombinators.Parsec
> }}}
>
> Parsec was installed with `cabal install --reinstall --user --enable-
> shared --disable-library-profiling parsec-3.1.5`. Some Parsec modules do
> not cause the missing `dyn_hi` file. For instance, all output files are
> created if Foo imports `Text.Parsec.Pos` instead of
> `Text.ParserCombinators.Parsec`.
>
> My installed Parsec library seems to be working correctly. I can link
> and run `main = parseTest (char 'a') "a"` in both `-dynamic` and
> `-static` modes, and I can also use Parsec from GHCi.
>
> GHC was built from source, commit
> 9e10963e394680dbb1b964c66cb428a2aa03df09, compiled by GHC 7.6.3 with
> XCode 5.1.1 on OS X 10.9.3.
New description:
== Overview ==
In dynamic-too compilation, a module is compiled the normal way, then the
backend runs twice to generate normal (.o, .hi) and dynamic (.dyn_o,
.dyn_hi) outputs. Compilation uses the .hi files of imported modules.
Effectively, the compiler assumes that all the information it gets from a
.hi file, used by the normal output, is also true of the corresponding
.dyn_hi file, used by the dynamic output. GHC has a few checks to verify
this, but they don’t always produce desirable results.
When importing a module from a package in --make mode, GHC checks that the
normal and dynamic interfaces match, in `checkBuildDynamicToo` in
`findAndReadIface`. If they don’t match, GHC silently disables dynamic-
too, so that no dynamic interface file is produced. No errors or warnings
are reported.
When importing a standalone module in --make mode, GHC does not examine
the dynamic interface at all.
Of the two cases described above, GHC uses the weaker checks when building
a package and stricter checks when using the installed package. The
weaker checks allow a package with mismatched normal and dynamic interface
files to build and install without errors. After it's installed, the
stronger checks suppress the creation of .dyn_hi files whenever the
mismatched module is imported. Thus, a package installs fine, but causes
problems when it's used.
== Reproducing ==
The attached code sets up an inconsistent pair of module interfaces and
runs both kinds of imports. To compile the first two files, build the
cabal package in `testcase9176/`. To compile the last file, install the
package, then run the makefile in `user/`.
* `Imported.hs` is compiled with different optimization flags, setting up
a situation where the normal and dyamic module interfaces do not match.
* `User.hs` importing directly `Imported.hs` loads only the static module
interface. The dynamic interface is ignored.
* `User.hs` importing from the installed package `Imported.hs` compares
the static and dynamic interfaces, turns off dynamic-too compilation, and
does not generate a .dyn_hi file. No errors or warnings are produced.
== Details ==
This bug appeared on my system in a Parsec module. Parsec installed with
no apparent problems, but other modules importing from Parsec would not
compile to .dyn_hi files.
GHC was built from source, commit
9e10963e394680dbb1b964c66cb428a2aa03df09, compiled by GHC 7.6.3 with XCode
5.1.1 on OS X 10.9.3.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9176#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list