{- |
Very simple random number generator
which should be fast and should suffice for generating just noise.
<http://www.softpanorama.org/Algorithms/random_generators.shtml>
-}
module Synthesizer.RandomKnuth (T, cons, ) where

import qualified System.Random as R


newtype T = Cons Int
   deriving Int -> T -> ShowS
[T] -> ShowS
T -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [T] -> ShowS
$cshowList :: [T] -> ShowS
show :: T -> String
$cshow :: T -> String
showsPrec :: Int -> T -> ShowS
$cshowsPrec :: Int -> T -> ShowS
Show


{-# INLINE cons #-}
cons :: Int -> T
cons :: Int -> T
cons = Int -> T
Cons


{-# INLINE factor #-}
factor :: Int
factor :: Int
factor = Int
40692

{-# INLINE modulus #-}
modulus :: Int
modulus :: Int
modulus = Int
2147483399 -- 2^31-249

{-
We have to split the 32 bit integer in order to avoid overflow on multiplication.
'split' must be chosen, such that 'splitRem' is below 2^16.
-}
{-# INLINE split #-}
split :: Int
split :: Int
split = forall a. Enum a => a -> a
succ forall a b. (a -> b) -> a -> b
$ forall a. Integral a => a -> a -> a
div Int
modulus Int
factor

{-# INLINE splitRem #-}
splitRem :: Int
splitRem :: Int
splitRem = Int
split forall a. Num a => a -> a -> a
* Int
factor forall a. Num a => a -> a -> a
- Int
modulus


instance R.RandomGen T where
   {-# INLINE next #-}
   next :: T -> (Int, T)
next (Cons Int
s) =
      -- efficient computation of @mod (s*factor) modulus@ without Integer
      let (Int
sHigh, Int
sLow) = forall a. Integral a => a -> a -> (a, a)
divMod Int
s Int
split
      in  (Int
s, Int -> T
Cons forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Integral a => a -> a -> a
mod Int
modulus forall a b. (a -> b) -> a -> b
$
                   Int
splitRemforall a. Num a => a -> a -> a
*Int
sHigh forall a. Num a => a -> a -> a
+ Int
factorforall a. Num a => a -> a -> a
*Int
sLow)
   {-# INLINE split #-}
   split :: T -> (T, T)
split (Cons Int
s) = (Int -> T
Cons (Int
sforall a. Num a => a -> a -> a
*Int
s), Int -> T
Cons (Int
13forall a. Num a => a -> a -> a
+Int
s))
   {-# INLINE genRange #-}
   genRange :: T -> (Int, Int)
genRange T
_ = (Int
1, forall a. Enum a => a -> a
pred Int
modulus)
{-
*Main> let s = 10000000000 in (next (Cons s), mod (fromIntegral s * fromIntegral factor) (fromIntegral modulus) :: Integer)
((1410065408,Cons 1920127854),1920127854)
-}