--------------------------------------------------------------------
-- |
-- Module    : Data.Vector.Random.Mersenne
-- Copyright : (c) Don Stewart 2010

-- License   : BSD3
--
-- Maintainer: Don Stewart <dons@galois.com>
-- Stability : provisional
-- Portability:
--
-- Generator for vectors of differen types
--

module Data.Vector.Random.Mersenne (random) where

import qualified System.Random.Mersenne     as R

import qualified Data.Vector.Generic         as G
import qualified Data.Vector.Generic.Mutable as GM

import Control.Monad.ST

-- | Return a random vector of length @n@, filled with random elements
-- of type @a@ generated by the mersenne-twister.
--
-- E.g. to compute the sum of 100 million random Double values in a vector:
--
-- > import qualified Data.Vector.Unboxed as U
-- > import System.Random.Mersenne
-- > import qualified Data.Vector.Random.Mersenne as G
-- > 
-- > main = do
-- >     g <- newMTGen Nothing
-- >     a <- G.random g 10000000 :: IO (U.Vector Double) -- 100 M
-- >     print (U.sum a)
--
random :: (R.MTRandom a, G.Vector v a) => R.MTGen -> Int -> IO (v a)
random g n = do
    v  <- GM.new n
    fill v 0
    G.unsafeFreeze v
  where
    fill v i
        | i < n = do
            x <- R.random g
            GM.unsafeWrite v i x
            fill v (i+1)
        | otherwise = return ()