Profiling can affect program behaviour (-fprof-late)
I found it quite surprising that turning on profiling could insert thunks into my program which then affected the behaviour when combined with some unsafe functions.
I am going to note the example here in case anyone else finds this confusing:
[matt@nixos:~/ghc-prof]$ cat Box.hs
{-# LANGUAGE MagicHash #-}
module Main where
import GHC.Exts
data Box = Box Any
asBox :: a -> Box
asBox x = Box (unsafeCoerce# x)
{-# NOINLINE asBox #-}
closureSize :: Box -> Int
closureSize (Box x) = I# (closureSize# x)
main = do
print (closureSize (asBox ()))
With just -prof
the program prints 4
and with -fprof-late
it prints 5
.
[matt@nixos:~/ghc-prof]$ cat Box.hs
{-# LANGUAGE MagicHash #-}
module Main where
import GHC.Exts
data Box = Box Any
asBox :: a -> Box
asBox x = Box (unsafeCoerce# x)
{-# NOINLINE asBox #-}
closureSize :: Box -> Int
closureSize (Box x) = I# (closureSize# x)
main = do
print (closureSize (asBox ()))
If you look at the STG
Before:
Main.asBox [InlPrag=NOINLINE] :: forall a. a -> Main.Box
[GblId, Arity=1, Unf=OtherCon []] =
CCS_DONT_CARE {} \r [x_sNk] Main.Box [x_sNk];
after
Main.asBox [InlPrag=NOINLINE] :: forall a. a -> Main.Box
[GblId, Arity=1, Unf=OtherCon []] =
CCS_DONT_CARE {} \r [x_sNl]
tick<asBox>
let {
sat_sNo [Occ=Once1] :: GHC.Types.Any
[LclId] =
CCCS {x_sNl} \u [] scc<asBox> x_sNl;
} in Main.Box [sat_sNo];
I don't know why this thunk is necessary but it violates the expectations of users using Box
that the value placed into the Box
is exactly the one which they passed into the function.
cc @AndreasK