Computing PI with OpenMP

Computing PI with OpenMP

This is a simple example of how to use OpenMP with fpm. It is an adapted version of the OpenMP example that can be found here under a CC-BY-4.0 license.

The code approximates the value of PI by performing parallelized numerical integration over a quarter of the unit circle. The code is structured as follows:

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

Using OpenMP as a dependency

To use OpenMP in your project, you need to add the openmp dependency to your fpm.toml file:

fpm.toml
name = "compute-pi-openmp"
version = "0.1.0"

[dependencies]
openmp = "*"

[[executable]]
name = "compute-pi-openmp"

OpenMP is a built-in dependency (i.e. metapackage), which means the above syntax needs to be used. To find out more about metapackages, see Built-in dependencies («Metapackages»).

Building and running the code

To build and run the code, one can use the following commands:

❯ fpm run
Project is up to date
Iterations:            10000, PI:         3.141391477611324
Took:    0.092s, with absolute error:  2.0E-04

And increasing the number of iterations for the approximation while simultaneously enabling compiler optimizations with --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