program saxpy use, intrinsic :: iso_fortran_env implicit none integer, parameter :: sp = REAL32 integer, parameter :: dp = REAL64 integer, parameter :: i64 = INT64 integer(i64) :: i, n, rate, system_start, system_end real(dp),dimension(:),allocatable :: x, y real(dp) :: a,cpu_start, cpu_end CHARACTER(100) :: my_arg CALL GET_COMMAND_ARGUMENT(1, my_arg) READ(my_arg,*)n allocate(x(n),y(n)) x = 1.0d0 y = 2.0d0 a = 2.0d0 CALL system_clock(count_rate=rate) call cpu_time(cpu_start) call SYSTEM_CLOCK(system_start) !$omp parallel do private(i) shared(n,y,a,x) do i = 1, n y(i) = y(i) + a * x(i) end do !$omp end parallel do call cpu_time(cpu_end) call SYSTEM_CLOCK(system_end) deallocate(x,y) print '(a,f8.6)', 'CPU Time: ', cpu_end - cpu_start print '(a,f8.6)', 'Wall Time: ', real(system_end-system_start)/real(rate) end program saxpy