
Hi, I've written a program that reads doubles from stdin and creates a distribution of the data according to specified ranges. The program works ok and speed is acceptable (17 secs for 300000 entries), but to run it I have to increase stack size: $ cat input | ./distrib +RTS -K100000000 -RTS How do I figure out why the program needs a lot of stack? Also, is there an easy way to increace performance? Thanks, Patrick import qualified Data.Map as M import Data.List (sort, foldl') import qualified Data.ByteString.Char8 as L import Data.ByteString.Lex.Double data Range n = Range n n | OutOfBounds deriving (Eq, Ord, Show) data Distrib n = Distrib (M.Map (Range n) Int) [Range n] deriving (Show) mkDist :: (Ord n) => [n] -> Distrib n mkDist ns = Distrib M.empty ranges where ranges = zipWith Range l (tail l) l = sort ns record :: (Ord n) => n -> Distrib n -> Distrib n record n (Distrib m rs) = Distrib (M.alter f slot m) rs where f (Just n) = Just $ n + 1 f Nothing = Just 1 slot = findSlot n rs findSlot x (r@(Range a b):rs) | x >= a && x < b = r | otherwise = findSlot x rs findSlot x [] = OutOfBounds mkDouble :: L.ByteString -> Double mkDouble bs = case readDouble bs of Just (d, rest) -> d main = do let d = mkDist [0, 5, 10, 50, 100] bs <- L.getContents let ds = map (abs . mkDouble) . L.lines $ bs let (Distrib m _) = foldr (\n acc -> record n acc) d ds putStrLn . show $ m -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

On Wed, Apr 27, 2011 at 11:52 AM, Patrick LeBoutillier
How do I figure out why the program needs a lot of stack?
Usually it is because you are building a large thunk.
Also, is there an easy way to increace performance?
Getting rid of the thunks should increase performance as well. I've had just a quick look on your code, but here are some suggestions:
record :: (Ord n) => n -> Distrib n -> Distrib n record n (Distrib m rs) = Distrib (M.alter f slot m) rs where f (Just n) = Just $ n + 1 f Nothing = Just 1 slot = findSlot n rs findSlot x (r@(Range a b):rs) | x >= a && x < b = r | otherwise = findSlot x rs findSlot x [] = OutOfBounds
Try changing "Just $ n + 1" to "Just $! n + 1". It is possible that this change alone removes the leak (it is the only obvious leak I'm seeing right now). Also, for findSlot you may want to do a binary search, but that isn't related to the leak at all. Cheers, -- Felipe.

Felipe,
I tried the $! bit, but I get the same result. I guess there's another
leak somewhere...
Patrick
On Wed, Apr 27, 2011 at 11:20 AM, Felipe Almeida Lessa
On Wed, Apr 27, 2011 at 11:52 AM, Patrick LeBoutillier
wrote: How do I figure out why the program needs a lot of stack?
Usually it is because you are building a large thunk.
Also, is there an easy way to increace performance?
Getting rid of the thunks should increase performance as well.
I've had just a quick look on your code, but here are some suggestions:
record :: (Ord n) => n -> Distrib n -> Distrib n record n (Distrib m rs) = Distrib (M.alter f slot m) rs where f (Just n) = Just $ n + 1 f Nothing = Just 1 slot = findSlot n rs findSlot x (r@(Range a b):rs) | x >= a && x < b = r | otherwise = findSlot x rs findSlot x [] = OutOfBounds
Try changing "Just $ n + 1" to "Just $! n + 1". It is possible that this change alone removes the leak (it is the only obvious leak I'm seeing right now).
Also, for findSlot you may want to do a binary search, but that isn't related to the leak at all.
Cheers,
-- Felipe.
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

GHC profiling is not that hard. There are a few tutorials on the Internet that can help you (try Real World Haskell, ch 25http://book.realworldhaskell.org/read/profiling-and-optimization.html) Running your code with "+RTS -pa -sstderr" can give you some hints on where it is hogging memory. Regards. Rafael On Wed, Apr 27, 2011 at 15:25, Patrick LeBoutillier < patrick.leboutillier@gmail.com> wrote:
Felipe,
I tried the $! bit, but I get the same result. I guess there's another leak somewhere...
Patrick
On Wed, Apr 27, 2011 at 11:20 AM, Felipe Almeida Lessa
wrote: On Wed, Apr 27, 2011 at 11:52 AM, Patrick LeBoutillier
wrote: How do I figure out why the program needs a lot of stack?
Usually it is because you are building a large thunk.
Also, is there an easy way to increace performance?
Getting rid of the thunks should increase performance as well.
I've had just a quick look on your code, but here are some suggestions:
record :: (Ord n) => n -> Distrib n -> Distrib n record n (Distrib m rs) = Distrib (M.alter f slot m) rs where f (Just n) = Just $ n + 1 f Nothing = Just 1 slot = findSlot n rs findSlot x (r@(Range a b):rs) | x >= a && x < b = r | otherwise = findSlot x rs findSlot x [] = OutOfBounds
Try changing "Just $ n + 1" to "Just $! n + 1". It is possible that this change alone removes the leak (it is the only obvious leak I'm seeing right now).
Also, for findSlot you may want to do a binary search, but that isn't related to the leak at all.
Cheers,
-- Felipe.
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Rafael Gustavo da Cunha Pereira Pinto

On Wednesday 27 April 2011 17:20:15, Felipe Almeida Lessa wrote:
On Wed, Apr 27, 2011 at 11:52 AM, Patrick LeBoutillier
wrote: How do I figure out why the program needs a lot of stack?
Usually it is because you are building a large thunk.
Also, is there an easy way to increace performance?
Getting rid of the thunks should increase performance as well.
I've had just a quick look on your code, but here are some suggestions:
record :: (Ord n) => n -> Distrib n -> Distrib n record n (Distrib m rs) = Distrib (M.alter f slot m) rs where f (Just n) = Just $ n + 1 f Nothing = Just 1 slot = findSlot n rs findSlot x (r@(Range a b):rs) | x >= a && x < b = r | otherwise = findSlot x rs findSlot x [] = OutOfBounds
Try changing "Just $ n + 1" to "Just $! n + 1". It is possible that this change alone removes the leak (it is the only obvious leak I'm seeing right now).
I'm not sure that alone would help. I think he'll still get a thunk (M.alter f slot (M.alter f slot (... ())). record would need to force the Map, easiest to make Distrib strict in the map, data Distrib n = Distrib !(M.Map (Range n Int)) [Range n] Another point is that he uses a foldr, which generally is a bad strategy for building Maps, much better to use foldl' in general. Some more gains I would expect from not using a Map here, but to use accumArray on an unboxed array (UArray Int Int, one would have to map the slots to indices, but that's trivial to do when finding the right slot).
Also, for findSlot you may want to do a binary search,
Not while the ranges are stored as a list. Exercise: Why is a binary search on a singly linked list a bad idea? Storing the 'list' of ranges as an array would make a binary search worthwhile, though, at least for situations with more ranges. For the four (or five including OutOfBounds) ranges in the example main, linear search of a singly linked list will be hard to beat.
but that isn't related to the leak at all.
Cheers,

Daniel,
On Wed, Apr 27, 2011 at 2:41 PM, Daniel Fischer
I'm not sure that alone would help. I think he'll still get a thunk (M.alter f slot (M.alter f slot (... ())).
record would need to force the Map, easiest to make Distrib strict in the map,
data Distrib n = Distrib !(M.Map (Range n Int)) [Range n]
Another point is that he uses a foldr, which generally is a bad strategy for building Maps, much better to use foldl' in general.
The bang and the foldl' made it super fast (1 sec) and extra stack is no longer required. After searching a bit on my own I had a feeling that the problem has with the call to M.alter, but I didn't know how to force the evaluation. For me this is the biggest problem with using Haskell on a day-to-day basis for work stuff (which I usually do in Perl or even BASH). It takes me longer to write the program and it (sometimes) takes longer for the program to run. I suppose with practice I'll get better... Thanks for the tips, Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

On Wed, Apr 27, 2011 at 3:41 PM, Daniel Fischer
Not while the ranges are stored as a list. Exercise: Why is a binary search on a singly linked list a bad idea?
I'm sorry if it sounded as if that was what I was suggesting. You can't do any better than O(n) with a linked list. Cheers, -- Felipe.
participants (4)
-
Daniel Fischer
-
Felipe Almeida Lessa
-
Patrick LeBoutillier
-
Rafael Gustavo da Cunha Pereira Pinto