[GHC] #8313: Poor performance of higher-order functions with unboxing

GHC ghc-devs at haskell.org
Fri Jan 17 15:27:04 UTC 2014


#8313: Poor performance of higher-order functions with unboxing
-------------------------------------+-------------------------------------
        Reporter:  dolio             |            Owner:
            Type:  task              |           Status:  new
        Priority:  low               |        Milestone:  _|_
       Component:  Compiler          |          Version:  7.6.3
      Resolution:                    |         Keywords:  slow unboxed
Operating System:  Unknown/Multiple  |  higher order
 Type of failure:  Runtime           |     Architecture:  Unknown/Multiple
  performance bug                    |       Difficulty:  Easy (less than 1
       Test Case:                    |  hour)
        Blocking:                    |       Blocked By:  6084
                                     |  Related Tickets:
-------------------------------------+-------------------------------------

Comment (by nomeata):

 Checking if this is really fixed, but here, `manual` is still slower than
 `auto`, so it does not seem to be fixed (although it might have been even
 slower before). Also, `manual` allocates much more – is that the symptom
 of this problem, or is it something else?

 I had slightly change the test due to
 [f6e2398adb63f5c35544333268df9c8837fd2581/base] to

 {{{#!haskell
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE MagicHash #-}

 import GHC.Exts
 import System.Environment

 rel# :: Int# -> Int# -> Int# -> Int#
 rel# i# j# k# = (i# +# j# +# k#) ># 100000000#

 rel :: Int -> Int -> Int -> Bool
 rel (I# i#) (I# j#) (I# k#) = tagToEnum# (rel# i# j# k#)

 manual :: (Int# -> Int# -> Int# -> Int#) -> (Int, Int, Int)
 manual r# = go 0# 0# 0#
  where
  go i# j# k# | tagToEnum# (r# i# j# k#) = (I# i#, I# j#, I# k#)
              | otherwise                = go j# k# (i# +# 1#)
 {-# NOINLINE manual #-}

 auto :: (Int -> Int -> Int -> Bool) -> (Int, Int, Int)
 auto r = go 0 0 0
  where
  go !i !j !k | r i j k   = (i, j, k)
              | otherwise = go j k (i+1)
 {-# NOINLINE auto #-}

 main = getArgs >>= \case
   "manual" : _ -> print $ manual rel# -- This case is significantly
 slower.
   "auto"   : _ -> print $ auto rel    -- Why?
 }}}

 and I get these numbers:

 {{{
 $ ./T8313 manual +RTS -t
 (33333333,33333334,33333334)
 <<ghc: 7200055256 bytes, 13828 GCs, 36364/44312 avg/max bytes residency (2
 samples), 1M in use, 0.00 INIT (0.00 elapsed), 3.03 MUT (3.05 elapsed),
 0.03 GC (0.03 elapsed) :ghc>>
 $ ./T8313 auto +RTS -t
 (33333333,33333334,33333334)
 <<ghc: 4800054800 bytes, 9192 GCs, 36364/44312 avg/max bytes residency (2
 samples), 1M in use, 0.00 INIT (0.00 elapsed), 1.43 MUT (1.43 elapsed),
 0.02 GC (0.02 elapsed) :ghc>>
 }}}

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


More information about the ghc-tickets mailing list