[commit: testsuite] master: Add missing files from #7702's test (d8296b1)
Ian Lynagh
igloo at earth.li
Thu Jun 6 14:40:19 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/d8296b17ca3db4ae977aeaf5899dcec2a279e1ac
>---------------------------------------------------------------
commit d8296b17ca3db4ae977aeaf5899dcec2a279e1ac
Author: Ian Lynagh <ian at well-typed.com>
Date: Thu Jun 6 13:39:51 2013 +0100
Add missing files from #7702's test
>---------------------------------------------------------------
tests/simplCore/should_compile/T7702.hs | 7 +++
tests/simplCore/should_compile/T7702.stderr | 1 +
.../should_compile/T7702plugin}/Makefile | 2 +-
.../should_compile/T7702plugin}/Setup.hs | 0
.../should_compile/T7702plugin/T7702Plugin.hs | 51 ++++++++++++++++++++
.../should_compile/T7702plugin/T7702plugin.cabal | 13 +++++
6 files changed, 73 insertions(+), 1 deletions(-)
diff --git a/tests/simplCore/should_compile/T7702.hs b/tests/simplCore/should_compile/T7702.hs
new file mode 100644
index 0000000..771ace0
--- /dev/null
+++ b/tests/simplCore/should_compile/T7702.hs
@@ -0,0 +1,7 @@
+-- The contents of this file are irrelevant. It is merely
+-- the target for compilation by the T7702Plugin, which
+-- exhibits the space leak in Trac #7702
+module Main where
+
+main :: IO ()
+main = return ()
diff --git a/tests/simplCore/should_compile/T7702.stderr b/tests/simplCore/should_compile/T7702.stderr
new file mode 100644
index 0000000..1286e58
--- /dev/null
+++ b/tests/simplCore/should_compile/T7702.stderr
@@ -0,0 +1 @@
+T7702Plugin
diff --git a/tests/plugins/simple-plugin/Makefile b/tests/simplCore/should_compile/T7702plugin/Makefile
similarity index 97%
copy from tests/plugins/simple-plugin/Makefile
copy to tests/simplCore/should_compile/T7702plugin/Makefile
index 17588bf..42c56c9 100644
--- a/tests/plugins/simple-plugin/Makefile
+++ b/tests/simplCore/should_compile/T7702plugin/Makefile
@@ -1,4 +1,4 @@
-TOP=../../..
+TOP=../../../..
include $(TOP)/mk/boilerplate.mk
include $(TOP)/mk/test.mk
diff --git a/tests/plugins/simple-plugin/Setup.hs b/tests/simplCore/should_compile/T7702plugin/Setup.hs
similarity index 100%
copy from tests/plugins/simple-plugin/Setup.hs
copy to tests/simplCore/should_compile/T7702plugin/Setup.hs
diff --git a/tests/simplCore/should_compile/T7702plugin/T7702Plugin.hs b/tests/simplCore/should_compile/T7702plugin/T7702Plugin.hs
new file mode 100644
index 0000000..cb6a03d
--- /dev/null
+++ b/tests/simplCore/should_compile/T7702plugin/T7702Plugin.hs
@@ -0,0 +1,51 @@
+module T7702Plugin ( plugin ) where
+
+import GhcPlugins
+
+-- A plugin that does nothing but tickle CoreM's writer.
+plugin :: Plugin
+plugin = defaultPlugin { installCoreToDos = install }
+ where
+ install :: [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo]
+ install _ todos = do
+ reinitializeGlobals
+
+ putMsgS "T7702Plugin"
+
+ -- 1 million times, so the allocation in this plugin dominates allocation due
+ -- to other compiler flags and the test framework can easily catch the difference
+ -- can't use replicateM_ because it causes its own problems
+ nothingX100000 ; nothingX100000 ; nothingX100000 ; nothingX100000 ; nothingX100000
+ nothingX100000 ; nothingX100000 ; nothingX100000 ; nothingX100000 ; nothingX100000
+
+ return todos
+
+-- this will result in a call to plusWriter in CoreM's
+-- >>= implementation, which was causing the space leak
+nothing :: CoreM ()
+nothing = liftIO (return ())
+
+nothingX10 :: CoreM ()
+nothingX10 = do
+ nothing ; nothing ; nothing ; nothing ; nothing
+ nothing ; nothing ; nothing ; nothing ; nothing
+
+nothingX100 :: CoreM ()
+nothingX100 = do
+ nothingX10 ; nothingX10 ; nothingX10 ; nothingX10 ; nothingX10
+ nothingX10 ; nothingX10 ; nothingX10 ; nothingX10 ; nothingX10
+
+nothingX1000 :: CoreM ()
+nothingX1000 = do
+ nothingX100 ; nothingX100 ; nothingX100 ; nothingX100 ; nothingX100
+ nothingX100 ; nothingX100 ; nothingX100 ; nothingX100 ; nothingX100
+
+nothingX10000 :: CoreM ()
+nothingX10000 = do
+ nothingX1000 ; nothingX1000 ; nothingX1000 ; nothingX1000 ; nothingX1000
+ nothingX1000 ; nothingX1000 ; nothingX1000 ; nothingX1000 ; nothingX1000
+
+nothingX100000 :: CoreM ()
+nothingX100000 = do
+ nothingX10000 ; nothingX10000 ; nothingX10000 ; nothingX10000 ; nothingX10000
+ nothingX10000 ; nothingX10000 ; nothingX10000 ; nothingX10000 ; nothingX10000
diff --git a/tests/simplCore/should_compile/T7702plugin/T7702plugin.cabal b/tests/simplCore/should_compile/T7702plugin/T7702plugin.cabal
new file mode 100644
index 0000000..953ba3c
--- /dev/null
+++ b/tests/simplCore/should_compile/T7702plugin/T7702plugin.cabal
@@ -0,0 +1,13 @@
+Name: T7702plugin
+Version: 0.1
+Synopsis: Plugin which tests space leak fix in Trac #7702
+Cabal-Version: >= 1.2
+Build-Type: Simple
+Author: Andrew Farmer
+
+Library
+ Build-Depends:
+ base,
+ ghc >= 7.2.1
+ Exposed-Modules:
+ T7702Plugin
More information about the ghc-commits
mailing list