[GHC] #14873: GHC HEAD regression (piResultTy)
GHC
ghc-devs at haskell.org
Thu Mar 1 21:10:45 UTC 2018
#14873: GHC HEAD regression (piResultTy)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone:
Component: Compiler | Version: 8.5
(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:
-------------------------------------+-------------------------------------
(Originally noticed [https://travis-
ci.org/goldfirere/singletons/jobs/347945148#L1179 here].)
The following program typechecks on GHC 8.2.2 on GHC 8.4.1, but panics on
GHC HEAD:
{{{#!hs
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
module Bug where
import Data.Kind (Type)
data family Sing (a :: k)
newtype instance Sing (f :: k1 ~> k2) =
SLambda { applySing :: forall t. Sing t -> Sing (Apply f t) }
data TyFun :: Type -> Type -> Type
type a ~> b = TyFun a b -> Type
infixr 0 ~>
type family Apply (f :: k1 ~> k2) (x :: k1) :: k2
class SingI (a :: k) where
sing :: Sing a
data ColSym1 :: f a -> a ~> Bool
type instance Apply (ColSym1 x) y = Col x y
class PColumn (f :: Type -> Type) where
type Col (x :: f a) (y :: a) :: Bool
class SColumn (f :: Type -> Type) where
sCol :: forall (x :: f a) (y :: a).
Sing x -> Sing y -> Sing (Col x y :: Bool)
instance (SColumn f, SingI x) => SingI (ColSym1 (x :: f a) :: a ~> Bool)
where
sing = SLambda (sCol (sing @_ @x))
}}}
{{{
$ /opt/ghc/head/bin/ghc Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
ghc: panic! (the 'impossible' happened)
(GHC version 8.5.20180201 for x86_64-unknown-linux):
piResultTy
k_aZU[tau:1]
(a_aW8[sk:1] |> <*>_N)
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
ghc:Outputable
pprPanic, called at compiler/types/Type.hs:947:35 in ghc:Type
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14873>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list