[Git][ghc/ghc][master] Perf: make SDoc monad one-shot (#18202)
Marge Bot
gitlab at gitlab.haskell.org
Mon Aug 24 04:33:20 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00
Perf: make SDoc monad one-shot (#18202)
With validate-x86_64-linux-deb9-hadrian:
T1969 -3.4% (threshold: +/-1%)
T3294 -3.3% (threshold: +/-1%)
T12707 -1.4% (threshold: +/-1%)
Additionally with validate-x86_64-linux-deb9-unreg-hadrian:
T4801 -2.4% (threshold: +/-2%)
T13035 -1.4% (threshold: +/-1%)
T13379 -2.4% (threshold: +/-2%)
ManyAlternatives -2.5% (threshold: +/-2%)
ManyConstructors -3.0% (threshold: +/-2%)
Metric Decrease:
T12707
T1969
T3294
ManyAlternatives
ManyConstructors
T13035
T13379
T4801
- - - - -
1 changed file:
- compiler/GHC/Utils/Outputable.hs
Changes:
=====================================
compiler/GHC/Utils/Outputable.hs
=====================================
@@ -1,4 +1,5 @@
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE PatternSynonyms #-}
{-
(c) The University of Glasgow 2006-2012
@@ -121,6 +122,7 @@ import qualified Data.List.NonEmpty as NEL
import GHC.Fingerprint
import GHC.Show ( showMultiLineString )
import GHC.Utils.Exception
+import GHC.Exts (oneShot)
{-
************************************************************************
@@ -304,7 +306,17 @@ code (either C or assembly), or generating interface files.
-- To display an 'SDoc', use 'printSDoc', 'printSDocLn', 'bufLeftRenderSDoc',
-- or 'renderWithContext'. Avoid calling 'runSDoc' directly as it breaks the
-- abstraction layer.
-newtype SDoc = SDoc { runSDoc :: SDocContext -> Doc }
+newtype SDoc = SDoc' (SDocContext -> Doc)
+
+-- See Note [The one-shot state monad trick] in GHC.Utils.Monad
+{-# COMPLETE SDoc #-}
+pattern SDoc :: (SDocContext -> Doc) -> SDoc
+pattern SDoc m <- SDoc' m
+ where
+ SDoc m = SDoc' (oneShot m)
+
+runSDoc :: SDoc -> (SDocContext -> Doc)
+runSDoc (SDoc m) = m
data SDocContext = SDC
{ sdocStyle :: !PprStyle
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1eb38a0a7168d7612c791c4289cc02d900d402f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1eb38a0a7168d7612c791c4289cc02d900d402f
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/20200824/de15caa8/attachment-0001.html>
More information about the ghc-commits
mailing list