[Git][ghc/ghc][wip/T25445] Performance-related fixes

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Mon Nov 11 08:49:50 UTC 2024



Simon Peyton Jones pushed to branch wip/T25445 at Glasgow Haskell Compiler / GHC


Commits:
43d003f1 by Simon Peyton Jones at 2024-11-11T08:44:16+00:00
Performance-related fixes

Addresses #25463 (too much specialisation) and #20825 (Lint is expensive)

- - - - -


3 changed files:

- compiler/GHC/Core/Lint.hs
- compiler/GHC/Data/Unboxed.hs
- compiler/GHC/Hs/Dump.hs


Changes:

=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -3016,6 +3016,12 @@ type WarnsAndErrs = (Bag SDoc, Bag SDoc)
 
 -- Using a unboxed tuple here reduced allocations for a lint heavy
 -- file by ~6%. Using MaybeUB reduced them further by another ~12%.
+--
+-- Warning: if you don't inline the matcher for JustUB etc, Lint becomes
+-- /tremendously/ inefficient, and compiling GHC.Tc.Errors.Types (which
+-- contains gigantic types) is very very slow indeed. Conclusion: make
+-- sure unfoldings are expose in GHC.Data.Unboxed, and that you compile
+-- Lint.hs with optimistation on.
 type LResult a = (# MaybeUB a, WarnsAndErrs #)
 
 pattern LResult :: MaybeUB a -> WarnsAndErrs -> LResult a


=====================================
compiler/GHC/Data/Unboxed.hs
=====================================
@@ -4,6 +4,13 @@
 {-# LANGUAGE PatternSynonyms #-}
 {-# LANGUAGE UnliftedNewtypes #-}
 
+{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
+  -- If you use -fomit-interface-pragmas for your build, we won't
+  -- inline the matcher for JustUB, and that turns out to have a
+  -- catastropic effect on Lint, which uses unboxed Maybes.
+  -- Simple fix: switch off -fomit-interface-pragmas for this tiny
+  -- and very stable module.
+
 module GHC.Data.Unboxed (
   MaybeUB(JustUB, NothingUB),
   fmapMaybeUB, fromMaybeUB, apMaybeUB, maybeUB


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -6,6 +6,10 @@
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE DataKinds #-}
 
+{-# OPTIONS_GHC -fno-specialise #-}
+   -- Don't do type-class specialisation; it goes mad in this module
+   -- See #25463
+
 -- | Contains a debug function to dump parts of the GHC.Hs AST. It uses a syb
 -- traversal which falls back to displaying based on the constructor name, so
 -- can be used to dump anything having a @Data.Data@ instance.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/43d003f14c9bc434861d1e29cfbf740daed3253f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/43d003f14c9bc434861d1e29cfbf740daed3253f
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/20241111/6e42e29c/attachment-0001.html>


More information about the ghc-commits mailing list