[commit: ghc] wip/ghc-8.0-det: Add a new determinism test (052fe1d)
git at git.haskell.org
git at git.haskell.org
Thu Jul 14 13:54:31 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ghc-8.0-det
Link : http://ghc.haskell.org/trac/ghc/changeset/052fe1d2c3425c0ff2b301da9018e2791ef75443/ghc
>---------------------------------------------------------------
commit 052fe1d2c3425c0ff2b301da9018e2791ef75443
Author: Bartosz Nitka <niteria at gmail.com>
Date: Thu Jun 30 06:59:02 2016 -0700
Add a new determinism test
This is one of the testcases that I forgot to commit
>---------------------------------------------------------------
052fe1d2c3425c0ff2b301da9018e2791ef75443
testsuite/tests/determinism/determ021/A.hs | 8 ++++++++
testsuite/tests/determinism/determ021/Makefile | 11 +++++++++++
.../determinism/{determ009 => determ021}/all.T | 4 ++--
.../tests/determinism/determ021/determ021.stdout | 22 ++++++++++++++++++++++
4 files changed, 43 insertions(+), 2 deletions(-)
diff --git a/testsuite/tests/determinism/determ021/A.hs b/testsuite/tests/determinism/determ021/A.hs
new file mode 100644
index 0000000..773a012
--- /dev/null
+++ b/testsuite/tests/determinism/determ021/A.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE ApplicativeDo #-}
+{-# OPTIONS_GHC -ddump-types #-}
+module A where
+
+test2 f = do
+ x <- f 3
+ y <- f 4
+ return (x + y)
diff --git a/testsuite/tests/determinism/determ021/Makefile b/testsuite/tests/determinism/determ021/Makefile
new file mode 100644
index 0000000..e88edef
--- /dev/null
+++ b/testsuite/tests/determinism/determ021/Makefile
@@ -0,0 +1,11 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+determ021:
+ $(RM) A.hi A.o
+ '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=0 -dunique-increment=1 A.hs
+ $(CP) A.hi A.normal.hi
+ $(RM) A.hi A.o
+ '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=16777215 -dunique-increment=-1 A.hs
+ diff A.hi A.normal.hi
diff --git a/testsuite/tests/determinism/determ009/all.T b/testsuite/tests/determinism/determ021/all.T
similarity index 50%
copy from testsuite/tests/determinism/determ009/all.T
copy to testsuite/tests/determinism/determ021/all.T
index 7cae393..35af362 100644
--- a/testsuite/tests/determinism/determ009/all.T
+++ b/testsuite/tests/determinism/determ021/all.T
@@ -1,4 +1,4 @@
-test('determ009',
+test('determ021',
extra_clean(['A.o', 'A.hi', 'A.normal.hi']),
run_command,
- ['$MAKE -s --no-print-directory determ009'])
+ ['$MAKE -s --no-print-directory determ021'])
diff --git a/testsuite/tests/determinism/determ021/determ021.stdout b/testsuite/tests/determinism/determ021/determ021.stdout
new file mode 100644
index 0000000..747064f
--- /dev/null
+++ b/testsuite/tests/determinism/determ021/determ021.stdout
@@ -0,0 +1,22 @@
+[1 of 1] Compiling A ( A.hs, A.o )
+TYPE SIGNATURES
+ test2 ::
+ forall t b (f :: * -> *).
+ (Num b, Num t, Applicative f) =>
+ (t -> f b) -> f b
+TYPE CONSTRUCTORS
+COERCION AXIOMS
+Dependent modules: []
+Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
+ integer-gmp-1.0.0.1]
+[1 of 1] Compiling A ( A.hs, A.o )
+TYPE SIGNATURES
+ test2 ::
+ forall t b (f :: * -> *).
+ (Num b, Num t, Applicative f) =>
+ (t -> f b) -> f b
+TYPE CONSTRUCTORS
+COERCION AXIOMS
+Dependent modules: []
+Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
+ integer-gmp-1.0.0.1]
More information about the ghc-commits
mailing list