GHC/ | GHC doesn't inline small type class method marked as INLINE with profiling enabled (#18372)

Simon Peyton Jones simonpj at microsoft.com
Mon Jun 22 12:43:14 UTC 2020


I get a 404 for https://gitlab.haskell.org/ghc/ghc/-/issues/18372

You may need to re-submit this…

s

From: Andrzej Rybczak <gitlab at gitlab.haskell.org>
Sent: 21 June 2020 15:44
To: Simon Peyton Jones <simonpj at microsoft.com>
Subject: GHC/ | GHC doesn't inline small type class method marked as INLINE with profiling enabled (#18372)


Andrzej Rybczak<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Farybczak&data=02%7C01%7Csimonpj%40microsoft.com%7C69826edc95e94f123d4208d815f18406%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637283474331207255&sdata=oSLeWvPZsSFhqr07wt3RveuWf9F%2Bs052fjkuTKEVzqE%3D&reserved=0> created an issue:

Summary

When profiling is enabled, GHC doesn't inline small type class methods which prevents further optimizations and specialization from happening.

Steps to reproduce

When the following module:

module Main where



import Optics.Core



data T = T { _t1 :: Int

           , _t2 :: Int

           }



t1 :: Lens' T Int

t1 = lensVL $ \f s -> (\n -> s { _t1 = n}) <$> f (_t1 s)

{-# INLINE t1 #-}



t2 :: Lens' T Int

t2 = lensVL $ \f s -> (\n -> s { _t2 = n}) <$> f (_t2 s)

{-# INLINE t2 #-}



t_val :: T

t_val = T 1 2

{-# NOINLINE t_val #-}



main :: IO ()

main = putStrLn . show $ view t1 t_val + view t2 t_val

is compiled with profiling enabled, here's how core of main looks:

main1

  = case ((($fStrongForget_$clinear main_l1) (id `cast` <Co:41>))

          `cast` <Co:42>)

           t_val

    of

    { I# x_a2c8 ->

    case ((($fStrongForget_$clinear main_l2) (id `cast` <Co:41>))

          `cast` <Co:42>)

           t_val

    of

    { I# y_a2cb ->

    case $wshowSignedInt 0# (+# x_a2c8 y_a2cb) [] of

    { (# ww5_a277, ww6_a278 #) ->

    : ww5_a277 ww6_a278

    }

    }

    }

So linear doesn't get inlined even though it's a small function that is even explicitly marked INLINE<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fwell-typed%2Foptics%2Fblob%2F5758cd6a18162cd0a69f4a044026d1bd878cfaf9%2Findexed-profunctors%2Fsrc%2FData%2FProfunctor%2FIndexed.hs%23L355&data=02%7C01%7Csimonpj%40microsoft.com%7C69826edc95e94f123d4208d815f18406%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637283474331207255&sdata=v6agV%2FTB5%2BpzLDcmEdTI8NNf281F39KhfLinCEi7vI0%3D&reserved=0>.

This prevents further optimizations from happening and leaves optics-related code in semi-optimized state, making looking at cost centers unreliable (see well-typed/optics#324<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fwell-typed%2Foptics%2Fissues%2F324&data=02%7C01%7Csimonpj%40microsoft.com%7C69826edc95e94f123d4208d815f18406%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637283474331217249&sdata=ThSQiMn4GzrEWaEg9uFycOCkka32wf9wjXAhznlZ%2Bjo%3D&reserved=0>).

When profiling is disabled, everything inlines and optimizes away as expected:

main1

  = case t_val of { T ds_d25F ds1_d25G ->

    case ds_d25F of { I# x_a2c7 ->

    case ds1_d25G of { I# y_a2ca ->

    case $wshowSignedInt 0# (+# x_a2c7 y_a2ca) [] of

    { (# ww5_a276, ww6_a277 #) ->

    : ww5_a276 ww6_a277

    }

    }

    }

    }

I'm attaching archive with cabal project that contains above module for easy reproduction: prof_test.tar.gz<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2Fuploads%2Fd3c051396724bcac1eeeb17ccb4bc779%2Fprof_test.tar.gz&data=02%7C01%7Csimonpj%40microsoft.com%7C69826edc95e94f123d4208d815f18406%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637283474331217249&sdata=2kBWLGNzNNoLhiU3GF4QsLoL%2BnWEzmLVxmtPoaQ9UfI%3D&reserved=0>

Profiling build was tested with profiling: True in cabal.project.local.

Expected behavior

GHC should inline class methods marked as INLINE when profiling is enabled.

Environment

  *   GHC version used: 8.10.1

Optional:

  *   Operating System: Arch Linux
  *   System Architecture: x86_64

—
Reply to this email directly or view it on GitLab<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2Fissues%2F18372&data=02%7C01%7Csimonpj%40microsoft.com%7C69826edc95e94f123d4208d815f18406%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637283474331227245&sdata=wlaM1SQDfNLA%2BwRNes4mO6iCnUMDpaAIsGIvzzxuZCI%3D&reserved=0>.
You're receiving this email because of your account on gitlab.haskell.org. If you'd like to receive fewer emails, you can unsubscribe<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fsent_notifications%2Ffcc5f69e58bc6dfc3bf5cd41bcba0129%2Funsubscribe&data=02%7C01%7Csimonpj%40microsoft.com%7C69826edc95e94f123d4208d815f18406%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637283474331227245&sdata=loI7zT2j7mgb2c2ku3gRt76DkRXQ0nSFebOuetCKqcQ%3D&reserved=0> from this thread or adjust your notification settings.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20200622/7826f2a5/attachment.html>


More information about the ghc-devs mailing list