
Dear all, I wonder why haskell do not take foldl' as default foldl if foldl is not used in production often. I was told that because foldl is lazy evaluated. I know what the advantage of lazy evaluation: do not evaluate the expression which is not needed to, and can work on infinite list. Can you give me a example about how foldl can work on an infinite list? Thanks. Best regards, Zhi-Qiang Lei zhiqiang.lei@gmail.com

On Jun 14, 2011, at 10:01 PM, Zhi-Qiang Lei wrote:
I wonder why haskell do not take foldl' as default foldl if foldl is not used in production often.
It would be quite interesting to grep over the ghc sources to find uses of foldl. ____________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

On Jun 14, 2011, at 8:16 PM, David Place wrote:
On Jun 14, 2011, at 10:01 PM, Zhi-Qiang Lei wrote:
I wonder why haskell do not take foldl' as default foldl if foldl is not used in production often.
It would be quite interesting to grep over the ghc sources to find uses of foldl.
From containers/Data/Tree.hs: -- takes a sequence (queue) of seeds -- produces a sequence (reversed queue) of trees of the same length unfoldForestQ :: Monad m => (b -> m (a, [b])) -> Seq b -> m (Seq (Tree a)) unfoldForestQ f aQ = case viewl aQ of EmptyL -> return empty a :< aQ' -> do (b, as) <- f a tQ <- unfoldForestQ f (Prelude.foldl (|>) aQ' as) let (tQ', ts) = splitOnto [] as tQ return (Node b ts <| tQ') where splitOnto :: [a'] -> [b'] -> Seq a' -> (Seq a', [a']) splitOnto as [] q = (q, as) splitOnto as (_:bs) q = case viewr q of q' :> a -> splitOnto (a:as) bs q' EmptyR -> error "unfoldForestQ" haskell2010/Array.hs: accum :: (Ix a) => (b -> c -> b) -> Array a b -> [(a,c)] -> Array a b accum f = foldl (\a (i,v) -> a // [(i,f (a!i) v)]) From pretty/Text/PrettyPrint/HughesPJ.hs: Version 3.0 28 May 1997 * Cured massive performance bug. If you write foldl <> empty (map (text.show) [1..10000]) you get quadratic behaviour with V2.0. Why? For just the same reason as you get quadratic behaviour with left-associated (++) chains. This is really bad news. One thing a pretty-printer abstraction should certainly guarantee is insensivity to associativity. It matters: suddenly GHC's compilation times went up by a factor of 100 when I switched to the new pretty printer. I fixed it with a bit of a hack (because I wanted to get GHC back on the road). I added two new constructors to the Doc type, Above and Beside: <> = Beside $$ = Above Then, where I need to get to a "TextBeside" or "NilAbove" form I "force" the Doc to squeeze out these suspended calls to Beside and Above; but in so doing I re-associate. It's quite simple, but I'm not satisfied that I've done the best possible job. I'll send you the code if you are interested. From random/System/Random.hs {- If we cannot unravel the StdGen from a string, create one based on the string given. -} stdFromString :: String -> (StdGen, String) stdFromString s = (mkStdGen num, rest) where (cs, rest) = splitAt 6 s num = foldl (\a x -> x + 3 * a) 1 (map ord cs) time/Data/Time/Format/Parse.hs -- many instances

Zhi-Qiang Lei wrote:
I wonder why haskell do not take foldl' as default foldl if foldl is not used in production often.
In the Haskell standard, which is not tied to any particular compiler, foldl is defined in the simplest way. The problem of stack overflows is left to be solved by each compiler. And in fact, with optimization turned on, GHC does figure out the right thing to do in many of the common cases. That is the history and the logic; but I agree with you that it would have made more sense for what we call foldl' to have been the default.
Can you give me a example about how foldl can work on an infinite list?
Prelude Data.List> foldl (const last) 0 [[3..], [7,8,9]]
9
Prelude Data.List> foldl' (const last) 0 [[3..], [7,8,9]]
participants (4)
-
David Place
-
Sean Perry
-
Yitzchak Gale
-
Zhi-Qiang Lei