Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Luke Palmer
On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin <[EMAIL PROTECTED]> wrote:
> Hello everyone,
>
> I have this piece of code I've been working on, and I've been stuck on
> tracking down a space leak in it for some time now.  The code is essentially
> a tight loop that updates a rather largish data structure with embedded
> functions that are called by the driver loop.  The code doesn't accumulate
> any data as the loop runs (at least deliberately), so I would expect the
> memory profile to be flat.  Unfortunately, the profile is a wedge :)   I've
> added bangs and `seq` literally everywhere, and it looks (to me at least)
> like there's nothing left to be lazily evaluated anywhere.  I've used
> retainer profiling, and the functions that are leaking space according to
> the profiler output are strict throughout.

I don't know what I can suggest as for general tactics.  Without
seeing the code it's hard to say what could be happening.  Just
remember that strictness is not always the answer!

>From the very limited amount of information I got from this
description, my first guess would be the data structure itself, or the
functions inside it.  If it's lazily generated, then you might not be
seeing the full amount of space it's taking up at once.  But that's
just a guess.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Jefferson Heard
Peter, from 500 feet, we can't see much, but your strictness might
actually be your problem depending on what "largish" looks like and
whether you're reading your data from disc.  It's entirely possible
that your data structure updates or disc reads are head-strict and
you're evaluating or loading the entirety of data in memory at a
single update.

-- Jeff

On Thu, Jul 17, 2008 at 2:58 PM, Luke Palmer <[EMAIL PROTECTED]> wrote:
> On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin <[EMAIL PROTECTED]> wrote:
>> Hello everyone,
>>
>> I have this piece of code I've been working on, and I've been stuck on
>> tracking down a space leak in it for some time now.  The code is essentially
>> a tight loop that updates a rather largish data structure with embedded
>> functions that are called by the driver loop.  The code doesn't accumulate
>> any data as the loop runs (at least deliberately), so I would expect the
>> memory profile to be flat.  Unfortunately, the profile is a wedge :)   I've
>> added bangs and `seq` literally everywhere, and it looks (to me at least)
>> like there's nothing left to be lazily evaluated anywhere.  I've used
>> retainer profiling, and the functions that are leaking space according to
>> the profiler output are strict throughout.
>
> I don't know what I can suggest as for general tactics.  Without
> seeing the code it's hard to say what could be happening.  Just
> remember that strictness is not always the answer!
>
> >From the very limited amount of information I got from this
> description, my first guess would be the data structure itself, or the
> functions inside it.  If it's lazily generated, then you might not be
> seeing the full amount of space it's taking up at once.  But that's
> just a guess.
>
> Luke
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

-- Jessica Edwards
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Justin Bailey
On Thu, Jul 17, 2008 at 11:14 AM, Peter Gavin <[EMAIL PROTECTED]> wrote:

> evaluated anywhere.  I've used retainer profiling, and the functions that
> are leaking space according to the profiler output are strict throughout.
>

Have you looked at the Core code generated? That might show something that
isn't strict which you think is. I believe "let" statements in Core
represent allocations, while "case" statements are strict.

In case you don't know, the best thing you can do to read core is to add
comment annotations ({-# CORE "..." #-} I think), which will help you
pinpoint which Haskell gets turned into core. To produce core with 6.8, use
the -fext-core flag.

Justin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Peter Gavin

Thanks for the responses.

This is basically what I've got looks like (grossly simplified):


data Monad m => Foo m a b =
 Foo
 { action :: m (Foo m a b, b)
 , update :: a -> Foo m a b
 }

The driver loop injects new values with update, and executes action 
whenever it's ready to, replacing the old Foo with the newly returned Foo.


I finally fixed the space leak it by inserting SPECIALIZE pragmas for 
Foo IO a b on every function that creates a Foo. I'm not sure if I can 
remove all the strictness annotations I've accumulated yet, though. 
This is a bit disconcerting, though, because in the future I'd like to 
not use IO and use a strict State instead. I hope I won't have to 
specialize for every monad that ends up getting used.


Thanks again,
Pete


Jefferson Heard wrote:

Peter, from 500 feet, we can't see much, but your strictness might
actually be your problem depending on what "largish" looks like and
whether you're reading your data from disc.  It's entirely possible
that your data structure updates or disc reads are head-strict and
you're evaluating or loading the entirety of data in memory at a
single update.

-- Jeff

On Thu, Jul 17, 2008 at 2:58 PM, Luke Palmer <[EMAIL PROTECTED]> wrote:

On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin <[EMAIL PROTECTED]> wrote:

Hello everyone,

I have this piece of code I've been working on, and I've been stuck on
tracking down a space leak in it for some time now.  The code is essentially
a tight loop that updates a rather largish data structure with embedded
functions that are called by the driver loop.  The code doesn't accumulate
any data as the loop runs (at least deliberately), so I would expect the
memory profile to be flat.  Unfortunately, the profile is a wedge :)   I've
added bangs and `seq` literally everywhere, and it looks (to me at least)
like there's nothing left to be lazily evaluated anywhere.  I've used
retainer profiling, and the functions that are leaking space according to
the profiler output are strict throughout.

I don't know what I can suggest as for general tactics.  Without
seeing the code it's hard to say what could be happening.  Just
remember that strictness is not always the answer!

>From the very limited amount of information I got from this
description, my first guess would be the data structure itself, or the
functions inside it.  If it's lazily generated, then you might not be
seeing the full amount of space it's taking up at once.  But that's
just a guess.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe







___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Peter Gavin

Replying to myself...

Interesting.  I removed all the bangs other than the obvious loop 
variables, and all the uses of seq that I had inserted, and there's 
still no leak.


Does anyone know why the leak would disappear when GHC is using IO other 
than a generic (unspecified) monad?  Is there something special about 
the >>= and return operators for IO that aren't true for other monads?


Thanks,
Pete


Peter Gavin wrote:

Thanks for the responses.

This is basically what I've got looks like (grossly simplified):


data Monad m => Foo m a b =
 Foo
 { action :: m (Foo m a b, b)
 , update :: a -> Foo m a b
 }

The driver loop injects new values with update, and executes action 
whenever it's ready to, replacing the old Foo with the newly returned Foo.


I finally fixed the space leak it by inserting SPECIALIZE pragmas for 
Foo IO a b on every function that creates a Foo. I'm not sure if I can 
remove all the strictness annotations I've accumulated yet, though. This 
is a bit disconcerting, though, because in the future I'd like to not 
use IO and use a strict State instead. I hope I won't have to specialize 
for every monad that ends up getting used.


Thanks again,
Pete


Jefferson Heard wrote:

Peter, from 500 feet, we can't see much, but your strictness might
actually be your problem depending on what "largish" looks like and
whether you're reading your data from disc.  It's entirely possible
that your data structure updates or disc reads are head-strict and
you're evaluating or loading the entirety of data in memory at a
single update.

-- Jeff

On Thu, Jul 17, 2008 at 2:58 PM, Luke Palmer <[EMAIL PROTECTED]> wrote:

On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin <[EMAIL PROTECTED]> wrote:

Hello everyone,

I have this piece of code I've been working on, and I've been stuck on
tracking down a space leak in it for some time now.  The code is 
essentially

a tight loop that updates a rather largish data structure with embedded
functions that are called by the driver loop.  The code doesn't 
accumulate
any data as the loop runs (at least deliberately), so I would expect 
the
memory profile to be flat.  Unfortunately, the profile is a wedge 
:)   I've
added bangs and `seq` literally everywhere, and it looks (to me at 
least)

like there's nothing left to be lazily evaluated anywhere.  I've used
retainer profiling, and the functions that are leaking space 
according to

the profiler output are strict throughout.

I don't know what I can suggest as for general tactics.  Without
seeing the code it's hard to say what could be happening.  Just
remember that strictness is not always the answer!

>From the very limited amount of information I got from this
description, my first guess would be the data structure itself, or the
functions inside it.  If it's lazily generated, then you might not be
seeing the full amount of space it's taking up at once.  But that's
just a guess.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe









___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2004-10-05 Thread Ben Lippmeier
In my experience, any time your program makes use of some state-like 
structure which gets updated over a number of iterations, you're going 
to be in trouble with space leaks.

There's a library function which summarises this nicely,
mapAccumL :: (state -> x -> (state, y)) -> state -> [x] -> (state, [y])
The GHC library docs describe mapAccumL as
"The mapAccumL function behaves like a combination of map and foldl; it 
applies a function to each element of a list, passing an accumulating 
parameter from left to right, and returning a final value of this 
accumulator together with the new list."

Now imagine that state is some large structure. The [x] list is a couple 
of hundred elements long, and you print out some -> but not all <- of 
the [y] elements. While the [y] list remains live, a whole collection of 
 half evaluated intermediate states also remain live -  enter the 
massive space leak.

Projects I have written which suffered massive space leaks include:
-> A parallel lazy evaluator,
http://cs.anu.edu.au/ample.
The state:the machine state, threads, stacks, the heaps.
The [x] list: machine instructions.
The [y] list: profiling info.
If you don't print out all possible profiling info then all those 
intermediate states remain live and you've got a massive space leak.

-> An astroids game I wrote for X.
The state:position, velocities of ship, astroids, missiles.
The [x] list: ship control data, key codes.
The [y] list: a list of graphics prims which get rendered to the screen.
You would think that because the list of prims gets consumed by the 
renderer it wouldn't leak.. but it did, about 200k / sec. Then I changed 
some seemingly irrelevant part of the code and the space leak went 
away.. and I have no idea why. yay.

-> My ICFP contest entry for this year,
Not really a mapAccumL type problem, but still a space leak.
At one stage I had a bug in the parser for my assembly language where it 
didn't handle comments properly. One of the entries I ran through my 
simulator had comments at the end of lines with Drop statements, but 
nowhere else.

The simulator ran fine until an ant found some food, carried it back to 
the hill, then attempted to drop it.. parser error. My Haskell program 
hadn't fully evaluated the thunks to read / parse / assemble that line 
of code until the ant had tried to use that part of the program.. I 
laughed, and laughed.. :).

...
I think the only way to totally slay bugs like these is to use some 
deepSeq'esque function on all your intermediate states, or any time when 
you reckon some evaluation should be 'finished'. Either that or explicly 
define intermediate structures to be fully strict.

I see the GHC people have got a seqExpr function in 
compiler/coreSyn/CoreSyn.lhs, which I imagine would be applied to the 
expression tree after every compiler stage.

Ben.

Graham Klyne wrote:
I've been starting to take note of discussion about space leaks in 
Haskell.  So far, it's not a topic that's bothered me, other than 
obvious programming errors, and I've never found the need to force 
strict evaluation of my Haskell programs.  I find myself wondering why 
this is.

Your comment about arithmetic expressions is telling:  the kind of 
program I have been writing (parsers, symbolic processing, etc.) 
performs almost no arithmetic.  (So far, I've used lists instead of 
arrays, so a usual source of arithmetic functions is missing.)

I've also worked with datasets that fit in memory, so failure to 
"stream" data hasn't been a problem.  I suspect that's the more 
pernicious case for space leaks, since the causes aren't always so obvious.

Are there any guidelines or warning signs to look out for that may be 
indicative of potential space-leak problems?  So far, I can think of:
- arithmetic results
- multiple uses of a large data value

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2004-10-05 Thread William Lee Irwin III
On Wed, Oct 06, 2004 at 12:27:35PM +1000, Ben Lippmeier wrote:
> Now imagine that state is some large structure. The [x] list is a couple 
> of hundred elements long, and you print out some -> but not all <- of 
> the [y] elements. While the [y] list remains live, a whole collection of 
>  half evaluated intermediate states also remain live -  enter the 
> massive space leak.
> Projects I have written which suffered massive space leaks include:
> -> A parallel lazy evaluator,
> http://cs.anu.edu.au/ample.
> The state:the machine state, threads, stacks, the heaps.
> The [x] list: machine instructions.
> The [y] list: profiling info.
> If you don't print out all possible profiling info then all those 
> intermediate states remain live and you've got a massive space leak.
> -> An astroids game I wrote for X.
> The state:position, velocities of ship, astroids, missiles.
> The [x] list: ship control data, key codes.
> The [y] list: a list of graphics prims which get rendered to the screen.

Know any tricks for 2D recurrences where only points along the i=j line
(which depend on all points where i <= j) are used for the final result?

-- wli
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] space leaks and optimizations

2010-01-08 Thread David Leimbach
>
>
> 2) While each step is predictable, the overall behavior of a lazy
> program can be rather surprising. So one must be very careful. GHC
> provides two ways to control the evaluation order, seq and bang
> patterns, but I am not sure which of these (if any) is the right tool.
> Consider the following example (from the Real World Haskell book):
> mean :: [Double] -> Double
> mean xs = sum / fromIntegral num where
>(num,sum) = foldl' f (0,0) xs :: (Int, Double)
>f (n,s) x = (n+1, s+x)
> Although it uses foldl', there is a space leak because Haskell tuples
> are not strict. There are two possible fixes:
>f (!n,!s) x = (n+1, s+x)
> or
>f (n,s) x = let n1=n+1; s1=s+x in n1 `seq` s1 `seq` (n1,s1)
> The first one is short, but less natural than the second one, where the
> offending thunks are suppressed on the spot. Unfortunately, the syntax
> is awkward; it would be nice to write something like
>f (n,s) x = (!n+1, !n+1)
> Well, I am becoming too grumpy, perhaps the bang patterns are fine. More
> important question: are there established practices to *avoid* space
> leaks rather than fixing them afterwards?
>
>
I believe the expectation is to learn to not be surprised in the areas where
lazy or non-strict evaluation can be overused, and to learn all the
advantages of non-strict evaluation vs strict, and the power it gives, such
that an imperative programmer doesn't feel surprised or angry when things go
wrong.

I blogged about writing a long running service in Haskell that ran into
problems with the lazy State monad, and lazy Data.Map, and I discussed how I
had to force evaluations of everything to get the program under control.
 This wasn't for a hobby, this was for a production system.  I believe I've
a much better handle on strict vs non-strict than when I started the
project, but I felt pretty lost for a while  in the process of doing it.

I was even using the Maybe monad with it's MonadPlus implementation to avoid
using case statements around deconstruction, which I'm sure exacerbated some
of my problem.  However, since Haskell will evaluate the outer-most stuff
first, the trick seems to be to find the point at which you *really* need
the values computed, then tell Haskell to get on with it.  You kind of have
to have an explicit sequence point where all things need to be resolved, and
you have to be able to see those in your code.  Sometimes you can get away
with only doing small pieces at a time.

I had about the worst situation I've ever seen for data growth in my code.
 I had a pile of non-strict expressions, that were all dependencies for the
next, running forever, and never getting evaluated except at asynchronous
and user-controlled moments.  If these expressions had been evaluated
strictly, they would have taken up constant space, but since they were all
thunks, I got linear data growth over time, until I blew up.

Some advice I've gotten since then was to think about using case for
strictness rather than explicitly using seq.  Turns out case's pattern
matching is pretty strict, and that you can often get by with that.  I
haven't spent a lot of time with core output, but my understanding is that
it's all let and case.



> 3) The standard library was not designed with space efficiency in mind;
> for example, there is sum but no sum'.
>

Actually I think that the standard library was designed to be consistent
with the way the language is documented to behave.  That is to say that it's
non-strict by default everywhere it's possible to be so.
 Control.Monad.State selects Control.Monad.State.Lazy by default instead of
Control.Monad.State.Strict, but both exist.

Yes, in some cases there's no strict equivalent provided, but is writing a
strict sum really a big problem?  I think there's stricter folds included
because they're not quite as trivial, but once you have a strict fold isn't
strict sum pretty easy?  I suppose the type of the contained element in the
list could make a big difference in whether the strict fold is strict
enough, but where do you stop providing strict versions of functions for
people?  It seems a line must be drawn somewhere, and the right solution is
to properly educate Haskell programmer about both the power and drawbacks of
non-strict evaluation, and when it's really necessary to turn things off.
 Giving examples is fine, but one must learn to see the patterns where there
is a problem that could brew.

Real World Haskell teaches us about the profiling tools that helped me
uncover my problems.


>
>
> Best regards,
> Alexei
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] space leaks and optimizations

2010-01-09 Thread Alexei Kitaev
Dear David,

Thank you for your comments. I understand your suggestion that a program
should contain some "synchronization points" where the values are
evaluated. But this is not easy. Maybe I should just practice more.

I while ago I played with the strict and lazy ST monads and was able to
achieve the desired behavior, though with difficulty. Unfortunately,
there is no universal solution, and one cannot always use standard
idioms. For example, the lazy version of ST (and State) has the problem
you described, while the strict version exhibits a space leak when used
with mapM or sequence. Simply put, one cannot construct a lazy producer
out of a strict state. I wrote a special version of sequence, which uses
ST.Lazy but forces the evaluation of the implicit state at each step:

import Control.Monad
import Control.Monad.ST
import qualified Control.Monad.ST.Lazy as Lazy

seqLST :: [Lazy.ST s a] -> Lazy.ST s [a]
seqLST xs = syncLST (f xs)
where
  f [] = return []
  f (x:xs) = liftM2 (:) x (seqLST xs)

syncLST :: Lazy.ST s a -> Lazy.ST s a
syncLST = join . Lazy.strictToLazyST . Lazy.lazyToStrictST . return

For the lazy State monad,
syncLState m = State $ \s -> s `seq` runState m s

I am not completely satisfied with this solution. For one thing, it's
slow and can hardly be optimized. It's also not clear whether one should
 evaluate the input state as I did (there was some reason but I don't
remember) or the output state. I think that a better idea would be to
use strict (ST s) together with a lazy continuation, (STC s a). It's
basically a function s -> a, but one has to wrap it with some
GHC-specific types like State#. Mathematically, (STC s a) is an algebra
over the (ST s) monad. I'll try that when I have time.

More generally, I am looking for reliable and easy to use tools and
idioms for space-conscious programming. I appreciate the design of the
strict ST and State monads. In particular, ST has a nice invariant that,
at any point, the implicit state is fully evaluated. However, I spend a
lot of time figuring how the strict and lazy monads actually work. Is
there any documentation? Reading the discussion related to your blog, I
realized that strict State is different in that it does not actually
force the state. But forcing can be achieved by wrapping all actions
with the following function:

sState :: (s -> (a,s)) -> State s a
sState f = State $ \s -> case f s of
 (a,s') -> s' `seq` (a,s')

I hope that somebody will answer my other questions about the
operational semantics and optimizations.

-Alexei

David Leimbach wrote:
>>
>> 2) While each step is predictable, the overall behavior of a lazy
>> program can be rather surprising. So one must be very careful. GHC
>> provides two ways to control the evaluation order, seq and bang
>> patterns, but I am not sure which of these (if any) is the right tool.
>> Consider the following example (from the Real World Haskell book):
>> mean :: [Double] -> Double
>> mean xs = sum / fromIntegral num where
>>(num,sum) = foldl' f (0,0) xs :: (Int, Double)
>>f (n,s) x = (n+1, s+x)
>> Although it uses foldl', there is a space leak because Haskell tuples
>> are not strict. There are two possible fixes:
>>f (!n,!s) x = (n+1, s+x)
>> or
>>f (n,s) x = let n1=n+1; s1=s+x in n1 `seq` s1 `seq` (n1,s1)
>> The first one is short, but less natural than the second one, where the
>> offending thunks are suppressed on the spot. Unfortunately, the syntax
>> is awkward; it would be nice to write something like
>>f (n,s) x = (!n+1, !n+1)
>> Well, I am becoming too grumpy, perhaps the bang patterns are fine. More
>> important question: are there established practices to *avoid* space
>> leaks rather than fixing them afterwards?
>>
>>
> I believe the expectation is to learn to not be surprised in the areas where
> lazy or non-strict evaluation can be overused, and to learn all the
> advantages of non-strict evaluation vs strict, and the power it gives, such
> that an imperative programmer doesn't feel surprised or angry when things go
> wrong.
> 
> I blogged about writing a long running service in Haskell that ran into
> problems with the lazy State monad, and lazy Data.Map, and I discussed how I
> had to force evaluations of everything to get the program under control.
>  This wasn't for a hobby, this was for a production system.  I believe I've
> a much better handle on strict vs non-strict than when I started the
> project, but I felt pretty lost for a while  in the process of doing it.
> 
> I was even using the Maybe monad with it's MonadPlus implementation to avoid
> using case statements around deconstruction, which I'm sure exacerbated some
> of my problem.  However, since Haskell will evaluate the outer-most stuff
> first, the trick seems to be to find the point at which you *really* need
> the values computed, then tell Haskell to get on with it.  You kind of have
> to have an explicit sequence point where all things need to

Re: [Haskell-cafe] space leaks and optimizations

2010-01-13 Thread Ryan Ingram
On Sat, Jan 9, 2010 at 2:23 AM, Alexei Kitaev  wrote:
> Reading the discussion related to your blog, I
> realized that strict State is different in that it does not actually
> force the state. But forcing can be achieved by wrapping all actions
> with the following function:
>
> sState :: (s -> (a,s)) -> State s a
> sState f = State $ \s -> case f s of
>                             (a,s') -> s' `seq` (a,s')
>
> I hope that somebody will answer my other questions about the
> operational semantics and optimizations.

Hi Alexei, you have a ton of great points but I wanted to discuss an
issue with this one.

It's unusual that this is what you want either; since it only reduces
the state to WHNF.  For example, if your state is a string, this only
evaluates enough to know whether or not the string is empty at each
step, and you can still get into trouble with code like this:

   put ("xxx" ++ some_bad_computation)

which leave bottoms inside of your state which won't show up until later.

Several attempts to solve this problem exist, but the most commonly
used one is the "rnf" strategy from Control.Parallel.Strategies, which
uses a typeclass to allow each type to specify how to evaluate itself
completely.

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] space leaks and optimizations

2010-01-15 Thread Henning Thielemann
Ryan Ingram schrieb:

> Hi Alexei, you have a ton of great points but I wanted to discuss an
> issue with this one.
> 
> It's unusual that this is what you want either; since it only reduces
> the state to WHNF.  For example, if your state is a string, this only
> evaluates enough to know whether or not the string is empty at each
> step, and you can still get into trouble with code like this:
> 
>put ("xxx" ++ some_bad_computation)
> 
> which leave bottoms inside of your state which won't show up until later.
> 
> Several attempts to solve this problem exist, but the most commonly
> used one is the "rnf" strategy from Control.Parallel.Strategies, which
> uses a typeclass to allow each type to specify how to evaluate itself
> completely.

Now available without parallelism in

http://hackage.haskell.org/packages/archive/deepseq/1.1.0.0/doc/html/Control-DeepSeq.html

I think that one should generally think before using seq, because it is
only strict in the top most constructor. If you know the type you 'seq'
on, then you might use a 'case' on it instead and can precisely control
the depth of the strictness. Otherwise you might use 'rnf'.

I have also some problems with space leaks. Recently I found a space
leak in my code, that was because a finalizer did not run as expected.
Now I'm seeking more information on how to use finalizers correctly ...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks in function that uses Data.Vector.Mutable

2013-01-23 Thread Johan Tibell
Hi!

You have to look outside the place function, which is strict enough. I
would look for a call to unsafeWrite that doesn't evaluate it's
argument before writing it into the vector. Perhaps you're doing
something like:

MV.unsafeWrite (i + 1, ...)

Since tuples are lazy the i + 1 will be stored as a thunk. I recommend doing:

data DescriptiveName a = DescriptiveName {-# UNPACK #-} !Int a

and using a

MV.MVector (PrimState m) (DescriptiveName t)

if speed is really of the essence.

Aside: You can't optimize place slightly by:

 * Making it strict in val1, and
 * Making it inline.

The reason you want it to inline* is that's the function is
polymorphic and inlining it at a call site when you know if you're
working in IO and ST will improve performance.

Here's the slightly optimized version:

place :: (PrimMonad m) =>
 MV.MVector (PrimState m) (Int, t) -> (Int, t) -> Int -> m ()
place v max@(!val1,_) i = place' i
 where
  place' i = do
let j = i - 1
if j < 0
then return ()
else do
  curr@(val2, _) <- MV.unsafeRead v j
  if val2 > val1
  then do
MV.unsafeWrite v j max
MV.unsafeWrite v i curr
place' j
  else return ()
{-# INLINE place #-}

* It should be enough to write two SPECIALIZE pragmas, one for IO and
one for ST, but GHC doesn't seem to like that for some reason:

/tmp/Test.hs:24:1: Warning:
RULE left-hand side too complicated to desugar
  (place @ (ST s) @ t ($fPrimMonadST @ s ($fMonadST @ s))) `cast` ...

/tmp/Test.hs:25:1: Warning:
RULE left-hand side too complicated to desugar
  (place @ IO @ t $fPrimMonadIO) `cast` ...

Cheers,
Johan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe