Skip to content
Snippets Groups Projects
Commit efd113f7 authored by Ben Gamari's avatar Ben Gamari
Browse files

testsuite: Add testcase for T13658

parent 49012ebc
No related branches found
No related tags found
No related merge requests found
{-# 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))
......@@ -268,3 +268,4 @@ test('T12600',
normal,
run_command,
['$MAKE -s --no-print-directory T12600'])
test('T13658', normal, compile, ['-dcore-lint'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment