darcs patch: Improve Control.Monad.filterM:
Chris Kuklewicz
haskell at list.mightyreason.com
Tue Aug 8 08:37:46 EDT 2006
Simon Marlow wrote:
> Spencer Janssen wrote:
>> Fri Aug 4 13:49:57 CDT 2006 Spencer Janssen <sjanssen at cse.unl.edu>
>> * Improve Control.Monad.filterM:
>> * filterM is defined in terms of foldr, making it a good consumer
>> in GHC's fusion framework
>> * filterM uses linear stack space with respect to the number of
>> items that the predicate returns true, rather than the total
>> number of elements in the input.
> ...
>> hunk ./Control/Monad.hs 151
>> -filterM _ [] = return []
>> -filterM p (x:xs) = do
>> - flg <- p x
>> - ys <- filterM p xs
>> - return (if flg then x:ys else ys)
>> +filterM p = foldr f (return [])
>> + where + f x xs = do
>> + flg <- p x
>> + if flg
>> + then xs >>= return . (x:)
>> + else xs
>> }
>
> The new definition looks less lazy than the original, so it's not a drop-in
> replacement. Also, we would need some measurements to test whether this
> version
> doesn't lose efficiency - it probably fuses better, but might be slower
> when it
> doesn't fuse. Rules to turn the foldr version back into the recursive
> version
> might be needed (or aggressive inlining).
>
> Cheers,
> Simon
>
The new one looks better to me. But the foldr is not needed:
filterM _ [] = return []
filterM p (x:xs) = do
flg <- p x
if flg
then do ys <- filterM p xs
return (x:ys)
else filterM p xs
The above filterM differs from the original in when the garbage collector will
be able to collect "x". It looks like the original had to hold onto "x" while
"ys" was being computed. The version above looks like it can discard "x" as
soon as the else branch is chosen.
--
Chris
More information about the Libraries
mailing list