[Haskell-cafe] {Probable Spam} transformers appears to benefit from more inline

David Sorokin david.sorokin at gmail.com
Tue Feb 16 12:24:18 UTC 2016


Ross,

In the past I noticed a very similar thing, but only I prefer using the INLINABLE pragma with monad transformers, for the INLINE pragma may lead to the performance degradation in some cases.

Thanks,
David

> 16 февр. 2016 г., в 14:11, Ross Paterson <R.Paterson at city.ac.uk> написал(а):
> 
> On Sun, Jan 24, 2016 at 06:21:38PM +0000, Oliver Charles wrote:
>> I've tried to put some fairly extensive benchmarks in place, which you can find
>> at https://github.com/ocharles/monad-yield. In that repository is a README.md
>> file that describes how I have been performing these benchmarks. The benchmarks
>> are defined over a common interface that each implementation of MonadYield
>> exports. The benchmarks are defined in "Benchmarks.hs", and the three
>> implementations are "Transformers.hs" (using transformers from GHC),
>> "TransformersInline.hs" (using transformers-ocharles from that repository,
>> which has many more INLINE pragmas) and "Inline.hs" (which doesn't depend on
>> anything other than base).
>> 
>> There are three main benchmarks that are ran - one is benchmarking essentially
>> the cost of ReaderT, the next the cost of StateT, and the last a composition of
>> ReaderT over StateT over ReaderT. The results of the benchmark can be found
>> here: https://ocharles.github.io/monad-yield/.
>> 
>> It seems that the current darcs release of transformers loses every time, but
>> if I sprinkle {-# INLINE #-} across the definition of lazy state, I get
>> identical performance to just writing out the lazy state monad by hand.
>> 
>> I was very surprised to see that I have to pay when I use transformers, and it
>> seems like this cost can be removed at the cost of slightly larger interface
>> files.
>> 
>> Before I submit a patch, I'd love to hear others thoughts. Should {-# INLINE #
>> -} be necessary? Is there any reason not to add it to every symbol in
>> transformers?
> 
> Thanks for this analysis.  I've now added INLINE to just about everything,
> per your suggestion.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list