In parallel with the DO-EXIT construct, Fortran has a DO-CYCLE construct as follows:
where control-info is empty if the loop is a DO-END DO; otherwise, control-info contains all information that a counting DO should have.DO control-info statements-1 CYCLE statements-2 END DO
When the execution of a DO-loop encounters the CYCLE statement, the DO-loop starts next iteration immediately.
This is not a recommended feature.  So,
if it is possible, do not use it.
        
INTEGER :: i
DO i = 1, 5
   IF (i == 3) THEN
      CYCLE
   ELSE
      WRITE(*,*)  i
   END IF
END DO
     
        
INTEGER :: Range
DO
   WRITE(*,*)  'An integer >= 2 please --> '
   READ(*,*)   Range
   IF (Range < 2) THEN
      WRITE(*,*)  'Input not in the required range'
      CYCLE
   END IF
   ... process Range ...
END DO
          Please compare this example with the technique used in
          the second prime number example
          in which EXIT is used rather than CYCLE.
Write a program to find all solutions.
        
! ----------------------------------------------------------
! This program solve the following puzzle:
!                RED
!            x   FOR
!            -------
!             DANGER
! where each distinct letter represents a different digit.
! Moreover, R, F and D cannot be zero.
! ----------------------------------------------------------
PROGRAM  Puzzle
   IMPLICIT  NONE
   INTEGER :: R, E, D, F, O, A, N, G    ! the digits
   INTEGER :: RED, FOR, DANGER          ! the constructed values
   INTEGER :: Count                     ! solutions count
   WRITE(*,*)  'This program solves the following puzzle:'
   WRITE(*,*)
   WRITE(*,*)  '    RED'
   WRITE(*,*)  'x   FOR'
   WRITE(*,*)  '-------'
   WRITE(*,*)  ' DANGER'
   WRITE(*,*)
   Count = 0
   DO R = 1, 9
     DO E = 0, 9
       IF (E == R) CYCLE
       DO D = 1, 9
         IF (D == R .OR. D == E) CYCLE
         DO F = 1, 9
           IF (F == R .OR. F == E .OR. F == D) CYCLE
           DO O = 0, 9
             IF (O == R .OR. O == E .OR. O == D .OR.            &
                 O == F)  CYCLE
             DO A = 0, 9
               IF (A == R .OR. A == E .OR. A == D .OR.          &
                   A == F .OR. A == O)  CYCLE
               DO N = 0, 9
                 IF (N == R .OR. N == E .OR. N == D .OR.        &
                     N == F .OR. N == O .OR. N == A)  CYCLE
                 DO G = 0, 9
                   IF (G == R .OR. G == E .OR. G == D .OR.      &
                       G == F .OR. G == O .OR. G == A .OR.      &
                       G == N)  CYCLE
                   RED    = R*100 + E*10 + D
                   FOR    = F*100 + O*10 + R
                   DANGER = D*100000 + A*10000 + N*1000 + G*100 + E*10 + R
                   IF (RED * FOR == DANGER) THEN
                      Count = Count + 1
                      WRITE(*,*) 'Solution ', Count, ':'
                      WRITE(*,*) '     RED = ', RED
                      WRITE(*,*) '     FOR = ', FOR
                      WRITE(*,*) '  DANGER = ', DANGER
                      WRITE(*,*)
                   END IF
                 END DO
               END DO
             END DO
           END DO
         END DO
       END DO
     END DO
   END DO
END PROGRAM  Puzzle
Click here to download this program.
        
This program solves the following puzzle:
    RED
x   FOR
-------
 DANGER
Solution 1:
     RED = 321
     FOR = 563
  DANGER = 180723
Solution 2:
     RED = 481
     FOR = 364
  DANGER = 175084
        
DO R = 1, 9
  DO E = 0, 9
    IF (E == R) CYCLE
    DO D = 1, 9
      IF (D == R .OR. D == E) CYCLE
      ... other loops ...
    END DO
  END DO
END DO
          The above only shows three loops for R, E and
          D.  At the beginning
          of the E loop, the value of E is checked to see if it
          is equal to the value of R.  If they are equal, the
          CYCLE brings the control to the next iteration.  Similarly,
          at the beginning of the D loop, the value of D
          is compared against the values of E and R.
          If they are equal, CYCLE causes the start of  the next
          iteration.  Note that D runs from 1 to 9.  RED = R*100 + E*10 + D FOR = F*100 + O*10 + R DANGER = D*100000 + A*10000 + N*1000 + G*100 + E*10 + R IF (RED * FOR == DANGER) THEN ... display READ, FOR and DANGER ... END IF