Data.Foldable causes missed foldr/build opportunities
Gabriel Gonzalez
gabriel439 at gmail.com
Thu Jul 25 20:32:36 CEST 2013
On 07/25/2013 11:22 AM, Edward Kmett wrote:
> In your case here mapM_ f would turn into Foldable.foldr ((>>) . f)
> (return ()) if it were to inline (which it isn't set up to do) rather
> than into Control.Monad.mapM_. Once it became Foldable.foldr it'd get
> stuck on the way to becoming GHC.List.foldr and then to fusion by the
> fact that we don't inline the members of the Foldable [] instance.
>
> As an aside, it is interesting that in
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Traversable.html#Traversable the
> traverse is INLINE'd but not the mapM, though it is irrelevant to your
> issue here, it is another thing that would likely be impacted.
>
> So there appears to be at least two obstacles in the way of this
> fusing away properly, and yet another in the way of normal mapM fusing.
>
> Some of this could be mitigated by rephrasing the foldr/build rule
> directly in terms of Foldable.foldr where it'd only typecheck if
> applied to a [] anyways, but it does look like a serious look will
> have to be made at what gets inlined as we proceed to investigate how
> to get this to work right.
>
If I understand what you are saying then I tried something similar to
this, too, where I provided a rewrite rule that would only rewrite if it
type-checked:
_each :: (Monad m) => [a] -> Producer a m ()
_each = Prelude.mapM_ yield
{-# RULES "_each" each = _each #-}
If I do this GHC spits out a big internal debug message when I compile
it. It does compile successfully, but it doesn't work and that rewrite
rule does not fire.
I think the most reliable way will just be making sure that there is a
clear chain of INLINEs all the way down.
> -Edward
>
> On Thu, Jul 25, 2013 at 1:55 PM, Gabriel Gonzalez
> <gabriel439 at gmail.com <mailto:gabriel439 at gmail.com>> wrote:
>
>
> On 07/25/2013 10:41 AM, Edward Kmett wrote:
>> One of the open concerns about it is definitely ensuring that we
>> get the fusion opportunities we can.
>>
>> If you put an INLINE pragma on your Foldable version of each do
>> the fusion rules fire after it gets inlined into a call site that
>> uses it as a list?
>>
>
> I tried both INLINE and INLINABLE and neither causes the fusion
> rules to fire. I also tried:
>
> * adding an orphan SPECIALIZE rule for `Data.Foldable.mapM_` in
> the module where I defined `each`
>
> * Specializing the type of `each` to consume lists, but still
> using the `Foldable` `mapM_`
>
> * Defining a new copy of `each` (using the `Foldable` version) in
> the same module as the code that uses it, specializing the type
> signature to lists, and trying out INLINE/INLINABLE or no pragma.
>
> None of those causes the rule to fire, either.
>
>
>> -Edward
>>
>> On Thu, Jul 25, 2013 at 1:22 PM, Gabriel Gonzalez
>> <gabriel439 at gmail.com <mailto:gabriel439 at gmail.com>> wrote:
>>
>> I'm now in favor of the `Data.Foldable` proposal, but I just
>> wanted to mention that the proposal needs to include some
>> extra pragma work to ensure that build/foldr optimizations
>> fire. I was just experimenting with the following combinator
>> for `pipes` trying out the following two versions:
>>
>> each :: (Monad m) => [a] -> Producer a m ()
>> each = mapM yield
>>
>> each :: (Monad m, Foldable f) => f a -> Producer a m ()
>> each = Data.Foldable.mapM yield
>>
>> When I do a pure `pipes`-based fold over both `Producers`s,
>> the version specialized to lists triggers a firing of the
>> build/foldr fusion rule and runs about 20% faster. The true
>> improvement for `mapM` by itself is probably even greater
>> than that because I haven't optimized the folding code yet.
>> The latter version does not trigger the rule firing. Either
>> way I'm going to include the latter `Foldable` version but I
>> just wanted to mention this because I remember people were
>> asking if this would impact fusion or not.
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org <mailto:Libraries at haskell.org>
>> http://www.haskell.org/mailman/listinfo/libraries
>>
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20130725/94de6ef9/attachment.htm>
More information about the Libraries
mailing list