[Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

Andrea Vezzosi sanzhiyan at gmail.com
Wed May 12 09:02:39 EDT 2010


On Wed, May 12, 2010 at 7:50 AM, wren ng thornton <wren at freegeek.org> wrote:
> wren ng thornton wrote:
>>
>> Here's one big difference:
>>
>>>> newtype ErrCPS e m a = ErrCPS { runErrCPS ::
>>>>    forall r . (e -> m r) --  error handler
>>>>    -> (a -> m r) --  success handler
>>>>    -> m r }
>>
>> The analogous version I use is:
>>
>>    newtype MaybeCPS a = MaybeCPS
>>        (forall r. (a -> Maybe r) -> Maybe r)
>>
>> While I also offer a transformer version of MaybeCPS, the transformer
>> *does* suffer from significant slowdown. Also, for MaybeCPS it's better to
>> leave the handlers inline in client code rather than to abstract them out;
>> that helps to keep things concrete. So perhaps you should first try a direct
>> CPS translation:
>>
>>    newtype ErrCPS e a = ErrCPS
>>        (forall r. (a -> Either e r) -> Either e r)
>>
>>    runErrCPS :: ErrCPS e a -> Either e a
>>    runErrCPS (ErrCPS f) = f return
>>
>> I'd be curious if this version suffers the same slowdown.
>
>
> With this change [1] I can't notice any difference for your benchmark[2].
> Then again, all the runTest calls take 0 msec and I've had no luck making
> the computation take much time; perhaps your computer can detect a
> difference.

On my machine, with ghc-6.12.1, yours and the original ErrCPS give
quite similar results, both ~2x slower than Either.
However it's important to note that these results are highly dependent
on the monadic expressions being evaluated, with a different benchmark
you can get an huge speedup with the CPS versions.

mkEMA is in fact quite peculiar, since there's no catchError and the
throwError call is rarely (or never?) made, and thanks to foldM you
get that (>>=) is only used in a right associated way, which is the
ideal situation for Either.

In a larger program one might mix the two to get the best of both
worlds i guess, and maybe we can make a library where each combinator
from Control.Monad is reimplemented with the most fitting alternative
behind the scenes.

the nice part is that you can get the CPS version in a generic way
using Codensity:
http://hackage.haskell.org/packages/archive/mmtl/0.1/doc/html/Control-Monad-Codensity.html


> You may want to see what standard benchmarking tools like Microbench[3] or
> the magnificent Criterion[4] have to say. I'd do it myself, but I haven't
> had a chance to reinstall everything since getting my new computer (due to
> the installation issues on newer versions of OSX).
>
>
> [1]
> http://community.haskell.org/~wren/wren-extras/src/Control/Monad/ErrCPS.hs
>
> [2]
> http://community.haskell.org/~wren/wren-extras/test/Control/Monad/ErrCPS/MaxCantorBenchmark.hs
>
> [3] http://hackage.haskell.org/package/microbench
>
> [4] http://hackage.haskell.org/package/criterion
>
> --
> Live well,
> ~wren
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list