Constant functions and selectors make for interesting arguments

David Feuer david at well-typed.com
Mon Jan 30 21:41:31 UTC 2017


Here's an example:

data Tree a = Bin (Tree a) a (Tree a) | Tip deriving Functor

{-# NOINLINE replace #-}
replace :: a -> Tree b -> Tree a
replace x t = x <$ t

When I compile this with -O2, I get

Rec {
-- RHS size: {terms: 18, types: 21, coercions: 0}
$fFunctorTree_$cfmap
  :: forall a_ar2 b_ar3. (a_ar2 -> b_ar3) -> Tree a_ar2 -> Tree b_ar3
$fFunctorTree_$cfmap =
  \ (@ a_aGb)
    (@ b_aGc)
    (f_aFH :: a_aGb -> b_aGc)
    (ds_dGN :: Tree a_aGb) ->
    case ds_dGN of _ {
      Bin a1_aFI a2_aFJ a3_aFK ->
        Bin
          ($fFunctorTree_$cfmap f_aFH a1_aFI)
          (f_aFH a2_aFJ)
          ($fFunctorTree_$cfmap f_aFH a3_aFK);
      Tip -> Tip
    }
end Rec }

$fFunctorTree_$c<$
  :: forall a_ar4 b_ar5. a_ar4 -> Tree b_ar5 -> Tree a_ar4
$fFunctorTree_$c<$ =
  \ (@ a_aGQ) (@ b_aGR) (eta_aGS :: a_aGQ) (eta1_B1 :: Tree b_aGR) ->
    $fFunctorTree_$cfmap (\ _ -> eta_aGS) eta1_B1

replace :: forall a_aqt b_aqu. a_aqt -> Tree b_aqu -> Tree a_aqt
replace = $fFunctorTree_$c<$

This is no good at all, because replacing the values in the same tree over and 
over will build up a giant chain of thunks in each node carrying all the 
previous values. I suppose that inlining per se may not be quite enough to fix 
this problem, but I suspect there's some way to fix it. Fixing it in Functor 
deriving would be a start (I can look into that), but fixing it in user code 
would be quite good too.

On Monday, January 30, 2017 9:01:34 PM EST Simon Peyton Jones via ghc-devs 
wrote:
> Functions whose body is no bigger (by the inliner’s metrics) than the call
> are always inlined vigorously.   So (\.....-> k) replaces a call by a
> single variable.  GHC will do that a lot.
 
> These ideas are best backed by use-cases where something good is not
> happening.   Do you have some?
 
> Simon
> 
> From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of David
> Feuer
 Sent: 27 January 2017 16:42
> To: ghc-devs <ghc-devs at haskell.org>
> Subject: Constant functions and selectors make for interesting arguments
> 
> GHC's inliner has a notion of "interesting argument" it uses to encourage
> inlining of functions called with (I think) dictionary arguments. I think
> another class of argument is very interesting, by being very boring. Any
> argument that looks like either
 
> \ _ ... (Con _ ... x ... _ ) ... _ -> coerce x
> 
> or
> 
> \ _ ... _ -> k
> 
> Has a pretty good chance of doing a lot of good when inlined, perhaps
> plugging a space leak. Would it make sense to try to identify such
> functions and consider them interesting for inlining?




More information about the ghc-devs mailing list