[GHC] #15694: GHC panic from pattern synonym, "Type-correct unfilled coercion hole"
GHC
ghc-devs at haskell.org
Sun Sep 30 17:54:56 UTC 2018
#15694: GHC panic from pattern synonym, "Type-correct unfilled coercion hole"
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.6.1
Keywords: | Operating System: Unknown/Multiple
PatternSynonyms |
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# Language RankNTypes, PatternSynonyms, TypeOperators, DataKinds,
PolyKinds, KindSignatures, GADTs #-}
import Data.Kind
import Data.Type.Equality
data Ctx :: Type -> Type where
E :: Ctx(Type)
(:&:) :: a -> Ctx(as) -> Ctx(a -> as)
data ApplyT(kind::Type) :: kind -> Ctx(kind) -> Type where
AO :: a -> ApplyT(Type) a E
AS :: ApplyT(ks) (f a) ctx
-> ApplyT(k -> ks) f (a:&:ctx)
pattern ASSO :: () => forall ks k (f :: k -> ks) (a1 :: k) (ctx :: Ctx ks)
(ks1 :: Type) k1 (a2 :: k1) (ctx1 :: Ctx ks1) a3. (kind ~ (k -> ks), a ~~
f, b ~~ (a1 :&: ctx), ks ~ (k1 -> ks1), ctx ~~ (a2 :&: E), ks1 ~ Type, f
a1 a2 ~~ a3) => a3 -> ApplyT kind a b
pattern ASSO a = AS (AS (AO a))
}}}
{{{
baldur at KindStar:~/hs$ ghci -ignore-dot-ghci 465.hs
GHCi, version 8.7.20180828: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( 465.hs, interpreted )
WARNING: file compiler/types/TyCoRep.hs, line 2378
in_scope InScope {kind_a1Cw a_a1Cx b_a1Cy ks_a1Cz k_a1CA f_a1CB
a1_a1CC ctx_a1CD ks1_a1CE k1_a1CF a2_a1CG ctx1_a1CH
a3_a1CI
k0_a1F8}
tenv [a1Cw :-> kind_a1Cw[sk:0], a1Cx :-> a_a1Cx[sk:0],
a1Cy :-> b_a1Cy[sk:0], a1Cz :-> ks_a1Cz[sk:0],
a1CA :-> k_a1CA[sk:0], a1CB :-> f_a1CB[sk:0],
a1CC :-> a1_a1CC[sk:0], a1CD :-> ctx_a1CD[sk:0],
a1CE :-> ks1_a1CE[sk:0], a1CF :-> k1_a1CF[sk:0],
a1CG :-> a2_a1CG[sk:0], a1CH :-> ctx1_a1CH[sk:0],
a1CI :-> a3_a1CI[sk:0]]
cenv []
tys [kind_a1Cw[sk:1] ~ (k_a1CA[sk:2] -> ks_a1Cz[sk:2]),
a_a1Cx[sk:1] ~~ f_a1CB[sk:2],
b_a1Cy[sk:1] ~~ (a1_a1CC[sk:2] ':&: ctx_a1CD[sk:2]),
ks_a1Cz[sk:2] ~ (k1_a1CF[sk:2] -> ks1_a1CE[sk:2]),
ctx_a1CD[sk:2] ~~ (a2_a1CG[sk:2] ':&: 'E), ks1_a1CE[sk:2] ~ *,
(f_a1CB[sk:2] a1_a1CC[sk:2] |> {co_a1Fc}) a2_a1CG[sk:2]
~~ a3_a1CI[sk:2]]
cos []
needInScope [a1F8 :-> k0_a1F8[sk:2], a1Fc :-> co_a1Fc]
WARNING: file compiler/types/TyCoRep.hs, line 2378
in_scope InScope {kind_a1Cw a_a1Cx b_a1Cy k0_a1HA ks_a1HB k_a1HC
f_a1HD a1_a1HE ctx_a1HF ks1_a1HG k1_a1HH a2_a1HI
ctx1_a1HJ a3_a1HK}
tenv [a1Cz :-> ks_a1HB[tau:4], a1CA :-> k_a1HC[tau:4],
a1CB :-> f_a1HD[tau:4], a1CC :-> a1_a1HE[tau:4],
a1CD :-> ctx_a1HF[tau:4], a1CE :-> ks1_a1HG[tau:4],
a1CF :-> k1_a1HH[tau:4], a1CG :-> a2_a1HI[tau:4],
a1CH :-> ctx1_a1HJ[tau:4], a1CI :-> a3_a1HK[tau:4],
a1F8 :-> k0_a1HA[tau:4]]
cenv []
tys [kind_a1Cw[sk:0] ~ (k_a1CA[sk:0] -> ks_a1Cz[sk:0]),
a_a1Cx[sk:0] ~~ f_a1CB[sk:0],
b_a1Cy[sk:0] ~~ (a1_a1CC[sk:0] ':&: ctx_a1CD[sk:0]),
ks_a1Cz[sk:0] ~ (k1_a1CF[sk:0] -> ks1_a1CE[sk:0]),
ctx_a1CD[sk:0] ~~ (a2_a1CG[sk:0] ':&: 'E), ks1_a1CE[sk:0] ~ *,
(f_a1CB[sk:0] a1_a1CC[sk:0] |> {co_a1Fc}) a2_a1CG[sk:0]
~~ a3_a1CI[sk:0]]
cos []
needInScope [a1Cw :-> kind_a1Cw[sk:0], a1Cx :-> a_a1Cx[sk:0],
a1Cy :-> b_a1Cy[sk:0], a1Fc :-> co_a1Fc]
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.7.20180828 for x86_64-unknown-linux):
ASSERT failed!
Type-correct unfilled coercion hole {co_a1Fc}
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in
ghc:Outputable
pprPanic, called at compiler/utils/Outputable.hs:1219:5 in
ghc:Outputable
assertPprPanic, called at compiler/typecheck/TcHsSyn.hs:1716:99 in
ghc:TcHsSyn
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
>
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15694>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list