
#16225: GHC HEAD-only Core Lint error (Trans coercion mis-match)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.8.1
Component: Compiler | Version: 8.7
(Type checker) |
Keywords: TypeInType | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets: #16188, #16204
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following code compiles on GHC 8.0.2 through GHC 8.6.3 with `-dcore-
lint`:
{{{#!hs
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
module Bug where
import Data.Kind
data family Sing :: k -> Type
data TyFun :: Type -> Type -> Type
type a ~> b = TyFun a b -> Type
infixr 0 ~>
type family Apply (f :: a ~> b) (x :: a) :: b
data TyCon1 :: (k1 -> k2) -> (k1 ~> k2)
type instance Apply (TyCon1 f) x = f x
data SomeApply :: (k ~> Type) -> Type where
SomeApply :: Apply f a -> SomeApply f
f :: SomeApply (TyCon1 Sing :: k ~> Type)
-> SomeApply (TyCon1 Sing :: k ~> Type)
f (SomeApply s)
= SomeApply s
}}}
However, it chokes on GHC HEAD:
{{{
$ ~/Software/ghc4/inplace/bin/ghc-stage2 --interactive Bug.hs -dcore-lint
GHCi, version 8.7.20190120: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
*** Core Lint errors : in result of Desugar (before optimization) ***
<no location info>: warning:
In the expression: SomeApply
@ k_a1Dz
@ (TyCon1 Sing)
@ Any
(s_a1Bq
`cast` (Sub (D:R:ApplyabTyCon1x[0]