[commit: ghc] wip/hie-module: Add perf test for #16190 (0f1eb88)
git at git.haskell.org
git at git.haskell.org
Fri Feb 15 10:15:47 UTC 2019
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/hie-module
Link : http://ghc.haskell.org/trac/ghc/changeset/0f1eb88c93143359fa671bb72aceebc299c87a95/ghc
>---------------------------------------------------------------
commit 0f1eb88c93143359fa671bb72aceebc299c87a95
Author: Sylvain Henry <sylvain at haskus.fr>
Date: Mon Feb 11 17:39:02 2019 +0100
Add perf test for #16190
>---------------------------------------------------------------
0f1eb88c93143359fa671bb72aceebc299c87a95
testsuite/tests/perf/compiler/T16190.hs | 17 +++++++++++++++++
testsuite/tests/perf/compiler/T16190_Embed.hs | 7 +++++++
testsuite/tests/perf/compiler/all.T | 6 ++++++
3 files changed, 30 insertions(+)
diff --git a/testsuite/tests/perf/compiler/T16190.hs b/testsuite/tests/perf/compiler/T16190.hs
new file mode 100644
index 0000000..79479f0
--- /dev/null
+++ b/testsuite/tests/perf/compiler/T16190.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module Main where
+
+import T16190_Embed
+import Foreign.Ptr
+import Foreign.Storable
+import Data.Word
+import GHC.Ptr
+
+ptr :: Ptr Word32
+ptr = Ptr $(embedBytes (replicate (3 * 1000 * 1000) 0x37))
+
+main :: IO ()
+main = do
+ w <- peek (ptr `plusPtr` 12)
+ print (w == (0x37373737 :: Word32))
diff --git a/testsuite/tests/perf/compiler/T16190_Embed.hs b/testsuite/tests/perf/compiler/T16190_Embed.hs
new file mode 100644
index 0000000..f7e50d6
--- /dev/null
+++ b/testsuite/tests/perf/compiler/T16190_Embed.hs
@@ -0,0 +1,7 @@
+module T16190_Embed where
+
+import Data.Word
+import Language.Haskell.TH
+
+embedBytes :: [Word8] -> Q Exp
+embedBytes bs = return (LitE (StringPrimL bs))
diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T
index 9103719..82847c2 100644
--- a/testsuite/tests/perf/compiler/all.T
+++ b/testsuite/tests/perf/compiler/all.T
@@ -390,3 +390,9 @@ test ('T15164',
],
compile,
['-v0 -O'])
+
+test('T16190',
+ [ collect_stats()
+ ],
+ multimod_compile,
+ ['T16190.hs', '-v0'])
More information about the ghc-commits
mailing list