
#14513: +RTS -hT does not report about SmallArray objects -------------------------------------+------------------------------------- Reporter: akio | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.2.1 System | Keywords: profiling | Operating System: Linux Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- +RTS -hT seems to ignore SmallArray# objects. Also the combination of SmallArray# objects and -hT causes a segfault on ghc 7.10. To reproduce, save the following progam as smallarray.hs {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE UnboxedTuples #-} import GHC.Exts import GHC.IO (IO(..), unIO) import Control.Concurrent import Control.Monad import System.Mem main :: IO () main = do forkIO $ forever $ performGC IO $ \s0 -> let !(# s01, msa #) = newSmallArray# 100# 'X' s0 !s02 = writeSmallArray# msa 4# 'Y' s01 !(# s1, sa #) = unsafeFreezeSmallArray# msa s02 !(# s2, () #) = unIO (threadDelay 5000000) s1 !(# v #) = indexSmallArray# sa 2# !(# s3, () #) = unIO (print v) s2 in (# s3, () #) }}} compile it, and run it like: {{{ ghc smallarray.hs -rtsopts -threaded ./samllarray +RTS -hT }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14513 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler