Performance issue with unnecessary reboxing
Depending on number of fields in a structure (A and F),
There was an error rendering this math block. KaTeX parse error: Expected group after '_' at position 4: fBA_̲
cfoo or There was an error rendering this math block. KaTeX parse error: Expected group after '_' at position 4: fBF_̲
cfoo will or will not be using cfoo
for 16 fields it uses it, for 12 - not
With lazy fields behaviour, it starts using
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
{-# 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 ()
Trac metadata
Trac field | Value |
---|---|
Version | 7.10.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |