[GHC] #12723: Family instance modules are not fingerprinted in ABI
GHC
ghc-devs at haskell.org
Mon Oct 17 07:56:48 UTC 2016
#12723: Family instance modules are not fingerprinted in ABI
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Driver | Version: 8.1
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:
-------------------------------------+-------------------------------------
This leads to the following delightful, five module bug:
{{{
-- A.hs
{-# LANGUAGE TypeFamilies #-}
module A where
type family F a
type instance F Int = Bool
-- B.hs
module B where
import A
-- C.hs
module C where
import B
-- D.hs
module D where
import C
-- E.hs
module E where
import D
import B
}}}
Build these modules. Then rename A to A2 (fixing B's import), and build
them again. You'll get:
{{{
ezyang at sabre:~/Dev/labs/T3871$ ghc --make E.hs
[1 of 5] Compiling A2 ( A2.hs, A2.o )
[2 of 5] Compiling B ( B.hs, B.o )
[3 of 5] Compiling C ( C.hs, C.o ) [B changed]
[5 of 5] Compiling E ( E.hs, E.o ) [B changed]
attempting to use module ‘A’ (./A.hs) which is not loaded
}}}
The problem is clear: D was not recompiled, but it needs to be, because
when the module gets renamed, we need to update its list of family
instance modules to rename A to A2. When we don't do this, the subsequent
family instance check chokes because it tries to load A. And why did D
decide not to get recompiled? Because the ABI hash of B did not change.
And that's WRONG.
(Also, family instances are really awful, you really do have to rebuild
everything when you change them. UGH.)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12723>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list