[Git][ghc/ghc][wip/codebuffer-perftest] base/encoding: add an allocations performance test (#22946)

Josh Meredith (@JoshMeredith) gitlab at gitlab.haskell.org
Fri Apr 28 10:42:22 UTC 2023



Josh Meredith pushed to branch wip/codebuffer-perftest at Glasgow Haskell Compiler / GHC


Commits:
3c4460eb by Josh Meredith at 2023-04-28T10:42:13+00:00
base/encoding: add an allocations performance test (#22946)

- - - - -


2 changed files:

- libraries/base/tests/perf/all.T
- + libraries/base/tests/perf/encodingAllocations.hs


Changes:

=====================================
libraries/base/tests/perf/all.T
=====================================
@@ -1,5 +1,16 @@
+# .stats files aren't yet supported in the JS backend
+setTestOpts(js_skip)
+
 #--------------------------------------
 # Check specialization of elem via rules
 #--------------------------------------
 
 test('T17752', [only_ways(['normal'])] , makefile_test, ['T17752'])
+
+#--------------------------------------
+
+# We don't expect the code in test to vary at all, but the variance is set to
+# 1% in case the constant allocations increase by other means.
+#
+# The JavaScript
+test('encodingAllocations', [only_ways(['normal']), collect_stats('bytes allocated', 1)], compile_and_run, ['-O2'])


=====================================
libraries/base/tests/perf/encodingAllocations.hs
=====================================
@@ -0,0 +1,36 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE CPP #-}
+{-# OPTIONS_GHC -dno-typeable-binds -O2 #-}
+
+module Main (main) where
+
+import System.IO
+import Data.Bits
+import GHC.Int
+import GHC.Exts
+import System.Environment
+import Distribution.Simple.Utils
+
+devnull :: FilePath
+#if defined(mingw32_HOST_OS)
+devnull = "NUL"
+#else
+devnull = "/dev/null"
+#endif
+
+main :: IO ()
+main = withTempFile "." "encodingAllocations.tmp" (const $ loop 1000000)
+
+loop :: Int -> Handle -> IO ()
+loop 0  !_ = pure ()
+loop !n !h = do
+  hPutChar h $! dummy_char n
+  loop (n-1) h
+
+-- unsafe efficient version of `chr`
+my_chr :: Int -> Char
+my_chr (I# i) = C# (chr# i)
+
+-- return either a or b
+dummy_char :: Int -> Char
+dummy_char !i = my_chr ((i .&. 1) + 97)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c4460eb7afe13b24b156f3da7980c29c6aef6a4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c4460eb7afe13b24b156f3da7980c29c6aef6a4
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/20230428/3950b893/attachment-0001.html>


More information about the ghc-commits mailing list