diff options
author | Matthew Pickering <matthewtpickering@gmail.com> | 2021-10-27 16:02:56 +0100 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2021-11-25 01:03:17 -0500 |
commit | 91c0a657aaf4da8d2b01a1bb4a1d9521ef54ea8d (patch) | |
tree | 4c047f836bf49fdeb123abe8705ea6f3b2db0499 /compiler/GHC/Unit | |
parent | 1669037430f968dd25a6339edfc95d6091974b61 (diff) | |
download | haskell-91c0a657aaf4da8d2b01a1bb4a1d9521ef54ea8d.tar.gz |
Correct retypechecking in --make mode
Note [Hydrating Modules]
~~~~~~~~~~~~~~~~~~~~~~~~
What is hydrating a module?
* There are two versions of a module, the ModIface is the on-disk version and the ModDetails is a fleshed-out in-memory version.
* We can **hydrate** a ModIface in order to obtain a ModDetails.
Hydration happens in three different places
* When an interface file is initially loaded from disk, it has to be hydrated.
* When a module is finished compiling, we hydrate the ModIface in order to generate
the version of ModDetails which exists in memory (see Note)
* When dealing with boot files and module loops (see Note [Rehydrating Modules])
Note [Rehydrating Modules]
~~~~~~~~~~~~~~~~~~~~~~~~~~~
If a module has a boot file then it is critical to rehydrate the modules on
the path between the two.
Suppose we have ("R" for "recursive"):
```
R.hs-boot: module R where
data T
g :: T -> T
A.hs: module A( f, T, g ) where
import {-# SOURCE #-} R
data S = MkS T
f :: T -> S = ...g...
R.hs: module R where
data T = T1 | T2 S
g = ...f...
```
After compiling A.hs we'll have a TypeEnv in which the Id for `f` has a type
type uses the AbstractTyCon T; and a TyCon for `S` that also mentions that same
AbstractTyCon. (Abstract because it came from R.hs-boot; we know nothing about
it.)
When compiling R.hs, we build a TyCon for `T`. But that TyCon mentions `S`, and
it currently has an AbstractTyCon for `T` inside it. But we want to build a
fully cyclic structure, in which `S` refers to `T` and `T` refers to `S`.
Solution: **rehydration**. *Before compiling `R.hs`*, rehydrate all the
ModIfaces below it that depend on R.hs-boot. To rehydrate a ModIface, call
`typecheckIface` to convert it to a ModDetails. It's just a de-serialisation
step, no type inference, just lookups.
Now `S` will be bound to a thunk that, when forced, will "see" the final binding
for `T`; see [Tying the knot](https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/tying-the-knot).
But note that this must be done *before* compiling R.hs.
When compiling R.hs, the knot-tying stuff above will ensure that `f`'s unfolding
mentions the `LocalId` for `g`. But when we finish R, we carefully ensure that
all those `LocalIds` are turned into completed `GlobalIds`, replete with
unfoldings etc. Alas, that will not apply to the occurrences of `g` in `f`'s
unfolding. And if we leave matters like that, they will stay that way, and *all*
subsequent modules that import A will see a crippled unfolding for `f`.
Solution: rehydrate both R and A's ModIface together, right after completing R.hs.
We only need rehydrate modules that are
* Below R.hs
* Above R.hs-boot
There might be many unrelated modules (in the home package) that don't need to be
rehydrated.
This dark corner is the subject of #14092.
Suppose we add to our example
```
X.hs module X where
import A
data XT = MkX T
fx = ...g...
```
If in `--make` we compile R.hs-boot, then A.hs, then X.hs, we'll get a `ModDetails` for `X` that has an AbstractTyCon for `T` in the the argument type of `MkX`. So:
* Either we should delay compiling X until after R has beeen compiled.
* Or we should rehydrate X after compiling R -- because it transitively depends on R.hs-boot.
Ticket #20200 has exposed some issues to do with the knot-tying logic in GHC.Make, in `--make` mode.
this particular issue starts [here](https://gitlab.haskell.org/ghc/ghc/-/issues/20200#note_385758).
The wiki page [Tying the knot](https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/tying-the-knot) is helpful.
Also closely related are
* #14092
* #14103
Fixes tickets #20200 #20561
Diffstat (limited to 'compiler/GHC/Unit')
-rw-r--r-- | compiler/GHC/Unit/Module/Graph.hs | 12 |
1 files changed, 8 insertions, 4 deletions
diff --git a/compiler/GHC/Unit/Module/Graph.hs b/compiler/GHC/Unit/Module/Graph.hs index abee5d97aa..0df5779416 100644 --- a/compiler/GHC/Unit/Module/Graph.hs +++ b/compiler/GHC/Unit/Module/Graph.hs @@ -25,6 +25,7 @@ module GHC.Unit.Module.Graph , isTemplateHaskellOrQQNonBoot , showModMsg , moduleGraphNodeModule + , moduleGraphNodeModSum , moduleGraphNodes , SummaryNode @@ -36,7 +37,6 @@ module GHC.Unit.Module.Graph , msKey ) - where import GHC.Prelude @@ -62,6 +62,7 @@ import qualified Data.Map as Map import GHC.Types.Unique.DSet import GHC.Types.SrcLoc import qualified Data.Set as Set +import GHC.Unit.Module -- | A '@ModuleGraphNode@' is a node in the '@ModuleGraph@'. -- Edges between nodes mark dependencies arising from module imports @@ -73,9 +74,12 @@ data ModuleGraphNode -- | There is a module summary node for each module, signature, and boot module being built. | ModuleNode ExtendedModSummary -moduleGraphNodeModule :: ModuleGraphNode -> Maybe ExtendedModSummary -moduleGraphNodeModule (InstantiationNode {}) = Nothing -moduleGraphNodeModule (ModuleNode ems) = Just ems +moduleGraphNodeModSum :: ModuleGraphNode -> Maybe ExtendedModSummary +moduleGraphNodeModSum (InstantiationNode {}) = Nothing +moduleGraphNodeModSum (ModuleNode ems) = Just ems + +moduleGraphNodeModule :: ModuleGraphNode -> Maybe ModuleName +moduleGraphNodeModule = fmap (ms_mod_name . emsModSummary) . moduleGraphNodeModSum instance Outputable ModuleGraphNode where ppr = \case |