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@gitlab.haskell.org>
Sent: 21 June 2020 15:44
To: Simon Peyton Jones <simonpj@microsoft.com>
Subject: GHC/ | GHC doesn't inline small type class method marked as INLINE with profiling enabled (#18372)
Andrzej
Rybczak created an issue:
When profiling is enabled, GHC doesn't inline small type class methods which prevents further optimizations and specialization from happening.
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.
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).
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
Profiling build was tested with profiling: True
in
cabal.project.local
.
GHC should inline class methods marked as INLINE when profiling is enabled.
Optional:
—
Reply to this email directly or
view it on GitLab.
You're receiving this email because of your account on gitlab.haskell.org. If you'd like to receive fewer emails, you can
unsubscribe from this thread or adjust your notification settings.