Skip to content

Commit

Permalink
Add missing files from #7702's test
Browse files Browse the repository at this point in the history
  • Loading branch information
Ian Lynagh committed Jun 6, 2013
1 parent 1ad2fda commit d8296b1
Show file tree
Hide file tree
Showing 6 changed files with 95 additions and 0 deletions.
7 changes: 7 additions & 0 deletions 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 ()
1 change: 1 addition & 0 deletions tests/simplCore/should_compile/T7702.stderr
@@ -0,0 +1 @@
T7702Plugin
20 changes: 20 additions & 0 deletions tests/simplCore/should_compile/T7702plugin/Makefile
@@ -0,0 +1,20 @@
TOP=../../../..
include $(TOP)/mk/boilerplate.mk
include $(TOP)/mk/test.mk

clean.%:
rm -rf pkg.$*

HERE := $(abspath .)
$(eval $(call canonicalise,HERE))

package.%:
$(MAKE) clean.$*
mkdir pkg.$*
"$(TEST_HC)" -outputdir pkg.$* --make -v0 -o pkg.$*/setup Setup.hs

echo "[]" > pkg.$*/local.package.conf

pkg.$*/setup configure --distdir pkg.$*/dist -v0 $(CABAL_PLUGIN_BUILD) --prefix="$(HERE)/pkg.$*/install" --with-compiler="$(TEST_HC)" --with-hc-pkg="$(GHC_PKG)" --package-db=pkg.$*/local.package.conf
pkg.$*/setup build --distdir pkg.$*/dist -v0
pkg.$*/setup install --distdir pkg.$*/dist -v0
3 changes: 3 additions & 0 deletions tests/simplCore/should_compile/T7702plugin/Setup.hs
@@ -0,0 +1,3 @@
import Distribution.Simple

main = defaultMain
51 changes: 51 additions & 0 deletions 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
13 changes: 13 additions & 0 deletions 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

0 comments on commit d8296b1

Please sign in to comment.