Prng_Class Module

module~~prng_class~~UsesGraph module~prng_class Prng_Class module~variablekind variableKind module~variablekind->module~prng_class module~m_strings m_strings module~variablekind->module~m_strings module~m_errors m_errors module~variablekind->module~m_errors module~m_allocate m_allocate module~variablekind->module~m_allocate module~m_indexing m_indexing module~variablekind->module~m_indexing module~m_time m_time module~variablekind->module~m_time module~m_parameters m_parameters module~variablekind->module~m_parameters module~m_unittester m_unitTester module~variablekind->module~m_unittester module~m_strings->module~prng_class module~m_errors->module~prng_class module~m_errors->module~m_strings module~m_errors->module~m_allocate module~m_errors->module~m_unittester module~m_allocate->module~prng_class iso_fortran_env iso_fortran_env iso_fortran_env->module~prng_class iso_fortran_env->module~variablekind iso_fortran_env->module~m_strings iso_fortran_env->module~m_errors iso_fortran_env->module~m_unittester module~m_indexing->module~prng_class module~m_time->module~prng_class module~m_parameters->module~m_strings module~m_unittester->module~m_allocate
Help

Prng Class

Class providing a pseudo-random number generator with an xorshift128+ or xorshift1024* generator that are both suitable for parallel applications. This is class is thread safe, and can be used in parallel without Prngs on different threads affecting each other.

If you are writing serial code, and/or do not need a parallel random number generator, you can use the overloaded functions and subroutines in m_random. See that module for more information.

Side note: The default random number generator in Matlab and Python is the Mersenne Twister algorithm. This algorithm is not great for parallel applications. It has a huge period, but you cannot easily jump the state as far as I can tell. These xorshift algorithms are fantastic, they have a high enough period for most applications, and can be easily jumped in only a few iterations.

Example Serial usage with a randomly generated seed

program PrngTest

use Prng_Class, only: Prng

implicit none

type(Prng) :: rng
integer(i64) :: seed(16)
integer(i32) :: i, id

real(r64) :: a

! Use a constructor to initialize the Prng with a random seed
! Using display = .true. will print the randomly generated seed to the screen
! So you can reproduce any results later if you wish.
rng = Prng(big = .true., display = .true.)

! Or you could have set the seed using this
! seed = [Some numbers, size 16 if big == .true., size 2 if big == .false.]
! and you can use rng = Prng(seed, .true., .true.)

! Draw from a uniform distribution
call rng%rngUniform(a)

! Draw an integer between 1 and 100 inclusive
call rng%rngInteger(id, 1, 100)

! Other distributions
call rng%rngNormal(a)
call rng%rngExponential(a, 1.d0)
call rng%rngWeibull(a, 1.d0, 1.d0)
stop
end program

Example parallel usage using OpenMP

program PrngTest

use omp_lib
use Prng_Class, only: Prng, getRandomSeed

implicit none

type(Prng), allocatable :: rng(:) ! Array of Prng classes, one for each thread
integer(i64) :: seed(16) ! Use xorshift1024*, so the seed is size 16
integer(i32) :: i, id
integer(i32) :: nThreads, iThread

real(r64) :: a

! Get a randomly generated seed
call getRandomSeed(seed, .true.)

! Get the number of threads available
!$omp parallel 
  nThreads = omp_get_num_threads()
!$omp end parallel

! Allocate an array of Prngs, one for each thread
allocate(rng(nThreads))

! In parallel, initialize each Prng with the same seed, and jump each prng by the thread ID it is associated with.
! This allows all Prngs to draw from the same stream, but at different points along the stream.
! This is better than giving each Prng its own randomly generated seed.

!$omp parallel shared(rng, seed) private(iThread, a)
  iThreads = omp_get_thread_num()
  rng(iThread + 1) = Prng(seed, big = .true.)
  call rng(iThread + 1)%jump(iThread) ! Jump the current thread's Prng by its thread number.
  call rng(iThread + 1)%rngNormal(a) ! Draw from normal distribution on each thread
!$omp end parallel

stop
end program

xorshift128+

This module contains routines to generate random numbers using the xorshift128+ method by Vigna's extensions to Marsaglia, G., 2003. Xorshift RNGs. Journal of Statistical Software 8, 1 - 6.

This module is a modified version of the public domain code written by Shun Sakuraba in 2015-2016. The original code can be found here. The modified code in coretran is distributed under the coretran license, see the repository for that information.

Vigna's xorshift128+ pseudorandom generator. Sebastiano Vigna. 2014. Further scramblings of Marsaglia's xorshift generators. CoRR, abs/1402.6246. xorshift128+ is known as a fast pseudorandom generator with reasonably good resilience to randomness tests. Since its primary imporance is its speed, do not forget to add inlining directives depending your compiler.

Why xorshift128+ ?

The seed of the xorshift128+ can be jumped by k cycles, where each cycle jumps ahead by \(2^{64}\) random numbers, but quickly. This ability to jump is an important aspect for using random number generators in general but especially in parallel in either OpenMP or MPI paradigms. The time taken to generate a 64 bit integer was 1.06 ns on an IntelR CoreTM i7-4770 CPU @3.40GHz (Haswell) as shown in Vigna (2014). xorshift128+ is the better for less massively parallel applications.

If the period of the random number generator is too small for your application, consider using the xorshift1024* generator which has a period of \(2^{512}\) numbers. The time to generate a 64 bit integer is slightly slower at 1.36 ns

xorshift1024*

This module contains routines to generate random numbers using the xorshift1024* method by Vigna's extensions to Marsaglia, G., 2003. Xorshift RNGs. Journal of Statistical Software 8, 1 - 6.

This module is a modified version of the public domain code written by Shun Sakuraba in 2015-2016. The original code can be found here. The modified code in coretran is distributed under the coretran license, see the repository for that information.

Vigna's xorshift1024 pseudorandom generator. Sebastiano Vigna. 2014. An experimental exploration of Marsaglia's xorshift generators, scrambled. CoRR, abs/1402.6246. xorshift1024 is a pseudorandom generator with reasonable speed and a good size state space.

Why xorshift1024* ?

The seed of the xorshift1024 can be jumped by k cycles, where each cycle jumps ahead by \(2^{512}\) random numbers, but quickly. This ability to jump is an important aspect for using random number generators in general but especially in parallel in either OpenMP or MPI paradigms. The time taken to generate a 64 bit integer was 1.36 ns on an IntelR CoreTM i7-4770 CPU @3.40GHz (Haswell) as shown in Vigna (2014). xorshift1024 is better for massively parallel applications that draw many realizations.

If the size of the random number generator is too much for your application, consider using the xorshift128+ generator which has a period of \(2^{64}\) numbers. The time to generate a 64 bit integer is faster at 1.06 ns

Used By

module~~prng_class~~UsedByGraph module~prng_class Prng_Class module~m_tests m_tests module~prng_class->module~m_tests module~m_random m_random module~prng_class->module~m_random program~test_coretran test_coretran module~m_tests->program~test_coretran module~m_random->module~m_tests module~m_random->program~test_coretran module~m_array1d m_array1D module~m_random->module~m_array1d program~scaletest_coretran scaleTest_coretran module~m_random->program~scaletest_coretran module~m_array1d->module~m_tests module~m_array1d->program~scaletest_coretran module~m_kdtree m_KdTree module~m_array1d->module~m_kdtree module~m_maths m_maths module~m_array1d->module~m_maths module~m_kdtree->module~m_tests module~m_kdtree->program~scaletest_coretran module~m_maths->module~m_tests module~m_maths->program~scaletest_coretran module~m_maths->module~m_kdtree
Help


Interfaces

public interface Prng

Overloaded Initializer for a Prng - Pseudo random number generator. Thread safe, xorshift1024* or xorshift128+ generator than can draw from different distributions. See Prng_Class for more information on how to use this class.

  • private function initWithSetseed_Prng(seed, big) result(this)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=i64), intent(in) :: seed(:)

    Fixed seeds of 64 bit integers. If big == true, must be length 16 else must be length 2.

    logical, intent(in), optional :: big

    Use the high period xorshift1024* (true) or xorshift128+ (false). Default is false.

    Return Value type(Prng)

    Prng Class

  • private function initWithRandomSeed_Prng(big, display) result(this)

    Arguments

    Type IntentOptional AttributesName
    logical, intent(in), optional :: big

    Use the high period xorshift1024* (true) or xorshift128+ (false). Default is false.

    logical, intent(in), optional :: display

    Display the randomly generated seed to the screen for reproducibility

    Return Value type(Prng)

    Prng Class

interface

  • public subroutine rngExponential_unscaled_d1(this, res)

    Arguments

    Type IntentOptional AttributesName
    class(Prng) :: this

    Prng Class

    real(kind=r64) :: res

    Draw from exponential distribution


Derived Types

type, public :: Prng

Class that generates pseudo random numbers. See Prng_Class for more information on how to use this class.

Components

TypeVisibility AttributesNameInitial
integer(kind=i64), public :: seed(0:15) =0
integer(kind=i32), public :: ptr
logical, public :: big

Constructor

Overloaded Initializer for a Prng - Pseudo random number generator. Thread safe, xorshift1024* or xorshift128+ generator than can draw from different distributions. See Prng_Class for more information on how to use this class.

private function initWithSetseed_Prng(seed, big)
private function initWithRandomSeed_Prng(big, display)

Type-Bound Procedures

procedure, public :: jump => jump_Prng

Jumps the Prng by \(2^{64}\) numbers if the Prng was instantiated with big = .false. or \(2^{512}\) if big = .true. This allows the Prng to be used correctly in parallel on multiple threads for OpenMP, or ranks for MPI.

generic, public :: rngExponential => rngExponential_d1_Prng_, rngExponential_d1D_Prng_, rngExponential_d2D_Prng_, rngExponential_d3D_Prng_

Prng%rngExponential() - Draw from an exponential distribution $$y = \frac{-ln(\tilde{u})}{\lambda}$$ where \(\tilde{u}\) is a sample from a uniform distribution

generic, public :: rngInteger => rngInteger_i1_Prng_, rngInteger_i1D_Prng_, rngInteger_i2D_Prng_, rngInteger_i3D_Prng_

Prng%rngInteger() - Draw a random integer in the interval \(x_{0} <= \tilde{u} <= x_{1}\) $$y = x_{0} + (\tilde{u} * x_{1})$$ where \(\tilde{u}\) is a sample from a uniform distribution, and integers are generated such that \(x_{0} <= \tilde{u} <= x_{1}\).

generic, public :: rngNormal => rngNormal_d1_Prng_, rngNormal_d1D_Prng_, rngNormal_d2D_Prng_, rngNormal_d3D_Prng_

Prng%rngNormal() - Draw from a normal distribution.

generic, public :: rngUniform => rngUniform_d1_Prng_, rngUniform_d1D_Prng_, rngUniform_d2D_Prng_, rngUniform_d3D_Prng_

Prng%rngUniform() - Draw from a uniform distribution Draws uniform random numbers on (0, 1) using either the xorshift1024* or xorshift128+ algorithms.

generic, public :: rngWeibull => rngWeibull_d1_Prng_, rngWeibull_d1D_Prng_, rngWeibull_d2D_Prng_, rngWeibull_d3D_Prng_

Prng%rngWeibull() - Draw from a Weibull distribution $$y = \left[ \frac{-1}{\lambda} ln(\tilde{u}) \right]^{\frac{1}{k}}$$ where \(\tilde{u}\) is a sample from a uniform distribution and \(\frac{-1}{\lambda} ln(\tilde{u})\) is a draw from an exponential distribution.


Subroutines

public subroutine getRandomSeed(seed, big)

Gets a randomly generated seed by getting the current integer time and then using a splitmix algorithm to generate the necessary number of seeds.

Arguments

Type IntentOptional AttributesName
integer(kind=i64), intent(inout) :: seed(:)

Random seeds of 64 bit integers. If big == true, must be size 16 else must be size 2.

logical, intent(in), optional :: big

Use the high period xorshift1024* (true) or xorshift128+ (false). Default is false.

public subroutine rngUniform_xorshift(this, val)

Arguments

Type IntentOptional AttributesName
class(Prng), intent(inout) :: this
real(kind=r64), intent(out) :: val