summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2014-09-23 12:09:07 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2014-09-23 12:09:07 +0100
commit01906c7399301e4f69959ecbd3b0d8bee5d5ef70 (patch)
treedd23c92d7ef1de7c04ca2692f4897bab1f1e35c7
parent5fa6e75960b3dddbc72c35eb3fc0f2759215dfbb (diff)
downloadhaskell-01906c7399301e4f69959ecbd3b0d8bee5d5ef70.tar.gz
Test Trac #9565 and #9583
-rw-r--r--testsuite/tests/simplCore/should_compile/T9565.hs23
-rw-r--r--testsuite/tests/simplCore/should_compile/T9583.hs19
-rw-r--r--testsuite/tests/simplCore/should_compile/all.T2
3 files changed, 44 insertions, 0 deletions
diff --git a/testsuite/tests/simplCore/should_compile/T9565.hs b/testsuite/tests/simplCore/should_compile/T9565.hs
new file mode 100644
index 0000000000..1dacb97214
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T9565.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances #-}
+
+-- This is a copy of typecheck/should_run/T3500b, but it's here for
+-- a different reason: at one time, it sent the compiler into a loop.
+-- ANd T3500b isn't tested 'fast' mode
+
+module T9565 where
+
+newtype Mu f = Mu (f (Mu f))
+
+type family Id m
+type instance Id m = m
+
+instance Show (Id (f (Mu f))) => Show (Mu f) where
+ show (Mu f) = show f
+
+showMu :: Mu (Either ()) -> String
+showMu = show
+
+item :: Mu (Either ())
+item = Mu (Right (Mu (Left ())))
+
+main = print (showMu item)
diff --git a/testsuite/tests/simplCore/should_compile/T9583.hs b/testsuite/tests/simplCore/should_compile/T9583.hs
new file mode 100644
index 0000000000..a77fcdd07f
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T9583.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# OPTIONS_GHC -O #-}
+
+module T9583 where
+
+import Data.Binary ( Binary(..) )
+import Data.Data ( Data )
+import Data.Typeable ( Typeable )
+import GHC.Generics ( Generic )
+
+data T = A
+ | B
+ | C T
+ | D T T
+ | E T T
+ deriving (Data, Generic, Typeable)
+
+instance Binary T
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 399498b800..bbdadbf1fa 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -207,3 +207,5 @@ test('T8848a', only_ways(['optasm']), compile, ['-ddump-rules'])
test('T8331', only_ways(['optasm']), compile, ['-ddump-rules'])
test('T6056', only_ways(['optasm']), multimod_compile, ['T6056', '-v0 -ddump-rule-firings'])
test('T9400', only_ways(['optasm']), compile, ['-O0 -ddump-simpl -dsuppress-uniques'])
+test('T9583', only_ways(['optasm']), compile, [''])
+test('T9565', only_ways(['optasm']), compile, [''])