Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-24 Thread Ben
On the test case i'm running the performance impacts of reversing the return list are negligible: mapM3 :: Monad m => (a -> m b) -> [a] -> m [b] {-# INLINE mapM3 #-} mapM3 fn lst = mapM3accum fn lst [] where mapM3accum _ [] accum = return $ reverse accum mapM3accum fn (x:xs) accum =

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-24 Thread Luke Palmer
On Thu, Apr 24, 2008 at 11:28 PM, Ben <[EMAIL PROTECTED]> wrote: > 2) Is there a reason to not use mapM3 above? Yes, there certainly is. mapM3 is not equivalent to mapM; it is too strict: *Main> take 3 $ head $ mapM return [1,2,3,4,undefined] [1,2,3] *Main> take 3 $ head $ mapM3 return [1,2,3,4

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-24 Thread Ben
Luke, Thanks for the nice answer. So maybe I'll give mapM3 the name mapM' and put it in my personal library. But I'm still a bit curious about the performance profile of mapM. The profiler is telling me they're allocating around the same amount of memory, so I am not clear what is making it slow

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-24 Thread Luke Palmer
On Fri, Apr 25, 2008 at 12:02 AM, Ben <[EMAIL PROTECTED]> wrote: > Luke, > > Thanks for the nice answer. So maybe I'll give mapM3 the name mapM' > and put it in my personal library. Except the answer was wrong. I forgot the reverse in my implementation, so that undefined we were seeing was jus

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-24 Thread Niklas Broberg
> > 2) Is there a reason to not use mapM3 above? > > Yes, there certainly is. mapM3 is not equivalent to mapM; it is too strict: > > *Main> take 3 $ head $ mapM return [1,2,3,4,undefined] > [1,2,3] > *Main> take 3 $ head $ mapM3 return [1,2,3,4,undefined] > [*** Exception: Prelude.undefined

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-24 Thread Don Stewart
niklas.broberg: > > > 2) Is there a reason to not use mapM3 above? > > > > Yes, there certainly is. mapM3 is not equivalent to mapM; it is too strict: > > > > *Main> take 3 $ head $ mapM return [1,2,3,4,undefined] > > [1,2,3] > > *Main> take 3 $ head $ mapM3 return [1,2,3,4,undefined] > > [*

RE: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-25 Thread Simon Peyton-Jones
| 1) Why is the Prelude mapM so slow? It seems like running 10x slower | than mapM_ when generating only 50,000 return values is a problem. All this does seem odd. I've submitted a ticket so we don't forget it http://hackage.haskell.org/trac/ghc/ticket/2236 It appears to be some bad (possibly

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-25 Thread Chaddaï Fouché
2008/4/25, Niklas Broberg <[EMAIL PROTECTED]>: > Wow. A 10x slowdown for a very commonly used function that in 99.8% of > all use cases has no need for the extra laziness at all. No wonder > some people say Haskell is a toy language... > A toy language that is still much faster than many current

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-25 Thread Niklas Broberg
> > Wow. A 10x slowdown for a very commonly used function that in 99.8% of > > all use cases has no need for the extra laziness at all. No wonder > > some people say Haskell is a toy language... > > A toy language that is still much faster than many currently popular > languages so... Is Ruby/

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-26 Thread Neil Mitchell
Hi > I didn't say I agree, I most certainly don't. What I meant with my > comment was that a slowdown of 10x, just to preserve laziness, is > perfect fuel for those who claim that laziness is good in theory but > bad in practice. A bad implementation of laziness will always be slower than a ba