foldl laziness support. Reply
Serge D. Mechveliani
mechvel at botik.ru
Mon Oct 16 06:23:36 EDT 2006
Concerning the laziness support problem,
I thank people for explanations about foldl and foldr.
>> I wonder how to avoid these numerous cost pitfalls.
>> Maybe, the complier could do more optimization?
Duncan Coutts <duncan.coutts at worc.ox.ac.uk> writes
> There are important differences between foldl, foldl' and foldr. It is
> quite important to choose the right one. I don't think this can be done
> automatically.
>
> In my experience, the choice is almost always between foldl' and foldr.
>
> [..]
I do not see foldl' in the standard library.
Is it of the GHC lib extension? has it strictness annotation?
> So as Lemmih says, in this case you want to use foldr:
>
> import List (union)
> main = let n = 10^4 :: Int
> in
> putStr
> (shows (take 2 $ unionMany [[1 .. i] | i <- [1 .. n]]) "\n")
>
> unionMany = foldr union []
I see. Thank you.
I have impression that something is here besides the intuition for the
foldl/foldr choice.
Here is a contrived example which is more close to my real situation.
-----------------------------------------------------------------
import qualified Data.Set as Set (Set(..), empty, member, insert)
import List (union, find)
main = let n = 10^6 :: Int in putStr (shows (g1 n) "\n")
f :: Int -> (Set.Set Int, [Int])
f n =
-- original version, I write so because it is easy to program
--
foldl add (Set.empty, []) [[1 .. i] | i <- [1 .. n]]
where
add (s, xs) ys = (Set.insert (sum xs) s, union xs ys)
{- attempt to optimize (fails)
--
h (Set.empty, []) [[1 .. i] | i <- [1 .. n]]
where
h (s, xs) [] = (s, xs)
h (s, xs) (ys: yss) = h (Set.insert (sum xs) s, union xs ys) yss
-}
g1, g2 :: Int -> Bool -- client functions
g1 n = case snd $ f n of x: _ -> even x
_ -> False
g2 n = let (set, xs) = f n
in
case find (> 100) xs of Just x -> Set.member (2*x) set
_ -> False
-----------------------------------------------------------------
Evidently, g1 n must have the cost of O(1).
But in ghc-6.6 -O, it has O(n).
How to improve f ? I tried foldr, and failed.
The situation is so that some clients are as g1, and others are as
g2, and, at least, g1 must be O(1).
Regards,
-----------------
Serge Mechveliani
mechvel at botik.ru
More information about the Glasgow-haskell-users
mailing list