The following program panics with GHC 8.6.3 and HEAD:
{-# LANGUAGE ConstraintKinds #-}{-# LANGUAGE DataKinds #-}{-# LANGUAGE PolyKinds #-}{-# LANGUAGE QuantifiedConstraints #-}moduleBugwhereimportData.KindtypeConstab=atypeSameKind(a::k)(b::k)=(()::Constraint)class(forall(b::k).SameKindab)=>C(k::ConstTypea)
$ /opt/ghc/8.6.3/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )Bug.hs:11:36: error:ghc: panic! (the 'impossible' happened) (GHC version 8.6.3 for x86_64-unknown-linux): No skolem info: [k1_a1X4[sk:1]] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2891:5 in ghc:TcErrors
As with #16244 (closed), I imagine that the real culprit is that SameKind a b would force a :: k, which would be ill-scoped.
Trac metadata
Trac field
Value
Version
8.6.3
Type
Bug
TypeOfFailure
OtherFailure
Priority
normal
Resolution
Unresolved
Component
Compiler (Type checker)
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.
Actually, this isn't really a QuantifiedConstraints bug, but rather a general rank-n types bug. This program also exhibits the same panic:
{-# LANGUAGE RankNTypes #-}{-# LANGUAGE TypeInType #-}moduleBugwhereimportData.KindtypeConstab=adataSameKind::k->k->TypenewtypeT(k::ConstTypea)=MkT(forall(b::k).SameKindab)
$ /opt/ghc/8.6.5/bin/ghc Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )Bug.hs:10:66: error:ghc: panic! (the 'impossible' happened) (GHC version 8.6.5 for x86_64-unknown-linux): No skolem info: [k1_aWg[sk:1]] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2891:5 in ghc:TcErrors
If you compile this program with GHC 8.2 or 8.4, then it simply goes into an infinite loop.
Ryan Scottchanged title from GHC panic (No skolem info) with QuantifiedConstraints and strange scoping to GHC panic (No skolem info) with RankNTypes and strange scoping
changed title from GHC panic (No skolem info) with QuantifiedConstraints and strange scoping to GHC panic (No skolem info) with RankNTypes and strange scoping
Commit e3c374cc ended up fixing the original program in this issue, as GHC now throws an error message instead of panicking:
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )Bug.hs:11:36: error: • Couldn't match kind ‘k1’ with ‘k’ ‘k1’ is a rigid type variable bound by the class declaration for ‘C’ at Bug.hs:11:45 ‘k’ is a rigid type variable bound by the class declaration for ‘C’ at Bug.hs:11:1-62 • In the second argument of ‘SameKind’, namely ‘b’ In the class declaration for ‘C’ |11 | class (forall (b :: k). SameKind a b) => C (k :: Const Type a) | ^
I'll add a regression test to !3200 (closed), since it's in very similar territory.
Commit 2420c555 adds a regression test (polykinds/T16245) for the original program in this issue, which no longer compiles. However, since the program in #16245 (comment 211369) still panics, and the program in #16245 (comment 211400) still loops infinitely, I'll keep this issue open.
{-# LANGUAGE NoStarIsType #-}{-# LANGUAGE RankNTypes #-}{-# LANGUAGE PolyKinds #-}import Data.Kindimport Control.Categoryclass Category hom => HasProduct (hom :: k -> k -> Type) where generic :: (forall (i :: a). hom i b) -> hom a b
It might be the issue that caused the original program in this issue to panic, but I don't think it's the same issue that causes the program in #16245 (comment 211369) to panic. The difference is that the former has been fixed, but the latter still panics on GHC 9.0 or later. Your program appears to be of the former variety, since it no longer panics on 9.0 or later:
$ ~/Software/ghc-9.0/bin/ghc Bug.hs[1 of 1] Compiling Main ( Bug.hs, Bug.o )Bug.hs:8:29: error: • Expected a type, but ‘a’ has kind ‘k1’ ‘k1’ is a rigid type variable bound by the class declaration for ‘HasProduct’ at Bug.hs:7:35-55 • In the kind ‘a’ In the type signature: generic :: (forall (i :: a). hom i b) -> hom a b In the class declaration for ‘HasProduct’ |8 | generic :: (forall (i :: a). hom i b) -> hom a b | ^