[GHC] #14175: Panic repSplitTyConApp_maybe
GHC
ghc-devs at haskell.org
Thu Aug 31 19:57:48 UTC 2017
#14175: Panic repSplitTyConApp_maybe
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1
(Type checker) |
Keywords: TypeInType | 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:
-------------------------------------+-------------------------------------
This definition panics!
{{{#!hs
{-# LANGUAGE TypeFamilies, TypeInType #-}
module Whoops where
import Data.Kind
type family PComp (k :: j -> Type) (x :: k) :: ()
}}}
{{{
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.3.20170828 for x86_64-unknown-linux):
repSplitTyConApp_maybe
j_aon[sk:1]
*
*
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1138:37 in
ghc:Outputable
pprPanic, called at compiler/types/Type.hs:1123:5 in ghc:Type
}}}
If I make it a type synonym instead, I get a proper error as expected.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14175>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list