[GHC] #15692: GHC panic from pattern synonyms + deferred type errors
GHC
ghc-devs at haskell.org
Sun Sep 30 14:33:22 UTC 2018
#15692: GHC panic from pattern synonyms + deferred type errors
-------------------------------------+-------------------------------------
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, TypeInType |
Architecture: | Type of failure: Compile-time
Unknown/Multiple | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# Language DataKinds, TypeOperators, PolyKinds, PatternSynonyms, GADTs
#-}
{-# Options_GHC -dcore-lint -fdefer-type-errors #-}
import Data.Kind
data Ctx :: Type -> Type where
E :: Ctx(Type)
(:&:) :: a -> Ctx(as) -> Ctx(a -> as)
data ApplyT (k::Type) :: k -> Ctx(k) -> Type where
AO :: a -> ApplyT(Type) a E
AS :: ApplyT(ks) (f a) ctx
-> ApplyT(k -> ks) f (a:&:ctx)
pattern ASSO = AS (AS (AO False))
}}}
{{{
$ ghci -ignore-dot-ghci 463.hs
hs/463.hs:16:27: warning: [-Wdeferred-type-errors]
• Couldn't match type ‘a a1 a2’ with ‘Bool’
Expected type: a3
Actual type: Bool
• In the pattern: False
In the pattern: AO False
In the pattern: AS (AO False)
|
16 | pattern ASSO = AS (AS (AO False))
| ^^^^^
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.7.20180828 for x86_64-unknown-linux):
urk! lookup local fingerprint
$mASSO
[iESflb :-> ($trModule, 1ca40dc83a9c879effdb760462cc9a2d),
iESgKD :-> ($tc'E, 79f67a27a14dc1bb6eecb39e4b061e2c),
iESgKF :-> ($tc':&:, 24793c0c1652ffcf92e04f47d38fa075),
iESgKH :-> ($tcCtx, a3f9358cbfe161bf59e75500d70ce0ae),
iESgKI :-> ($tc'AO, 72111d1891cb082e989c20a2191a8b4b),
iESgKK :-> ($tc'AS, ff019c04c400d5fbdd46ff8a816d4913),
iESgKM :-> ($tcApplyT, cbfe28374b4115925c7213e6330ab115)]
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in
ghc:Outputable
pprPanic, called at compiler/iface/MkIface.hs:524:37 in
ghc:MkIface
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
>
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15692>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list