[GHC] #13607: Panic with profiled compiler: Dynamic linker not initialised

#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

#13607: Panic when shared object file is missing: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, you don't need a profiled compiler after all. You can reproduce this with an ordinary GHC with one extra step. As before, install some library, like `random-1.1`: {{{ $ cabal install random-1.1 -w /opt/ghc/head/bin/ghc }}} Then figure out its package ID: {{{ $ /opt/ghc/head/bin/ghc-pkg describe random name: random version: 1.1 id: random-1.1-Gnn89iTXDuaz90MEyLmyr ... }}} This time, however, you'll need to change the contents of `.cabal` (where `cabal-install` puts its shared object files). On Linux, this can be accomplished like so: {{{ $ cd ~/.cabal/lib/x86_64-linux-ghc-8.3.20170509/ $ mv libHSrandom-1.1-Gnn89iTXDuaz90MEyLmyr-ghc8.3.20170509.so libHSrandom-1.1-Gnn89iTXDuaz90MEyLmyr-ghc8.3.20170509-dummy.so }}} Now compile `Bar.hs` as before: {{{ $ /opt/ghc/head/bin/ghc -fforce-recomp Bar.hs -j2 -package-id random-1.1-Gnn89iTXDuaz90MEyLmyr [1 of 3] Compiling Foo ( Foo.hs, Foo.o ) <no location info>: error: ghc: panic! (the 'impossible' happened) (GHC version 8.3.20170509 for x86_64-unknown-linux): Dynamic linker not initialised Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug [2 of 3] Compiling Foo2 ( Foo2.hs, Foo2.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) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13607#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13607: Panic when shared object file is missing: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by angerman): With a `quick` build of `ghc-8.4.3` I get: {{{ <no location info>: error: <command line>: can't load .so/.DLL for: /Users/angerman/.cabal/lib/x86_64-osx-ghc-8.4.3/libHSrandom-1.1 -9LLJAJa4iQFLJiLXBOBXBV-ghc8.4.3.dylib (dlopen(/Users/angerman/.cabal/lib/x86_64-osx-ghc-8.4.3/libHSrandom-1.1 -9LLJAJa4iQFLJiLXBOBXBV-ghc8.4.3.dylib, 5): Symbol not found: _base_GHCziList_splitAtzuzdszdwsplitAtzq_info Referenced from: /Users/angerman/.cabal/lib/x86_64-osx- ghc-8.4.3/libHSrandom-1.1-9LLJAJa4iQFLJiLXBOBXBV-ghc8.4.3.dylib Expected in: /Users/angerman/Projects/zw3rk/ghc/libraries/base/dist- install/build/libHSbase-4.11.1.0-ghc8.4.3.dylib in /Users/angerman/.cabal/lib/x86_64-osx-ghc-8.4.3/libHSrandom-1.1 -9LLJAJa4iQFLJiLXBOBXBV-ghc8.4.3.dylib) [2 of 3] Compiling Foo2 ( Foo2.hs, Foo2.o ) <no location info>: error: ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): Dynamic linker not initialised CallStack (from HasCallStack): panic, called at compiler/ghci/Linker.hs:106:53 in ghc:Linker Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} with `-j2` A tiny bit of `Debut.Trace.trace` on the functions gives us: {{{ [1 of 3] Compiling Foo ( Foo.hs, Foo.o ) linkExpr initDynLinker modifyPLS_ False ;; <- getOrSetLibHSghcInitLinkerDone reallyInitDynLinker linkExpr initDynLinker modifyPLS_ linkPackages' link link_one.2 link link_one.2 link link_one.1 link_one.2 link link_one.1 linkPackage link_one.2 link link_one.1 linkPackage linkPackage link_one.2 link link_one.1 link_one.2 link link_one.1 link_one.2 link link_one.1 linkPackage linkPackage linkPackage linkPackage True ;; <- getOrSetLibHSghcInitLinkerDone modifyPLS linkDependencies getLinkDeps linkPackages' linkPackages' link }}} prior to the crash. The `link_one.N` are the various branches of the `link_one` function. For completeness, here's the `-prof-auto-all -prof-cafs` output: {{{ <no location info>: error: ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): Dynamic linker not initialised CallStack (from -prof): Panic.panic (compiler/utils/Panic.hs:(184,1)-(188,68)) Util.sharedGlobalM (compiler/utils/Util.hs:(1015,1)-(1016,47)) Linker.v_PersistentLinkerState (compiler/ghci/Linker.hs:(101,62)-(104,20)) Linker.CAF:lvl261_rHOo (<no location info>) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13607#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13607: Panic when shared object file is missing: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by angerman): After making sure that command line errors get call stacks as well (why don't have have this by default? Legacy?) {{{ [1 of 3] Compiling Foo ( Foo.hs, Foo.o ) <no location info>: error: <command line>: can't load .so/.DLL for: libHSrandom-1.1-9LLJAJa4iQFLJiLXBOBXBV.dylib (dlopen(libHSrandom-1.1-9LLJAJa4iQFLJiLXBOBXBV.dylib, 5): image not found) CallStack (from -prof): Panic.cmdLineErrorIO (compiler/utils/Panic.hs:(204,1)-(208,73)) Linker.load_dyn (compiler/ghci/Linker.hs:(1323,1)-(1327,89)) Linker.linkPackage (compiler/ghci/Linker.hs:(1240,1)-(1315,66)) Linker.linkPackages'.link_one (compiler/ghci/Linker.hs:(1224,6)-(1236,106)) Linker.linkPackages'.link (compiler/ghci/Linker.hs:(1221,6)-(1222,37)) Linker.linkPackages' (compiler/ghci/Linker.hs:(1214,1)-(1236,106)) Linker.reallyInitDynLinker (compiler/ghci/Linker.hs:(298,1)-(310,30)) Linker.initDynLinker.\ (compiler/ghci/Linker.hs:(291,25)-(295,47)) Linker.modifyPLS_ (compiler/ghci/Linker.hs:113:1-71) Linker.initDynLinker (compiler/ghci/Linker.hs:(290,1)-(295,47)) Linker.linkExpr (compiler/ghci/Linker.hs:(527,1)-(561,20)) HscMain.hscCompileCoreExpr' (compiler/main/HscMain.hs:(1774,1)-(1796,24)) HscMain.hscCompileCoreExpr (compiler/main/HscMain.hs:(1770,1)-(1771,84)) IOEnv.liftIO (compiler/utils/IOEnv.hs:183:5-33) IOEnv.tryIOEnvFailure (compiler/utils/IOEnv.hs:149:1-21) IOEnv.tryM.\ (compiler/utils/IOEnv.hs:146:38-64) IOEnv.tryM (compiler/utils/IOEnv.hs:146:1-65) TcSplice.runMeta' (compiler/typecheck/TcSplice.hs:(719,1)-(781,22)) TcSplice.defaultRunMeta (compiler/typecheck/TcSplice.hs:(678,1)-(687,74)) Hooks.lookupHook (compiler/main/Hooks.hs:104:1-50) Hooks.getHooked (compiler/main/Hooks.hs:101:1-59) HscTypes.metaRequestE (compiler/main/HscTypes.hs:747:1-53) TcSplice.runMeta (compiler/typecheck/TcSplice.hs:(673,1)-(675,21)) TcSplice.runMetaE (compiler/typecheck/TcSplice.hs:698:1-31) RnSplice.runRnSplice (compiler/rename/RnSplice.hs:(293,1)-(332,43)) RnSplice.rnSpliceExpr.run_expr_splice (compiler/rename/RnSplice.hs:(408,5)-(431,12)) RnSplice.rnSpliceGen (compiler/rename/RnSplice.hs:(247,1)-(279,31)) RnSplice.rnSpliceExpr (compiler/rename/RnSplice.hs:(400,1)-(431,12)) RnExpr.rnExpr (compiler/rename/RnExpr.hs:(116,1)-(420,67)) TcRnMonad.wrapLocFstM (compiler/typecheck/TcRnMonad.hs:(843,1)-(846,23)) RnBinds.rnGRHS (compiler/rename/RnBinds.hs:1201:1-54) RnBinds.rnGRHSs.\ (compiler/rename/RnBinds.hs:(1193,49)-(1195,47)) RnBinds.rnGRHSs (compiler/rename/RnBinds.hs:(1192,1)-(1195,47)) RnBinds.rnMatch'.\ (compiler/rename/RnBinds.hs:(1162,46)-(1169,58)) RnBinds.rnMatch' (compiler/rename/RnBinds.hs:(1160,1)-(1169,59)) RnBinds.rnMatch (compiler/rename/RnBinds.hs:1154:1-56) RnUtils.mapFvRn (compiler/rename/RnUtils.hs:(187,1)-(189,63)) RnBinds.rnMatchGroup (compiler/rename/RnBinds.hs:(1144,1)-(1148,54)) RnBinds.rnBind (compiler/rename/RnBinds.hs:(449,1)-(512,38)) RnBinds.rnLBind (compiler/rename/RnBinds.hs:(440,1)-(443,43)) Bag.mapBagM (compiler/utils/Bag.hs:(244,1)-(251,50)) RnBinds.rnValBindsRHS (compiler/rename/RnBinds.hs:(294,1)-(316,52)) RnSource.rnSrcDecls.\ (compiler/rename/RnSource.hs:(133,64)-(235,22)) RnSource.extendPatSynEnv (compiler/rename/RnSource.hs:(1950,1)-(1984,20)) RnSource.rnSrcDecls (compiler/rename/RnSource.hs:(93,1)-(235,24)) TcRnDriver.rnTopSrcDecls (compiler/typecheck/TcRnDriver.hs:(1299,1)-(1315,4)) IOEnv.thenM.\ (compiler/utils/IOEnv.hs:(78,37)-(79,60)) IOEnv.thenM (compiler/utils/IOEnv.hs:(78,1)-(79,61)) IOEnv.runIOEnv (compiler/utils/IOEnv.hs:122:1-30) TcRnMonad.initTcRnIf (compiler/typecheck/TcRnMonad.hs:(405,1)-(415,9)) TcRnMonad.initTcWithGbl (compiler/typecheck/TcRnMonad.hs:(319,1)-(361,35)) TcRnMonad.initTc (compiler/typecheck/TcRnMonad.hs:(206,1)-(311,5)) TcRnDriver.tcRnModule (compiler/typecheck/TcRnDriver.hs:(157,1)-(184,45)) HscTypes.liftIO.\ (compiler/main/HscTypes.hs:251:31-55) HscTypes.liftIO (compiler/main/HscTypes.hs:251:5-55) HscMain.ioMsgMaybe (compiler/main/HscMain.hs:(250,1)-(255,122)) HscMain.Typecheck-Rename (compiler/main/HscMain.hs:(463,16)-(464,73)) HscTypes.>>=.\ (compiler/main/HscTypes.hs:(246,33)-(248,56)) HscTypes.>>= (compiler/main/HscTypes.hs:(246,5)-(248,56)) HscMain.hscIncrementalFrontend (compiler/main/HscMain.hs:(583,1)-(645,81)) HscMain.hscIncrementalCompile (compiler/main/HscMain.hs:(671,1)-(717,52)) DriverPipeline.compileOne' (compiler/main/DriverPipeline.hs:(135,1)-(287,55)) GhcMake.upsweep_mod.compile_it_discard_iface (compiler/main/GhcMake.hs:(1463,13)-(1465,61)) GhcMake.upsweep_mod (compiler/main/GhcMake.hs:(1403,1)-(1559,49)) GhcMake.parUpsweep_one (compiler/main/GhcMake.hs:(1066,1)-(1229,65)) ErrUtils.prettyPrintGhcErrors (compiler/main/ErrUtils.hs:(681,1)-(690,44)) GhcMake.parUpsweep.\.spawnWorkers.\.\ (compiler/main/GhcMake.hs:(921,43)-(976,75)) GhcMake.parUpsweep.\.spawnWorkers.\ (compiler/main/GhcMake.hs:(921,13)-(976,75)) GhcMake.parUpsweep.\.spawnWorkers (compiler/main/GhcMake.hs:(920,11)-(976,75)) GhcMonad.liftIO (compiler/main/GhcMonad.hs:112:3-30) GhcMake.parUpsweep.\ (compiler/main/GhcMake.hs:(877,62)-(1006,44)) GhcMake.parUpsweep (compiler/main/GhcMake.hs:(844,1)-(1036,36)) GhcMake.load'.upsweep_fn (compiler/main/GhcMake.hs:(393,9)-(394,41)) GhcMake.load' (compiler/main/GhcMake.hs:(246,1)-(494,38)) GhcMake.load (compiler/main/GhcMake.hs:(238,1)-(240,44)) GhcMonad.>>=.\ (compiler/main/GhcMonad.hs:109:26-57) GhcMonad.>>= (compiler/main/GhcMonad.hs:109:3-57) Panic.withSignalHandlers (compiler/utils/Panic.hs:(255,1)-(313,37)) GHC.runGhc (compiler/main/GHC.hs:(441,1)-(446,26)) Exception.gcatch (compiler/utils/Exception.hs:65:3-37) Exception.ghandle (compiler/utils/Exception.hs:75:1-21) GHC.defaultErrorHandler (compiler/main/GHC.hs:(381,1)-(413,7)) Main.main (ghc/Main.hs:(90,1)-(150,64)) [2 of 3] Compiling Foo2 ( Foo2.hs, Foo2.o ) <no location info>: error: ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): Dynamic linker not initialised CallStack (from -prof): Panic.panic (compiler/utils/Panic.hs:(186,1)-(190,68)) Util.sharedGlobalM (compiler/utils/Util.hs:(1015,1)-(1016,47)) Linker.v_PersistentLinkerState (compiler/ghci/Linker.hs:(101,62)-(104,20)) Linker.CAF:lvl261_rHOT (<no location info>) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} From this I think we can assume that initializing the linker just failed. We put the panic back into the `MVar` and when the other thread got to read it we failed hard. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13607#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13607: Panic when shared object file is missing: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by angerman): {{{ [1 of 3] Compiling Foo ( Foo.hs, Foo.o ) <no location info>: error: <command line>: can't load .so/.DLL for: libHSrandom-1.1-9LLJAJa4iQFLJiLXBOBXBV.dylib (dlopen(libHSrandom-1.1-9LLJAJa4iQFLJiLXBOBXBV.dylib, 5): image not found) CallStack (from -prof): Panic.cmdLineErrorIO (compiler/utils/Panic.hs:(204,1)-(208,73)) Linker.load_dyn (compiler/ghci/Linker.hs:(1325,1)-(1329,89)) Linker.linkPackage (compiler/ghci/Linker.hs:(1242,1)-(1317,66)) Linker.linkPackages'.link_one (compiler/ghci/Linker.hs:(1226,6)-(1238,106)) Linker.linkPackages'.link (compiler/ghci/Linker.hs:(1223,6)-(1224,37)) Linker.linkPackages' (compiler/ghci/Linker.hs:(1216,1)-(1238,106)) Linker.reallyInitDynLinker (compiler/ghci/Linker.hs:(300,1)-(312,30)) Linker.initDynLinker.\.\ (compiler/ghci/Linker.hs:(295,26)-(297,58)) Linker.modifyILD (compiler/ghci/Linker.hs:119:1-62) Linker.initDynLinker.\ (compiler/ghci/Linker.hs:(294,25)-(297,58)) Linker.modifyPLS_ (compiler/ghci/Linker.hs:113:1-71) Linker.initDynLinker (compiler/ghci/Linker.hs:(293,1)-(297,58)) Linker.linkExpr (compiler/ghci/Linker.hs:(529,1)-(563,20)) HscMain.hscCompileCoreExpr' (compiler/main/HscMain.hs:(1774,1)-(1796,24)) HscMain.hscCompileCoreExpr (compiler/main/HscMain.hs:(1770,1)-(1771,84)) IOEnv.liftIO (compiler/utils/IOEnv.hs:183:5-33) IOEnv.tryIOEnvFailure (compiler/utils/IOEnv.hs:149:1-21) IOEnv.tryM.\ (compiler/utils/IOEnv.hs:146:38-64) IOEnv.tryM (compiler/utils/IOEnv.hs:146:1-65) TcSplice.runMeta' (compiler/typecheck/TcSplice.hs:(719,1)-(781,22)) TcSplice.defaultRunMeta (compiler/typecheck/TcSplice.hs:(678,1)-(687,74)) Hooks.lookupHook (compiler/main/Hooks.hs:104:1-50) Hooks.getHooked (compiler/main/Hooks.hs:101:1-59) HscTypes.metaRequestE (compiler/main/HscTypes.hs:747:1-53) TcSplice.runMeta (compiler/typecheck/TcSplice.hs:(673,1)-(675,21)) TcSplice.runMetaE (compiler/typecheck/TcSplice.hs:698:1-31) RnSplice.runRnSplice (compiler/rename/RnSplice.hs:(293,1)-(332,43)) RnSplice.rnSpliceExpr.run_expr_splice (compiler/rename/RnSplice.hs:(408,5)-(431,12)) RnSplice.rnSpliceGen (compiler/rename/RnSplice.hs:(247,1)-(279,31)) RnSplice.rnSpliceExpr (compiler/rename/RnSplice.hs:(400,1)-(431,12)) RnExpr.rnExpr (compiler/rename/RnExpr.hs:(116,1)-(420,67)) TcRnMonad.wrapLocFstM (compiler/typecheck/TcRnMonad.hs:(843,1)-(846,23)) RnBinds.rnGRHS (compiler/rename/RnBinds.hs:1201:1-54) RnBinds.rnGRHSs.\ (compiler/rename/RnBinds.hs:(1193,49)-(1195,47)) RnBinds.rnGRHSs (compiler/rename/RnBinds.hs:(1192,1)-(1195,47)) RnBinds.rnMatch'.\ (compiler/rename/RnBinds.hs:(1162,46)-(1169,58)) RnBinds.rnMatch' (compiler/rename/RnBinds.hs:(1160,1)-(1169,59)) RnBinds.rnMatch (compiler/rename/RnBinds.hs:1154:1-56) RnUtils.mapFvRn (compiler/rename/RnUtils.hs:(187,1)-(189,63)) RnBinds.rnMatchGroup (compiler/rename/RnBinds.hs:(1144,1)-(1148,54)) RnBinds.rnBind (compiler/rename/RnBinds.hs:(449,1)-(512,38)) RnBinds.rnLBind (compiler/rename/RnBinds.hs:(440,1)-(443,43)) Bag.mapBagM (compiler/utils/Bag.hs:(244,1)-(251,50)) RnBinds.rnValBindsRHS (compiler/rename/RnBinds.hs:(294,1)-(316,52)) RnSource.rnSrcDecls.\ (compiler/rename/RnSource.hs:(133,64)-(235,22)) RnSource.extendPatSynEnv (compiler/rename/RnSource.hs:(1950,1)-(1984,20)) RnSource.rnSrcDecls (compiler/rename/RnSource.hs:(93,1)-(235,24)) TcRnDriver.rnTopSrcDecls (compiler/typecheck/TcRnDriver.hs:(1299,1)-(1315,4)) IOEnv.thenM.\ (compiler/utils/IOEnv.hs:(78,37)-(79,60)) IOEnv.thenM (compiler/utils/IOEnv.hs:(78,1)-(79,61)) IOEnv.runIOEnv (compiler/utils/IOEnv.hs:122:1-30) TcRnMonad.initTcRnIf (compiler/typecheck/TcRnMonad.hs:(405,1)-(415,9)) TcRnMonad.initTcWithGbl (compiler/typecheck/TcRnMonad.hs:(319,1)-(361,35)) TcRnMonad.initTc (compiler/typecheck/TcRnMonad.hs:(206,1)-(311,5)) TcRnDriver.tcRnModule (compiler/typecheck/TcRnDriver.hs:(157,1)-(184,45)) HscTypes.liftIO.\ (compiler/main/HscTypes.hs:251:31-55) HscTypes.liftIO (compiler/main/HscTypes.hs:251:5-55) HscMain.ioMsgMaybe (compiler/main/HscMain.hs:(250,1)-(255,122)) HscMain.Typecheck-Rename (compiler/main/HscMain.hs:(463,16)-(464,73)) HscTypes.>>=.\ (compiler/main/HscTypes.hs:(246,33)-(248,56)) HscTypes.>>= (compiler/main/HscTypes.hs:(246,5)-(248,56)) HscMain.hscIncrementalFrontend (compiler/main/HscMain.hs:(583,1)-(645,81)) HscMain.hscIncrementalCompile (compiler/main/HscMain.hs:(671,1)-(717,52)) DriverPipeline.compileOne' (compiler/main/DriverPipeline.hs:(135,1)-(287,55)) GhcMake.upsweep_mod.compile_it_discard_iface (compiler/main/GhcMake.hs:(1463,13)-(1465,61)) GhcMake.upsweep_mod (compiler/main/GhcMake.hs:(1403,1)-(1559,49)) GhcMake.parUpsweep_one (compiler/main/GhcMake.hs:(1066,1)-(1229,65)) ErrUtils.prettyPrintGhcErrors (compiler/main/ErrUtils.hs:(681,1)-(690,44)) GhcMake.parUpsweep.\.spawnWorkers.\.\ (compiler/main/GhcMake.hs:(921,43)-(976,75)) GhcMake.parUpsweep.\.spawnWorkers.\ (compiler/main/GhcMake.hs:(921,13)-(976,75)) GhcMake.parUpsweep.\.spawnWorkers (compiler/main/GhcMake.hs:(920,11)-(976,75)) GhcMonad.liftIO (compiler/main/GhcMonad.hs:112:3-30) GhcMake.parUpsweep.\ (compiler/main/GhcMake.hs:(877,62)-(1006,44)) GhcMake.parUpsweep (compiler/main/GhcMake.hs:(844,1)-(1036,36)) GhcMake.load'.upsweep_fn (compiler/main/GhcMake.hs:(393,9)-(394,41)) GhcMake.load' (compiler/main/GhcMake.hs:(246,1)-(494,38)) GhcMake.load (compiler/main/GhcMake.hs:(238,1)-(240,44)) GhcMonad.>>=.\ (compiler/main/GhcMonad.hs:109:26-57) GhcMonad.>>= (compiler/main/GhcMonad.hs:109:3-57) Panic.withSignalHandlers (compiler/utils/Panic.hs:(255,1)-(313,37)) GHC.runGhc (compiler/main/GHC.hs:(441,1)-(446,26)) Exception.gcatch (compiler/utils/Exception.hs:65:3-37) Exception.ghandle (compiler/utils/Exception.hs:75:1-21) GHC.defaultErrorHandler (compiler/main/GHC.hs:(381,1)-(413,7)) Main.main (ghc/Main.hs:(90,1)-(150,64)) [2 of 3] Compiling Foo2 ( Foo2.hs, Foo2.o ) <no location info>: error: <command line>: can't load .so/.DLL for: libHSrandom-1.1-9LLJAJa4iQFLJiLXBOBXBV.dylib (dlopen(libHSrandom-1.1-9LLJAJa4iQFLJiLXBOBXBV.dylib, 5): image not found) CallStack (from -prof): Panic.cmdLineErrorIO (compiler/utils/Panic.hs:(204,1)-(208,73)) Linker.load_dyn (compiler/ghci/Linker.hs:(1325,1)-(1329,89)) Linker.linkPackage (compiler/ghci/Linker.hs:(1242,1)-(1317,66)) Linker.linkPackages'.link_one (compiler/ghci/Linker.hs:(1226,6)-(1238,106)) Linker.linkPackages'.link (compiler/ghci/Linker.hs:(1223,6)-(1224,37)) Linker.linkPackages' (compiler/ghci/Linker.hs:(1216,1)-(1238,106)) Linker.reallyInitDynLinker (compiler/ghci/Linker.hs:(300,1)-(312,30)) Linker.initDynLinker.\.\ (compiler/ghci/Linker.hs:(295,26)-(297,58)) Linker.modifyILD (compiler/ghci/Linker.hs:119:1-62) Linker.initDynLinker.\ (compiler/ghci/Linker.hs:(294,25)-(297,58)) Linker.modifyPLS_ (compiler/ghci/Linker.hs:113:1-71) Linker.initDynLinker (compiler/ghci/Linker.hs:(293,1)-(297,58)) Linker.linkExpr (compiler/ghci/Linker.hs:(529,1)-(563,20)) HscMain.hscCompileCoreExpr' (compiler/main/HscMain.hs:(1774,1)-(1796,24)) HscMain.hscCompileCoreExpr (compiler/main/HscMain.hs:(1770,1)-(1771,84)) IOEnv.liftIO (compiler/utils/IOEnv.hs:183:5-33) IOEnv.tryIOEnvFailure (compiler/utils/IOEnv.hs:149:1-21) IOEnv.tryM.\ (compiler/utils/IOEnv.hs:146:38-64) IOEnv.tryM (compiler/utils/IOEnv.hs:146:1-65) TcSplice.runMeta' (compiler/typecheck/TcSplice.hs:(719,1)-(781,22)) TcSplice.defaultRunMeta (compiler/typecheck/TcSplice.hs:(678,1)-(687,74)) Hooks.lookupHook (compiler/main/Hooks.hs:104:1-50) Hooks.getHooked (compiler/main/Hooks.hs:101:1-59) HscTypes.metaRequestE (compiler/main/HscTypes.hs:747:1-53) TcSplice.runMeta (compiler/typecheck/TcSplice.hs:(673,1)-(675,21)) TcSplice.runMetaE (compiler/typecheck/TcSplice.hs:698:1-31) RnSplice.runRnSplice (compiler/rename/RnSplice.hs:(293,1)-(332,43)) RnSplice.rnSpliceExpr.run_expr_splice (compiler/rename/RnSplice.hs:(408,5)-(431,12)) RnSplice.rnSpliceGen (compiler/rename/RnSplice.hs:(247,1)-(279,31)) RnSplice.rnSpliceExpr (compiler/rename/RnSplice.hs:(400,1)-(431,12)) RnExpr.rnExpr (compiler/rename/RnExpr.hs:(116,1)-(420,67)) TcRnMonad.wrapLocFstM (compiler/typecheck/TcRnMonad.hs:(843,1)-(846,23)) RnBinds.rnGRHS (compiler/rename/RnBinds.hs:1201:1-54) RnBinds.rnGRHSs.\ (compiler/rename/RnBinds.hs:(1193,49)-(1195,47)) RnBinds.rnGRHSs (compiler/rename/RnBinds.hs:(1192,1)-(1195,47)) RnBinds.rnMatch'.\ (compiler/rename/RnBinds.hs:(1162,46)-(1169,58)) RnBinds.rnMatch' (compiler/rename/RnBinds.hs:(1160,1)-(1169,59)) RnBinds.rnMatch (compiler/rename/RnBinds.hs:1154:1-56) RnUtils.mapFvRn (compiler/rename/RnUtils.hs:(187,1)-(189,63)) RnBinds.rnMatchGroup (compiler/rename/RnBinds.hs:(1144,1)-(1148,54)) RnBinds.rnBind (compiler/rename/RnBinds.hs:(449,1)-(512,38)) RnBinds.rnLBind (compiler/rename/RnBinds.hs:(440,1)-(443,43)) Bag.mapBagM (compiler/utils/Bag.hs:(244,1)-(251,50)) RnBinds.rnValBindsRHS (compiler/rename/RnBinds.hs:(294,1)-(316,52)) RnSource.rnSrcDecls.\ (compiler/rename/RnSource.hs:(133,64)-(235,22)) RnSource.extendPatSynEnv (compiler/rename/RnSource.hs:(1950,1)-(1984,20)) RnSource.rnSrcDecls (compiler/rename/RnSource.hs:(93,1)-(235,24)) TcRnDriver.rnTopSrcDecls (compiler/typecheck/TcRnDriver.hs:(1299,1)-(1315,4)) IOEnv.thenM.\ (compiler/utils/IOEnv.hs:(78,37)-(79,60)) IOEnv.thenM (compiler/utils/IOEnv.hs:(78,1)-(79,61)) IOEnv.runIOEnv (compiler/utils/IOEnv.hs:122:1-30) TcRnMonad.initTcRnIf (compiler/typecheck/TcRnMonad.hs:(405,1)-(415,9)) TcRnMonad.initTcWithGbl (compiler/typecheck/TcRnMonad.hs:(319,1)-(361,35)) TcRnMonad.initTc (compiler/typecheck/TcRnMonad.hs:(206,1)-(311,5)) TcRnDriver.tcRnModule (compiler/typecheck/TcRnDriver.hs:(157,1)-(184,45)) HscTypes.liftIO.\ (compiler/main/HscTypes.hs:251:31-55) HscTypes.liftIO (compiler/main/HscTypes.hs:251:5-55) HscMain.ioMsgMaybe (compiler/main/HscMain.hs:(250,1)-(255,122)) HscMain.Typecheck-Rename (compiler/main/HscMain.hs:(463,16)-(464,73)) HscTypes.>>=.\ (compiler/main/HscTypes.hs:(246,33)-(248,56)) HscTypes.>>= (compiler/main/HscTypes.hs:(246,5)-(248,56)) HscMain.hscIncrementalFrontend (compiler/main/HscMain.hs:(583,1)-(645,81)) HscMain.hscIncrementalCompile (compiler/main/HscMain.hs:(671,1)-(717,52)) DriverPipeline.compileOne' (compiler/main/DriverPipeline.hs:(135,1)-(287,55)) GhcMake.upsweep_mod.compile_it_discard_iface (compiler/main/GhcMake.hs:(1463,13)-(1465,61)) GhcMake.upsweep_mod (compiler/main/GhcMake.hs:(1403,1)-(1559,49)) GhcMake.parUpsweep_one (compiler/main/GhcMake.hs:(1066,1)-(1229,65)) ErrUtils.prettyPrintGhcErrors (compiler/main/ErrUtils.hs:(681,1)-(690,44)) GhcMake.parUpsweep.\.spawnWorkers.\.\ (compiler/main/GhcMake.hs:(921,43)-(976,75)) GhcMake.parUpsweep.\.spawnWorkers.\ (compiler/main/GhcMake.hs:(921,13)-(976,75)) GhcMake.parUpsweep.\.spawnWorkers (compiler/main/GhcMake.hs:(920,11)-(976,75)) GhcMonad.liftIO (compiler/main/GhcMonad.hs:112:3-30) GhcMake.parUpsweep.\ (compiler/main/GhcMake.hs:(877,62)-(1006,44)) GhcMake.parUpsweep (compiler/main/GhcMake.hs:(844,1)-(1036,36)) GhcMake.load'.upsweep_fn (compiler/main/GhcMake.hs:(393,9)-(394,41)) GhcMake.load' (compiler/main/GhcMake.hs:(246,1)-(494,38)) GhcMake.load (compiler/main/GhcMake.hs:(238,1)-(240,44)) GhcMonad.>>=.\ (compiler/main/GhcMonad.hs:109:26-57) GhcMonad.>>= (compiler/main/GhcMonad.hs:109:3-57) Panic.withSignalHandlers (compiler/utils/Panic.hs:(255,1)-(313,37)) GHC.runGhc (compiler/main/GHC.hs:(441,1)-(446,26)) Exception.gcatch (compiler/utils/Exception.hs:65:3-37) Exception.ghandle (compiler/utils/Exception.hs:75:1-21) GHC.defaultErrorHandler (compiler/main/GHC.hs:(381,1)-(413,7)) Main.main (ghc/Main.hs:(90,1)-(150,64)) }}} this looks more the the proper error message. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13607#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13607: Panic when shared object file is missing: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #9868, #10355, | Differential Rev(s): Phab:D5012 #10919, #13137, #13531 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D5012 * related: => #9868, #10355, #10919, #13137, #13531 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13607#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13607: Panic when shared object file is missing: Dynamic linker not initialised
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: #9868, #10355, | Differential Rev(s): Phab:D5012
#10919, #13137, #13531 |
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13607: Panic when shared object file is missing: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #9868, #10355, | Differential Rev(s): Phab:D5012 #10919, #13137, #13531 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 Comment: I believe this should be fixed in 8.6. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13607#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC