[Arrays] Random Access Times ?

Ron de Bruijn rondebruijn@yahoo.com
Sat, 3 May 2003 10:37:32 -0700 (PDT)


Hi there,

I tested below program with for x filled in 1 and
50000. And I saw that when I used 50000 it took more
than ten times more time than when I used 1, to
complete the expression. So much for randow access
memory(RAM). 

Isn't there somekind of other array that really works
with random access? 

module Test where

import IOExts

data Lesson = Lesson String Int Int String String
	deriving Show

main = do
	testing <- newIOArray (0,60000) (Lesson "Hallo" 0 0
"" "")
	sequence(map(writeIOArray testing x) (test))
	a<-readIOArray testing 0
	putStr (decompose a)
	
test::[Lesson]
test=(replicate 100000 (Lesson "" 1 2 "" ""))

decompose (Lesson s1 _ _ _ _) = s1

Greets Ron



__________________________________
Do you Yahoo!?
The New Yahoo! Search - Faster. Easier. Bingo.
http://search.yahoo.com