3

是否有与 Python 的 for-else 语句等效的 Fortran 语句?

例如,下面将一个数字列表排序到不同的范围内。在 Python 中,它是:

absth = [1, 2, 3, 4, 5]
vals = [.1, .2, .5, 1.2, 3.5, 3.7, 16.8, 19.8, 135.60]


counts = [0] * len(absth)
for v in vals:
    for i, a in enumerate(absth):
        if v < a:
            counts[i] += 1
            break
    else:
        counts[-1] += 1

在 Fortran 中,它的工作原理相同:

do iv = 1, nvals

  is_in_last_absth = .true.

  do ia = 1, nabsth - 1
    if vals(iv) < absth(ia) then
      counts(ia) = counts(ia) + 1
      is_in_last_absth = .false.
      exit
    end if
  end do

  if (is_in_last_absth) then
    counts(nabsth) = counts(nabsth) + 1
  end if

end do

但是有没有办法不用is_in_last_absthelsePython 那样使用和替换它?

4

6 回答 6

5

没有直接等效于该 python 构造。

但请注意,可以通过在循环之后检查 do 变量的值来检测带有计数循环控制的 do 循环的提前终止。

do iv = 1, nvals
  do ia = 1, nabsth - 1
    if (vals(iv) < absth(ia)) then
      counts(ia) = counts(ia) + 1
      exit
    end if
  end do

  ! If the loop terminates because it completes the iteration 
  ! count (and not because the exit statement is executed) then 
  ! the do variable is one step beyond the value it had 
  ! during the last iteration.
  if (ia == nabsth) then
    counts(nabsth) = counts(nabsth) + 1
  end if
end do

退出语句不仅可以跳出 do 循环:

do iv = 1, nvals
  outer_block: block
    do ia = 1, nabsth - 1
      if (vals(iv) < absth(ia)) then
        counts(ia) = counts(ia) + 1
        exit outer_block
      end if
    end do

    counts(nabsth) = counts(nabsth) + 1
  end block outer_block
end do

并且循环语句可以循环该语句嵌套在其中的任何 do 构造:

outer_loop: do iv = 1, nvals
  do ia = 1, nabsth - 1
    if (vals(iv) < absth(ia)) then
      counts(ia) = counts(ia) + 1
      cycle outer_loop
    end if
  end do

  counts(nabsth) = counts(nabsth) + 1
end do outer_loop
于 2016-12-01T10:45:40.103 回答
3

如果问题是关于对一系列数字进行分箱,并且absth是每个箱的上限(最后一个没有上限),那么我可能会写这样的东西:

PROGRAM test

  IMPLICIT NONE

  INTEGER :: ix   
  INTEGER, DIMENSION(5) :: absth = [1, 2, 3, 4, 5]   
  REAL, DIMENSION(9) :: vals = [.1, .2, .5, 1.2, 3.5, 3.7, 16.8, 19.8, 135.60]   
  INTEGER, DIMENSION(SIZE(absth)+1) :: bins

  bins = 0

  DO ix = 1, SIZE(bins)-1
     bins(ix) = COUNT(vals<absth(ix))   
  END DO   
  bins(ix) = COUNT(vals)

  bins = bins-EOSHIFT(bins,-1)
  WRITE(*,*) 'bins = ', bins
  ! which writes  3  1  0  2  0  3

END PROGRAM test

然后,当我对逻辑正确感到高兴时,我会将其变成一个函数并添加一些错误检查。

如果问题更笼统,并询问重现 Pythonfor-else结构的惯用 Fortran(90 后)方法,这里也有答案。

于 2016-12-01T09:53:55.510 回答
2

GO TO 语句允许任意跳转。特别是,您编写了 for 循环,然后是 else 块,然后是标记的 continue。在循环内,如果条件为真,则跳转到标记的继续。否则 for 循环将正常终止,else 块将被执行然后继续,完全匹配 python 的 for...else 构造的语义。

例如:

        INTEGER nabsth, nvals
        PARAMETER (nabsth=5, nvals=9)
        INTEGER absth(nabsth), counts(nabsth)
        REAL vals(nvals)
        DATA absth/1, 2, 3, 4, 5/
        DATA counts/0, 0, 0, 0, 0/
        DATA vals/.1, .2, .5, 1.2, 3.5, 3.7, 16.8, 19.8, 135.60/

        do iv = 1, nvals

          do ia = 1, nabsth - 1
            if (vals(iv) < absth(ia)) then
              counts(ia) = counts(ia) + 1
              goto 10
            end if
          end do
          counts(nabsth) = counts(nabsth) + 1
10        continue
        end do
        WRITE (*,*), counts
        end

生产

       3           1           0           2           3
于 2016-12-01T06:22:28.927 回答
2

Since the else part of Python's for-else block is executed only when all the elements are processed, how about simply using the if statement for the last element? For example,

program main
    implicit none
    integer i, n
    print *, "n = ?" ; read(*,*) n

    do i = 1, 10
        if ( i <= n ) then
            print *, i
        else
            exit
        endif
        if ( i == 10 ) print *, "reached the final index"
    enddo

    print *, "done"
end program

which probably corresponds to

n = int( input( "n = ? \n" ) )

for i in range( 1, 11 ):
    if i <= n:
        print( i )
    else:
        break
else:
    print( "reached the final index" )

print( "done" )

Another way might be to use a labeled block construct, for example:

program main
    implicit none
    integer i, n
    print *, "n = ?" ; read(*,*) n

    loop_i : block

      do i = 1, 10
          if ( i <= n ) then
              print *, i
          else
              exit loop_i
          endif
      enddo
      print *, "reached the final index"

    endblock loop_i

    print *, "done"
end program

According to Chap.20.1.7: "Exit from nearly any construct" in Modern Fortran Explained (by Metcalf et al) and also the F2008 Standards Chap.8.1.10 (obtained from here), it is OK to exit from any labeled construct like block, if, associate etc, but we may need a relatively new compiler (gfortran-6 worked for me). The IBM man page for exit is also useful.

于 2016-12-01T10:30:12.813 回答
0

有时 GOTO 很好。WHERE ELSEWHERE 可能有用...

do iv = 1, nvals

  is_in_last_absth = .true.
  Mask = .FALSE.
  Mask(1:(nabsth - 1)) = .TRUE.)
  Mask2 = .FALSE.
  WHERE(MASK)
    WHERE( vals(iv) < absth)
      mask2 = .TRUE.
    ENDWHERE

    WHERE(Mask2)
      Count = Count + 1
    ELSE
      LastCount = LastCount + 1
    ENDWHERE

  END WHERE
end do

count(2:(n-1)) = count(2:(n-1))+ lastcount(1:(n))
于 2016-12-01T22:19:17.973 回答
0

据我所知,Python 是唯一(或极少数)具有 for-else 语句的语言。不,Fortran 没有它。

于 2016-12-01T05:15:22.397 回答