[commit: ghc] master: Test Trac #9565 and #9583 (01906c7)

git at git.haskell.org git at git.haskell.org
Tue Sep 23 11:09:18 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/01906c7399301e4f69959ecbd3b0d8bee5d5ef70/ghc

>---------------------------------------------------------------

commit 01906c7399301e4f69959ecbd3b0d8bee5d5ef70
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Sep 23 12:09:07 2014 +0100

    Test Trac #9565 and #9583


>---------------------------------------------------------------

01906c7399301e4f69959ecbd3b0d8bee5d5ef70
 .../T3500b.hs => simplCore/should_compile/T9565.hs}   |  7 +++++--
 testsuite/tests/simplCore/should_compile/T9583.hs     | 19 +++++++++++++++++++
 testsuite/tests/simplCore/should_compile/all.T        |  2 ++
 3 files changed, 26 insertions(+), 2 deletions(-)

diff --git a/testsuite/tests/typecheck/should_run/T3500b.hs b/testsuite/tests/simplCore/should_compile/T9565.hs
similarity index 58%
copy from testsuite/tests/typecheck/should_run/T3500b.hs
copy to testsuite/tests/simplCore/should_compile/T9565.hs
index 59a2c47..1dacb97 100644
--- a/testsuite/tests/typecheck/should_run/T3500b.hs
+++ b/testsuite/tests/simplCore/should_compile/T9565.hs
@@ -1,6 +1,10 @@
 {-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances #-}
 
-module Main where
+-- 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))
 
@@ -10,7 +14,6 @@ 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
 
diff --git a/testsuite/tests/simplCore/should_compile/T9583.hs b/testsuite/tests/simplCore/should_compile/T9583.hs
new file mode 100644
index 0000000..a77fcdd
--- /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 399498b..bbdadbf 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, [''])



More information about the ghc-commits mailing list