[GHC] #14174: GHC panic with TypeInType and type family
GHC
ghc-devs at haskell.org
Thu Aug 31 19:14:09 UTC 2017
#14174: GHC panic with TypeInType and type family
-------------------------------------+-------------------------------------
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 rather simple type family,
{{{#!hs
{-# LANGUAGE TypeFamilies, TypeOperators, TypeInType #-}
module GenWhoops where
import GHC.Generics
type family GenComp k (x :: k) (y :: k) :: Ordering where
GenComp ((x :+: y) p) ('L1 x) ('L1 y) = GenComp (x p) x y
}}}
produces the following panic:
{{{
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.3.20170828 for x86_64-unknown-linux):
piResultTy
k_a1LK[tau:1]
p_a1Lz[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:949:35 in ghc:Type
}}}
This happens with both GHC 8.2.1 and something very close to HEAD.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14174>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list