[Haskell-cafe] Performance Issue

Daniel Fischer daniel.is.fischer at web.de
Thu Feb 26 13:38:44 EST 2009


Am Donnerstag, 26. Februar 2009 18:48 schrieb Luke Palmer:
> 2009/2/26 James Swaine <james.swaine at gmail.com>
>
> > --gets r[k], which is the value at the kth
> > --position in the overall sequence of
> > --pseudorandom numbers
> > getRandAt :: Int64 -> Int64 -> Float
> > getRandAt 0 seed = multiplier * (fromIntegral seed)
> > getRandAt k seed = multiplier * (fromIntegral x_next)
> >     where
> >         x_prev = (a^k * seed) `mod` divisor
> >         x_next = (a * x_prev) `mod` divisor
>
> One thing that comes to mind is that this exponentiation, with a very big
> exponent, could potentially take a very long time. I believe that GHC
> implements (^) using a repeated squaring technique, so it runs in log(k)
> time, which ought to be no problem.  I'm not sure about other compilers
> though.

Another thing: if you don't need to pick random indices, but use them in 
order, it may be faster to have a list of the random numbers :

randInts = iterate ((`mod` divisor) . (*a)) seed

or carry x[k] around as state.

>
> Also note:
>
> (a^k * seed) `mod` divisor = ((a^k `mod` divisor) * seed) `mod` divisor =
> (a^(k `mod` phi(divisor)) * seed) `mod` divisor.
>
> Where phi is the Euler totient function: phi(2^46) = 2^23.

phi(2^n) = 2^(n-1).

Apart from that, correct.

>
> Modulo errors... it's been a while since I've done this stuff.
>
> Luke



More information about the Haskell-Cafe mailing list