[Arrays] Random Access Times ?
Derek Elkins
ddarius@hotpop.com
Sat, 3 May 2003 14:30:54 -0400
On Sat, 3 May 2003 10:37:32 -0700 (PDT)
Ron de Bruijn <rondebruijn@yahoo.com> wrote:
> 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
Haskell is a lazy language. It may be that Hugs lazily fills the array,
in which case writing to index 1 will only force it to write out 3
elements (index 0,1 and what you are writing). Writing to 50000 would
force it to write out 0-50000 first. Try touching each element of the
array, then timing lookup.