[GHC] #15725: Core Lint error: Trans coercion mis-match

GHC ghc-devs at haskell.org
Wed Oct 10 09:22:33 UTC 2018


#15725: Core Lint error: Trans coercion mis-match
-------------------------------------+-------------------------------------
        Reporter:  RyanGlScott       |                Owner:  (none)
            Type:  bug               |               Status:  patch
        Priority:  normal            |            Milestone:  8.8.1
       Component:  Compiler          |              Version:  8.6.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  crash or panic                     |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #15703            |  Differential Rev(s):  Phab:D5217
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by monoidal):

 If this helps, I reduced to
 {{{
 #!hs
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE TypeInType #-}

 module Bug where

 import Data.Kind (Type)

 newtype Identity a = Identity a
 newtype Par1 a = Par1 a

 data family Sing :: forall k. k -> Type
 data instance Sing :: forall k. k -> Type

 type family Rep1 (f :: Type -> Type) :: Type -> Type
 type instance Rep1 Identity = Par1

 type family From1 (z :: f a) :: Rep1 f a
 type instance From1 ('Identity x) = 'Par1 x

 und :: a
 und = und

 f :: forall (a :: Type) (x :: Identity a).  Sing x
 f = g
     where g :: forall (a :: Type) (f :: Type -> Type) (x :: f a). Sing x
           g = seq (und :: Sing (From1 x)) und
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15725#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list