
#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: 14873 => #14873 Comment: It looks like commit faec8d358985e5d0bf363bd96f23fe76c9e281f7 (`Track type variable scope more carefully.`) nabbed this one. After that commit, I get error messages instead of panics on each program in the ticket. For the first program: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind type family F (f :: forall a. g a) :: Type where F (f :: forall a. g a) = Int }}} {{{ $ ghc/inplace/bin/ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:8:1: error: You have written a *complete user-suppled kind signature*, but the following variable is undetermined: k0 :: * Perhaps add a kind signature. Inferred kinds of user-written variables: g :: k0 -> * f :: forall (a :: k0). g a | 8 | type family F (f :: forall a. g a) :: Type where | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} For the second program: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug2 where import Data.Kind type family F f :: Type where F ((f :: forall a. g a) :: forall a. g a) = Int }}} {{{ $ ghc/inplace/bin/ghc-stage2 Bug2.hs [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) Bug2.hs:9:7: error: • Expected kind ‘forall (a :: k1). g a’, but ‘f’ has kind ‘k0’ • In the first argument of ‘F’, namely ‘((f :: forall a. g a) :: forall a. g a)’ In the type family declaration for ‘F’ | 9 | F ((f :: forall a. g a) :: forall a. g a) = Int | ^ }}} I'll add regression tests and close this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler