#7436: Derived Foldable and Traversable instances become extremely inefficient 
due
to eta-expansion
---------------------------------+------------------------------------------
    Reporter:  shachaf           |       Owner:                         
        Type:  bug               |      Status:  new                    
    Priority:  normal            |   Milestone:                         
   Component:  Compiler          |     Version:  7.6.1                  
    Keywords:                    |          Os:  Unknown/Multiple       
Architecture:  Unknown/Multiple  |     Failure:  Runtime performance bug
  Difficulty:  Unknown           |    Testcase:                         
   Blockedby:                    |    Blocking:                         
     Related:                    |  
---------------------------------+------------------------------------------

Comment(by shachaf):

 The two instances I gave work as as they are without deriving (no Core
 necessary -- the code is a simplified version of what `-ddump-deriv`
 generated). Here's a simpler version without type classes (or lists):

 {{{
 data Nat = Z | S Nat

 mkNat :: Int -> Nat
 mkNat 0 = Z
 mkNat n = S (mkNat (n-1))

 unNat :: Nat -> ()
 unNat Z = ()
 unNat (S n) = unNat n

 fast :: (b -> b) -> b -> Nat -> b
 fast s z Z = z
 fast s z (S n) = s (fast s z n)

 slow :: (b -> b) -> b -> Nat -> b
 slow s z Z = z
 slow s z (S n) = s (slow (\e -> s e) z n)

 main :: IO ()
 --main = print $ unNat . fast S Z . mkNat $ n
 main = print $ unNat . slow S Z . mkNat $ n
   where n = 100000
 }}}

 And the `+RTS -s` output for both:

 * Fast:

 {{{
 shachaf@carbon:~/9$ ghc -rtsopts -O2 C.hs && time ./C +RTS -s
 [1 of 1] Compiling Main             ( C.hs, C.o )
 Linking C ...
 ()
        9,651,768 bytes allocated in the heap
           10,904 bytes copied during GC
           44,416 bytes maximum residency (2 sample(s))
           21,120 bytes maximum slop
                1 MB total memory in use (0 MB lost due to fragmentation)

                                     Tot time (elapsed)  Avg pause  Max
 pause
   Gen  0        17 colls,     0 par    0.00s    0.00s     0.0000s
 0.0000s
   Gen  1         2 colls,     0 par    0.00s    0.00s     0.0001s
 0.0002s

   INIT    time    0.00s  (  0.00s elapsed)
   MUT     time    0.00s  (  0.00s elapsed)
   GC      time    0.00s  (  0.00s elapsed)
   EXIT    time    0.00s  (  0.00s elapsed)
   Total   time    0.00s  (  0.00s elapsed)

   %GC     time       0.0%  (9.8% elapsed)

   Alloc rate    2,412,942,000 bytes per MUT second

   Productivity 100.0% of total user, 116.6% of total elapsed


 real    0m0.005s
 user    0m0.004s
 sys     0m0.000s
 }}}

 * Slow:

 {{{
 shachaf@carbon:~/9$ ghc -rtsopts -O2 C.hs && time ./C +RTS -s
 [1 of 1] Compiling Main             ( C.hs, C.o )
 Linking C ...
 ()
       11,251,768 bytes allocated in the heap
        4,122,872 bytes copied during GC
        1,223,248 bytes maximum residency (3 sample(s))
          528,816 bytes maximum slop
                4 MB total memory in use (0 MB lost due to fragmentation)

                                     Tot time (elapsed)  Avg pause  Max
 pause
   Gen  0        19 colls,     0 par    0.00s    0.00s     0.0002s
 0.0002s
   Gen  1         3 colls,     0 par    0.00s    0.00s     0.0006s
 0.0016s

   INIT    time    0.00s  (  0.00s elapsed)
   MUT     time    8.23s  (  8.25s elapsed)
   GC      time    0.00s  (  0.01s elapsed)
   EXIT    time    0.00s  (  0.00s elapsed)
   Total   time    8.24s  (  8.25s elapsed)

   %GC     time       0.0%  (0.1% elapsed)

   Alloc rate    1,366,747 bytes per MUT second

   Productivity 100.0% of total user, 99.8% of total elapsed


 real    0m8.253s
 user    0m8.237s
 sys     0m0.000s
 }}}

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

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to