Kevin Atkinson wrote:
> 
> Even though it is possible to define foldl with foldr or vis versa it
> (with the current implantation of Haskell with ghc) not nearly as
> efficient.  To demonstrate this consider folding of a range.
> 
> import System
> 
> foldR f i (a,z) = g a
>     where g a | a == z    = i
>               | otherwise = f a (g (a+1))
> 
> foldL f v (a,z) = g v a
>     where g v a | a == z    = v
>                 | otherwise = g (f v a) (a+1)

After playing with it a little I released that these folds will not
include the last number in the range.  Well I never documented what they
did so consider it part of the desired behavior ;)

> 
> foldL2 f z l = foldR (\ a h -> \ b -> h (b `f` a)) id l z
> 
> foldR2 f z l = foldL (\ h a -> \ b -> h (a `f` b)) id l z
> 
> main = do (c:_) <- getArgs
>           let zero  = 0::Double  -- Will overflow with Int, and Integer
>                                  -- are not nearly as efficient
>               range = (0,100000)
>           case c of
>            "L"  -> print$ foldL  (+) zero range
>            "R"  -> print$ foldR  (+) zero range
>            "L2" -> print$ foldL2 (+) zero range
>            "R2" -> print$ foldR2 (+) zero range
> 
> ghc -O Main.hs
> ./a.out ? +RTS -sstderr -K4m
> 
>   Total Time  Allocated on Heap  GC   Memory
> L   0.02 s        10,132        0.0%    1 Mb
> R   0.17       1,214,356       41.2%    5 Mb
> L2  1.07       6,014,868       50.5%   11 Mb
> R2  1.19       4,409,236       61.3%   13 Mb
> 
> ./a.out R2 +RTS -sstderr -K4m -A10m
> 
>   Total Time  Allocated on Heap  GC   Memory
> L   0.02 s        same          0.0%   10 Mb
> R   0.12 s        same          0.0%   14 Mb
> L2  0.41 s        same          0.0%   18 Mb
> R2  0.38 s        same          0.0%   18 Mb
> 
> (I chose the best time from several tries)
> 
> As you can see when I defined one in terms of the other I suffered a
> serious performance lost, both in memory and speed.
> 
> As expected the direct foldL is the fastest because it is done in
> constant space.  The foldR has to build up a stack however it is fairly
> efficient.  The foldL2 I believe is building up both a stack and a huge
> lambda expression thus is horribly inefficient compared to foldL.  The
> foldR2 essentially does the same thing that foldR does however it is
> building up a huge lambda expression rather than a stack and thus is not
> nearly as efficient.  However, with proper Optimization I imagine that
> foldR2 could be as efficient as foldR.  I don't know about foldL2
> though.
> 
> --
> Kevin Atkinson
> [EMAIL PROTECTED]
> http://metalab.unc.edu/kevina/

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/


Reply via email to