[GHC] #16257: -fexternal-interpreter with external C shared library leads to undefined symbol during template haskell phase
GHC
ghc-devs at haskell.org
Wed Jan 30 16:00:02 UTC 2019
#16257: -fexternal-interpreter with external C shared library leads to undefined
symbol during template haskell phase
-------------------------------------+-------------------------------------
Reporter: guibou | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
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:
-------------------------------------+-------------------------------------
I'm building the following `Foo.hs` program using the `hmatrix-gsl`
library:
{{{#!haskell
{-# LANGUAGE TemplateHaskell #-}
import Numeric.GSL.Integration
main = do
print $([| 10 |])
print $ integrateQNG 1 (\x -> x) 0 1
}}}
I observes undefined symbols during the template haskell phase when using
`-fexternal-interpreter`:
Without `-fexternal-interpreter`:
{{{
$ ghc -package hmatrix-gsl Foo.hs
[1 of 1] Compiling Main ( Foo.hs, Foo.o )
Linking Foo ...
[nix-shell:~/bug_report_external]$ ./Foo
10
(0.5,5.551115123125783e-15)
}}}
But with `-fexternal-interpreter`:
{{{
$ ghc -fexternal-interpreter -package hmatrix-gsl Foo.hs
[1 of 1] Compiling Main ( Foo.hs, Foo.o )
<command line>: can't load .so/.DLL for: /nix/store
/6dhcmmfgy5fa0p3d235yaz4qfx8jhpar-gsl-2.5/lib/libgsl.so (/nix/store
/6dhcmmfgy5fa0p3d235yaz4qfx8jhpar-gsl-2.5/lib/libgsl.so: undefined symbol:
cblas_ctrmv)
}}}
I suspect that it happen during the template haskell phase because I
cannot observe this issue without template haskell.
I can observe this issue with a few other libraries, I used `hmatrix-gsl`
in this example because it is on hackage. Actually, you can even reduce
the file to:
{{{#!haskell
{-# LANGUAGE TemplateHaskell #-}
main = do
print $([| 10 |])
}}}
and get the same error as long as you have `-package hmatrix-gsl` in your
command line.
I generate the build environment with this nix file:
{{{#!nix
with import (fetchTarball {
# 25/01/2019
url = https://github.com/nixos/nixpkgs/archive/11cf7d6e1ff.tar.gz;
sha256 = "0zcg4mgfdk3ryiqj1j5iv5bljjvsgi6q6j9z1vkq383c4g4clc72";
}) {};
mkShell {
buildInputs = [(haskellPackages.ghcWithPackages(p: [p.hmatrix-gsl]))];
}
}}}
It setups `ghc-8.6.3` with `hmatrix-gsl-0.19.0.1` (the latest on hackage).
Note that `hmatrix-gsl` depends on library `gsl` which have a weird symbol
setup. The main library file `libgsl` does not contain the `cbal_ctrmv`
symbol which is contained in another library `libgslcbal` which is not a
dependency of the shared object `libgsl.so`.
library `gslcblas` is listed in `extra-libraries` of the `hmatrix-gsl`
package:
{{{
ghc-pkg field hmatrix-gsl extra-libraries
extra-libraries:
gsl gslcblas m
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16257>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list