For uniform variates on (0, 1) the mean is 0.5 and the mean absolute deviation from 0.5 is 0.25. Given uniform variate x1 one can construct variates x2, x3, x4 so that for the 4 variates the mean and mean absolute deviation from 0.5 match the theoretical values. For integrals from 0 to 1 of a few functions (x^2, exp(x), log(1+x)) using groups of 4 variates constructed this way gave much more accurate results than 4 independent uniform variates and was also faster (since generating random variates has a cost). For the code
module mc_func_mod
implicit none
private
public :: dp, ifunc, f, f_integral, f_name
integer, parameter :: dp = selected_real_kind(15, 307), ifunc = 1
contains
elemental function f(x)
! function to integrate
real(kind=dp), intent(in) :: x
real(kind=dp) :: f
select case (ifunc)
case (1) ; f = x**2
case (2) ; f = exp(x)
case (3) ; f = log(1+x)
end select
end function f
!
elemental function f_integral(jfunc)
! value of integral from 0 to 1 of f
integer, intent(in) :: jfunc
real(kind=dp) :: f_integral
select case (jfunc)
case (1) ; f_integral = 1/3.0_dp
case (2) ; f_integral = exp(1.0_dp) - 1
case (3) ; f_integral = 2.0_dp * log(2.0_dp) - 1
end select
end function f_integral
!
elemental function f_name(jfunc)
! name of function
integer, intent(in) :: jfunc
character (len=10) :: f_name
select case (jfunc)
case (1) ; f_name = "x^2"
case (2) ; f_name = "exp(x)"
case (3) ; f_name = "log(1+x)"
end select
end function f_name
end module mc_func_mod
!
program monte_carlo
use iso_fortran_env, only: compiler_version, compiler_options
use mc_func_mod, only: dp, f, ifunc, f_integral, f_name
implicit none
integer, parameter :: nsim = 100, nran = (10**6)/4, i64=selected_int_kind(15)
integer :: i, j, imethod
integer(kind=i64) :: itick, t1, t2
real(dp) :: estimates(nsim)
real(dp) :: x1, x2, x3, x4, fsum, std_dev, mean_estimates, sum_sq_diff, start_time, end_time
character (len=10) :: methods(2) = ["ordinary ", "antithetic"]
print*,"compiler version: ",trim(compiler_version())
print*,"compiler options: ",trim(compiler_options())
call system_clock(count_rate=itick)
print*,"#random variates: ", nran*4
print*,"ifunc: ",ifunc
print*,"function: ",trim(f_name(ifunc))
do_method: do imethod = 1,2
print "(/,a)", "method: " // trim(methods(imethod))
call system_clock(t1)
call cpu_time(start_time)
do i = 1, nsim
fsum = 0.0_dp
do j = 1, nran
if (imethod == 1) then ! 4 separate uniform variates
call random_number(x1)
call random_number(x2)
call random_number(x3)
call random_number(x4)
else ! 1 uniform variate and 3 related variates
call random_number(x1)
if (x1 < 0.5_dp) then
x2 = 0.5_dp - x1 ! set x2 so that average of x1 and x2 is 0.25
else
x2 = 1.5_dp - x1 ! set x2 so that average of x1 and x2 is 0.75
end if
! reflect x1 and x2 across 0.5 to get x3 and x4
x3 = 1 - x1
x4 = 1 - x2
end if
fsum = fsum + f(x1) + f(x2) + f(x3) + f(x4)
end do
estimates(i) = fsum / (4 * real(nran, dp))
end do
mean_estimates = sum(estimates) / nsim
sum_sq_diff = sum((estimates - mean_estimates)**2)
std_dev = sqrt(sum_sq_diff / real(nsim, dp))
call cpu_time(end_time)
call system_clock(t2)
print*, "Estimated value: ", mean_estimates
print*, "Absolute error: ", abs(mean_estimates - f_integral(ifunc))
print*, "Standard error: ", std_dev/sqrt(real(nsim, kind=dp))
print*, "Execution time: ", end_time - start_time, " seconds"
print*, "Wall time: ", (t2-t1)/real(itick, kind=dp), " seconds"
end do do_method
end program monte_carlo
I got results with gfortran -O3 -march=native -flto with ifunc=1 of
compiler version: GCC version 14.0.0 20230604 (experimental)
compiler options: -march=skylake -mmmx -mpopcnt -msse -msse2 -msse3 -mssse3 -msse4.1 -msse4.2 -mavx -mavx2 -mno-sse4a -mno-fma4 -mno-xop -mfma -mno-avx512f -mbmi -mbmi2 -maes -mpclmul -mno-avx512vl -mno-avx512bw -mno-avx512dq -mno-avx512cd -mno-avx512er -mno-avx512pf -mno-avx512vbmi -mno-avx512ifma -mno-avx5124vnniw -mno-avx5124fmaps -mno-avx512vpopcntdq -mno-avx512vbmi2 -mno-gfni -mno-vpclmulqdq -mno-avx512vnni -mno-avx512bitalg -mno-avx512bf16 -mno-avx512vp2intersect -mno-3dnow -madx -mabm -mno-cldemote -mclflushopt -mno-clwb -mno-clzero -mcx16 -mno-enqcmd -mf16c -mfsgsbase -mfxsr -mno-hle -msahf -mno-lwp -mlzcnt -mmovbe -mno-movdir64b -mno-movdiri -mno-mwaitx -mno-pconfig -mno-pku -mno-prefetchwt1 -mprfchw -mno-ptwrite -mno-rdpid -mrdrnd -mrdseed -mno-rtm -mno-serialize -mno-sgx -mno-sha -mno-shstk -mno-tbm -mno-tsxldtrk -mno-vaes -mno-waitpkg -mno-wbnoinvd -mxsave -mxsavec -mxsaveopt -mxsaves -mno-amx-tile -mno-amx-int8 -mno-amx-bf16 -mno-uintr -mno-hreset -mno-kl -mno-widekl -mno-avxvnni -mno-avx512fp16 -mno-avxifma -mno-avxvnniint8 -mno-avxneconvert -mno-cmpccxadd -mno-amx-fp16 -mno-prefetchi -mno-raoint -mno-amx-complex --param=l1-cache-size=32 --param=l1-cache-line-size=64 --param=l2-cache-size=8192 -mtune=skylake -O3 -flto
#random variates: 1000000
ifunc: 1
function: x^2
method: ordinary
Estimated value: 0.33337875894428776
Absolute error: 4.5425610954441531E-005
Standard error: 2.8270602516907821E-005
Execution time: 1.2968750000000000 seconds
Wall time: 1.3189625000000000 seconds
method: antithetic
Estimated value: 0.33333553788588632
Absolute error: 2.2045525530089982E-006
Standard error: 3.6637637330178165E-006
Execution time: 0.32812500000000000 seconds
Wall time: 0.33898689999999998 seconds
and for ifunc=2
#random variates: 1000000
ifunc: 2
function: exp(x)
method: ordinary
Estimated value: 1.7182745325322504
Absolute error: 7.2959267947148021E-006
Standard error: 4.8536724073670133E-005
Execution time: 5.9843750000000000 seconds
Wall time: 5.9756036000000003 seconds
method: antithetic
Estimated value: 1.7182820841485560
Absolute error: 2.5568951089738334E-007
Standard error: 3.2167852470787950E-006
Execution time: 5.0000000000000000 seconds
Wall time: 5.0001290999999997 seconds
and for ifunc=3
#random variates: 1000000
ifunc: 3
function: log(1+x)
method: ordinary
Estimated value: 0.38628603900688629
Absolute error: 8.3221130042776537E-006
Standard error: 1.8752880904260943E-005
Execution time: 3.8281250000000000 seconds
Wall time: 3.8361136000000000 seconds
method: antithetic
Estimated value: 0.38629384765015679
Absolute error: 5.1346973378718630E-007
Standard error: 7.8368582622719970E-007
Execution time: 2.7812500000000000 seconds
Wall time: 2.7909590000000000 seconds
I get similar results with ifort -O3. I wonder how well this method generalizes to higher-dimensional Monte Carlo integration.
ETA: Antithetic variates are a known technique for variance reduction. The Wikipedia article discusses combining uniform variate x with 1-x, but with the revised code below I find that using 4 related variates works even better.
Revised code and results:
module mc_func_mod
implicit none
private
public :: dp, ifunc, f, f_integral, f_name
integer, parameter :: dp = selected_real_kind(15, 307), ifunc = 3
contains
elemental function f(x)
! function to integrate
real(kind=dp), intent(in) :: x
real(kind=dp) :: f
select case (ifunc)
case (1) ; f = x**2
case (2) ; f = exp(x)
case (3) ; f = log(1+x)
end select
end function f
!
elemental function f_integral(jfunc)
! value of integral from 0 to 1 of f
integer, intent(in) :: jfunc
real(kind=dp) :: f_integral
select case (jfunc)
case (1) ; f_integral = 1/3.0_dp
case (2) ; f_integral = exp(1.0_dp) - 1
case (3) ; f_integral = 2.0_dp * log(2.0_dp) - 1
end select
end function f_integral
!
elemental function f_name(jfunc)
! name of function
integer, intent(in) :: jfunc
character (len=10) :: f_name
select case (jfunc)
case (1) ; f_name = "x^2"
case (2) ; f_name = "exp(x)"
case (3) ; f_name = "log(1+x)"
end select
end function f_name
end module mc_func_mod
!
program monte_carlo
use iso_fortran_env, only: compiler_version, compiler_options
use mc_func_mod, only: dp, f, ifunc, f_integral, f_name
implicit none
integer, parameter :: nsim = 100, nran = (10**6)/4, i64 = selected_int_kind(15), nmethods = 3
integer :: i, j, imethod
integer(kind=i64) :: itick, t1, t2
real(dp) :: estimates(nsim)
real(dp) :: x1, x2, x3, x4, fsum, std_dev, mean_estimates, sum_sq_diff, start_time, end_time
character (len=20) :: methods(nmethods) = [character (len=20) :: "ordinary", "antithetic-2", "antithetic-4"]
print*,"compiler version: ",trim(compiler_version())
print*,"compiler options: ",trim(compiler_options())
call system_clock(count_rate=itick)
print*,"#random variates: ", nran*4
print*,"ifunc: ",ifunc
print*,"function: ",trim(f_name(ifunc))
do_method: do imethod = 1,nmethods
print "(/,a)", "method: " // trim(methods(imethod))
call system_clock(t1)
call cpu_time(start_time)
do i = 1, nsim
fsum = 0.0_dp
do j = 1, nran
if (imethod == 1) then ! 4 separate uniform variates
call random_number(x1)
call random_number(x2)
call random_number(x3)
call random_number(x4)
else if (imethod == 2) then ! 2 uniform variates and 2 antithetic variates
call random_number(x1)
call random_number(x2)
x3 = 1 - x1
x4 = 1 - x2
else ! 1 uniform variate and 3 related variates
call random_number(x1)
if (x1 < 0.5_dp) then
x2 = 0.5_dp - x1 ! set x2 so that average of x1 and x2 is 0.25
else
x2 = 1.5_dp - x1 ! set x2 so that average of x1 and x2 is 0.75
end if
! reflect x1 and x2 across 0.5 to get x3 and x4
x3 = 1 - x1
x4 = 1 - x2
end if
fsum = fsum + f(x1) + f(x2) + f(x3) + f(x4)
end do
estimates(i) = fsum / (4 * real(nran, dp))
end do
mean_estimates = sum(estimates) / nsim
sum_sq_diff = sum((estimates - mean_estimates)**2)
std_dev = sqrt(sum_sq_diff / real(nsim, dp))
call cpu_time(end_time)
call system_clock(t2)
print*, "Estimated value: ", mean_estimates
print*, "Absolute error: ", abs(mean_estimates - f_integral(ifunc))
print*, "Standard error: ", std_dev/sqrt(real(nsim, kind=dp))
print*, "Execution time: ", end_time - start_time, " seconds"
print*, "Wall time: ", (t2-t1)/real(itick, kind=dp), " seconds"
end do do_method
end program monte_carlo
Results:
#random variates: 1000000
ifunc: 1
function: x^2
method: ordinary
Estimated value: 0.33334033354830317
Absolute error: 7.0002149698544791E-006
Standard error: 2.9265616727108698E-005
Execution time: 1.3125000000000000 seconds
Wall time: 1.3279851000000000 seconds
method: antithetic-2
Estimated value: 0.33334297610831598
Absolute error: 9.6427749826655251E-006
Standard error: 1.0936660038148731E-005
Execution time: 0.67187500000000000 seconds
Wall time: 0.67663379999999995 seconds
method: antithetic-4
Estimated value: 0.33333539505447651
Absolute error: 2.0617211431983584E-006
Standard error: 3.9821047110537445E-006
Execution time: 0.35937500000000000 seconds
Wall time: 0.36495689999999997 seconds