Unwanted eta-expansion

Simon Peyton-Jones simonpj at microsoft.com
Tue Oct 4 09:30:30 CEST 2011


Combining lambdas makes a big difference in GHC. For example
	f = \x. let y = E in \z. BODY
The function f takes one argument, and returns a heap-allocated lambda.  If E is cheap (say just a constructor) it might well be more efficient to transform to
	f = \xz. let y = E in BODY

Pattern matching is another example, and GHC indeed eta expands through that by default, if it makes two lambdas into one.

To switch it off try -fno-do-lambda-eta-expansion.

Simon


| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Roman Cheplyaka
| Sent: 04 October 2011 07:40
| To: glasgow-haskell-users at haskell.org
| Subject: Unwanted eta-expansion
| 
| Suppose I want a foldl which is evaluated many times on the same
| list but with different folding functions.
| 
| I would write something like this, to perform pattern-matching on the
| list only once:
| 
|     module F where
|     myFoldl :: [a] -> (b -> a -> b) -> b -> b
|     myFoldl [] = \f a -> a
|     myFoldl (x:xs) = let y = myFoldl xs in \f a -> y f (f a x)
| 
| However, for some reason GHC eta-expands it back. Here's what I see in
| the core:
| 
|   % ghc -O2 -ddump-simpl -fforce-recomp -dsuppress-module-prefixes \
|     -dsuppress-uniques -dsuppress-coercions F.hs
| 
|     ==================== Tidy Core ====================
|     Rec {
|     myFoldl [Occ=LoopBreaker]
|       :: forall a b. [a] -> (b -> a -> b) -> b -> b
|     [GblId, Arity=3, Caf=NoCafRefs, Str=DmdType SLL]
|     myFoldl =
|       \ (@ a) (@ b) (ds :: [a]) (eta :: b -> a -> b) (eta1 :: b) ->
|         case ds of _ {
|           [] -> eta1; : x xs -> myFoldl @ a @ b xs eta (eta eta1 x)
|         }
|     end Rec }
| 
| Why does it happen and can it be suppressed?
| 
| This is GHC 7.0.4.
| 
| 
| --
| Roman I. Cheplyaka :: http://ro-che.info/
| 
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list