[Haskell-cafe] Proposal: (.:) operator in base.

Tom Ellis tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Tue Aug 23 09:22:13 UTC 2016


*Very* interesting.  Here is the key section of the GHC users guide:

    GHC will only inline the function if it is fully applied, where “fully
    applied” means applied to as many arguments as appear (syntactically) on
    the LHS of the function definition

That this is a good heuristic is *extremely* counterintuitive to me.  I
would have supposed that being more explicit, for example

    {-# INLINE (.) f g #-}

to inline on all static applications of at least two arguments would have
been a much clearer way to communicate this message.

What's the rationale behind the current behaviour?

Tom


On Tue, Aug 23, 2016 at 09:56:25AM +0100, Matthew Pickering wrote:
> I think the point which no-one has articulated yet is that the
> source-level arity of (.) affects whether GHC will decide to inline it. 
>
> Only fully saturated applications are inlined
[...]
> 
> On Tue, Aug 23, 2016 at 8:33 AM, Tom Ellis
> <tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote:
> > On the contrary, they're exactly the same (on GHC 7.6.3):
> >
> >     module Foo where
> >
> >     comp1 f g x = f (g x)
> >
> >     comp2 f g = \x -> f (g x)
> >
> >
> >     % ghc -O0 -dsuppress-all -fforce-recomp -no-link -ddump-prep test.hs
> >     [1 of 1] Compiling Foo              ( test.hs, test.o )
> >
> >     ==================== CorePrep ====================
> >     Result size of CorePrep = {terms: 24, types: 36, coercions: 0}
> >
> >     comp2
> >     comp2 =
> >       \ @ t_aeU @ t1_aeV @ t2_aeW f_sfz g_sfy x_sfx ->
> >         let {
> >           sat_sfI
> >           sat_sfI = g_sfy x_sfx } in
> >         f_sfz sat_sfI
> >
> >     comp1
> >     comp1 =
> >       \ @ t_af5 @ t1_af6 @ t2_af7 f_sfG g_sfF x_sfE ->
> >         let {
> >           sat_sfJ
> >           sat_sfJ = g_sfF x_sfE } in
> >         f_sfG sat_sfJ
> >
> > (the same holds for -O2, if you compile them separately)
> >
> > On Tue, Aug 23, 2016 at 05:19:38PM +1000, Ben wrote:
> >> At the semantic level of "does my program compute correct results" they're
> >> identical.  At the operational level of "how fast does my program run"
> >> they're different.
> >>
> >>
> >> On August 23, 2016 5:09:19 PM GMT+10:00, Tom Ellis <tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote:
> >> >On Mon, Aug 22, 2016 at 10:23:07PM -0700, wren romano wrote:
> >> >>     (.) f g = \x -> f (g x)
> >> >>
> >> >> vs:
> >> >>
> >> >>     (.) f g x = f (g x)
> >> >>
> >> >> has ramifications, though it's fairly easy to guess which one of
> >> >those
> >> >> two will be most performant.
> >> >
> >> >Are these not synonyms?  What is the meaning of
> >> >
> >> >    fargs var = expr
> >> >
> >> >if not
> >> >
> >> >    fargs = \var -> expr
> >> >
> >> >?


More information about the Haskell-Cafe mailing list