[Git][ghc/ghc][wip/simplifier-tweaks] Add a strategic inline pragma

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Thu Jun 29 15:02:27 UTC 2023



Simon Peyton Jones pushed to branch wip/simplifier-tweaks at Glasgow Haskell Compiler / GHC


Commits:
a52e3c44 by Simon Peyton Jones at 2023-06-29T14:23:22+01:00
Add a strategic inline pragma

- - - - -


1 changed file:

- compiler/GHC/HsToCore/Pmc/Solver/Types.hs


Changes:

=====================================
compiler/GHC/HsToCore/Pmc/Solver/Types.hs
=====================================
@@ -325,6 +325,11 @@ lookupVarInfoNT ts x = case lookupVarInfo ts x of
     go _                = Nothing
 
 trvVarInfo :: Functor f => (VarInfo -> f (a, VarInfo)) -> Nabla -> Id -> f (a, Nabla)
+{-# INLINE trvVarInfo #-}
+-- This function is called a lot and we want to specilise it, not only
+-- for the type class, but also for its 'f' function argument.
+-- Before the INLINE pragma it sometimes inlined and sometimes didn't,
+-- depending delicately on GHC's optimisations.  Better to use a pragma.
 trvVarInfo f nabla at MkNabla{ nabla_tm_st = ts at TmSt{ts_facts = env} } x
   = set_vi <$> f (lookupVarInfo ts x)
   where



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a52e3c443e456f62898f0df65ef9435e706f4436
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/20230629/fa1b1cb6/attachment.html>


More information about the ghc-commits mailing list