[GHC] #16245: GHC panic (No skolem info) with QuantifiedConstraints and strange scoping

#16245: GHC panic (No skolem info) with QuantifiedConstraints and strange scoping -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 (Type checker) | Keywords: TypeInType, | Operating System: Unknown/Multiple QuantifiedConstraints | Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program panics with GHC 8.6.3 and HEAD: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE QuantifiedConstraints #-} module Bug where import Data.Kind type Const a b = a type SameKind (a :: k) (b :: k) = (() :: Constraint) class (forall (b :: k). SameKind a b) => C (k :: Const Type a) }}} {{{ $ /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, I imagine that the real culprit is that `SameKind a b` would force `a :: k`, which would be ill-scoped. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16245 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16245: GHC panic (No skolem info) with QuantifiedConstraints and strange scoping -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler (Type | Version: 8.6.3 checker) | Keywords: TypeInType, Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * milestone: => 8.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16245#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC