[GHC] #14257: Heap profiling with ghc and hp2ps and strict function application ($!) gives samples out of sequence (regression)

GHC ghc-devs at haskell.org
Wed Sep 20 14:10:07 UTC 2017


#14257: Heap profiling with ghc and hp2ps and strict function application ($!)
gives samples out of sequence (regression)
-------------------------------------+-------------------------------------
           Reporter:  carlostome     |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Runtime        |           Version:  8.2.1
  System                             |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #14006
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following program generates an invalid .hp file when compiled with ghc
 8.2.1 but it does not when using ghc 8.0.2.

 {{{#!hs
 {-# LANGUAGE ScopedTypeVariables #-}
 module Main where

   eval :: forall a b. (a -> b -> b) -> b -> [a] -> b
   eval f b xs = load xs []
     where
       load :: [a] -> [a] -> b
       load [] stk          = unload b stk
       load (x:xs) stk      = load xs (x : stk)

       unload :: b -> [a] -> b
       unload  v []         = v
       unload  v (x  : stk) = unload ((f $! x) $! v) stk

   main :: IO ()
   main = print (eval (||) False (True : replicate 10000000 False))
 }}}

 If strict application ($!) is substituted for normal application ($) or
 removed then the .hp generated file is correct.

 For reproducing the error:
 {{{
 ghc -O2 --make -prof -fprof-auto Example.hs -fforce-recomp
 ./Example +RTS -hc
 hp2ps -e8in -c Example.hp
 }}}
 It outputs:
 {{{
 hp2ps: Example.hp, line 43, samples out of sequence
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14257>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list