[GHC] #15629: "No skolem info" panic (GHC 8.6 only)
GHC
ghc-devs at haskell.org
Wed Sep 12 10:21:16 UTC 2018
#15629: "No skolem info" panic (GHC 8.6 only)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.6.1-beta1
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):
For what it's worth, here is a slightly more minimal version of the
original program:
{{{#!hs
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
module Bug (f) where
import Data.Kind
import Data.Proxy
data TyFun :: Type -> Type -> Type
type a ~> b = TyFun a b -> Type
infixr 0 ~>
type family F x :: Type -> Type
data F1Sym :: forall x a. x ~> F x a
data F2Sym :: forall x a. F x a ~> x
data Comp :: forall b c a. (b ~> c) -> (a ~> b) -> (a ~> c)
sg :: forall a b c (f :: b ~> c) (g :: a ~> b) (x :: a).
Proxy f -> Proxy g -> Proxy (Comp f g)
sg _ _ = Proxy
f :: forall (x :: Type). Proxy x -> ()
f _ = ()
where
g :: forall ab. Proxy ((Comp (F1Sym :: x ~> F x z) F2Sym) :: F x ab ~>
F x ab)
g = sg Proxy Proxy
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15629#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list