
#14396: Hs-boot woes during family instance consistency checks -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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: -------------------------------------+------------------------------------- Consider this set of modules (related to #13981 but not the same) {{{ {-# LANGUAGE TypeFamilies #-} module Fam where type family XListPat a {-# LANGUAGE TypeFamilies #-} module T1 where import Fam import {-# SOURCE #-} T( SyntaxExpr ) type instance XListPat Int = SyntaxExpr {-# LANGUAGE TypeFamilies #-} module T2 where import Fam type instance XListPat Bool = Int -- T.hs-boot module T where data SyntaxExpr = S -- T.hs module T where import T1 import T2 data SyntaxExpr = S }}} Compiled with GHC 8.0, 8.2, and HEAD we get {{{ ghc.exe: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-mingw32): tcIfaceGlobal (local): not found You are in a maze of twisty little passages, all alike. While forcing the thunk for TyThing SyntaxExpr which was lazily initialized by initIfaceTcRn, I tried to tie the knot, but I couldn't find SyntaxExpr in the current type environment. If you are developing GHC, please read Note [Tying the knot] and Note [Type-checking inside the knot]. Consider rebuilding GHC with profiling for a better stack trace. Contents of current type environment: [] }}} Reason: * After renaming, but before type checking, we try to do family-instance consistency checking in `FamInst.checkFamInstConsistency` * To do so we have to pull in the axioms from `T1` and `T2`. * Then we poke on those axioms, to check consistency, we pull in both LHS and RHS of the type instances. * Alas that pulls on `SyntaxExpr`, which we have not yet typechecked. I don't think it's enough to make lazier the loading of the RHS of the axiom, because I think `checkFamInstConsistency` ends up looking at the RHS too. See the call to `compatibleBranches` in `lookupFamInstEnvConflicts`. This setup is actually used in Alan's `wip/ttg-2017-10-13` branch for Trees That Grow. Here module `T` is `HsExpr`, `T1` is `HsPat`. And indeed GHC 8.0 crashes when compiling this branch. SO it's becoming a real problem. Generally I'm concerned that #13981 may also become more pressing; and #14080 is still open -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14396 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler