[commit: testsuite] master: Add test case for #8569 (c9d164a)

git at git.haskell.org git at git.haskell.org
Fri Nov 29 19:09:51 UTC 2013


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/c9d164ac641fca43134201672db15c333d90805c/testsuite

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

commit c9d164ac641fca43134201672db15c333d90805c
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Fri Nov 29 19:08:55 2013 +0000

    Add test case for #8569


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

c9d164ac641fca43134201672db15c333d90805c
 tests/stranal/sigs/T8569.hs |   15 +++++++++++++++
 tests/stranal/sigs/all.T    |    2 ++
 2 files changed, 17 insertions(+)

diff --git a/tests/stranal/sigs/T8569.hs b/tests/stranal/sigs/T8569.hs
new file mode 100644
index 0000000..ee6c413
--- /dev/null
+++ b/tests/stranal/sigs/T8569.hs
@@ -0,0 +1,15 @@
+{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-}
+{-# LANGUAGE GADTs #-}
+
+module T8569 where
+
+import StrAnalAnnotation (StrAnal(StrAnal))
+
+data Rep t where
+  Rint :: Rep Int
+  Rdata :: Rep i -> (t -> i) -> Rep t
+
+addUp :: Rep a -> a -> Int
+addUp Rint n  = n
+addUp (Rdata i f) x = addUp i (f x)
+{-# ANN addUp (StrAnal "<S,1*U><L,U>") #-}
diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T
index 89df993..74ddd9f 100644
--- a/tests/stranal/sigs/all.T
+++ b/tests/stranal/sigs/all.T
@@ -16,3 +16,5 @@ setTestOpts(only_ways(['optasm']))
 # Use this as a template
 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])
+



More information about the ghc-commits mailing list