From 48720a07607a4b88ef78d9afbf55115deffee2c5 Mon Sep 17 00:00:00 2001 From: Matthew Craven <5086-clyring@users.noreply.gitlab.haskell.org> Date: Thu, 28 Dec 2023 18:09:52 -0500 Subject: [PATCH] Apply Note [Sensitivity to unique increment] to LargeRecord --- testsuite/tests/perf/compiler/LargeRecord.hs | 3 +++ testsuite/tests/perf/compiler/T8095.hs | 2 +- testsuite/tests/perf/compiler/all.T | 4 +++- 3 files changed, 7 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/LargeRecord.hs b/testsuite/tests/perf/compiler/LargeRecord.hs index c31ef0ed0866..b70367a98ae0 100644 --- a/testsuite/tests/perf/compiler/LargeRecord.hs +++ b/testsuite/tests/perf/compiler/LargeRecord.hs @@ -11,6 +11,9 @@ {- Notes on LargeRecord ~~~~~~~~~~~~~~~~~~~~~~~ +Subject to Note [Sensitivity to unique increment] in T12545.hs with spread of 2.2% + + I noticed that in GHC of July 2022, when compiling this module I got lots of "SPEC" rules diff --git a/testsuite/tests/perf/compiler/T8095.hs b/testsuite/tests/perf/compiler/T8095.hs index bed4dff72671..5c0cf5cae814 100644 --- a/testsuite/tests/perf/compiler/T8095.hs +++ b/testsuite/tests/perf/compiler/T8095.hs @@ -1,6 +1,6 @@ {-# OPTIONS_GHC -freduction-depth=1000 #-} {-# LANGUAGE TypeOperators,DataKinds,KindSignatures,TypeFamilies,PolyKinds,UndecidableInstances #-} --- Subject to Note [Sensitivity to unique increment] with spread of 1.7% +-- Subject to Note [Sensitivity to unique increment] in T12545.hs with spread of 1.7% import GHC.TypeLits data Nat1 = Zero | Succ Nat1 type family Replicate1 (n :: Nat1) (x::a) :: [a] diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index bf06a5dd9b3a..4c19400b8899 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -206,9 +206,11 @@ test('CoOpt_Singletons', ######### +# LargeRecord is subject to Note [Sensitivity to unique increment] in T12545.hs +# observed spread was 2.2% test ('LargeRecord', [ only_ways(['normal']), - collect_compiler_stats('bytes allocated',1) + collect_compiler_stats('bytes allocated',5) , extra_files(['SuperRecord.hs']) ], multimod_compile, -- GitLab