
Hi, all When I fold a list to update Data.Array, memory usage is very high. Consider following source, which counts occurence of each element in a list (1): import Data.Array import Data.List import Control.DeepSeq go :: [Int] -> [Int] go = elems . foldl' update (array (0,99) [(i,0) | i <- [0..99]]) where update acc x = acc // [(x, acc ! x + 1)] main = putStrLn . unwords . map show . go . concat . replicate 5000 $ [0..99] Above program uses about 350MB at heap. Memory usage is same if I try to force strictness in array update with `seq` (2) : where update acc x = let v = acc ! x + 1 a' = acc // [(x,v `seq` v)] in a' `seq` a' However, when I use `deepseq`, memory usage is gone (around 35Kbyte) (3): where update acc x = let v = acc ! x + 1 a' = acc // [(x,v `seq` v)] in a' `deepseq` a' What's the missing part in (2)? At (2), evaluation of updated array a' is forced and the value of array cell is also evaluated forcefully with `seq`. Any help would be appreciated deeply. -- Regards, Chul-Woong Yang

Immutable array update creates a new array for each call to update (//),
thus if you need frequent update, it is recommended to use MArray (such as
ST or IO variant) instead.
i.e: the loop can be rewrite as:
update_ u x = readArray u x >>= \old -> writeArray u x (1+old)
array100 = runSTUArray $ do
stu <- newArray (0, 99) 0 :: ST s (STUArray s Int Int)
mapM_ (update_ stu) (concat . replicate 5000 $ [0..99])
return stu
- baojun
On Tue, Apr 26, 2016 at 4:53 PM Chul-Woong Yang
Hi, all
When I fold a list to update Data.Array, memory usage is very high. Consider following source, which counts occurence of each element in a list (1):
import Data.Array import Data.List import Control.DeepSeq go :: [Int] -> [Int] go = elems . foldl' update (array (0,99) [(i,0) | i <- [0..99]]) where update acc x = acc // [(x, acc ! x + 1)] main = putStrLn . unwords . map show . go . concat . replicate 5000 $ [0..99]
Above program uses about 350MB at heap. Memory usage is same if I try to force strictness in array update with `seq` (2) :
where update acc x = let v = acc ! x + 1 a' = acc // [(x,v `seq` v)] in a' `seq` a'
However, when I use `deepseq`, memory usage is gone (around 35Kbyte) (3):
where update acc x = let v = acc ! x + 1 a' = acc // [(x,v `seq` v)] in a' `deepseq` a'
What's the missing part in (2)? At (2), evaluation of updated array a' is forced and the value of array cell is also evaluated forcefully with `seq`.
Any help would be appreciated deeply. -- Regards, Chul-Woong Yang _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Thank you for your answer.
I'll look into MArray.
However, I want to know whether `seq` forces evaluation
of array update (//) or not.
My prior experimen shows that `deepseq` forces evaluation
while `seq` does not force. Is it right?
And, is there no way to force evaluation of array update
with `seq`?
2016-04-27 15:12 GMT+09:00 Baojun Wang
Immutable array update creates a new array for each call to update (//), thus if you need frequent update, it is recommended to use MArray (such as ST or IO variant) instead.
i.e: the loop can be rewrite as:
update_ u x = readArray u x >>= \old -> writeArray u x (1+old) array100 = runSTUArray $ do stu <- newArray (0, 99) 0 :: ST s (STUArray s Int Int) mapM_ (update_ stu) (concat . replicate 5000 $ [0..99]) return stu
- baojun
On Tue, Apr 26, 2016 at 4:53 PM Chul-Woong Yang
wrote: Hi, all
When I fold a list to update Data.Array, memory usage is very high. Consider following source, which counts occurence of each element in a list (1):
import Data.Array import Data.List import Control.DeepSeq go :: [Int] -> [Int] go = elems . foldl' update (array (0,99) [(i,0) | i <- [0..99]]) where update acc x = acc // [(x, acc ! x + 1)] main = putStrLn . unwords . map show . go . concat . replicate 5000 $ [0..99]
Above program uses about 350MB at heap. Memory usage is same if I try to force strictness in array update with `seq` (2) :
where update acc x = let v = acc ! x + 1 a' = acc // [(x,v `seq` v)] in a' `seq` a'
However, when I use `deepseq`, memory usage is gone (around 35Kbyte) (3):
where update acc x = let v = acc ! x + 1 a' = acc // [(x,v `seq` v)] in a' `deepseq` a'
What's the missing part in (2)? At (2), evaluation of updated array a' is forced and the value of array cell is also evaluated forcefully with `seq`.
Any help would be appreciated deeply. -- Regards, Chul-Woong Yang _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

seq only force to WHNF (https://wiki.haskell.org/Weak_head_normal_form),
while deepseq could force elements in the data structure (hence the name)
list1 :: [Int]
list1 = [undefined]
list1' = length (list1 `seq` list1) -- OK
list1'' = length (list1 `deepseq` list1) -- error
I'd expect something similar happened in IArray.
On Tue, Apr 26, 2016 at 11:36 PM Chul-Woong Yang
Thank you for your answer. I'll look into MArray.
However, I want to know whether `seq` forces evaluation of array update (//) or not. My prior experimen shows that `deepseq` forces evaluation while `seq` does not force. Is it right? And, is there no way to force evaluation of array update with `seq`?
2016-04-27 15:12 GMT+09:00 Baojun Wang
: Immutable array update creates a new array for each call to update (//), thus if you need frequent update, it is recommended to use MArray (such as ST or IO variant) instead.
i.e: the loop can be rewrite as:
update_ u x = readArray u x >>= \old -> writeArray u x (1+old) array100 = runSTUArray $ do stu <- newArray (0, 99) 0 :: ST s (STUArray s Int Int) mapM_ (update_ stu) (concat . replicate 5000 $ [0..99]) return stu
- baojun
On Tue, Apr 26, 2016 at 4:53 PM Chul-Woong Yang
wrote: Hi, all
When I fold a list to update Data.Array, memory usage is very high. Consider following source, which counts occurence of each element in a list (1):
import Data.Array import Data.List import Control.DeepSeq go :: [Int] -> [Int] go = elems . foldl' update (array (0,99) [(i,0) | i <- [0..99]]) where update acc x = acc // [(x, acc ! x + 1)] main = putStrLn . unwords . map show . go . concat . replicate 5000 $ [0..99]
Above program uses about 350MB at heap. Memory usage is same if I try to force strictness in array update with `seq` (2) :
where update acc x = let v = acc ! x + 1 a' = acc // [(x,v `seq` v)] in a' `seq` a'
However, when I use `deepseq`, memory usage is gone (around 35Kbyte) (3):
where update acc x = let v = acc ! x + 1 a' = acc // [(x,v `seq` v)] in a' `deepseq` a'
What's the missing part in (2)? At (2), evaluation of updated array a' is forced and the value of array cell is also evaluated forcefully with `seq`.
Any help would be appreciated deeply. -- Regards, Chul-Woong Yang _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (2)
-
Baojun Wang
-
Chul-Woong Yang