[GHC] #13658: Assertion failure on HEAD: "optCoercion changed types!"
GHC
ghc-devs at haskell.org
Sun May 7 18:45:04 UTC 2017
#13658: Assertion failure on HEAD: "optCoercion changed types!"
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.1
Component: Compiler | Version: 8.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by slyfox):
Slightly shorter example without foldl:
{{{#!hs
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE BangPatterns #-}
{- # OPTIONS_GHC -Werror #-}
{-# OPTIONS_GHC -g -O2 #-}
module Bug (bug) where
-- import GHC.Base (seq)
import Unsafe.Coerce (unsafeCoerce)
undefined :: a
undefined = undefined
data TypeRep (a :: k) where
TrTyCon :: TypeRep (a :: k)
TrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1).
TypeRep (a b)
data SomeTypeRep where
SomeTypeRep :: forall k (a :: k).
TypeRep a
-> SomeTypeRep
mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1).
TypeRep (a :: k1 -> k2)
-> TypeRep (a b)
mkTrApp TrTyCon = undefined
mkTrApp TrApp = undefined
bug :: SomeTypeRep
-- bug = f x -- this works
bug = f (f x)
where x = SomeTypeRep TrTyCon
f :: SomeTypeRep -> SomeTypeRep
f (SomeTypeRep acc) = SomeTypeRep (mkTrApp (unsafeCoerce acc))
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13658#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list