I have the following code
program openmp_test
implicit none
!=============
integer ( kind = 4 ), parameter :: Nx = 100
integer ( kind = 4 ), parameter :: Ny = 100
real ( kind = 8 ) :: dx = 0.03
real ( kind = 8 ) :: dy = 0.03
!=============
integer (kind = 4 ) :: nsteps = 1000
integer (kind = 4 ) :: nprint = 100
integer (kind = 4 ) :: tsteps
real ( kind = 8 ) :: dtime = 1.0e-4
!===============
real ( kind = 8 ) :: tau = 0.0003
real ( kind = 8 ) :: epsilonb = 0.01
real ( kind = 8 ) :: kappa = 1.8
real ( kind = 8 ) :: delta = 0.02
real ( kind = 8 ) :: aniso = 6.0
real ( kind = 8 ) :: alpha = 0.9
real ( kind = 8 ) :: gama = 10.0
real ( kind = 8 ) :: teq = 1.0
real ( kind = 8 ) :: theta0= 0.2
real ( kind = 8 ) :: seed = 5.0
real ( kind = 8 ) :: pix = 4.0*atan(1.0)
!===============
real ( kind = 8 ) , dimension( Nx, Ny ) :: phi, tempr
real ( kind = 8 ) , dimension( Nx, Ny ) :: lap_phi, lap_tempr
real ( kind = 8 ) , dimension( Nx, Ny ) :: phidx, phidy
real ( kind = 8 ) , dimension( Nx, Ny ) :: epsil, epsilon_deriv
real ( kind = 8 ) :: phi_old, term1, term2
real ( kind = 8 ) :: theta, m
integer ( kind = 4 ) :: i, j, ip, im, jp, jm
!============================================================
phi = 0.0
tempr = 0.0
do i = 1, Nx
do j = 1, Ny
if ( (i - Nx/2.0)*(i - Nx/2.0) + (j - Ny/2.0)*(j - Ny/2.0)&
& < seed ) then
phi(i,j) = 1.0
end if
end do
end do
!============================================================
time_loop: do tsteps = 1, nsteps
!$omp parallel do private(i,j,ip,im,jp,jm)
do j = 1, Ny
do i =1, Nx
jp = j + 1
jm = j - 1
ip = i + 1
im = i - 1
if ( im == 0 ) im = Nx
if ( ip == ( Nx + 1) ) ip = 1
if ( jm == 0 ) jm = Ny
if ( jp == ( Ny + 1) ) jp = 1
!=====
lap_phi(i,j) = ( phi(ip,j) + phi(im,j) + phi(i,jm) + phi(i,jp)&
& - 4.0*phi(i,j)) / ( dx*dy )
lap_tempr(i,j) = ( tempr(ip,j) + tempr(im,j) + tempr(i,jm) + &
& tempr(i,jp) - 4.0*tempr(i,j)) / ( dx*dy )
!======
phidx(i,j) = ( phi(ip,j) - phi(im,j) ) / dx
phidy(i,j) = ( phi(i,jp) - phi(i,jm) ) / dy
!======
theta = atan2( phidy(i,j),phidx(i,j) )
!======
epsil(i,j) = epsilonb*( 1.0 + delta*cos(aniso*&
& ( theta - theta0 ) ) )
epsilon_deriv(i,j) = -epsilonb*aniso*delta*sin&
& ( aniso*( theta - theta0 ) )
end do
end do
!$omp end parallel do
!$omp parallel do private(i,j,ip,im,jp,jm)
do j = 1, Ny
do i =1, Nx
jp = j + 1
jm = j - 1
ip = i + 1
im = i - 1
if ( im == 0 ) im = Nx
if ( ip == ( Nx + 1) ) ip = 1
if ( jm == 0 ) jm = Ny
if ( jp == ( Ny + 1) ) jp = 1
phi_old = phi(i,j)
!========
term1 = ( epsil(i,jp)*epsilon_deriv(i,jp)*phidx(i,jp)&
& - epsil(i,jm)*epsilon_deriv(i,jm)*phidx(i,jm) ) / dy
term2 = -( epsil(ip,j)*epsilon_deriv(ip,j)*phidy(ip,j)&
& - epsil(im,j)*epsilon_deriv(im,j)*phidy(im,j) ) / dx
!========
m = alpha/pix*atan( gama*( teq - tempr(i,j) ) )
!========
phi(i,j) = phi(i,j) + ( dtime/tau )*( term1 + term2 +&
& epsil(i,j)**2*lap_phi(i,j) ) + &
& phi_old*( 1.0 - phi_old )*( phi_old -0.5 + m )
tempr(i,j) = tempr(i,j) + dtime*lap_tempr(i,j) &
& + kappa*( phi(i,j) - phi_old )
end do
end do
!$omp end parallel do
! print steps
if ( mod( tsteps, nprint ) .eq. 0 ) print *, 'Done steps = ', tsteps
end do time_loop
!============================================================================
! output file
open ( 1, file = "phi.dat" )
do i = 1, Nx
write( 1, 10 ) ( phi(i,j),j = 1, Ny )
end do
10 FORMAT(1000000F10.6)
close( 1 )
end program openmp_test
Intel ifx compiler
If I run with intel compiler with the command
ifx main.f90 /Qopenmp /F5000000
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.0.0 Build 20231017
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 14.32.31332.0
Copyright (C) Microsoft Corporation. All rights reserved.
-out:main.exe
-subsystem:console
-stack:5000000
-defaultlib:libiomp5md.lib
-nodefaultlib:vcomp.lib
-nodefaultlib:vcompd.lib
main.obj
>main
Done steps = 100
Done steps = 200
Done steps = 300
Done steps = 400
Done steps = 500
Done steps = 600
Done steps = 700
Done steps = 800
Done steps = 900
Done steps = 1000
I get the right output which shows numerical values
gfortran
But if I run with gfortran compiler the code runs fine but the output results are different
The commands are
>gfortran -frecursive main.f90 -fopenmp -o main
>main
Done steps = 100
Done steps = 200
Done steps = 300
Done steps = 400
Done steps = 500
Done steps = 600
Done steps = 700
Done steps = 800
Done steps = 900
Done steps = 1000
>gfortran -fmax-stack-var-size=5000000 main.f90 -fopenmp -o main
f951.exe: Warning: Flag '-fmax-stack-var-size=5000000' overwrites '-frecursive' implied by '-fopenmp'
>main
Done steps = 100
Done steps = 200
Done steps = 300
Done steps = 400
Done steps = 500
Done steps = 600
Done steps = 700
Done steps = 800
Done steps = 900
Done steps = 1000
The output file (in both cases of gfortran) has values :
NaN NaN
So my questions are:
What are the right gfortran commands to run this code?
Or there are some gfortran specific OpenMP implementation details that are missing in the code?
My computer details are
GNU Fortran (GCC) 13.2.0
Copyright (C) 2023 Free Software Foundation, Inc.
This is free software; see the source for copying conditions. There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
Processor 11th Gen Intel(R) Core™ i5-11500 @ 2.70GHz 2.71 GHz
Installed RAM 8.00 GB (7.83 GB usable)
System type 64-bit operating system, x64-based processor