subroutine hypercube01_monomial_integral ( m, e, integral ) !*****************************************************************************80 ! !! hypercube01_monomial_integral(): integral inside unit hypercube, M dimensions. ! ! Discussion: ! ! The integration region is ! ! 0 <= X(1:M) <= 1. ! ! The monomial is F(X) = product ( 1 <= I <= M ) X(I)^E(I). ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 January 2014 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the spatial dimension. ! ! Input, integer E(M), the exponents. ! Each exponent must be nonnegative. ! ! Output, real ( kind = rk ) INTEGRAL, the integral. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer e(m) integer i real ( kind = rk ) integral if ( any ( e(1:m) < 0 ) ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'HYPERCUBE01_MONOMIAL_INTEGRAL - Fatal error!' write ( *, '(a)' ) ' All exponents must be nonnegative.' stop 1 end if integral = 1.0D+00 do i = 1, m integral = integral / real ( e(i) + 1, kind = rk ) end do return end subroutine hypercube01_sample ( m, n, x ) !*****************************************************************************80 ! !! hypercube01_sample() samples interior of the unit hypercube in M dimensions. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 January 2014 ! ! Author: ! ! John Burkardt ! ! Reference: ! ! Russell Cheng, ! Random Variate Generation, ! in Handbook of Simulation, ! edited by Jerry Banks, ! Wiley, 1998, pages 168. ! ! Reuven Rubinstein, ! Monte Carlo Optimization, Simulation, and Sensitivity ! of Queueing Networks, ! Krieger, 1992, ! ISBN: 0894647644, ! LC: QA298.R79. ! ! Parameters: ! ! Input, integer M, the spatial dimension. ! ! Input, integer N, the number of points. ! ! Output, real ( kind = rk ) X(M,N), the points. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) x(m,n) call random_number ( harvest = x(1:m,1:n) ) return end function hypercube01_volume ( m ) !*****************************************************************************80 ! !! hypercube01_volume(): volume of the unit hypercube in M dimensions. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 January 2014 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the spatial dimension. ! ! Output, real ( kind = rk ) HYPERCUBE01_VOLUME, the volume. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) real ( kind = rk ) hypercube01_volume integer m call i4_fake_use ( m ) hypercube01_volume = 1.0D+00 return end subroutine i4_fake_use ( n ) !*****************************************************************************80 ! !! i4_fake_use() pretends to use a variable. ! ! Discussion: ! ! Some compilers will issue a warning if a variable is unused. ! Sometimes there's a good reason to include a variable in a program, ! but not to use it. Calling this function with that variable as ! the argument will shut the compiler up. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 21 April 2020 ! ! Author: ! ! John Burkardt ! ! Input: ! ! integer N, the variable to be "used". ! implicit none integer n if ( n /= n ) then write ( *, '(a)' ) ' i4_fake_use(): variable is NAN.' end if return end subroutine monomial_value ( m, n, e, x, value ) !*****************************************************************************80 ! !! monomial_value() evaluates a monomial. ! ! Discussion: ! ! This routine evaluates a monomial of the form ! ! product ( 1 <= i <= m ) x(i)^e(i) ! ! where the exponents are nonnegative integers. Note that ! if the combination 0^0 is encountered, it should be treated ! as 1. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 20 April 2014 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the spatial dimension. ! ! Input, integer N, the number of points at which the ! monomial is to be evaluated. ! ! Input, integer E(M), the exponents. ! ! Input, real ( kind = rk ) X(M,N), the point coordinates. ! ! Output, real ( kind = rk ) VALUE(N), the value of the monomial. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n integer e(m) integer i real ( kind = rk ) value(n) real ( kind = rk ) x(m,n) value(1:n) = 1.0D+00 do i = 1, m if ( 0 /= e(i) ) then value(1:n) = value(1:n) * x(i,1:n) ** e(i) end if end do return end