
#13607: Panic with profiled compiler: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- There are several Trac tickets floating around which mention this panic, including: * #9868 (ghc: panic! Dynamic linker not initialised) * #10355 (Dynamic linker not initialised) * #10919 (ghc: panic! (the 'impossible' happened) ... Dynamic linker not initialised) * #13137 (Dynamic linker not initialised.) * #13531 (GHC fails with "Dynamic linker not initialised" when -j is on and trying to load nonexistent .so file) However, none seem particularly simple to reproduce. I have a (marginally) easier way to trigger this panic. You'll need the following: * A copy of GHC HEAD built with the `prof` flavor. For reference, I am using GHC HEAD built against 1f4fd37efac4795493677d5df81c83d22eac5f74. * A single package built with `cabal-install`. For simplicity, I used `random`: {{{ $ cabal install random-1.1 -w ~/Software/ghc3/inplace/bin/ghc-stage2 }}} Once it's installed, you'll need to learn `random`'s package ID, which can be done with `ghc-pkg`. For instance: {{{ 3$ ~/Software/ghc3/inplace/bin/ghc-pkg describe random name: random version: 1.1 id: random-1.1-Gnn89iTXDuaz90MEyLmyr ... }}} * You'll need these three Haskell files: {{{#!hs -- Foo.hs {-# LANGUAGE TemplateHaskell #-} module Foo where import Language.Haskell.TH foo :: Bool foo = $(conE 'True) }}} {{{#!hs -- Foo2.hs {-# LANGUAGE TemplateHaskell #-} module Foo2 where import Language.Haskell.TH foo2 = $(conE 'False) }}} {{{#!hs -- Bar.hs module Bar where import Foo import Foo2 bar :: () bar = foo `seq` foo2 `seq` () }}} Once you have all of these, you can trigger the bug by invoking GHC like so: {{{ $ ~/Software/ghc3/inplace/bin/ghc-stage2 -fforce-recomp Bar.hs -j2 -package-id random-1.1-Gnn89iTXDuaz90MEyLmyr [1 of 3] Compiling Foo ( Foo.hs, Foo.o ) <no location info>: error: <command line>: can't load .so/.DLL for: libHSrandom-1.1-Gnn89iTXDuaz90MEyLmyr.so (libHSrandom-1.1-Gnn89iTXDuaz90MEyLmyr.so: cannot open shared object file: No such file or directory) [2 of 3] Compiling Foo2 ( Foo2.hs, Foo2.o ) <no location info>: error: ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.3.20170423 for x86_64-unknown-linux): Dynamic linker not initialised CallStack (from -prof): Linker.CAF (<entire-module>) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} In case it's important, this is using 64-bit Linux. cc'ing angerman, who requested an easier way to reproduce this panic in https://ghc.haskell.org/trac/ghc/ticket/13137#comment:6. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13607 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler