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

Do LOOP fails when NOWHERE NEAR LIMITS

WSinc
New Contributor I
1,854 Views

This do loop example has NO passes thru it.

   dk4=100000000

    khi4=huge(k4)/2 ! nowhere near upper limit
    klo4=-khi4  !  nowhere near lower limit
   kount=(khi4-klo4)/dk4+1
    print *,"klo,hi=",klo4,khi4," kount 4=",kount
    do k4=klo4,khi4,dk4
        print *,"k4=",k4
    enddo

It gives the correct result (22) for KOUNT, but the compiler apparently gives ZERO for the same thing.

All variables are integer(4)

0 Kudos
24 Replies
IanH
Honored Contributor II
1,471 Views

Looks ok to me.  I added IMPLICIT NONE and an explicit default integer declaration for all referenced variables, and:

>ifort /check:all /warn:all /stand /standard-semantics "2015-03-09 do-loop-1.f90" && "2015-03-09 do-loop-1.exe"
Intel(R) Visual Fortran Intel(R) 64 Compiler XE for applications running on Intel(R) 64, Version 15.0.2.179 Build 201501
21
Copyright (C) 1985-2015 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 10.00.40219.01
Copyright (C) Microsoft Corporation.  All rights reserved.

"-out:2015-03-09 do-loop-1.exe"
-subsystem:console
"2015-03-09 do-loop-1.obj"
 klo,hi= -1073741823 1073741823  kount 4= 22
 k4= -1073741823
 k4= -973741823
 k4= -873741823
 k4= -773741823
 k4= -673741823
 k4= -573741823
 k4= -473741823
 k4= -373741823
 k4= -273741823
 k4= -173741823
 k4= -73741823
 k4= 26258177
 k4= 126258177
 k4= 226258177
 k4= 326258177
 k4= 426258177
 k4= 526258177
 k4= 626258177
 k4= 726258177
 k4= 826258177
 k4= 926258177
 k4= 1026258177

 

0 Kudos
John_Campbell
New Contributor II
1,471 Views

Bill,

I agree with your findings. I thought the loop would be calculated as I have expanded it, but perhaps not. (it may depend on the compiler version.)

     integer*4 dk4, khi4, klo4, kount, k4

     dk4   = 100000000

     khi4  = huge(k4)/2 ! nowhere near upper limit
     klo4  = -khi4  !  nowhere near lower limit
     kount = (khi4-klo4)/dk4+1
!
     print *,"klo,hi=",klo4,khi4," kount 4=",kount
     print *,"khi4-klo4", khi4-klo4
!
     print *," "
     print *," test DO loop"
     do k4 = klo4,khi4,dk4
        print *,"k4=",k4
     end do
     print *," exit do k4=",k4
!
     print *," "
     print *," test DO loop calculations"
     k4 = klo4
     do       !                 k4 = klo4,khi4,dk4
        if ( k4 > khi4 ) exit

        print *,"k4=",k4

        k4 = k4 + dk4
     end do
     print *," exit do k4=",k4
!
     end

 

0 Kudos
IanH
Honored Contributor II
1,471 Views

Ok - I see no iterations on the 32 bit platform.

As discussed in the other threads, the calculation of the iteration count is formally stated as the expression (finish - start + step) / step, conducted in the kind of the do variable.  If the compiler honours the parentheses (as is usually required by the language rules) then the result of the sub-expression in the parentheses exceeds what an default integer variable can hold - that's a numeric operation that is not defined by the arithmetic used by the processor - non-confoming program - anything can happen.

0 Kudos
andrew_4619
Honored Contributor III
1,471 Views

I have changed my view on this one a bit. If we read the standard on this (which now have!) it is a non-conforming program however it did think it was slightly perverse calculating (finish - start + step) / step which overflows when (finish - start)/step  + 1 which does not could be used and would gives a productive loop in the examples cited. However, a few moments thought and we can see the case where start is negative and finish is positive  will overflow by the second method in some cases.

In the general cases the iteration count has to be determined at run time and I guess  the standard writers picked the form of the calculation to preclude the forced need to evaluate several permutations for every such do loop. I think I will now go away and do something useful!

0 Kudos
John_Campbell
New Contributor II
1,471 Views

I think the basic problem is  (finish - start + step) / step does cause integer*4 overflow, which is not what was claimed in this thread's title. IMHO, this is basically a bad choice of Integer*4 DO loop subscripts, which was Steve's original warning.

John

0 Kudos
mecej4
Honored Contributor III
1,471 Views

We may need to read through the minutes of the standards committee to find out why the count is calculated from (finish - start + step) / step rather than (finish-start)/step (finish-start)/step + 1 or some other mathematically equivalent form which, in certain cases, skirts around integer overflow. To me the following is a plausible reason.

Most DO loops do something useful in addition to executing a specified number of times. Typically, the DO index is used in some expression as a subscript, as a subprogram argument, etc. Therefore, if it can be predetermined that the sequential additions of step to the DO index (as in i = i + step) will cause overflow, it may be considered proper to prevent the DO loop from being entered at all, and accept the inevitable in a graceful way at the earliest possible.

The last value of the DO loop index just prior to exiting the loop can be outside the bounds finish and start. Thus, when step is positive, even if finish is less than HUGE_INT, computing the last value can cause integer overflow.

0 Kudos
Arjen_Markus
Honored Contributor I
1,471 Views

Well, (finish-start)/step gives too small a value: start = 1, step = 1, finish = 10 would lead to 9 steps, rather than 10.

0 Kudos
mecej4
Honored Contributor III
1,471 Views

Thanks, Arjen; typo fixed.

0 Kudos
WSinc
New Contributor I
1,471 Views

It's kinda interesting that SOME of us get the correct number of iterations when we run it -

while others don't.

But I feel rather strongly that it should be consistent across ALL platforms.

Using integer(8) arithmetic would solve that problem, but then it has to be addressed

again for INTEGER(8) variables. Seems like a lotta guesswork, apparently - - - since the standard does not really address that issue.

 

Since the standard does not give us explicit warnings about INTEGER OVERFLOW regarding DO LOOPS,

most of would assume that all possible values of START, STOP and STEP would give consistent results for all platforms.

I wonder if we see this problem on 64 bit CPUs ?

Was that "correct" result obtained on a 64 bit machine? I think so -

You are doing 64 bit arithmetic there (implicitly) so you dont get the 32 bit overflow (?).

Hey, John Campbell, how do we know what is "correct?" Can you run that with 8 byte variables?

Of course you have to change STEP to a much larger number to get smaller # of steps. Like = 1x10**18.

 

As I said in an earlier thread, since the values of the limits and the step size can be determined by formulas, or by data inputs,

we really dont have much control over those, and so cannot reliably predict when there would be problems.

 

 

 

0 Kudos
WSinc
New Contributor I
1,471 Views

An afterthought ;

Why not use REAL(16) arithmetic to calculate that?

We are always guaranteed to get the correct answer for ANY combination of inputs.

You get  a REAL(16) result, which you would round off to get the final number.

NO_STEPS = (real(STOP,16) - real(start,16)+real(step,16))/real(step,16)

Since the compiler supports REAL(16) arithmetic, this should not cause any problems.

0 Kudos
FortranFan
Honored Contributor III
1,471 Views

Bill,

Why don't you introduce a simple check using double precision arithmetic in this specific "huge" loop of interest to you:

program p

   use, intrinsic :: iso_fortran_env, only : i8 => int64, dp => real64

   !.. Named constants
   integer(i8), parameter :: start = 1
   integer(i8), parameter :: finish = huge(1_i8)
   integer(i8), parameter :: step = finish/4_i8

   !.. Program variables
   integer(i8) :: i

   loop_h: do i = start, finish, step
      
      print *, " i = ", i

      if ((real(i, kind=dp) + real(step, kind=dp)) > real(finish, kind=dp)) exit loop_h
      
   end do loop_h

   stop

end program p
  i =  1
  i =  2305843009213693952
  i =  4611686018427387903
  i =  6917529027641081854
  i =  9223372036854775805
Press any key to continue . . .

Separately, if you can explain what exactly you're trying to do in detail, perhaps readers may have suggestions for you on how to revise your algorithm(s) to avoid such loops altogether and which, as Steve alluded to very early on in this topic, may be the best way to proceed.

0 Kudos
WSinc
New Contributor I
1,471 Views

Oh sure, there are ways to get around this problem, and that's one of them.

You have to be really careful even when simulating a DO LOOP, since the index can overflow.

Unless we do as you suggest, and avoid using integers, or convert the index to an integer to a REAL

quantity before testing it.

 

In the cryptography work that I do, you very often get some weird values of the parameters,

and those can be generated by data inputs or formulas.

In you example, try setting the START to -huge(I8). 

Does it still work OK?

0 Kudos
mecej4
Honored Contributor III
1,471 Views

The suggestion in #12 is valid only for a DO in which the index is increasing; i.e., step is positive.You would have to be sure that this is the case, or add more code to cover "backward" loops.

0 Kudos
WSinc
New Contributor I
1,471 Views

 a more general result would be to properly compute the no of iterations:

NITER = (stop-start)/step + 1  ! You still have to be careful,

!  since this can give an overflow, so 

!  maybe reals should be used instead.

then do this:

INDEX = START

DO ITER=1,NITER

!  code here

INDEX=INDEX + STEP

ENDDO

Since you never TEST the index, the problem is avoided.

0 Kudos
FortranFan
Honored Contributor III
1,471 Views

mecej4 wrote:

The suggestion in #12 is valid only for a DO in which the index is increasing; i.e., step is positive.You would have to be sure that this is the case, or add more code to cover "backward" loops.

Yes, I wasn't trying to be comprehensive by any means.  And, of course, in the more general situation, one may need quadruple instead of double precision.  I'm simply suggesting the onus be on the user (Bill) for such needs rather than the compiler.

0 Kudos
mecej4
Honored Contributor III
1,471 Views

FortranFan wrote:
I'm simply suggesting the onus be on the user (Bill) for such needs rather than the compiler.

Amen!

0 Kudos
John_Campbell
New Contributor II
1,471 Views

I thought the count calculation should be  "(finish - start + step) / step" ,  rather than  "(finish - start) / step + 1" to allow for zero step do loops.

0 Kudos
GVautier
New Contributor II
1,471 Views

Hello

Back to Fortran 66 where loops where always entered once and all programmers have to add a test before each loop.

More seriously, what I expect from a loop is that it has to be repeated from start value up to end value with the given step.

The only point to remind is that the counter is incremented before the test with the end value. So in my sense, the maximum end value has to be less or equal to HUGE()-step to avoid overflow.

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,471 Views

One should also be mindful of performing loops performing steps who's step value cannot be exactly represented. For example a step of 0.1, which has an infinite repeating binary fraction.

The compiler computes an iteration count before execution. How the compiler advances the loop control variable is unknown (undefined). If the compiler chooses to set the loop control variable to start, then on each iteration advance it by way of += step, then on large loop counts it is highly likely that due to accumulation of round off error, that the loop control variable can deviate substantially from being a multiple of step from the start. A more accurate method would be for the compiler to generate lcv = (start + (iteration-1)*step).

! Never code:
do SimTime = 0.0, 86400.0, .001

! rather code
do iSimTimeIteraton = 0, 8640000
  SimTime = .001_8 * iSimTimeIteraton

Jim Dempsey

0 Kudos
mecej4
Honored Contributor III
1,374 Views

The DO index variables and the expressions m1,m2,m3 are required to be of scalar integer type in F95 and later. Even in F90 the use of other types in this context was declared obsolescent. Vendors, of course, may continue to allow other types, in particular real types, as an extension.

0 Kudos
Reply