summaryrefslogtreecommitdiff
path: root/testsuite/tests
diff options
context:
space:
mode:
authorMatthew Pickering <matthewtpickering@gmail.com>2021-10-27 16:02:56 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-11-25 01:03:17 -0500
commit91c0a657aaf4da8d2b01a1bb4a1d9521ef54ea8d (patch)
tree4c047f836bf49fdeb123abe8705ea6f3b2db0499 /testsuite/tests
parent1669037430f968dd25a6339edfc95d6091974b61 (diff)
downloadhaskell-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 'testsuite/tests')
-rw-r--r--testsuite/tests/driver/T20030/test1/T20030_test1j.stderr13
-rw-r--r--testsuite/tests/driver/T20030/test1/all.T8
-rw-r--r--testsuite/tests/driver/T20200loop/Base.hs10
-rw-r--r--testsuite/tests/driver/T20200loop/Datatypes.hs13
-rw-r--r--testsuite/tests/driver/T20200loop/Datatypes.hs-boot5
-rw-r--r--testsuite/tests/driver/T20200loop/InternalToAbstract.hs7
-rw-r--r--testsuite/tests/driver/T20200loop/Pretty.hs11
-rw-r--r--testsuite/tests/driver/all.T2
8 files changed, 69 insertions, 0 deletions
diff --git a/testsuite/tests/driver/T20030/test1/T20030_test1j.stderr b/testsuite/tests/driver/T20030/test1/T20030_test1j.stderr
new file mode 100644
index 0000000000..81b29def80
--- /dev/null
+++ b/testsuite/tests/driver/T20030/test1/T20030_test1j.stderr
@@ -0,0 +1,13 @@
+[ 1 of 13] Compiling A[boot] ( A.hs-boot, A.o-boot )
+[ 2 of 13] Compiling B ( B.hs, B.o )
+[ 3 of 13] Compiling C[boot] ( C.hs-boot, C.o-boot )
+[ 4 of 13] Compiling A ( A.hs, A.o )
+[ 5 of 13] Compiling C ( C.hs, C.o )
+[ 6 of 13] Compiling E[boot] ( E.hs-boot, E.o-boot )
+[ 7 of 13] Compiling G ( G.hs, G.o )
+[ 8 of 13] Compiling H ( H.hs, H.o )
+[ 9 of 13] Compiling E ( E.hs, E.o )
+[10 of 13] Compiling I ( I.hs, I.o )
+[11 of 13] Compiling J[boot] ( J.hs-boot, J.o-boot )
+[12 of 13] Compiling K ( K.hs, K.o )
+[13 of 13] Compiling J ( J.hs, J.o )
diff --git a/testsuite/tests/driver/T20030/test1/all.T b/testsuite/tests/driver/T20030/test1/all.T
index 43aa5f424c..b1d4309065 100644
--- a/testsuite/tests/driver/T20030/test1/all.T
+++ b/testsuite/tests/driver/T20030/test1/all.T
@@ -4,3 +4,11 @@ test('T20030_test1',
, 'I.hs', 'J.hs-boot', 'J.hs', 'K.hs' ])
],
multimod_compile, ['I.hs K.hs', '-v1'])
+
+test('T20030_test1j',
+ [ extra_files([ 'A.hs-boot' , 'A.hs' , 'B.hs' , 'C.hs-boot' , 'C.hs'
+ , 'D.hs' , 'E.hs-boot' , 'E.hs' , 'F.hs' , 'G.hs' , 'H.hs'
+ , 'I.hs', 'J.hs-boot', 'J.hs', 'K.hs' ])
+ , req_smp
+ ],
+ multimod_compile, ['I.hs K.hs', '-v1 -j'])
diff --git a/testsuite/tests/driver/T20200loop/Base.hs b/testsuite/tests/driver/T20200loop/Base.hs
new file mode 100644
index 0000000000..b03ff5902b
--- /dev/null
+++ b/testsuite/tests/driver/T20200loop/Base.hs
@@ -0,0 +1,10 @@
+module Base where
+
+data QName = QName
+data Definition = D
+
+udef :: a
+udef = udef
+
+getConstInfo :: Monad m => QName -> m Definition
+getConstInfo = udef
diff --git a/testsuite/tests/driver/T20200loop/Datatypes.hs b/testsuite/tests/driver/T20200loop/Datatypes.hs
new file mode 100644
index 0000000000..8c9b5762b3
--- /dev/null
+++ b/testsuite/tests/driver/T20200loop/Datatypes.hs
@@ -0,0 +1,13 @@
+module Datatypes where
+
+import Base
+import Pretty
+
+
+getConstructorData :: Monad m => QName -> m Definition
+getConstructorData = getConstInfo
+
+getConType :: QName -> IO a
+getConType t = do
+ _ <- prettyTCM t
+ return udef
diff --git a/testsuite/tests/driver/T20200loop/Datatypes.hs-boot b/testsuite/tests/driver/T20200loop/Datatypes.hs-boot
new file mode 100644
index 0000000000..29ff4a94e6
--- /dev/null
+++ b/testsuite/tests/driver/T20200loop/Datatypes.hs-boot
@@ -0,0 +1,5 @@
+module Datatypes where
+
+import Base
+
+getConstructorData :: Monad m => QName -> m Definition
diff --git a/testsuite/tests/driver/T20200loop/InternalToAbstract.hs b/testsuite/tests/driver/T20200loop/InternalToAbstract.hs
new file mode 100644
index 0000000000..2fc1b83f47
--- /dev/null
+++ b/testsuite/tests/driver/T20200loop/InternalToAbstract.hs
@@ -0,0 +1,7 @@
+module InternalToAbstract where
+
+import Base
+import {-# SOURCE #-} Datatypes (getConstructorData)
+
+reify :: Monad m => QName -> m Definition
+reify c = getConstructorData c
diff --git a/testsuite/tests/driver/T20200loop/Pretty.hs b/testsuite/tests/driver/T20200loop/Pretty.hs
new file mode 100644
index 0000000000..26861b8b7d
--- /dev/null
+++ b/testsuite/tests/driver/T20200loop/Pretty.hs
@@ -0,0 +1,11 @@
+module Pretty where
+
+import Control.Monad
+
+import InternalToAbstract
+import Base
+
+prettyTCM :: Monad m => QName -> m Definition
+prettyTCM x = reify x
+
+
diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T
index be93ec1d51..742f74f953 100644
--- a/testsuite/tests/driver/all.T
+++ b/testsuite/tests/driver/all.T
@@ -299,3 +299,5 @@ test('T20439', normal, run_command,
{compiler} -E -fno-code -XCPP -v Foo.hs 2>&1 | grep "Copying" | sed "s/.*to//" '])
test('T20459', normal, multimod_compile_fail,
['T20459B', ''])
+test('T20200loop', extra_files(['T20200loop']), multimod_compile,
+ ['Datatypes', '-iT20200loop -O -v0'])