[GHC] #16257: -fexternal-interpreter with external C shared library leads to undefined symbol during template haskell phase

#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

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I established with Ryan that I can reproduce this on nix but he can't on a normal linux distribution where `libgsl` is installed globally. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Log of `ghc -fexternal-interpreter -package hmatrix-gsl Foo.hs -opti -v` https://gist.github.com/mpickering/507c62e15cea344ae90b8026b6a53d2e -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): If you swap `gsl` and `gslcblas` does it fix the problem? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): If I add a dependency between `libgsl.so` and `libgslcblas.so` then it works. {{{ patchelf --add-needed /nix/store/6dhcmmfgy5fa0p3d235yaz4qfx8jhpar- gsl-2.5/lib/libgslcblas.so /nix/store/6dhcmmfgy5fa0p3d235yaz4qfx8jhpar- gsl-2.5/lib/libgsl.so readelf /nix/store/6dhcmmfgy5fa0p3d235yaz4qfx8jhpar-gsl-2.5/lib/libgsl.so -a | grep NEEDED 0x0000000000000001 (NEEDED) Shared library: [/nix/store /6dhcmmfgy5fa0p3d235yaz4qfx8jhpar-gsl-2.5/lib/libgslcblas.so] 0x0000000000000001 (NEEDED) Shared library: [libm.so.6] 0x0000000000000001 (NEEDED) Shared library: [libc.so.6] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by guibou): @mpickering, thank you for the workaround. Do you think this can be considered as a packaging issue (of `libgsl`)? or is this still a ghc issue considering that it works without `-fexternal-interpreter`? I tried to flip `gsl` and `gslcblas` in `external-libraries` and it does not change anything. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I think it's a bug in GHC but it's not clear to me why it works for Ryan but not for me. There isn't a dependency as you're meant to be able to use different libraries with `gsl` other than just `gslcblas` according to the documentation. https://www.gnu.org/software/gsl/manual/html_node/Linking- programs-with-the-library.html -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by guibou): This `Dockerfile` shows that indeed the problem does not appear on a "normal" system: {{{ FROM ubuntu:latest RUN apt-get update RUN apt-get install -y wget RUN wget -qO- https://get.haskellstack.org/ | sh RUN stack setup RUN apt-get install -y libgsl23 RUN apt-get install -y libblas-dev liblapack-dev RUN apt-get install -y pkg-config RUN stack install vector RUN apt-get install -y libgsl-dev RUN stack install hmatrix-gsl COPY Foo.hs /root/Foo.hs RUN stack ghc -- -package hmatrix-gsl -fexternal-interpreter /root/Foo.hs }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Can you provide the output of `-opti -v` as well? (I'm disappointed your repro didn't use `buildFHSUserEnv`!) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by guibou): (It also fails in a `buildFHSUserEnv`, but I'm not really surprised, because even if the FHS is respected, it still uses most the nix link strategies and `rpath`.) `-opti -v` are there: https://gist.github.com/guibou/9bf3475faf00e4de0b5eb57247139921 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by guibou): Note that instead of patching the library, `LD_PRELOAD` can be used: {{{ LD_PRELOAD=/nix/store/6dhcmmfgy5fa0p3d235yaz4qfx8jhpar- gsl-2.5/lib/libgslcblas.so ghc -package hmatrix-gsl Foo.hs -fexternal- interpreter -fforce-recomp [1 of 1] Compiling Main ( Foo.hs, Foo.o ) Linking Foo ... }}} Succeed after 25s. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by concert): I think I am seeing the same issue via a slightly different route. I've got a package that builds and binds some C and sets `extra-lib-dirs` in its package.yaml. In a module depending on it I get the "can't load .so/.DLL" error when using template haskell (or in my case quasiquotes). The library I depend on to trigger is here (you will need meson to build it): https://gitlab.com/concert/hs-rage This may be packaged wrong, being my first stab at something like this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16257#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC