[commit: testsuite] master: Test case about HyperStr and UseDemand (3cb91b3)
git at git.haskell.org
git at git.haskell.org
Mon Dec 2 18:02:41 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3cb91b31449d4ddbe0cfba4e59e5da52cbd284bd/testsuite
>---------------------------------------------------------------
commit 3cb91b31449d4ddbe0cfba4e59e5da52cbd284bd
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Mon Dec 2 18:02:10 2013 +0000
Test case about HyperStr and UseDemand
which was used by SPJ to reduce my ignorance, so I want to ensure I do
not break it.
>---------------------------------------------------------------
3cb91b31449d4ddbe0cfba4e59e5da52cbd284bd
tests/stranal/sigs/HyperStrUse.hs | 9 +++++++++
tests/stranal/sigs/all.T | 1 +
2 files changed, 10 insertions(+)
diff --git a/tests/stranal/sigs/HyperStrUse.hs b/tests/stranal/sigs/HyperStrUse.hs
new file mode 100644
index 0000000..88ba3e3
--- /dev/null
+++ b/tests/stranal/sigs/HyperStrUse.hs
@@ -0,0 +1,9 @@
+{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-}
+module HyperStrUse where
+
+import StrAnalAnnotation (StrAnal(StrAnal))
+
+f :: (Int, Int) -> Bool -> Int
+f (x,y) True = error (show x)
+f (x,y) False = x +1
+{-# ANN f (StrAnal "<S(SL),1*U(1*U(U),A)><S,1*U>m") #-}
diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T
index 74ddd9f..4080eb9 100644
--- a/tests/stranal/sigs/all.T
+++ b/tests/stranal/sigs/all.T
@@ -17,4 +17,5 @@ setTestOpts(only_ways(['optasm']))
test('StrAnalExample', normal, compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags])
test('T8569', expect_broken(8569), compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags])
+test('HyperStrUse', normal, compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags])
More information about the ghc-commits
mailing list