[GHC] #15170: GHC HEAD panic (dischargeFmv)
GHC
ghc-devs at haskell.org
Sun May 20 20:05:33 UTC 2018
#15170: GHC HEAD panic (dischargeFmv)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.5
checker) |
Resolution: | 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: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Here's as small of an example as I can muster:
{{{#!hs
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
module Bug where
import Data.Kind
import Data.Proxy
data TyFun :: Type -> Type -> Type
type a ~> b = TyFun a b -> Type
infixr 0 ~>
type family Apply (f :: k1 ~> k2) (x :: k1) :: k2
type f @@ x = Apply f x
infixl 9 @@
wat :: forall (a :: Type)
(b :: a ~> Type)
(c :: forall (x :: a). Proxy x ~> b @@ x ~> Type)
(f :: forall (x :: a) (y :: b @@ x). Proxy x ~> Proxy y ~> c
@@ ('Proxy :: Proxy x) @@ y)
(x :: a).
(forall (xx :: a) (yy :: b @@ xx). Proxy (f @@ ('Proxy :: Proxy xx)
@@ ('Proxy :: Proxy yy)))
-> ()
wat _ = ()
}}}
{{{
$ /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.20180501 for x86_64-unknown-linux):
dischargeFmv
[D] _ {0}:: (Apply
(f_a1rx[sk:2] xx_a1rH[tau:3] yy_a1rI[tau:3] |> Sym
((TyFun
<Proxy xx_a1rH[tau:3]>_N
((TyFun
(Proxy
(Sym {co_a1rP})
(Coh <yy_a1rI[tau:3]>_N
{co_a1rP}))_N
(Sym {co_a1s4} ; (Apply
(Sym {co_a1rP})
<*>_N
(Coh ((Coh <s_a1rQ[fmv:0]>_N
((TyFun
(Sym {co_a1rP})
<*>_N)_N
->_N <*>_N) ; Sym {co_a1s3}) ; (Apply
<Proxy
xx_a1rH[tau:3]>_N
((TyFun
(Sym {co_a1rP})
<*>_N)_N
->_N <*>_N)
(Coh <c_a1rw[sk:2] xx_a1rH[tau:3]>_N
(Sym ((TyFun
<Proxy
xx_a1rH[tau:3]>_N
((TyFun
(Sym {co_a1rP})
<*>_N)_N
->_N <*>_N))_N
->_N <*>_N)))
<'Proxy>_N)_N)
(Sym ((TyFun
(Sym {co_a1rP})
<*>_N)_N
->_N <*>_N)))
(Coh <yy_a1rI[tau:3]>_N
{co_a1rP}))_N))_N
->_N <*>_N))_N
->_N
<*>_N))
'Proxy :: (Proxy (yy_a1rI[tau:3] |> {co_a1rP}) ~>
s_a1rS[fmv:0]))
~# (s_a1sj[fmv:0] :: (Proxy (yy_a1rI[tau:3] |> {co_a1rP})
~> s_a1rS[fmv:0]))
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1162:37 in
ghc:Outputable
pprPanic, called at compiler/typecheck/TcSMonad.hs:3047:25 in
ghc:TcSMonad
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15170#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list