Skip to content
Snippets Groups Projects
Commit b1eb38a0 authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

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
parent 364258e0
No related branches found
No related tags found
No related merge requests found
{-# 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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment