
I used what I thought, initially was an elegant contruction technique in Haskell. Something like this do ... sequence $ [ reffill b s | s <- [0..(fi temits)-1], b <- [0..(fi nc)-1]] ...(push list on to matrix stack)
Try the sequence_ (note the underscore) function, it should be a big win here. Cheers, Spencer Janssen Now thats interesting. I can see that this function is more appropriate since I do not need to retrieve data from the IO monad, but what I don't understand is why it's actually faster. I will give it a try and test it on a large set to see if things change. Thanks for the tip.

Matthew Bromberg wrote:
I used what I thought, initially was an elegant contruction technique in Haskell. Something like this do ... sequence $ [ reffill b s | s <- [0..(fi temits)-1], b <- [0..(fi nc)-1]] ...(push list on to matrix stack)
Try the sequence_ (note the underscore) function, it should be a big win here. Cheers, Spencer Janssen
Now thats interesting. I can see that this function is more appropriate since I do not need to retrieve data from the IO monad, but what I don't understand is why it's actually faster. I will give it a try and test it on a large set to see if things change. Thanks for the tip.
The best way I have to explain is to pedantically go through how I would try to understand why it is faster. I hope this is something useful in this message, and nothing that is taken as condescending. Thinking about memory usage and garbage collection in strict language like Java is tricky, and thinking about them in non-strict Haskell is another layer of consideration. ( But in this case it will be quite easy to understand from the code.) I will look at the code: 1. See that sequence and sequence_ are exposed by Prelude 2. Since that is part of the Haskell 98 definition, google a copy of the "Haskell 98 report" at http://www.haskell.org/onlinereport/ 3. Look at "8. Standard Prelude" at http://www.haskell.org/onlinereport/standard-prelude.html 4. Scroll down to sequence and sequence_ to see:
sequence :: Monad m => [m a] -> m [a] sequence = foldr mcons (return []) where mcons p q = p >>= \x -> q >>= \y -> return (x:y)
sequence_ :: Monad m => [m a] -> m () sequence_ = foldr (>>) (return ())
A more generally useful way to look up the actual ghc source code is: 1. In ghci do ":i sequence" to see it comes from Control.Monad 2. look at http://www.haskell.org/ghc/docs/latest/html/libraries/index.html 3. See "Control.Monad" is in the "base" packagage 4. Browse through http://haskell.org/ghc/ to "Developers(Wiki)" and "Getting the Sources" to http://hackage.haskell.org/trac/ghc/wiki/GhcDarcs 5. Follow the link to package "base" via http://darcs.haskell.org/packages/base/ 6. Browse to "Control" and "Monad.hs" to http://darcs.haskell.org/packages/base/Control/Monad.hs 7. Scroll down to sequence and sequence_ to see:
-- | Evaluate each action in the sequence from left to right, -- and collect the results. sequence :: Monad m => [m a] -> m [a] {-# INLINE sequence #-} sequence ms = foldr k (return []) ms where k m m' = do { x <- m; xs <- m'; return (x:xs) }
-- | Evaluate each action in the sequence from left to right, -- and ignore the results. sequence_ :: Monad m => [m a] -> m () {-# INLINE sequence_ #-} sequence_ ms = foldr (>>) (return ()) ms
The implementation code is only 1 or 2 lines, and reveals it is just really useful shorthand for a right fold. Right folds are notorious for being bad memory consumers when they are strict in the second argument of their accumulation function. And indeed this is the problem in this case. Looking at sequence_ first, since it is simpler: It essentially says to put (>>) between all the elements of the list of IO actions which is equivalent to putting the actions one after another in "do" notation. It never needs to remember the result of any of the actions, so the garbage collector will occasionally run and destroy the intermediate results. Those intermediate results may pile up in memory as dead references, so the gc might clean them only after they (or something else) cause memory pressure. Now look at sequence, and remember that the Monad m here is Monad IO. The IO monad runs in a strict manner. Consider " do { x <- m; xs <- m'; return (x:xs) }" which could have been written sequence ms = foldr k (return []) ms where k m m' = do x <- m xs <- m' return (x:xs) sequence [a,b,c] = foldr k (return []) [a,b,c] can be expanded via the foldr definition and some syntactic sugar as a `k` (b `k` (c `k` return [])) can be expanded via the `k` definition and some syntactic sugar as do x <- a xs <- (b `k` (c `k` return [])) return (x:xs) So you can see the return value of a is x. Then it goes and computes the rest of the sequence for b and c while holding onto the reference for x. The "return (x:xs)" line is later and also refers to x, which means x is live instead of dead, so the garbage collector will not remove it. The same analysis applies to the values returned by b and c. All the intermediate values are live until the first `k` executes the "return" statement with all the values. This is why the memory usage is maximal. The problem was created by the IO Monad evaluating the b and c strictly once "xs <- (b `k` (c `k` return []))" was encountered. The use of sequence with a different Monad which was lazy instead would have different evaluation order and memory usage. In particular "Control.Monad.ST.Strict" and "Control.Monad.ST.Lazy" have opposite behaviors in this regard. Other things I notice from the code: sequence and sequence_ work with any Monad, which should make one curious about what they are good shorthand for in non-deterministic monads like List. They are also just as handy in Maybe / Either / etc... The Haddock formatted comments, which are where the documentation comes from: http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.htm... The GHC specific comment "INLINE" is being used. This reliably turns sequence and sequence_ into shorthand for their foldr definitions during compilation, allowing further improvements such as deforestation when possible. -- Chris

Hello Matthew, Sunday, July 23, 2006, 10:35:41 AM, you wrote:
sequence $ [ reffill b s | s <- [0..(fi temits)-1], b <- [0..(fi
nc)-1]]
Now thats interesting. I can see that this function is more appropriate since I do not need to retrieve data from the IO monad, but what I don't understand is why it's actually faster. I will give it a try and test it on a large set to see if things change.
let's see at their (possible) definitions: sequence [] = return [] sequence (action:actions) = do x <- action xs <- sequence actions return (x:xs) sequence_ [] = return () sequence_ (action:actions) = do action sequence_ actions sequence_ is TAIL-RECURSIVE function. moreover, when it's inlined, the result is what just all the action in list are sequentially performed without creating any intermediate data structures. so, using sequence_ in above example is equivalent to implementing this cycle by hand. but when you use sequence, result of each action is saved and list of all results is built. this list requires 12 bytes per element, so you got 600 mb of garbage and much slower execution -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi,
sequence [] = return [] sequence (action:actions) = do x <- action xs <- sequence actions return (x:xs)
sequence_ [] = return () sequence_ (action:actions) = do action sequence_ actions
So, by appending an underscore at the end of a name, you massively improve the runtime behaviour of the program. That to me sounds like a hack :) Would it not be possible to add a GHC rule like the following: forall a b . sequence a >> b = sequence_ a >> b I'm not sure if thats correct, a valid rule definition, or semantics preserving, but if it was it would be nice :) Thanks Neil

Neil Mitchell wrote:
Would it not be possible to add a GHC rule like the following:
forall a b . sequence a >> b = sequence_ a >> b
I'm not sure if thats correct, a valid rule definition, or semantics preserving, but if it was it would be nice :)
Now there's a good idea! Cheers, Simon

Simon Marlow wrote:
Neil Mitchell wrote:
Would it not be possible to add a GHC rule like the following:
forall a b . sequence a >> b = sequence_ a >> b
I'm not sure if thats correct, a valid rule definition, or semantics preserving, but if it was it would be nice :)
Now there's a good idea!
Well this would work in the case of sequence vs sequence_ but it seems to me that what's really needed is a compiler that can do whole program optimization so that the list building inside sequence would be eliminated in this case (because the list is never used) without needing an ad-hoc re-write rule. Otherwise, a programmer must know about all the re-write rules as well as all the functions, and be able to apply them in their head to calculate what the space/time complexity of their program actually is, which imho is much more difficult than just writing sequence_ in the first place. Has anyone done work on an equivalent of MLton for Haskell? Thanks, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

On Mon, 24 Jul 2006, Brian Hulley wrote:
[...] it seems to me that what's really needed is a compiler that can do whole program optimization [...]
Has anyone done work on an equivalent of MLton for Haskell?
http://repetae.net/john/computer/jhc/
Tony.
--
f.a.n.finch

Looks possible. But it'd depend on using '>>' not '>>= \_ -> ...', so a bit fragile. Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Neil | Mitchell | Sent: 23 July 2006 13:57 | To: Bulat Ziganshin | Cc: haskell-cafe@haskell.org | Subject: Re: Re[2]: [Haskell-cafe] Why Haskell? | | Hi, | | > sequence [] = return [] | > sequence (action:actions) = do x <- action | > xs <- sequence actions | > return (x:xs) | > | > sequence_ [] = return () | > sequence_ (action:actions) = do action | > sequence_ actions | | So, by appending an underscore at the end of a name, you massively | improve the runtime behaviour of the program. That to me sounds like a | hack :) | | Would it not be possible to add a GHC rule like the following: | | forall a b . sequence a >> b = sequence_ a >> b | | I'm not sure if thats correct, a valid rule definition, or semantics | preserving, but if it was it would be nice :) | | Thanks | | Neil | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

Bulat Ziganshin-2 wrote:
Hello Matthew,
Sunday, July 23, 2006, 10:35:41 AM, you wrote:
sequence $ [ reffill b s | s <- [0..(fi temits)-1], b <- [0..(fi
nc)-1]]
Now thats interesting. I can see that this function is more appropriate since I do not need to retrieve data from the IO monad, but what I don't understand is why it's actually faster. I will give it a try and test it on a large set to see if things change.
let's see at their (possible) definitions:
sequence [] = return [] sequence (action:actions) = do x <- action xs <- sequence actions return (x:xs)
sequence_ [] = return () sequence_ (action:actions) = do action sequence_ actions
sequence_ is TAIL-RECURSIVE function. moreover, when it's inlined, the result is what just all the action in list are sequentially performed without creating any intermediate data structures. so, using sequence_ in above example is equivalent to implementing this cycle by hand.
but when you use sequence, result of each action is saved and list of all results is built. this list requires 12 bytes per element, so you got 600 mb of garbage and much slower execution
Thanks Bulat, that was concise and explains it well. Now the question is what do I do if I do have data building up in the monad. ie if I want to generate a large list of doubles in the IO monad? Moreover those doubles depend in some way on data wrapped up or generated in the monad. It seems that building a list of IO actions in advance is a bad idea.
Perhaps the implementaton with the tail call will work in this case if an extra accumulator argument is added.
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- View this message in context: http://www.nabble.com/Why-Haskell--tf1986013.html#a5458595 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

Bulat Ziganshin-2 wrote:
Hello Matthew,
Sunday, July 23, 2006, 10:35:41 AM, you wrote:
sequence $ [ reffill b s | s <- [0..(fi temits)-1], b <- [0..(fi
nc)-1]]
Now thats interesting. I can see that this function is more appropriate since I do not need to retrieve data from the IO monad, but what I don't understand is why it's actually faster. I will give it a try and test it on a large set to see if things change.
let's see at their (possible) definitions:
sequence [] = return [] sequence (action:actions) = do x <- action xs <- sequence actions return (x:xs)
sequence_ [] = return () sequence_ (action:actions) = do action sequence_ actions
sequence_ is TAIL-RECURSIVE function. moreover, when it's inlined, the result is what just all the action in list are sequentially performed without creating any intermediate data structures. so, using sequence_ in above example is equivalent to implementing this cycle by hand.
but when you use sequence, result of each action is saved and list of all results is built. this list requires 12 bytes per element, so you got 600 mb of garbage and much slower execution
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Well lo and behold I also need decent performance when doing a lot of IO actions that do not discard their arguments. For example suppose I want to generate a huge array of random numbers. I certainly don't want to multiply my memory requirements by the factor of 12 you mention. It doesn't seem too hard, however to devise tail recursive functions that fit the bill. For example suppose I define a function that repeatedly applies an IO action like this repIO act llist = let repIO' iolact (act) (x0:xl) = do lact <- iolact z <- act x0 repIO' (return (z:lact)) act xl repIO' iolact act [] = iolact nullio = return [] in repIO' nullio (act) llist I can then create a list of random numbers in the IO monad like this main = repIO (\x -> (randomIO :: IO Double)) [1..10] >>= print Of course this one reverses the input list indices. There must be library functions that support a more space efficient way to do these kinds of repetitive sequential IO actions. Ultimately for this little application I want to map the result to an array inside the IO monad. It looks like I have to create the list first. Suppose however I pulled the random value out of the IO monad using unsafePerformIO separately for each index. Lazy evaluation would cause the IO action to occur in an unspecified order. But for the randomIO function I don't really care what order it's called in. Would this have any other unforseen consequences? Are there cases where the IO action would only be partially evaluated, messing up the random number generator? -- View this message in context: http://www.nabble.com/Why-Haskell--tf1986013.html#a5498263 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

On 7/26/06, SevenThunders
Bulat Ziganshin-2 wrote:
Hello Matthew,
Sunday, July 23, 2006, 10:35:41 AM, you wrote:
sequence $ [ reffill b s | s <- [0..(fi temits)-1], b <- [0..(fi
nc)-1]]
Now thats interesting. I can see that this function is more appropriate since I do not need to retrieve data from the IO monad, but what I don't understand is why it's actually faster. I will give it a try and test it on a large set to see if things change.
let's see at their (possible) definitions:
sequence [] = return [] sequence (action:actions) = do x <- action xs <- sequence actions return (x:xs)
sequence_ [] = return () sequence_ (action:actions) = do action sequence_ actions
sequence_ is TAIL-RECURSIVE function. moreover, when it's inlined, the result is what just all the action in list are sequentially performed without creating any intermediate data structures. so, using sequence_ in above example is equivalent to implementing this cycle by hand.
but when you use sequence, result of each action is saved and list of all results is built. this list requires 12 bytes per element, so you got 600 mb of garbage and much slower execution
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Well lo and behold I also need decent performance when doing a lot of IO actions that do not discard their arguments. For example suppose I want to generate a huge array of random numbers.
Well, why would you want a huge array of random numbers? In Haskell there are two big ways to gain efficiency, strictness and laziness. In this case I think laziness is a big candidate (the "huge array" part gives it away). Also there is no reason generating random numbers should be in the IO monad - in fact the built-ins for random numbers are mainly regular pure functions. You only need IO in the very beginning to get a seed. So basically, try to use the extra modularity options that Haskell gives you to separate things that *need* to be IO and things that can just be regular lazy structures (like an infinite list of random numbers occupying memory the size of a pointer). In your case you'd use newStdGen in the IO monad to get a generator, and then produce a "huge" (e.g. infinite) list of random numbers using that (in a pure non-side-effect way), where only the numbers actually needed will ever be computed. If however you do need to do actual IO actions and you find it takes too much space, you can add some extra laziness using unsafeIntereaveIO. It basically just postpones an action until its result is needed. This is what readFile uses, btw, to get lazy IO. I think that's the way to go (rather than unsafePerformIO) because it's still IO so you don't end up in the situation where you have a pure function returning different results everytime you call it, and you still get laziness. Be careful, though, that your particular IO action won't behave strangely if it gets called at some random time or not at all. /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Sebastian Sylvan-2 wrote:
Well, why would you want a huge array of random numbers? In Haskell there are two big ways to gain efficiency, strictness and laziness. In this case I think laziness is a big candidate (the "huge array" part gives it away). Also there is no reason generating random numbers should be in the IO monad - in fact the built-ins for random numbers are mainly regular pure functions. You only need IO in the very beginning to get a seed.
So basically, try to use the extra modularity options that Haskell gives you to separate things that *need* to be IO and things that can just be regular lazy structures (like an infinite list of random numbers occupying memory the size of a pointer). In your case you'd use newStdGen in the IO monad to get a generator, and then produce a "huge" (e.g. infinite) list of random numbers using that (in a pure non-side-effect way), where only the numbers actually needed will ever be computed.
If however you do need to do actual IO actions and you find it takes too much space, you can add some extra laziness using unsafeIntereaveIO. It basically just postpones an action until its result is needed. This is what readFile uses, btw, to get lazy IO. I think that's the way to go (rather than unsafePerformIO) because it's still IO so you don't end up in the situation where you have a pure function returning different results everytime you call it, and you still get laziness. Be careful, though, that your particular IO action won't behave strangely if it gets called at some random time or not at all.
/S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
This kind of sidesteps my question concerning the efficiency of sequence (which it seems could be improved.) You are however correct about how I generate my random numbers. I could have used randomR and stayed out of the IO monad altogether. Also you do bring up an interesting point with regards to whether laziness buys you something with regards to the use of random numbers in a simulation such as mine. The answer is rather complicated. What is going on is that physical processes are being modeled as random processes, which requires the generation of a noise field, which is usually added to the real data of interest. This sort of thing happens all the time in physics and engineering and even numerical computations (e.g. Monte Carlo integration or Markov Chain Monte Carlo evaluation of Bayesian posteriors.). In my case, I have matrix statistics that will be computed after averaging over large amounts of data. Those computations will have to be performed; lazy evaluation won't make them go away. Moreover, to gain efficiency it is usually better to exercise the numerical libraries, such as BLAS over large matrices. Hence I believe it is more efficient to generate all my statistics in advance if possible. In some cases it is possible to reason about the process analytically and thereby mitigate the need to actually generate the random numbers, or to at least generate the final answer as a 'compressed' result, with smaller amounts of data being generated. However in most cases this is intractable and so the brute force approach is the only practical alternative. -- View this message in context: http://www.nabble.com/Why-Haskell--tf1986013.html#a5527728 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.
participants (10)
-
Brian Hulley
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Matthew Bromberg
-
Neil Mitchell
-
Sebastian Sylvan
-
SevenThunders
-
Simon Marlow
-
Simon Peyton-Jones
-
Tony Finch