Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28588 Discussions

OpenMP default variable as private or shared on windows 10

Fortran10
Beginner
132 Views

I have following code

 

program openmp_test
    implicit none
    
    !=============
    
    integer ( kind = 4 ), parameter :: Nx = 700
    integer ( kind = 4 ), parameter :: Ny = 700
    real ( kind = 4 )               :: dx = 0.03
    real ( kind = 4 )               :: dy = 0.03
    
    !=============
    
    integer (kind = 4 ) :: nsteps = 7000
    integer (kind = 4 ) :: nprint = 1000
    integer (kind = 4 ) :: tsteps 
    real ( kind = 4 )   :: dtime  = 1.0e-4
    real ( kind = 8 )   :: computed_time 
    integer (kind =   :: rate, stop_count, start_count
    
    !===============
    
    real ( kind = 4 )   :: tau   = 0.0003
    real ( kind = 4 )   :: epsilonb = 0.01
    real ( kind = 4 )   :: kappa = 1.8
    real ( kind = 4 )   :: delta = 0.02
    real ( kind = 4 )   :: aniso = 6.0
    real ( kind = 4 )   :: alpha = 0.9
    real ( kind = 4 )   :: gama  = 10.0
    real ( kind = 4 )   :: teq   = 1.0
    real ( kind = 4 )   :: theta0= 0.2 
    real ( kind = 4 )   :: seed  = 5.0
    
    real ( kind = 4 )   :: pix   = 4.0*atan(1.0)
    
    !===============
    
    real ( kind = 4 ) , dimension( Nx, Ny ) :: phi, tempr
    real ( kind = 4 ) , dimension( Nx, Ny ) :: lap_phi, lap_tempr
    real ( kind = 4 ) , dimension( Nx, Ny ) :: phidx, phidy
    real ( kind = 4 ) , dimension( Nx, Ny ) :: epsil, epsilon_deriv
    real ( kind = 4 )                       :: phi_old, term1, term2
    real ( kind = 4 )                       :: 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
    
    
    
    
    
    ! ======
    ! Start timing the code
    ! ========
    call system_clock (count=start_count , count_rate=rate)
    
    
    
    
    
    !============================================================
    
    
    
    
    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 ) == 0 ) print *, 'Done steps  =  ', tsteps
        
        
        
    end do time_loop
    
    
    
    !====
    ! end timing the code
    !====
    call system_clock (count=stop_count)
    
    
    computed_time = real(max(stop_count - start_count , 1_8 )) /real(rate)    
    
    
    
    
    
    
    !________________________________________________________________
    !                                  Output
    ! 
    
    
    
    
    
    ! ====
    ! Print time of computation
    ! ====
    
    print*, ""
    print*, ""
    print*, "-------------------------------------------------"
    print*, ' The code took     = ', computed_time,' seconds'
    
    
    
    
    
    ! ====
    ! Quick dislin plot for graphics validation
    ! ====
    
    call qplclr (phi,Nx,Ny)
    
    
    
    
    
    
    !=======================================================================
    ! Save file for graphics validation with gnuplot
    
    
    
    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

 

 The default variable status in omp parallel construct is shared as to my knowledge. So I was supposed to have race condition because variables like theta, phi_old are not declared private. But it seems like the compiler takes them as private and I do not find any race condition. To confirm it I run it many times on windows 10 with following tests.

 

Without OpenMP flag

ifx_no_openmp.PNG

 

 

With OpenMP flag

ifx_openmp.PNG

 

 

To confirm the visual output I have.

 

dislin_output.PNG

 

1) It seems like the code was run in parallel using OpenMP flag (due to time difference in computation).

2) The compiler does not seem to consider those variables shared but private.

3) The output of the code with OpenMP compiler flag is the same as without OpenMP flag. 

 

 

So what does this behavior mean here? The compiler automatically detects these variables as private and run the code safely to avoid any race condition?  

 

My system details are

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

 

 

0 Kudos
1 Solution
jimdempseyatthecove
Honored Contributor III
86 Views

A race condition means a conflict may occur; it does not necessarily mean the conflict will occur.

In the case above, register pressure may have been low enough such that theta and phi_old were registerized inside the loops. And in this case you code was lucky. Do not assume that because this test ran without issue that the code itself was not error free. It just happened to be error free (but not by design). You should use the OpenMP clause default(none) to expose coding errors.

 

Jim Dempsey

View solution in original post

0 Kudos
1 Reply
jimdempseyatthecove
Honored Contributor III
87 Views

A race condition means a conflict may occur; it does not necessarily mean the conflict will occur.

In the case above, register pressure may have been low enough such that theta and phi_old were registerized inside the loops. And in this case you code was lucky. Do not assume that because this test ran without issue that the code itself was not error free. It just happened to be error free (but not by design). You should use the OpenMP clause default(none) to expose coding errors.

 

Jim Dempsey

0 Kudos
Reply