Redundant recompilation caused by storing transitive deps in ifaces
Suppose I have these files
module Main where
import M1
main = print x1
module M1 where
import M2
x1 = x2 + 1
module M2 where
x2 = 1
Now if I build this program, and then add a dependency to M2:
module M2 where
import M3
x2 = 1 + x3
module M3 where
x3 = 1
and build Main, this is what I would ideally see:
$ ghc-stage1 Main.hs
[1 of 4] Compiling M3 ( M3.hs, M3.o )
[2 of 4] Compiling M2 ( M2.hs, M2.o )
Linking Main ...
but instead I see this
$ ghc-stage1 Main.hs
[1 of 4] Compiling M3 ( M3.hs, M3.o )
[2 of 4] Compiling M2 ( M2.hs, M2.o )
[3 of 4] Compiling M1 ( M1.hs, M1.o ) [M2 changed]
[4 of 4] Compiling Main ( Main.hs, Main.o ) [M1 changed]
Linking Main ...
So M1 and Main are redundantly recompiled.
One (maybe the only) problem here is that we currently store transitive dependencies in interface files. Because of this then in the example above adding a dependency to M2 causes changes in interfaces of M1 and Main, so we can't avoid recompiling those.
Instead we should store only the direct dependencies, so that adding a dep to M3 won't cause any changes in M1's interface.
Original description of this issue below:
Consider storing direct home module dependencies instead of transitive closure in interface files
Haskell interface files (*.hi) store a list of the transitive closure of home module dependencies. With !931 (closed), after (incremental) builds, this list is guaranteed to be up to date (noted on the wiki). Unfortunately this means that recompilation may be done even though the object file hasn't changed (only the interface file). This also results in more cases that we touch the interface file, which can cause more recompilation in e.g. a make build system (see note on the wiki).
By swapping from the transitive closure of home module dependencies to just the direct dependencies, this list can be kept up to date while avoiding many unneeded recompilations and touching the interface file. This is a good use case (note it assumes optimizations are disabled).
Some work needs to be done to verify that this change is actually possible. What are the current uses of this info (see here).
TODO
There is probably a similar issue with transitive closure of packages. Investigate if this can be simplified too.