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

 {{{
 {-# LANGUAGE DeriveFunctor, DeriveFoldable #-}
 import Prelude hiding (foldr)
 import Data.Foldable

 data List a = Nil | Cons a (List a)
     deriving (Functor, Foldable)

 mkList :: Int -> List Int
 mkList 0 = Nil
 mkList n = Cons n (mkList (n-1))

 main :: IO ()
 main = print $ foldr (\x y -> y) "end" (mkList n)
   where n = 100000
 }}}

 Takes `n^2` time to run with GHC 7.6.1 -O2.

 The generated `Foldable` code looks something like this:

 {{{
 instance Foldable List where
     foldr f z Nil = z
     foldr f z (Cons x xs) = f x (foldr (\a b -> f a b) z xs)
 }}}

 Eta-reducing the function, i.e.

 {{{
 instance Foldable List where
     foldr f z Nil = z
     foldr f z (Cons x xs) = f x (foldr f z xs)
 }}}

 Makes the program linear in `n` (in this case, runtime goes from 8.160s to
 0.004s).

 The `Traversable` instance also has the same issue.

 There seem to be three different issues:

 * Derived `Foldable` and `Traversable` instances are nearly unusable for
 large
 structures.

 * An eta-expanded definition like `foldr` becomes asymptotically worse for
 some
 reason.

 Maybe this is expected behavior for this function, since `f` gets eta-
 expanded
 at each iteration?

 * `Foldable` instances are generated with `foldr` instead of `foldMap`.

 This isn't directly related, since the code would have the same problem
 either
 way, but since I'm already writing about it... `foldMap` can allow
 asymptotically better operations on a structure than `foldr` (for example,
 finding the rightmost leaf of a binary tree using `Data.Monoid.Last`), so
 it
 should probably be generated instead. A `foldMap` definition should look
 like a
 simpler version of `traverse`, which is already derivable. Maybe this
 should be
 a separate ticket.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7436>
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