#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 twanvl):

 The current deriving code uses 'holes'. For example, the fmap derivation
 has the type:
 {{{
 ft_fmap :: FFoldType (LHsExpr RdrName -> State [RdrName] (LHsExpr
 RdrName))
 }}}
 The deriviation takes an expresion (`LHsExpr RdrName`) to plug in the
 hole, and returns the total expression.
 For example, `fmap f` for the type `"[a]"` is `\xs -> [|map f $xs|]`. Note
 that the lambda is at the meta level. This also means that we can't just
 use `f` itself, we have to use `\x -> [|f $x|]`.

 When this is passed as an argument to a higher order function such as
 `fmap` or `foldr`, this lambda must be brought to the ast level. This is
 done by wrapping it in a concrete lambda. Since there is no way to tell
 wether the thing we are making concrete is in eta reducable form. Of
 course we could have a data type to capture eta-reducable expressions.

 It would be much simpler to only have concrete lambdas. I.e. to derive
 `[|\xs -> map f xs|]` or without eta expanding, `[|map f|]`.
 The only downside is that the generated code becomes a bit weirder. For
 example, for the type:
 {{{
 data Foo a = Foo Int (Bar a) (a,a,a)
 }}}
 we currently generate
 {{{
 fmap f (Foo x y z) = Foo x (fmap (\a -> f a) y) (case z of (a,b,c) -> (f
 a, f b, f c))
 }}}
 but this would become instead:
 {{{
 fmap f (Foo x y z) = Foo ((\x' -> x') x) (fmap f y) ((\z' -> case z' of
 (a,b,c) -> (f a, f b, f c)) z)
 }}}

 Similarly for foldr, where we now generate
 {{{
 foldr f a0 (Foo x y z) = f x (foldr (\u v -> f u v) (case z of (a,b,c) ->
 f a (f b (f c a0))) y)
 }}}
 this would become
 {{{
 foldr f a0 (Foo x y z)
        = f x
        $ (\y' a0' -> foldr f a0' y') y
        $ (\z' a0' -> case z' of (a,b,c) -> f a (f b (f c a0)) ) z
        $ a0
 }}}

 This shouldn't be a very difficult change, it might even simplify the code
 a bit. If I have some free time this weekend, and if I manage to get a
 working ghc build, I'll give it a try.

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