Time difference using if and where statement

I am trying to understand the if and where statement with the following example. Apparently, there is no error in the code but there is a lot of difference in the output time. The where statement is quite slow. So far i have not found any reason for it. Does where statement execution always take more time?

program where_test
  implicit none

  integer               :: tsteps,i,j
  integer, parameter    :: N = 64
  real, dimension(N,N)  :: r,c
  real                  :: t_start, t_end

    call cpu_time(t_start)

    do tsteps = 1, 100000

      call random_number(r)

       c = 0.01+0.8*r

         do i = 1, N
           do j= 1, N

     !        if (c(i,j)>=0.80)   c(i,j)=0.80
     !        if (c(i,j)<0.0002)  c(i,j)=0.0002

               where (c>=0.80)   c=0.80
               where (c<0.0002)  c=0.0002
      
           end do
         end do

           if(mod(tsteps,1000).eq.0) print*, 'Done steps  =  ',tsteps

      end do

      call cpu_time(t_end)

      print*, 'Time = ', t_end - t_start

end program
1 Like

I am using gfortran on virtual machine. with compiler options: gfortran main.f90 -o main

where (c>=0.8)... operates on the whole array, element by element, so it is by itself equivalent of an if(c(i, j) >= 0.8)... enclosed in double do loop.
Also, the second if/where is a no-op as c=0.01+0.8*r cannot be less than 0.002

1 Like

If both statements are equivalent then why where statement takes a longer execution time?

1 Like

They are not. As @kargl noted, where should be outside the loops. Otherwise you make the loop over c array quadruple.

1 Like

If I read your intent correctly, and since you seem to regard speed as important, consider replacing

c = 0.01+0.8*r

by

c = 0.0002+(0.8-0.0002)*r

and doing away with the DO loops on i and j. You will not need IF or WHERE constructs at all. Your original code throws away a small section of of the random numbers that were generated. The suggested change entails no such discarding.

It’s highly doubtful OP is interested in a lesson in arithmetic! +1 for clever programming though!

@shahid,

If you’re really need to do such comparisons, then as indicated upthread, do

   where (c>=0.80)   c=0.80
   where (c<0.0002)  c=0.0002

against your IF inside your DO loop.

That is, place the WHERE statements outside your loop.

Also, try not to include IO statements inside of your timing measurements, your PRINT can introduce sufficient noise to affect your timing.

2 Likes

Since MIN and MAX are elemental functions, I think the code can be written

program where_test
  implicit none
  integer               :: tsteps
  integer, parameter    :: N = 64
  real, dimension(N,N)  :: c
  real                  :: t_start, t_end
  call cpu_time(t_start)
  do tsteps = 1, 100000
    call random_number(c)
    c = max(0.002,min(0.8,0.01 + 0.8*c))
    if (mod(tsteps,1000).eq.0) print*, 'Done steps  =  ',tsteps
  end do
  call cpu_time(t_end)
  print*, 'Time = ', t_end - t_start
end program
1 Like

My basic idea is just to understand the where construct or statement. In comparison to the if statement or if construct I saw that the where construct is taking a long time. So using -O2 compiler flag with gfortran the where construct shows faster execution (my original code at the top). Therefore it appears to me that where construct execution speed depends on the optimization flag.

I ran with the -O2 flag without changing anything in the code and it shows faster time. So it confuses me why it is not the solution?

You seem not to realize an important point. You execute the WHERE construct N^2 = 4096 times, even though doing just one execution was enough!

2 Likes

As pointed out by others, the correct comparison should be as follows (I have not tried the code). Note that where is placed outside the loops.

program where_test
  implicit none

  integer               :: tsteps,i,j
  integer, parameter    :: N = 64
  real, dimension(N,N)  :: r,c
  real                  :: t_start, t_end

    call cpu_time(t_start)

    do tsteps = 1, 100000

      call random_number(r)

       c = 0.01+0.8*r

         !do i = 1, N
         !  do j= 1, N
         !
         !   if (c(i,j)>=0.80)   c(i,j)=0.80
         !    if (c(i,j)<0.0002)  c(i,j)=0.0002
         !
         !  end do
         !end do


         where (c>=0.80)   c=0.80
         where (c<0.0002)  c=0.0002
      
         if(mod(tsteps,1000).eq.0) print*, 'Done steps  =  ',tsteps

      end do

      call cpu_time(t_end)

      print*, 'Time = ', t_end - t_start

end program
1 Like

Yeah. That is correct.