[GHC] #9176: GHC not generating dyn_hi files
GHC
ghc-devs at haskell.org
Fri Jun 6 04:07:08 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 does not seem to be broken. 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:
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.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9176#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list