The following program panics on GHC 8.2 and later:
{-# LANGUAGE DataKinds #-}{-# LANGUAGE ImpredicativeTypes #-}{-# LANGUAGE RankNTypes #-}{-# LANGUAGE TypeApplications #-}moduleBugwhereimportType.ReflectionnewtypeFoo=MkFoo(foralla.a)foo::TypeRepMkFoofoo=typeRep@MkFoo
$ /opt/ghc/8.6.1/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )GHC error in desugarer lookup in Bug: attempting to use module ‘main:Bug’ (Bug.hs) which is not loadedghc: panic! (the 'impossible' happened) (GHC version 8.6.1 for x86_64-unknown-linux): initDs
Trac metadata
Trac field
Value
Version
8.6.1
Type
Bug
TypeOfFailure
OtherFailure
Priority
normal
Resolution
Unresolved
Component
Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Edited
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
0
Show closed items
No child items are currently assigned. Use child items to break down this issue into smaller parts.
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
{-# LANGUAGE DataKinds #-}{-# LANGUAGE ImpredicativeTypes #-}{-# LANGUAGE RankNTypes #-}{-# LANGUAGE TypeApplications #-}moduleBugwhereimportType.ReflectionnewtypeFoo=MkFoo(foralla.a)foo::TypeRepMkFoofoo=undefined
instead. And that program is accepted... but it really shouldn't be.
The problem is that the type of foo is TypeRep @((forall a. a) -> Foo) 'MkFoo, which involves an impredicative instantiation of the kind variable of TypeRep. This is not currently allowed.
I would fix the missing impredicativity check before worrying about initDs.
However, with #12045 (closed), I suppose we'll want to start allowing impredicative kind instantiations... even then, we won't be able to deal with type representations involving foralls (at least, not without another rewrite of TypeRep). So, I suppose tackling the initDs bug directly is also a step forward.
I would fix the missing impredicativity check before worrying about initDs.
In case you didn't notice this, I deliberately enabled ImpredicativeTypes in this program :)
I, too, am surprised that this panics, though. Especially since typeIsTypeable appears to already answer "no" when a type contains a nested forall like this:
typeIsTypeable(ForAllTy{})=False
It's possible that something else is going wrong, though.
It turns out that this problem is more general than just this one example (which happens to use ImpredicativeTypes). Here is //another// program which triggers the same panic:
{-# LANGUAGE ExistentialQuantification #-}{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE TypeInType #-}moduleBugwhereimportData.KindimportType.ReflectiontypefamilyFatypeinstanceFInt=TypedataBar=forall(a::FInt).MkBarabar::TypeRep(MkBarTrue)bar=typeRep
This time, the culprit is likely the fact that MkBar True contains a cast/coercion somewhere, which is another thing that Typeable doesn't support.
{-# LANGUAGE TypeInType #-}{-# LANGUAGE UnboxedSums #-}moduleBugwhereimportType.ReflectiondataQuux=MkQuux(#Bool|Int#)bar::TypeRepMkQuuxbar=typeRep
$ /opt/ghc/8.6.2/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )GHC error in desugarer lookup in Bug: attempting to use module ‘main:Bug’ (Bug.hs) which is not loadedghc: panic! (the 'impossible' happened) (GHC version 8.6.2 for x86_64-unknown-linux): initDs
Also for data constructors that use Eq# behind the scenes:
{-# LANGUAGE DataKinds #-}{-# LANGUAGE GADTs #-}{-# LANGUAGE PolyKinds #-}moduleBugwhereimportData.KindimportType.ReflectiondataQuuz::(Type~Type)=>TypewhereMkQuuz::Quuzquuz::TypeRepMkQuuzquuz=typeRep
$ /opt/ghc/8.6.5/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )GHC error in desugarer lookup in Bug: attempting to use module ‘main:Bug’ (Bug.hs) which is not loadedghc: panic! (the 'impossible' happened) (GHC version 8.6.5 for x86_64-unknown-linux): initDs
Note that this does not panic if you change TypeRep MkQuuz to TypeRep Quuz; that merely triggers the same error message as in #13933.
Aha, I've figured out what's going on here. The culprit isn't typeIsTypeable at all, unlike what I surmised in #15862 (comment 163203). Instead, the real issue is that the code in the Typeable solver isn't synchronized properly with the validity checks in TcTypeable, which means that it tries to generate Typeable evidence for type constructors that TcTypeable rejects as impermissible. This, in turn, results in the panics observed above.