[Git][ghc/ghc][wip/compact-sourcetext] testsuite: add test for T22744
Zubin (@wz1000)
gitlab at gitlab.haskell.org
Wed May 10 10:21:05 UTC 2023
Zubin pushed to branch wip/compact-sourcetext at Glasgow Haskell Compiler / GHC
Commits:
48435306 by Zubin Duggal at 2023-05-10T15:50:56+05:30
testsuite: add test for T22744
- - - - -
3 changed files:
- testsuite/tests/perf/compiler/Makefile
- testsuite/tests/perf/compiler/all.T
- + testsuite/tests/perf/compiler/genT22744
Changes:
=====================================
testsuite/tests/perf/compiler/Makefile
=====================================
@@ -32,3 +32,8 @@ MultiLayerModulesTH_OneShot_Prep: MultiLayerModulesTH_Make_Prep
InstanceMatching:
./genMatchingTest 0
'$(TEST_HC)' $(TEST_HC_OPTS) -fno-code -fwrite-interface Defs.hs
+
+T22744:
+ ./genT22744
+ '$(TEST_HC)' $(TEST_HC_OPTS) T22744.hs
+
=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -670,3 +670,13 @@ test('RecordUpdPerf',
],
multimod_compile,
['RecordUpdPerf', '-fno-code -v0'])
+
+test('T22744',
+ [ collect_compiler_stats('peak_megabytes_allocated',20),
+ pre_cmd('$MAKE -s --no-print-directory T22744'),
+ extra_files(['genT22744']),
+ compile_timeout_multiplier(2)
+ ],
+ multimod_compile,
+ ['T22744', '-v0'])
+
=====================================
testsuite/tests/perf/compiler/genT22744
=====================================
@@ -0,0 +1,28 @@
+#!/usr/bin/env bash
+
+NUMDEP=10000
+NUMMOD=100
+
+seq 1 $NUMDEP | xargs -I{} touch foo{}
+
+cat > T22744.hs << EOF
+module Main where
+EOF
+
+for i in $(seq $NUMMOD); do
+ cat > M$i.hs << EOF
+{-# LANGUAGE TemplateHaskell #-}
+module M$i where
+import Language.Haskell.TH.Syntax
+import Control.Monad
+
+\$(do forM_ [1..$NUMDEP] $ \i -> addDependentFile $ "foo" ++ show i
+ return [])
+EOF
+ echo "import M$i" >> T22744.hs
+done
+
+cat >> T22744.hs << EOF
+main = pure ()
+EOF
+
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/48435306f9d518deb11c3641369017df547debb4
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/48435306f9d518deb11c3641369017df547debb4
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230510/9c6bd54f/attachment-0001.html>
More information about the ghc-commits
mailing list