使用 OpenMP 计算 PI
目录
使用 OpenMP 计算 PI¶
这是使用 fpm 和 OpenMP 的一个简单示例。这是 此处可以找到的 OpenMP 示例的改编版本,该示例受 CC-BY-4.0 许可证保护。
该代码通过对四分之一单位圆进行并行数值积分来近似计算 PI 值。代码结构如下
app/main.f90¶
program compute_pi_openmp
use, intrinsic :: iso_fortran_env, only: dp => real64, i8 => int64, real128
implicit none
integer(kind=i8) :: i, n_iterations
real(kind=dp) :: delta, x, pi
real(kind=dp) :: start, end
pi = 0.0_dp
n_iterations = get_iterations(10000_i8)
delta = 1.0_dp / n_iterations
x = 0.0_dp
call cpu_time(start)
!$omp parallel do default(none) private(x) shared(delta, n_iterations) reduction(+:pi)
do i = 1, n_iterations
x = i * delta
pi = pi + sqrt(1.0_dp - x**2)
end do
!$omp end parallel do
call cpu_time(end)
pi = 4.0_dp * pi / n_iterations
print "(A, I16, A, F25.15)", "Iterations: ", n_iterations, ", PI: ", pi
print "(A, F8.3, A, ES8.1)", "Took: ", end - start, "s, with absolute error: ", acos(-1.0_real128) - pi
contains
integer(i8) function get_iterations(default_iterations)
integer(kind=i8), intent(in) :: default_iterations
character(len=100) :: buffer, msg
integer :: stat
get_iterations = default_iterations
if (command_argument_count() >= 1) then
call get_command_argument(1, buffer)
read (buffer, fmt=*, iostat=stat, iomsg=msg) get_iterations
if (stat /= 0) stop msg
end if
end function get_iterations
end program compute_pi_openmp
使用 OpenMP 作为依赖项¶
要在您的项目中使用 OpenMP,您需要在 fpm.toml
文件中添加openmp
依赖项
fpm.toml¶
name = "compute-pi-openmp"
version = "0.1.0"
[dependencies]
openmp = "*"
[[executable]]
name = "compute-pi-openmp"
OpenMP 是一种内置依赖项(即元包),这意味着需要使用以上语法。要详细了解元包,请参阅内置依赖项(“元包”)。
构建和运行代码¶
要构建和运行代码,可以使用以下命令
❯ fpm run
Project is up to date
Iterations: 10000, PI: 3.141391477611324
Took: 0.092s, with absolute error: 2.0E-04
同时启用编译器优化和 --profile-release
逐渐增加近似值的迭代次数
❯ fpm run --profile-release -- 1000000000
main.f90 done.
compute-pi-openmp done.
[100%] Project compiled successfully.
Iterations: 1000000000, PI: 3.141592651589789
Took: 3.511s, with absolute error: 2.0E-09