
Hello @ all, Sometimes one has an imperative algorithm, and wants to write a program in Haskell which do has the same effect... So the question is - how a construct as the following can efficiently be written? -- Pseudo code: n[1..10000] = false for (1..10000) |i| for (i,2*i..10000) |j| n[j] = not n[j] -- Certainly it is in this special case equivalent to (True where the index is): map (^2) [1..100] But I mean the destructive updates in the imperative code in Haskell without filling the (many times more than in imperative languages) memory with recursively called functions... The idea, I thought, is tail recursion, so perhaps I just have a big bug in my code, caused by the fact, that it needs even for 5000 approximately 100MB memory: -- import Data.Array main :: IO () main = putStr $! unlines $! map show $! filter snd $! zip [1..] $! elems $! calc $! la 5000 where la x = array (1,x) [(y,False)|y<-[1..x]] calc :: Array Int Bool -> Array Int Bool calc x = f 1 x where k :: Int k = snd $ bounds x f :: Int -> Array Int Bool -> Array Int Bool f !a !x | a < k = f (a+1) $! g a x | otherwise = g a x g !a !x = x//[(j,not (x!j))|j<-[a,a*2..k]] -- -- Thanks for you answers in advance H.

H.
Hello @ all,
Sometimes one has an imperative algorithm, and wants to write a program in Haskell which do has the same effect...
So the question is - how a construct as the following can efficiently be written?
-- Pseudo code: n[1..10000] = false for (1..10000) |i| for (i,2*i..10000) |j| n[j] = not n[j] --
Certainly it is in this special case equivalent to (True where the index is): map (^2) [1..100]
But I mean the destructive updates in the imperative code in Haskell without filling the (many times more than in imperative languages) memory with recursively called functions...
The idea in Haskell is not to think of stepping through the array. Look at accumArray and ixmap. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Jon Fairbairn
The idea in Haskell is not to think of stepping through the array. Look at accumArray and ixmap.
Thanks for your answer. But I can't really see how the calc-function can be written more efficiently with accumArray or ixmap, perhaps you can write it as an example? -- Regards, H.

H.
Jon Fairbairn
writes: The idea in Haskell is not to think of stepping through the array. Look at accumArray and ixmap.
Thanks for your answer.
But I can't really see how the calc-function can be written more efficiently with accumArray or ixmap, perhaps you can write it as an example?
Well, for your example, neither is needed since you could write something like: upb = 10000 listArray (1,upb) (repeat False) //map (\n->(2^n,True)) [1..floor (logBase 2 $ fromIntegral upb)] or a = listArray (1,upb) (repeat False) b = a//map (\n->(2^n,not (a!(2^n)))) [1..floor (logBase 2 $ fromIntegral upb)] but the first one is obviously better, so it depends on what you really want to do. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2007-05-07)

The key is letting haskell be lazy and produce the output one item at a time. My solution below generates a list of all indices to be inversed (with indices being duplicated as appropriate), then for each index in that list inverses the corresponding element in the array. The list can be written compactly using either list comprehensions or list monads. Using list monads:
listOfIndices ubound = [1..ubound] >>= \i -> [i,(2*i) .. ubound]
and using list comprehension and concatenation - slightly longer but probably more readable:
listOfIndices' ubound = concat [ [i,(2*i) .. ubound] | i <- [1..ubound] ]
const . not == (\x _ -> (not x)), i.e. a function that discards the second argument and returns the complement of the first.
calc ubound = accumArray (const.not) False (1,ubound) $ [(x,False) | x <- listOfIndices ubound]
zip [1..] (elems arr) == assocs arr putStrLn . unlines . map show ~~ mapM_ print
main = mapM_ print $ filter snd $ assocs $ calc 100000
This solution goes up to 100k in 25M of heap and up to 400k in 200M of heap. While working better, the space requirement seems to be (at least almost) quadratic, so this is probably not a complete solution to your problem (unless all you really needed was those 10k elements, or at most 400k).

"Simon Brenner"
The key is letting haskell be lazy and produce the output one item at a time.
True.
This solution goes up to 100k in 25M of heap and up to 400k in 200M of heap. While working better, the space requirement seems to be (at least almost) quadratic, so this is probably not a complete solution to your problem (unless all you really needed was those 10k elements, or at most 400k).
Hmmm... what were you testing? :m Data.Array Prelude Data.Array> let test upb = let a = listArray (1,upb) (repeat False) in a//map (\n->(2^n,not (a!(2^n)))) [1..floor (logBase 2 $ fromIntegral upb)] ! upb (0.02 secs, 1567316 bytes) Prelude Data.Array> test 100000 False (0.02 secs, 1310876 bytes) Prelude Data.Array> test 400000 False (0.09 secs, 3710792 bytes) Prelude Data.Array> test 800000 False (0.16 secs, 6913864 bytes) Prelude Data.Array> -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Simon Brenner
listOfIndices' ubound = concat [ [i,(2*i) .. ubound] | i <- [1..ubound] ] calc ubound = accumArray (const.not) False (1,ubound) $ [(x,False) | x <- listOfIndices ubound]
Thanks a lot! Your solution works fine as long as there are not to much modifications (you mentioned the memory...) -- accumArray ----------------------------------- 20 Mb total memory in use INIT time 0.02s ( 0.00s elapsed) MUT time 1.73s ( 1.81s elapsed) GC time 2.83s ( 2.86s elapsed) EXIT time 0.00s ( 0.01s elapsed) Total time 4.59s ( 4.68s elapsed) So I tried another possibility, STUArrays, which are significantly faster and use less memory: ------------------------------------------------- main = mapM_ print $ filter snd $ runST calc x = 100000 :: Int calc = do arr <- newArray (1,x) False :: ST s (STUArray s Int Bool) calc' arr d <- getAssocs arr return (d) where calc' arr = f 1 where f a | a < x = g a >> f (a+1) | otherwise = g a where g b | b <= x = readArray arr b >>= \i-> writeArray arr b (not i) >> g (b+a) | otherwise = return () ------------------------------------------------- (it is the first time I'm using this Type) -- STUArray ------------------------------------- 8 Mb total memory in use INIT time 0.01s ( 0.00s elapsed) MUT time 0.21s ( 0.28s elapsed) GC time 0.21s ( 0.21s elapsed) EXIT time 0.00s ( 0.01s elapsed) Total time 0.43s ( 0.49s elapsed) But 8MB seems still too much, how can it be further optimised? -- Best Regards and thanks for you answers in advance H.
participants (3)
-
H.
-
Jon Fairbairn
-
Simon Brenner