Profiling wrongly attributes allocations to a function with Int# result
Profiling can't decide whether the given function allocates or not at all. The code snippet says it all:
{-# LANGUAGE MagicHash #-}
import GHC.Exts
-- ghc -prof --make bork.hs -fprof-auto -O1
-- ./bork +RTS -s -P -RTS
main = do
let f :: Int -> Int#
-- {-# NOINLINE f #-}
f x = case x `div` 17 of I# i -> i
-- {-# NOINLINE g #-}
g h = sum $ map (\y -> I# (h y)) [0..1000000]
g f `seq` return ()
-- COST CENTRE MODULE %time %alloc ticks bytes
-- main.g Main 73.6 93.3 159 224000328
-- main.f Main 24.1 6.7 52 16000016
-- main.g.\ Main 2.3 0.0 5 0
-- When either of the NOINLINE is enabled, the profile becomes:
-- COST CENTRE MODULE %time %alloc ticks bytes
-- main.g Main 72.9 93.3 161 224000328
-- main.f Main 16.7 0.0 37 0
-- main.g.\ Main 10.4 6.7 23 16000016
-- So, does f actually allocate or not?
-- Profiling is quite a bit less useful if it can't answer that reliably,
-- because in larger code snippets it's hard to decide from source
-- or from Core/STG.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |