[GHC] #10649: Performance issue with unnecessary reboxing
GHC
ghc-devs at haskell.org
Fri Jul 17 11:27:07 UTC 2015
#10649: Performance issue with unnecessary reboxing
-------------------------------------+-------------------------------------
Reporter: pacak | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Runtime
Unknown/Multiple | performance bug
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Revisions: |
-------------------------------------+-------------------------------------
Depending on number of fields in a structure (A and F), $fBA_$cfoo or
$fBF_$cfoo will or will not be using $w$cfoo
for 16 fields it uses it, for 12 - not
With lazy fields behaviour, it starts using $w$cfoo around 100-200 fields.
Adding -funfolding-use-threshold=90 helps in this case, but given enough
fields (about 50 of them, of different types) value of 1000000000 is not
helping and with very cheap operation (like addition or allocation of
cons-like structure) overhead from sending those parameters via stack into
worker becomes very significant - I have code that works ~3-5 times
slower.
This issue is not specific to generics, I can provide more examples if
necessary
{{{#!hs
{-# LANGUAGE FlexibleContexts, FlexibleInstances, DeriveGeneric,
DefaultSignatures #-}
{-# LANGUAGE TypeOperators, BangPatterns #-}
{-# OPTIONS -funbox-strict-fields -ddump-to-file -ddump-simpl -ddump-stg
-dsuppress-all -ddump-asm #-}
import Data.Word
import GHC.Generics
data A = A !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word
!Word !Word !Word
deriving Generic
data F = F !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word
!Word !Word !Word !Word !Word !Word
deriving Generic
class B a where
foo :: a -> Word
{-# INLINE foo #-}
default foo :: (Generic a, GB (Rep a)) => a -> Word
foo !x = gfoo (from x)
class GB f where
gfoo :: (f a) -> Word
instance GB x => GB (M1 D d (M1 C c x)) where
{-# INLINE gfoo #-}
gfoo (M1 (M1 x)) = gfoo x
instance (GB a, GB b) => GB (a :*: b) where
{-# INLINE gfoo #-}
gfoo (a :*: b) = gfoo a + gfoo b
instance GB (M1 S s (Rec0 Word)) where
{-# INLINE gfoo #-}
gfoo (M1 (K1 x)) = x
instance B A
instance B F
main :: IO ()
main = return ()
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10649>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list