[Haskell-cafe] Can this be made to fuse?

David Feuer david.feuer at gmail.com
Thu Sep 22 20:09:51 UTC 2022


sequence never helps anyone with anything, optimization-wise. I should
double check that I wasn't working in a weird compilation environment or
something when I checked the most recent version. GHC doesn't like to fire
rules that might duplicate work, and Q may well be too general on the
inside for the compiler to be able to tell. Do those Q things *ever* get
specialized? If so, to what, and when?

On Thu, Sep 22, 2022, 3:12 PM Joachim Breitner <mail at joachim-breitner.de>
wrote:

> A simple composition of a pure [Type] -> Type function, fmap'ped and
> Control.Monad.sequence is not going to help, is it? At least the sequence
> might fuse with a producer, not sure if the fmap then gets in the way to
> fuse with the pure function though.
>
> 22.09.2022 20:14:20 David Feuer <david.feuer at gmail.com>:
>
> The recursion is the first barrier. The whole thing ends up a loop
> breaker. Using `fix` fixes that, but it still doesn't fuse for some reason.
> After I sent this, I realized that foldl' is really the wrong thing, since
> that builds up a large Q action that, when run, produces the expression.
> The nicer thing is to use foldM within Q, and wrap mfix around that. I'm
> still not seeing fusion with that, and I wonder if that's because of the
> complexity of the Q type with its higher-rank constrained polymorphism and
> such.
>
> On Thu, Sep 22, 2022, 1:56 PM Joachim Breitner <mail at joachim-breitner.de>
> wrote:
>
>> Hi,
>>
>> Am Sonntag, dem 11.09.2022 um 19:05 -0400 schrieb David Feuer:
>> > The template-haskell package has functions `tupE` and `tupP` for
>> > building tuple expressions and patterns, respectively, but nothing
>> > really similar for building tuple types. I came up with the version
>> > below the other day:
>> >
>> > -- | Given a list of types, produce the type of a tuple of
>> > -- those types. This is analogous to 'tupE' and 'tupP'.
>> > --
>> > -- @
>> > -- tupT [[t|Int|], [t|Char|], [t|Bool]] = [t| (Int, Char, Bool) |]
>> > -- @
>> > tupT :: [Q Type] -> Q Type
>> > tupT ts = n `seq` res
>> >   where
>> >     -- We build the expression with a thunk inside that will be filled
>> in with
>> >     -- the length of the list once that's been determined. This works
>> >     -- efficiently (in one pass) because TH.Type is rather lazy.
>> >     (res, n) = foldl' (\(acc, !k) ty -> ([t| $acc $ty |], k + 1))
>> >                       (tupleT n, 0)
>> >                       ts
>> >
>> > I strongly suspect this is quite fast enough in practice, but it's a
>> > bit annoying that it won't participate in list fusion; tupT (map f xs)
>> > will (lazily) generate an intermediate list. I wasn't able to convince
>> > GHC to fuse it, short of a custom rewrite rule or two (tupT (build f)
>> > = ..., tupT (augment f r = ...). Does anyone know if it's possible?
>>
>> Can you say why it would not fuse? It seems it could, if tupT inlines,
>> and then you have foldl' applied to (map f xs), and at this point I
>> would hope that fusion kicks in.
>>
>> Cheers,
>> Joachim
>>
>> --
>> Joachim Breitner
>>   mail at joachim-breitner.de
>>   http://www.joachim-breitner.de/
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20220922/b1f60d51/attachment.html>


More information about the Haskell-Cafe mailing list