... | ... | @@ -22,82 +22,91 @@ How this knot tying works is a dark corner of GHC, but hopefully this wiki page |
|
|
Knot-tying is all intimately tied up with the treatment of `hs-boot` files, so those tickets are listed here.
|
|
|
|
|
|
|
|
|
|
|
|
Use Keyword = `hs-boot` to ensure that a ticket ends up on these lists.
|
|
|
|
|
|
|
|
|
|
|
|
**Open Tickets:**
|
|
|
|
|
|
<table><tr><th>[\#1012](https://gitlab.haskell.org//ghc/ghc/issues/1012)</th>
|
|
|
<table><tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/1012">#1012</a></th>
|
|
|
<td>ghc panic with mutually recursive modules and template haskell</td></tr>
|
|
|
<tr><th>[\#8441](https://gitlab.haskell.org//ghc/ghc/issues/8441)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/8441">#8441</a></th>
|
|
|
<td>Allow family instances in an hs-boot file</td></tr>
|
|
|
<tr><th>[\#9450](https://gitlab.haskell.org//ghc/ghc/issues/9450)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/9450">#9450</a></th>
|
|
|
<td>GHC instantiates Data instances before checking hs-boot files</td></tr>
|
|
|
<tr><th>[\#9562](https://gitlab.haskell.org//ghc/ghc/issues/9562)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/9562">#9562</a></th>
|
|
|
<td>Type families + hs-boot files = unsafeCoerce</td></tr>
|
|
|
<tr><th>[\#10333](https://gitlab.haskell.org//ghc/ghc/issues/10333)</th>
|
|
|
<td>hs-boot modification doesn't induce recompilation</td></tr>
|
|
|
<tr><th>[\#12034](https://gitlab.haskell.org//ghc/ghc/issues/12034)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/10333">#10333</a></th>
|
|
|
<td>hs-boot modification doesn't induce recompilation</td></tr>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/12034">#12034</a></th>
|
|
|
<td>Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer</td></tr>
|
|
|
<tr><th>[\#12063](https://gitlab.haskell.org//ghc/ghc/issues/12063)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/12063">#12063</a></th>
|
|
|
<td>Knot-tying failure when type-synonym refers to non-existent data</td></tr>
|
|
|
<tr><th>[\#13069](https://gitlab.haskell.org//ghc/ghc/issues/13069)</th>
|
|
|
<td>hs-boot files permit default methods in type class (but don't typecheck them)</td></tr>
|
|
|
<tr><th>[\#13180](https://gitlab.haskell.org//ghc/ghc/issues/13180)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13069">#13069</a></th>
|
|
|
<td>hs-boot files permit default methods in type class (but don't typecheck them)</td></tr>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13180">#13180</a></th>
|
|
|
<td>Confusing error when hs-boot abstract data implemented using synonym</td></tr>
|
|
|
<tr><th>[\#13299](https://gitlab.haskell.org//ghc/ghc/issues/13299)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13299">#13299</a></th>
|
|
|
<td>Typecheck multiple modules at the same time</td></tr>
|
|
|
<tr><th>[\#13322](https://gitlab.haskell.org//ghc/ghc/issues/13322)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13322">#13322</a></th>
|
|
|
<td>Pattern synonyms in hs-boot files</td></tr>
|
|
|
<tr><th>[\#13347](https://gitlab.haskell.org//ghc/ghc/issues/13347)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13347">#13347</a></th>
|
|
|
<td>Abstract classes in hs-boot should not be treated as injective</td></tr>
|
|
|
<tr><th>[\#13981](https://gitlab.haskell.org//ghc/ghc/issues/13981)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13981">#13981</a></th>
|
|
|
<td>Family instance consistency checks happens too early when hs-boot defined type occurs on LHS</td></tr>
|
|
|
<tr><th>[\#14092](https://gitlab.haskell.org//ghc/ghc/issues/14092)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/14092">#14092</a></th>
|
|
|
<td>hs-boot unfolding visibility not consistent between --make and -c</td></tr>
|
|
|
<tr><th>[\#14103](https://gitlab.haskell.org//ghc/ghc/issues/14103)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/14103">#14103</a></th>
|
|
|
<td>Retypechecking the loop in --make mode is super-linear when there are many .hs-boot modules</td></tr>
|
|
|
<tr><th>[\#14382](https://gitlab.haskell.org//ghc/ghc/issues/14382)</th>
|
|
|
<td>The 'impossible' happened whilst installing gi-gtk via cabal</td></tr>
|
|
|
<tr><th>[\#16127](https://gitlab.haskell.org//ghc/ghc/issues/16127)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/14382">#14382</a></th>
|
|
|
<td>The 'impossible' happened whilst installing gi-gtk via cabal</td></tr>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/16127">#16127</a></th>
|
|
|
<td>Panic: piResultTys1 in compiler/types/Type.hs:1022:5</td></tr></table>
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
**Closed Tickets:**
|
|
|
|
|
|
<table><tr><th>[\#2412](https://gitlab.haskell.org//ghc/ghc/issues/2412)</th>
|
|
|
<td>Interaction between type synonyms and .hs-boot causes panic "tcIfaceGlobal (local): not found"</td></tr>
|
|
|
<tr><th>[\#4003](https://gitlab.haskell.org//ghc/ghc/issues/4003)</th>
|
|
|
<table><tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/2412">#2412</a></th>
|
|
|
<td>Interaction between type synonyms and .hs-boot causes panic "tcIfaceGlobal (local): not found"</td></tr>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/4003">#4003</a></th>
|
|
|
<td>tcIfaceGlobal panic building HEAD with 6.12.2</td></tr>
|
|
|
<tr><th>[\#7672](https://gitlab.haskell.org//ghc/ghc/issues/7672)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/7672">#7672</a></th>
|
|
|
<td>boot file entities are sometimes invisible and are not (semantically) unified with corresponding entities in implementing module</td></tr>
|
|
|
<tr><th>[\#10083](https://gitlab.haskell.org//ghc/ghc/issues/10083)</th>
|
|
|
<td>ghc: panic! (the 'impossible' happened)</td></tr>
|
|
|
<tr><th>[\#11062](https://gitlab.haskell.org//ghc/ghc/issues/11062)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/10083">#10083</a></th>
|
|
|
<td>ghc: panic! (the 'impossible' happened)</td></tr>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/11062">#11062</a></th>
|
|
|
<td>Type families + hs-boot files = panic (type family consistency check too early)</td></tr>
|
|
|
<tr><th>[\#12035](https://gitlab.haskell.org//ghc/ghc/issues/12035)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/12035">#12035</a></th>
|
|
|
<td>hs-boot knot tying insufficient for ghc --make</td></tr>
|
|
|
<tr><th>[\#12042](https://gitlab.haskell.org//ghc/ghc/issues/12042)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/12042">#12042</a></th>
|
|
|
<td>Infinite loop with type synonyms and hs-boot</td></tr>
|
|
|
<tr><th>[\#12064](https://gitlab.haskell.org//ghc/ghc/issues/12064)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/12064">#12064</a></th>
|
|
|
<td>tcIfaceGlobal error with existentially quantified types</td></tr>
|
|
|
<tr><th>[\#13140](https://gitlab.haskell.org//ghc/ghc/issues/13140)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13140">#13140</a></th>
|
|
|
<td>Handle subtyping relation for roles in Backpack</td></tr>
|
|
|
<tr><th>[\#13591](https://gitlab.haskell.org//ghc/ghc/issues/13591)</th>
|
|
|
<td>"\*\*\* Exception: expectJust showModule" in ghci with hs-boot</td></tr>
|
|
|
<tr><th>[\#13710](https://gitlab.haskell.org//ghc/ghc/issues/13710)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13591">#13591</a></th>
|
|
|
<td>"*** Exception: expectJust showModule" in ghci with hs-boot</td></tr>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13710">#13710</a></th>
|
|
|
<td>panic with boot and -jX</td></tr>
|
|
|
<tr><th>[\#13803](https://gitlab.haskell.org//ghc/ghc/issues/13803)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/13803">#13803</a></th>
|
|
|
<td>Panic while forcing the thunk for TyThing IsFile (regression)</td></tr>
|
|
|
<tr><th>[\#14075](https://gitlab.haskell.org//ghc/ghc/issues/14075)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/14075">#14075</a></th>
|
|
|
<td>GHC panic with parallel make</td></tr>
|
|
|
<tr><th>[\#14080](https://gitlab.haskell.org//ghc/ghc/issues/14080)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/14080">#14080</a></th>
|
|
|
<td>GHC panic while forcing the thunk for TyThing IsFile (regression)</td></tr>
|
|
|
<tr><th>[\#14396](https://gitlab.haskell.org//ghc/ghc/issues/14396)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/14396">#14396</a></th>
|
|
|
<td>Hs-boot woes during family instance consistency checks</td></tr>
|
|
|
<tr><th>[\#14531](https://gitlab.haskell.org//ghc/ghc/issues/14531)</th>
|
|
|
<tr><th><a href="https://gitlab.haskell.org//ghc/ghc/issues/14531">#14531</a></th>
|
|
|
<td>tcIfaceGlobal (local): not found</td></tr></table>
|
|
|
|
|
|
|
|
|
|
|
|
## Practical advice
|
|
|
|
|
|
|
|
|
- Add a `pprTrace` to a type environment, and have GHC spin into a loop or panic? This may be because you are forcing a thunk too early. Try printing out the unique keys of the environment instead, or moving the trace later.
|
|
|
|
|
|
- Consider using `mkNaked****` instead of the usual functions if you are within the knot-tying code
|
... | ... | @@ -131,8 +140,18 @@ data IfaceRule data CoreRule |
|
|
|
|
|
Taking `IfaceType` and `Type` as an example, we can see the big difference in a constructor for type constructor application:
|
|
|
|
|
|
|
|
|
```
|
|
|
dataType=...|TyConAppTyCon[KindOrType]dataIfaceType=...|IfaceTyConAppIfaceTyConIfaceTcArgsdataIfaceTyCon=IfaceTyCon{ ifaceTyConName ::IfExtName, ifaceTyConInfo ::IfaceTyConInfo}
|
|
|
data Type
|
|
|
= ...
|
|
|
| TyConApp TyCon [KindOrType]
|
|
|
|
|
|
data IfaceType
|
|
|
= ...
|
|
|
| IfaceTyConApp IfaceTyCon IfaceTcArgs
|
|
|
data IfaceTyCon
|
|
|
= IfaceTyCon { ifaceTyConName :: IfExtName
|
|
|
, ifaceTyConInfo :: IfaceTyConInfo }
|
|
|
```
|
|
|
|
|
|
|
... | ... | @@ -145,10 +164,13 @@ In `Type`, the type constructor application contains the full `TyCon` which cont |
|
|
## Tying the knot when loading interfaces
|
|
|
|
|
|
|
|
|
|
|
|
Consider the following Haskell file:
|
|
|
|
|
|
|
|
|
```
|
|
|
dataT=MkTSdataS=MkST
|
|
|
data T = MkT S
|
|
|
data S = MkS T
|
|
|
```
|
|
|
|
|
|
|
... | ... | @@ -160,7 +182,12 @@ There are three parts to this: |
|
|
1. First, `typecheckIface` in `TcIface` typechecks all of the `IfaceDecl`s in the `ModIface`, and then writes them into a mutable variable which makes them available to other typechecking code to tie the knot:
|
|
|
|
|
|
```
|
|
|
-- Typecheck the decls. This is done lazily, so that the knot-tying-- within this single module work out right. In the If monad there is-- no global envt for the current interface; instead, the knot is tied-- through the if_rec_types field of IfGblEnv; names_w_things <- loadDecls ignore_prags (mi_decls iface);let type_env = mkNameEnv names_w_things
|
|
|
-- Typecheck the decls. This is done lazily, so that the knot-tying
|
|
|
-- within this single module work out right. In the If monad there is
|
|
|
-- no global envt for the current interface; instead, the knot is tied
|
|
|
-- through the if_rec_types field of IfGblEnv
|
|
|
; names_w_things <- loadDecls ignore_prags (mi_decls iface)
|
|
|
; let type_env = mkNameEnv names_w_things
|
|
|
; writeMutVar tc_env_var type_env
|
|
|
```
|
|
|
|
... | ... | @@ -182,14 +209,30 @@ The **home package table** is a mapping containing all of the `ModDetails` of mo |
|
|
## Tying the knot when typechecking a module
|
|
|
|
|
|
|
|
|
|
|
|
As we typecheck Haskell source code, we produce `TyCon`s and other type-checking entities. If some declarations are mutually recursive, then we need to similarly tie the knot. There are two primary cases when this can occur:
|
|
|
|
|
|
|
|
|
|
|
|
**A mutually recursive set of source declarations.** GHC simply arranges for every declaration in a mutually recursive set of declarations to be typechecked "all at once." For example, `tcTyClDecls` in `TcTyClsDecls` uses `fixM` to refer to the resulting type declarations, so they can be placed in the environment when we typecheck these very type declarations.
|
|
|
|
|
|
|
|
|
|
|
|
**An hs file which implements an hs-boot file.** This is the trickiest case of knot-tying during type checking, so let's look at a particular example:
|
|
|
|
|
|
|
|
|
```
|
|
|
-- A.hs-bootmoduleAwheredataT-- B.hsmoduleBwhereimport{-#SOURCE#-}AdataS=MkST-- A.hsmoduleAwhereimportBdataT=MkTS
|
|
|
-- A.hs-boot
|
|
|
module A where
|
|
|
data T
|
|
|
-- B.hs
|
|
|
module B where
|
|
|
import {-# SOURCE #-} A
|
|
|
data S = MkS T
|
|
|
-- A.hs
|
|
|
module A where
|
|
|
import B
|
|
|
data T = MkT S
|
|
|
```
|
|
|
|
|
|
|
... | ... | |