[commit: testsuite] master: Test Trac #7837 (2d5ead6)

Simon Peyton Jones simonpj at microsoft.com
Tue Apr 16 17:45:55 CEST 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

https://github.com/ghc/testsuite/commit/2d5ead66f94cfd29ac53cc3ecd9fa4f36583a835

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

commit 2d5ead66f94cfd29ac53cc3ecd9fa4f36583a835
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Apr 16 09:54:40 2013 +0100

    Test Trac #7837

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

 tests/indexed-types/should_compile/T7837.hs     |   24 +++++++++++++++++++++++
 tests/indexed-types/should_compile/T7837.stderr |    3 ++
 tests/indexed-types/should_compile/all.T        |    1 +
 3 files changed, 28 insertions(+), 0 deletions(-)

diff --git a/tests/indexed-types/should_compile/T7837.hs b/tests/indexed-types/should_compile/T7837.hs
new file mode 100644
index 0000000..45235f8
--- /dev/null
+++ b/tests/indexed-types/should_compile/T7837.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
+
+module T7837 where
+
+type family Scalar a
+class Fractional (Scalar a) => Norm a where
+  norm :: a -> Scalar a
+
+type instance Scalar Double = Double
+instance Norm Double where norm = abs
+
+normalize :: (Norm a, a ~ Scalar a) => a -> a
+normalize x = x / norm x
+{-# NOINLINE normalize #-}
+
+normalize_Double :: Double -> Double
+normalize_Double = signum
+{-# NOINLINE normalize_Double #-}
+
+-- This rule should fire in 'foo'
+{-# RULES "normalize/Double" normalize = normalize_Double #-}
+
+foo :: Double
+foo = normalize (4 :: Double)
diff --git a/tests/indexed-types/should_compile/T7837.stderr b/tests/indexed-types/should_compile/T7837.stderr
new file mode 100644
index 0000000..eff5d02
--- /dev/null
+++ b/tests/indexed-types/should_compile/T7837.stderr
@@ -0,0 +1,3 @@
+Rule fired: Class op abs
+Rule fired: Class op signum
+Rule fired: normalize/Double
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index 23b8824..15e9877 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -209,4 +209,5 @@ test('T7489', normal, compile, [''])
 test('T7585', normal, compile, [''])
 test('T7282', normal, compile, [''])
 test('T7804', normal, compile, [''])
+test('T7837', normal, compile, ['-O -ddump-rule-firings'])
 





More information about the ghc-commits mailing list