Re: [Haskell-cafe] Space leak in hexpat-0.20.3/List-0.5.1

2013-04-30 Thread oleg
Wren Thornton wrote: So I'm processing a large XML file which is a database of about 170k entries, each of which is a reasonable enough size on its own, and I only need streaming access to the database (basically printing out summary data for each entry). Excellent, sounds like a job for SAX.

[Haskell-cafe] Space leak in hexpat-0.20.3/List-0.5.1

2013-04-28 Thread wren ng thornton
Hello all, So I'm processing a large XML file which is a database of about 170k entries, each of which is a reasonable enough size on its own, and I only need streaming access to the database (basically printing out summary data for each entry). Excellent, sounds like a job for SAX. However,

Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-30 Thread Yves Parès
Have you tried to compile your code with optimisations? I guess GHC's strictness analysis would find strict evaluation is better here. 2012/1/30 Joey Hess j...@kitenet.net Claude Heiland-Allen wrote: Control.Monad.State.Strict is strict in the actions, but the state itself is still lazy,

Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-30 Thread Joey Hess
Yves Parès wrote: Have you tried to compile your code with optimisations? I guess GHC's strictness analysis would find strict evaluation is better here. The original code I saw this happen to the wild was built with -O2. I didn't try building the test case with optimisations. -- see shy jo

[Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Joey Hess
The attached test case quickly chews up hundreds of MB of memory. If modified to call work' instead, it runs in constant space. Somehow the value repeatedly read in from the file and stored in the state is leaking. Can anyone help me understand why? (ghc 7.0.4) -- see shy jo {-# LANGUAGE

Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Claude Heiland-Allen
Hi, On 30/01/12 01:07, Joey Hess wrote: The attached test case quickly chews up hundreds of MB of memory. If modified to call work' instead, it runs in constant space. Somehow the value repeatedly read in from the file and stored in the state is leaking. Can anyone help me understand why?

Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Joey Hess
Claude Heiland-Allen wrote: Control.Monad.State.Strict is strict in the actions, but the state itself is still lazy, so you end up building a huge thunk in the state containing all the updates that ever took place to the initial state. Using this should fix it: modify' :: MonadState s m

Re: [Haskell-cafe] Space leak with unsafePerformIO

2010-06-28 Thread Henning Thielemann
On Sun, 27 Jun 2010, Henning Thielemann wrote: Maybe I can combine splitAtLazy and (++) to a function like splitAtAndAppend :: [x] - ([a] - [b]) - ([a] - [b]) - [a] - [b] but I'm afraid I will need pairs temporarily and then I run into the same problems. I have now implemented a solution

Re: [Haskell-cafe] Space leak with unsafePerformIO

2010-06-27 Thread Bertram Felgenhauer
Henning Thielemann wrote: Attached is a program with a space leak that I do not understand. I have coded a simple 'map' function, once using unsafePerformIO and once without. UnsafePerformIO has a space leak in some circumstances. In the main program I demonstrate cases with and without space

Re: [Haskell-cafe] Space leak with unsafePerformIO

2010-06-27 Thread Henning Thielemann
On Sun, 27 Jun 2010, Bertram Felgenhauer wrote: If the compiler had produced Main.lvl3 = case Main.ds of wild_Xw { (prefix_aCf, suffix_aCh) - suffix_aCh } Main.lvl4 = Main.go1 Main.lvl3 instead, then there would not be a leak. This whole record selector thunk business is very

[Haskell-cafe] Space leak with unsafePerformIO

2010-06-26 Thread Henning Thielemann
Attached is a program with a space leak that I do not understand. I have coded a simple 'map' function, once using unsafePerformIO and once without. UnsafePerformIO has a space leak in some circumstances. In the main program I demonstrate cases with and without space leak. Without space leak the

Re: [Haskell-cafe] Space leak

2010-03-15 Thread Ketil Malde
Arnoldo Muller arnoldomul...@gmail.com writes: I am trying to use haskell in the analysis of bio data. One of the main reasons I wanted to use haskell is because lazy I/O allows you to see a large bio-sequence as if it was a string in memory. Funny you should mention it. I've written a

Re: [Haskell-cafe] Space leak

2010-03-13 Thread Jason Dagit
On Thu, Mar 11, 2010 at 3:44 PM, Arnoldo Muller arnoldomul...@gmail.comwrote: Daniel, Thank you so much for helping me out with this issue! Thanks to all the other answers from haskel-cafe members too! As a newbie, I am not able to understand why zip and map would make a problem... Is

Re: [Haskell-cafe] Space leak

2010-03-13 Thread Jason Dagit
On Wed, Mar 10, 2010 at 2:03 PM, Arnoldo Muller arnoldomul...@gmail.comwrote: Hello Justin, I tried and what I saw was a constant increase in memory usage. Any particular profiling option that you would use? A great place to get started with profiling is the chapter in Real-World Haskell:

Re: [Haskell-cafe] Space leak

2010-03-13 Thread Arnoldo Muller
Jason, I am trying to use haskell in the analysis of bio data. One of the main reasons I wanted to use haskell is because lazy I/O allows you to see a large bio-sequence as if it was a string in memory. In order to achieve the same result in an imperative language I would have to write lots of

Re: [Haskell-cafe] Space leak

2010-03-13 Thread David Leimbach
On Sat, Mar 13, 2010 at 3:58 PM, Arnoldo Muller arnoldomul...@gmail.comwrote: Jason, I am trying to use haskell in the analysis of bio data. One of the main reasons I wanted to use haskell is because lazy I/O allows you to see a large bio-sequence as if it was a string in memory. In order

Re: [Haskell-cafe] Space leak

2010-03-13 Thread Rafael Almeida
On Sat, Mar 13, 2010 at 8:58 PM, Arnoldo Muller arnoldomul...@gmail.com wrote: Jason, I am trying to use haskell in the analysis of bio data. One of the main reasons I wanted to use haskell is because lazy I/O allows you to see a large bio-sequence as if it was a string in memory. In order

Re: [Haskell-cafe] Space leak

2010-03-13 Thread Brandon S. Allbery KF8NH
On Mar 13, 2010, at 18:58 , Arnoldo Muller wrote: In order to achieve the same result in an imperative language I would have to write lots of error-prone iterators. I saw lazy I/O as a very strong point in favor of Haskell. Besides the space leaks that can occur and that are a bit difficult

Re: [Haskell-cafe] Space leak

2010-03-13 Thread Daniel Fischer
Am Sonntag 14 März 2010 00:58:09 schrieb Arnoldo Muller: Jason, I am trying to use haskell in the analysis of bio data. One of the main reasons I wanted to use haskell is because lazy I/O allows you to see a large bio-sequence as if it was a string in memory. In order to achieve the same

Re: [Haskell-cafe] Space leak

2010-03-11 Thread Stephen Tetley
Hi Arnoldo This doesn't address the space leak, but your parseChromosome function looks very inefficient - isInfixOf is repeatedly checking the prefix chromosome for C1 to CY. If you have a lot of CY's in a file then it will do a lot of work parsing them. The cleanest way of handling this would

Re: [Haskell-cafe] Space leak

2010-03-11 Thread Daniel Fischer
Am Donnerstag 11 März 2010 00:24:28 schrieb Daniel Fischer: Hmm, offhand, I don't see why that isn't strict enough. Turns out, mapM_ was a red herring. The villain was (zip and map). I must confess, I don't know why it sort-of worked without the mapM_, though. sort-of, because that also hung on

Re: [Haskell-cafe] Space leak

2010-03-11 Thread Arnoldo Muller
Daniel, Thank you so much for helping me out with this issue! Thanks to all the other answers from haskel-cafe members too! As a newbie, I am not able to understand why zip and map would make a problem... Is there any link I could read that could help me to understand why in this case zip and

[Haskell-cafe] Space leak

2010-03-10 Thread Arnoldo Muller
Hello, I am learning haskell and I found a space leak that I find difficult to solve. I've been asking at #haskell but we could not solve the issue. I want to lazily read a set of 22 files of about 200MB each, filter them and then I want to output the result into a unique file. If I modify the

Re: [Haskell-cafe] Space leak

2010-03-10 Thread Bulat Ziganshin
Hello Arnoldo, Wednesday, March 10, 2010, 11:45:56 PM, you wrote: I am learning haskell and I found a space leak that I find difficult to solve. I've been asking at #haskell but we could not solve the issue. make some experiments - leave only one file and use version A, then replace

Re: [Haskell-cafe] Space leak

2010-03-10 Thread Daniel Fischer
Am Mittwoch 10 März 2010 21:45:56 schrieb Arnoldo Muller: Hello, I am learning haskell and I found a space leak that I find difficult to solve. I've been asking at #haskell but we could not solve the issue. I want to lazily read a set of 22 files of about 200MB each, filter them and then I

Re: [Haskell-cafe] Space leak

2010-03-10 Thread Arnoldo Muller
Hello Daniel: Thanks! I employed mapM'_ but I am still getting the space leak. Any other hint? Arnoldo On Wed, Mar 10, 2010 at 10:40 PM, Daniel Fischer daniel.is.fisc...@web.dewrote: Am Mittwoch 10 März 2010 21:45:56 schrieb Arnoldo Muller: Hello, I am learning haskell and I found a

Re: [Haskell-cafe] Space leak

2010-03-10 Thread Arnoldo Muller
Hello Bulat, I ran program A with writeFile instead of appendFile and it still works without problems. Regarding program B, if I use writeFile the leaking still occurs. Any other hints? :) Arnoldo On Wed, Mar 10, 2010 at 10:32 PM, Bulat Ziganshin bulat.zigans...@gmail.com wrote: Hello

Re: [Haskell-cafe] Space leak

2010-03-10 Thread Arnoldo Muller
Hello Justin, I tried and what I saw was a constant increase in memory usage. Any particular profiling option that you would use? I do remember that there was a particular option in which the leak would dissapear (for the same amount of work) and that is why I stopped using the profiler.

Re: [Haskell-cafe] Space leak

2010-03-10 Thread Bulat Ziganshin
Hello Arnoldo, Wednesday, March 10, 2010, 11:45:56 PM, you wrote: I am learning haskell and I found a space leak that I find difficult to solve. I've been asking at #haskell but we could not solve the issue. what if you use program B on single file? -- Best regards, Bulat

Re: [Haskell-cafe] Space leak

2010-03-10 Thread Arnoldo Muller
Bulat, The same happens, the memory starts to quickly fill up... Arnoldo On Wed, Mar 10, 2010 at 11:16 PM, Bulat Ziganshin bulat.zigans...@gmail.com wrote: Hello Arnoldo, Wednesday, March 10, 2010, 11:45:56 PM, you wrote: I am learning haskell and I found a space leak that I find

Re: [Haskell-cafe] Space leak

2010-03-10 Thread Daniel Fischer
Am Mittwoch 10 März 2010 23:01:28 schrieb Arnoldo Muller: Hello Daniel: Thanks! I employed mapM'_ but I am still getting the space leak. Any other hint? Hmm, offhand, I don't see why that isn't strict enough. With some datafiles, I could try to investigate. One question, how does programme

Re: [Haskell-cafe] Space Leak with semi-implicit parallelization and the nasty Garbage collector

2009-12-24 Thread Michael Lesniak
Hello Daniel, thanks for your fast response. That's strange: On your system total time elapsed according to GHC is ~190%, on mine (reproducible!) ~140% (see below). I once had a problem with a particular linux kernel[1], unfortunately I currently (over the holidays) have no other computers

Re: [Haskell-cafe] Space Leak with semi-implicit parallelization and the nasty Garbage collector

2009-12-23 Thread Daniel Fischer
Am Donnerstag 24 Dezember 2009 02:14:51 schrieb Michael Lesniak: Hello haskell-cafe (and merry christmas!), I have a strange problem with the garbage collector / memory which I'm unable to find a solution for. I think the source of my problems has to do with lazy evaluation, but currently I'm

[Haskell-cafe] space leak hints?

2009-07-03 Thread Uwe Hollerbach
Good evening, all, I wonder if I could tap your collective wisdom regarding space leaks? I've been messing about with haskeem, my little scheme interpreter, and I decided to see if I could make it run reasonably space-efficiently. So far... no. Here's what I tried: I wrote a tiny scheme program

[Haskell-cafe] space leak with 'concat' ?

2009-01-27 Thread Henning Thielemann
$ ghc +RTS -M16m -c30 -RTS -e 'concat $ repeat bla' This breaks down after a while, also if I increase the memory restriction: ... ablablablablablablablablablablablablablablablablablablablablablaHeap exhausted; Current maximum heap size is 15998976 bytes (15 Mb); use `+RTS -Msize' to increase

Re: [Haskell-cafe] space leak with 'concat' ?

2009-01-27 Thread Jonathan Cast
On Tue, 2009-01-27 at 22:12 +0100, Henning Thielemann wrote: $ ghc +RTS -M16m -c30 -RTS -e 'concat $ repeat bla' This breaks down after a while, also if I increase the memory restriction: ... ablablablablablablablablablablablablablablablablablablablablablaHeap exhausted; Current maximum

Re: [Haskell-cafe] space leak with 'concat' ?

2009-01-27 Thread Henning Thielemann
On Tue, 27 Jan 2009, Jonathan Cast wrote: To show that there's nothing wrong with concat per se, try this version instead: ghc +RTS -M16m -c30 -RTS -e 'print $ concat $ repeat bla' This should print forever without any problems. You are right, this works. My example was extracted from a

Re: [Haskell-cafe] space leak with 'concat' ?

2009-01-27 Thread Henning Thielemann
On Tue, 27 Jan 2009, Henning Thielemann wrote: On Tue, 27 Jan 2009, Jonathan Cast wrote: To show that there's nothing wrong with concat per se, try this version instead: ghc +RTS -M16m -c30 -RTS -e 'print $ concat $ repeat bla' This should print forever without any problems. You are

Re: [Haskell-cafe] space leak with 'concat' ?

2009-01-27 Thread Jake McArthur
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Henning Thielemann wrote: | in that module I defined the text to be printed as top-level | variable which might have been the problem. But this can't be the | problem of the compiled version of the program, where I encountered the | leak. So I have

Re: [Haskell-cafe] space leak with 'concat' ?

2009-01-27 Thread Sterling Clover
Note that only monomorphic declarations are CAFed. If you have an explicit polymorphic signature, it will be treated as a function and garbage-collected as usual. So if you have, e.g., a list of Doubles, declaring it as foo :: Num a = [a] would do the trick. Cheers, S. On Tue, Jan 27, 2009 at

[Haskell-cafe] Space leak with Data.Binary and decodeFile

2009-01-11 Thread Maxime Henrion
Hello all, I've been observing a huge space leak with some code using Data.Binary that I cannot make sense of and I hope someone here can shed some light on this, so I'll try to explain my problem as clearly as possible. I qualify the space leak as huge because if I let the program run, it

Re: [Haskell-cafe] Space leak - help needed

2008-03-14 Thread Justin Bailey
On Thu, Mar 13, 2008 at 4:50 PM, Krzysztof Kościuszkiewicz [EMAIL PROTECTED] wrote: Retainers are thunks or objects on stack that keep references to live objects. All retainers of an object are called the object's retainer set. Now when one makes a profiling run, say with ./jobname +RTS

Re: [Haskell-cafe] Space leak - help needed

2008-03-13 Thread Bertram Felgenhauer
Krzysztof Kościuszkiewicz wrote: I have tried both Poly.StateLazy and Poly.State and they work quite well - at least the space leak is eliminated. Now evaluation of the parser state blows the stack... The code is at http://hpaste.org/6310 Apparently, stUpdate is too lazy. I'd define

Re: [Haskell-cafe] Space leak - help needed

2008-03-13 Thread Krzysztof Kościuszkiewicz
On Thu, Mar 13, 2008 at 05:52:05PM +0100, Bertram Felgenhauer wrote: ... Now evaluation of the parser state blows the stack... The code is at http://hpaste.org/6310 Apparently, stUpdate is too lazy. I'd define stUpdate' :: (s - s) - Parser s t () stUpdate' f = stUpdate f

Re: [Haskell-cafe] Space leak - help needed

2008-03-13 Thread Krzysztof Kościuszkiewicz
On Wed, Mar 12, 2008 at 12:34:38PM -0700, Justin Bailey wrote: The stack blows up when a bunch of unevaluated thunks build up, and you try to evaluate them. One way to determine where those thunks are getting built is to use GHCs retainer profiling. Retainer sets will show you the call stack

Re: [Haskell-cafe] Space leak - help needed

2008-03-12 Thread Krzysztof Kościuszkiewicz
On Mon, Mar 03, 2008 at 05:20:09AM +0100, Bertram Felgenhauer wrote: Another story from an (almost) happy Haskell user that finds himself overwhelmed by laziness/space leaks. I'm trying to parse a large file (600MB) with a single S-expression like structure. With the help of

Re: [Haskell-cafe] Space leak - help needed

2008-03-12 Thread Justin Bailey
On Wed, Mar 12, 2008 at 12:12 PM, Krzysztof Kościuszkiewicz [EMAIL PROTECTED] wrote: I have tried both Poly.StateLazy and Poly.State and they work quite well - at least the space leak is eliminated. Now evaluation of the parser state blows the stack... The code is at

[Haskell-cafe] Space leak - help needed

2008-03-02 Thread Krzysztof Kościuszkiewicz
Dear Haskellers, Another story from an (almost) happy Haskell user that finds himself overwhelmed by laziness/space leaks. I'm trying to parse a large file (600MB) with a single S-expression like structure. With the help of ByteStrings I'm down to 4min processing time in constant space. However,

Re: [Haskell-cafe] Space leak - help needed

2008-03-02 Thread Luke Palmer
On Mon, Mar 3, 2008 at 2:23 AM, Krzysztof Kościuszkiewicz [EMAIL PROTECTED] wrote: Dear Haskellers, Another story from an (almost) happy Haskell user that finds himself overwhelmed by laziness/space leaks. I'm trying to parse a large file (600MB) with a single S-expression like

Re: [Haskell-cafe] Space leak - help needed

2008-03-02 Thread Bertram Felgenhauer
Krzysztof Kościuszkiewicz wrote: Another story from an (almost) happy Haskell user that finds himself overwhelmed by laziness/space leaks. I'm trying to parse a large file (600MB) with a single S-expression like structure. With the help of ByteStrings I'm down to 4min processing time in

Re: [Haskell-cafe] space leak?

2007-11-02 Thread Justin Bailey
Massimiliano, I had to update your code for it to compile (removed sequence from testpdf'. However, I don't see any significant difference in the memory profile of either testpdf or testpdf'. Not sure how you are watching the memory usage, but if you didn't know the option +RTS -sstderr will

[Haskell-cafe] space leak?

2007-11-02 Thread Massimiliano Gubinelli
( these two lines are just to fool the gmane post algorithm which complains for top-posting) Hi, i'm learning Haskell and trying to use the HPDF 1.2 library I've come across some large memory consumption for which I do not understand the origin. I've tried heap profiling but without

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Dominic Steinitz
On Saturday 03 February 2007 19:56, Pepe Iborra wrote: pad :: [Word8] - [Word8] pad xs = pad' xs 0 pad' (x:xs) l = x : pad' xs (succ l) pad' [] l = [0x80] ++ ps ++ lb     where        pl = (64-(l+9)) `mod` 64        ps = replicate pl 0x00        lb = i2osp 8 (8*l) Pepe, Thanks but this

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Stefan O'Rear
On Sun, Feb 04, 2007 at 08:20:23AM +, Dominic Steinitz wrote: Someone suggested pad :: Num a = [a] - [a] pad = pad' 0 where pad' !l [] = [0x80] ++ ps ++ lb where pl = (64-(l+9)) `mod` 64 ps = replicate pl 0x00 lb = i2osp 8 (8*l)

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Dominic Steinitz
On Saturday 03 February 2007 19:42, [EMAIL PROTECTED] wrote: I have re-written SHA1 so that is more idiomatically haskell and it is easy to see how it implements the specification. The only problem is I now have a space leak. I can see where the leak is but I'm less sure what to do

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Stefan O'Rear
On Sun, Feb 04, 2007 at 08:30:44AM +, Dominic Steinitz wrote: On Saturday 03 February 2007 19:42, [EMAIL PROTECTED] wrote: I would try something along the following lines (untested): \begin{spec} catWithLen xs f = xs ++ f (length xs) \end{spec} \begin{code} catWithLen :: [a] -

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Dominic Steinitz
On Sunday 04 February 2007 08:28, Stefan O'Rear wrote: On Sun, Feb 04, 2007 at 08:20:23AM +, Dominic Steinitz wrote: Someone suggested pad :: Num a = [a] - [a] pad = pad' 0 where pad' !l [] = [0x80] ++ ps ++ lb where pl = (64-(l+9)) `mod` 64 ps =

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Stefan O'Rear
On Sun, Feb 04, 2007 at 09:45:12AM +, Dominic Steinitz wrote: pad :: Num a = [a] - [a] pad = pad' 0 where pad' l [] | l `seq` False = undefined Stupid typo, that should be: where pad' l _ | l `seq` False = undefined pad' l [] = [0x80] ++ ps ++ lb where pl =

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread kahl
\begin{code} catWithLen :: [a] - (Int - [a]) - [a] catWithLen xs f = h 0 xs where h k [] = f k h k (x : xs) = case succ k of-- forcing evaluation k' - x : h k' xs \end{code} Thanks but this gives a different problem:

[Haskell-cafe] Space Leak Help

2007-02-03 Thread Dominic Steinitz
I have re-written SHA1 so that is more idiomatically haskell and it is easy to see how it implements the specification. The only problem is I now have a space leak. I can see where the leak is but I'm less sure what to do about getting rid of it. Here's the offending function: pad :: [Word8]

Re: [Haskell-cafe] Space Leak Help

2007-02-03 Thread kahl
I have re-written SHA1 so that is more idiomatically haskell and it is easy to see how it implements the specification. The only problem is I now have a space leak. I can see where the leak is but I'm less sure what to do about getting rid of it. Here's the offending

Re: [Haskell-cafe] Space Leak Help

2007-02-03 Thread Pepe Iborra
hi Dominic Explicit recursion works just fine for me and keeps things simple: pad :: [Word8] - [Word8] pad xs = pad' xs 0 pad' (x:xs) l = x : pad' xs (succ l) pad' [] l = [0x80] ++ ps ++ lb where pl = (64-(l+9)) `mod` 64 ps = replicate pl 0x00 lb = i2osp 8 (8*l) at the

[Haskell-cafe] Space leak whilst implementing streams

2006-08-26 Thread ephemeral . elusive
Hello, I have been using arrows to implement stream processors. At first, I tried using the implementation presented in John Hughes' AFP arrows lectures. However, this appeared to have a space leak in its implementation of the left operator for ArrowChoice. I found a way to remove this space

Re: [Haskell-cafe] Space leak whilst implementing streams

2006-08-26 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: I found a way to remove this space leak, however, I do not really understand why there was a space leak in the first place. I would really appreciate any light that could be shed on this. instance ArrowChoice SF where left (SF f) = SF (\xs - combine xs (f [y

[Haskell-cafe] Space leak when returning pairs?

2006-05-19 Thread Shin-Cheng Mu
Dear members, I am experiencing a space leak, which I suspect to be an instance of the problem addressed by Wadler before. I'd appreciate if someone here would take a look. Given the following datatype: data XMLEvent = StartEvent String | EndEvent String |

Re: [Haskell-cafe] Space leak when returning pairs?

2006-05-19 Thread Henning Thielemann
On Fri, 19 May 2006, Shin-Cheng Mu wrote: idX :: [XMLEvent] - ([XMLEvent], [XMLEvent]) idX [] = ([], []) idX (StartEvent a : strm) = let (ts, strm') = idX strm (us, strm'') = idX strm' in (StartEvent a [] : ts ++ EndEvent a : us, strm'') idX (EndEvent _:

Re: [Haskell-cafe] Space leak when returning pairs?

2006-05-19 Thread Shin-Cheng Mu
Dear Henning, On May 19, 2006, at 6:16 PM, Henning Thielemann wrote: On Fri, 19 May 2006, Shin-Cheng Mu wrote: idX :: [XMLEvent] - ([XMLEvent], [XMLEvent]) idX (StartEvent a : strm) = let (ts, strm') = idX strm (us, strm'') = idX strm' in (StartEvent a [] : ts ++

Re: [Haskell-cafe] Space leak when returning pairs?

2006-05-19 Thread Malcolm Wallace
Henning Thielemann [EMAIL PROTECTED] wrote: let ~(ts, strm') = idX strm ~(us, strm'') = idX strm' Let-bindings are already lazy, so the ~ here is redundant. Regards, Malcolm ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Space leak when returning pairs?

2006-05-19 Thread Shin-Cheng Mu
On May 19, 2006, at 6:16 PM, Henning Thielemann wrote: let ~(ts, strm') = idX strm ~(us, strm'') = idX strm' I seem to have found a partial solution to the problem. It's rather ugly, however, and I think there should be a better way. The original definition for one of the clauses was

Re: [Haskell-cafe] Space leak when returning pairs?

2006-05-19 Thread Chris Kuklewicz
Shin-Cheng Mu wrote: Dear members, I am experiencing a space leak, which I suspect to be an instance of the problem addressed by Wadler before. I'd appreciate if someone here would take a look. Given the following datatype: data XMLEvent = StartEvent String | EndEvent

Re: [Haskell-cafe] Space leak when returning pairs?

2006-05-19 Thread Malcolm Wallace
Shin-Cheng Mu [EMAIL PROTECTED] wrote: I was wondering where the space leak came from and suspected that it's the leak described in one of Philip Wadler's early paper Fixing Some Space Leaks With a Garbage Collector (1987). But since Wadler has addressed this problem a long time ago, I