Someone else already replied with much information.  I figured I'd try
to add a small amount.

Basically, to clarify, the problem is that at every character you read,
you do something like 'arr // list'.  (//) is *not* an O(1) operation as
you might expect.  In fact, it *copies* the entire array.  Why?  Because
if you later reference the old one, it needs to have a "backup" version.
The solution, if you want to use arrays, is basically to use a mutable
state array, like IO(U)Array or ST(U)Array.

However, you might be better off using a different data structure.  An
easy solution would be to use a finite map from Data.FiniteMap.  You'll
incur a little overhead, but then again, the distribution of letters in
natural language text is anything but flat; some you will likely never
see and you're wasting space in your array for these.

Of course, you could use a more informed coding tree based on letter
distributions, but this is probably overkill.

--
 Hal Daume III                                   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume


> -----Original Message-----
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of mies
> Sent: Thursday, June 19, 2003 2:11 AM
> To: [EMAIL PROTECTED]
> Subject: Array + memory usage
> 
> 
> Hello, i'm a haskell newbie, and i'm trying to use arrays for 
> counting 
> letters. But when I input a textfile of lets say 100KB the 
> program uses 
> 75 M of memory, and I really don;t have a clue where the 
> problem could 
> be. I have searched many topics here but I didn't find a solution. I 
> have made an axample of how i am using the array.
> 
> module Main where
> 
> import Array
> import IO
> 
> main = do let fr = testUpdater f 100000
>           writeFile "test.txt" (show (fr!155))
> 
> f :: Array Int Int
> f = (array (0,255) [(i, 0) | i <- [0..255]])
> 
> testUpdater :: Array Int Int -> Int -> Array Int Int 
> testUpdater fr 0 = fr testUpdater fr x = testUpdater 
> ((fr//[(155, fr!(155) + 1)])) (x - 1)
> 
> updateF :: Array Int Int -> Array Int Int
> updateF x = (x//[(155, x!(155) + 1)])
> 
> Regards, Richard Nieuwenhuis
> [EMAIL PROTECTED]
> 
> _______________________________________________
> Haskell mailing list
> [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
> 
_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to