[GHC] #14481: Mutually dependent modules with orphan instances causes missing symbols with single-shot compilation

#14481: Mutually dependent modules with orphan instances causes missing symbols with single-shot compilation -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 (Type checker) | 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: -------------------------------------+------------------------------------- Alan Zimmerman encountered this nasty bug in his Trees That Grow branch: Consider we have the following types, {{{#!hs module Types where data Expr p = Var String | App (Expr p) (Expr p) | ADecl (Decl p) data Decl p = Bind String (Expr p) }}} Now imagine that for some reason we want to define orphan instances for some class (`Show`, for instance) for these types in two separate modules. We would have: {{{#!hs -- Instances1.hs module Instances1 where import {-# SOURCE #-} Instances2 () import Types deriving instance Show (Decl p) -- Instances1.hs-boot module Instances1 where import Types instance Show (Decl p) -- Instances2.hs module Instances2 where import {-# SOURCE #-} Instances1 () import Types deriving instance Show (Expr p) -- Instances2.hs-boot module Instances2 where import Types instance Show (Expr p) }}} Now, for instance, say we have some program that uses this whole mess, {{{#!hs -- Main.hs module Main where import Types -- Use SOURCE import to ensure GHC doesn't grab dictionary from unfolding in -- interface file import {-# SOURCE #-} Instances2 main = putStrLn $ show $ (Var "hi" :: Expr Int) }}} With `--make` mode we can compile `Main.hs` with no trouble: {{{ $ ghc --make Main.hs [1 of 6] Compiling Types ( Types.hs, Types.o ) [2 of 6] Compiling Instances2[boot] ( Instances2.hs-boot, Instances2.o-boot ) [3 of 6] Compiling Main ( Main.hs, Main.o ) [4 of 6] Compiling Instances1[boot] ( Instances1.hs-boot, Instances1.o-boot ) [5 of 6] Compiling Instances2 ( Instances2.hs, Instances2.o ) [6 of 6] Compiling Instances1 ( Instances1.hs, Instances1.o ) Linking Main ... $ ./Main Var "hi" }}} However, if we instead use single-shot mode, we end up never producing object code for one of the boot DFuns, {{{ $ ghc -c Types.hs $ ghc -c Instances1.hs-boot $ ghc -c Instances2.hs $ ghc -c Instances2.hs-boot $ ghc -c Instances1.hs $ ghc -c Main.hs $ ghc -o test Types.o Instances1.o Instances2.o Main.o Main.o:s1lN_info: error: undefined reference to 'Instances2_zdfxShowExpr_closure' Main.o(.data.rel.ro+0x8): error: undefined reference to 'Instances2_zdfxShowExpr_closure' collect2: error: ld returned 1 exit status `gcc' failed in phase `Linker'. (Exit code: 1) }}} In the case of `--make` mode the symbol in question is emitted in the object code for `Instances2`. However, when we use single-shot mode the `hi-boot` file for `Instances2` doesn't exist when the `hs` file is compiled. It seems that this makes the DFun impedance matching logic in `TcRnDriver.checkBootIface'` not fire. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14481 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14481: Mutually dependent modules with orphan instances causes missing symbols with single-shot compilation -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: invalid | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => invalid Comment: Ahh, never mind; this is actually fine. The bug is actually one in the GHC build system (or perhaps GHC's `-M` mode). We need to ensure that we always compile a module's `hs-boot` file before its associated source file. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14481#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14481: Mutually dependent modules with orphan instances causes missing symbols with single-shot compilation -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: invalid | 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 bgamari): Indeed this is a bug in `ghc -M`. For instance {{{ $ ghc -c Instances2.hs $ cat Makefile # DO NOT DELETE: Beginning of Haskell dependencies Types.o : Types.hs Instances2.o-boot : Instances2.hs-boot Instances2.o-boot : Types.hi Main.o : Main.hs Main.o : Instances2.hi-boot Main.o : Types.hi Instances1.o-boot : Instances1.hs-boot Instances1.o-boot : Types.hi Instances2.o : Instances2.hs Instances2.o : Instances1.hi-boot Instances2.o : Types.hi Instances1.o : Instances1.hs Instances1.o : Instances2.hi-boot Instances1.o : Types.hi # DO NOT DELETE: End of Haskell dependencies }}} I believe GHC should have produced the following dependencies as well: {{{ Instances1.o : Instances1.hi-boot Instances2.o : Instances2.hi-boot }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14481#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14481: Mutually dependent modules with orphan instances causes missing symbols with single-shot compilation -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14482 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #14482 Comment: I've opened #14482 to track this issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14481#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14481: Mutually dependent modules with orphan instances causes missing symbols with single-shot compilation -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14482 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The repro from which I deduced this can be found here: https://github.com/bgamari/T14481-repro -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14481#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14481: Mutually dependent modules with orphan instances causes missing symbols with single-shot compilation -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14482 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): There may be more bugs along the lines of #14482. In general we require that hs-boot files are compiled before hs files. However, we aren't very good at checking this in single-shot mode. `tcHiBootIface` makes something of an attempt, but the logic there will fail if the compiler hasn't seen any SOURCE imports of the module being compiled (since the module will have no entry in `eps_is_boot`, leading `tcHiBootIface` to conclude that the module simply has no boot file). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14481#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14481: Mutually dependent modules with orphan instances causes missing symbols with single-shot compilation -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14482 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alanz): Thanks for this analysis. Based on it, I added some dummy types to the original problem files and it now links. So there is a short term workaround at least. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14481#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC