[GHC] #15870: No skolem info panic

#15870: No skolem info panic -------------------------------------+------------------------------------- Reporter: sheaf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.2 (Type checker) | Keywords: | 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: -------------------------------------+------------------------------------- I've been toying with some type-level lenses and running into some issues with kind unification, when I ran into a panic: {{{ bug.hs:30:34: error:ghc.exe: panic! (the 'impossible' happened) (GHC version 8.6.2 for x86_64-unknown-mingw32): No skolem info: [k_a1Hgj] 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 }}} Here's a boiled down version (with a bit of extraneous code left in for context, as it's so short): {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} data Optic a where --Index :: Nat -> Optic a --Name :: Symbol -> Optic a (:.:) :: Optic a -> Optic b -> Optic a -- composition class Gettable a (optic :: Optic a) where type Get a (optic :: Optic a) {- some basic instances, e.g. instance Gettable (a,b) (Index 0) where type Get (a,b) (Index 0) = a ... -} instance forall a b (g1 :: Optic a) (g2 :: Optic b). ( Gettable a g1 , b ~ Get a g1 , Gettable b g2 ) => Gettable a (g1 :.: g2) where type Get a (g1 :.: g2) = Get a g2 }}} The program I am actually trying to write has the instance declaration changed to {{{#!hs instance forall a b (g1 :: Optic a) (g2 :: Optic (Get a g1)). ( Gettable a g1 , b ~ Get a g1 , Gettable b g2 ) => Gettable a (g1 :.: g2) where type Get a (g1 :.: g2) = Get (Get a g1) g2 }}} but GHC complains that it can't match kinds: {{{ • Expected kind ‘Optic b’, but ‘g2’ has kind ‘Optic (Get a g1)’ • In the second argument of ‘Gettable’, namely ‘g2’ In the instance declaration for ‘Gettable a (g1 :.: g2)’ | 20 | , Gettable b g2 | }}} I don't know if there is a way around that, and I'd be interested to hear any advice. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15870 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15870: No skolem info panic -------------------------------------+------------------------------------- Reporter: sheaf | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.3 Component: Compiler (Type | Version: 8.6.2 checker) | Resolution: | Keywords: 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): * priority: normal => highest * milestone: => 8.6.3 Comment: First, this appears to be a regression from GHC 8.4, which simply gives an error message: {{{ $ /opt/ghc/8.4.4/bin/ghci Bug.hs -XTypeInType GHCi, version 8.4.4: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:30:34: error: • Expected kind ‘Optic a’, but ‘g2’ has kind ‘Optic b’ • In the second argument of ‘Get’, namely ‘g2’ In the type ‘Get a g2’ In the type instance declaration for ‘Get’ | 30 | type Get a (g1 :.: g2) = Get a g2 | ^^ }}} So that's not good. I'll mark this as highest priority as a result. Second, the error message: {{{ • Expected kind ‘Optic b’, but ‘g2’ has kind ‘Optic (Get a g1)’ • In the second argument of ‘Gettable’, namely ‘g2’ In the instance declaration for ‘Gettable a (g1 :.: g2)’ | 20 | , Gettable b g2 | }}} Is actually expected behavior (at least, at the moment). Even though you've written `b ~ Get a g1`, GHC isn't able to make use of this fact at the type level yet. See #12677/#15710 for the tickets tracking this infelicity. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15870#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15870: No skolem info panic -------------------------------------+------------------------------------- Reporter: sheaf | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.3 Component: Compiler (Type | Version: 8.6.2 checker) | Resolution: | Keywords: 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The regression was introduced in commit faec8d358985e5d0bf363bd96f23fe76c9e281f7 (`Track type variable scope more carefully.`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15870#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15870: No skolem info panic -------------------------------------+------------------------------------- Reporter: sheaf | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.3 Component: Compiler (Type | Version: 8.6.2 checker) | Resolution: | Keywords: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): I know why the crash happens. * In the instance decl we bring into scope the skolems of the instance * Then, we process the local family instance equation. In doing so we call the dreaded `tcFamTyPats` -- and it calls `solveEqualities` (wrongly I believe) * This `solveEqualities` tries to report an error; but it can't see the skolems, hence the panic. Really `solveEqualities` should only be called in an empty type environment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15870#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15870: No skolem info panic
-------------------------------------+-------------------------------------
Reporter: sheaf | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.6.3
Component: Compiler (Type | Version: 8.6.2
checker) |
Resolution: | Keywords:
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: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#15870: No skolem info panic -------------------------------------+------------------------------------- Reporter: sheaf | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.6.3 Component: Compiler (Type | Version: 8.6.2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: indexed- crash or panic | types/should_fail/T15870 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => indexed-types/should_fail/T15870 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15870#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC