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

Reply via email to