简体   繁体   English

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

[英]Is there a Fortran equivalent of Python's for-else statement?

Is there a Fortran equivalent of Python's for-else statement? 是否有与Python的for-else语句等效的Fortran?

For example, the following sorts a list of numbers into different ranges. 例如,以下将数字列表排序到不同的范围。 In Python, it is: 在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

In Fortran, this works the same: 在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

But is there a way to not have to use is_in_last_absth and replace it with something like the else in Python? 但是有没有办法不必使用is_in_last_absth并将其替换为Python中else呢?

If the question is specifically about binning a series of numbers, with absth being the upper limits on each bin (bar the last which has no upper limit), then I'd probably write something like this: 如果问题特别是关于对一系列数字进行absth ,而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

then, when I was happy that the logic was correct I'd turn it into a function and add in some error checking. 然后,当我对逻辑正确感到满意时,我会将其转换为一个函数并添加一些错误检查。

If the question is more general, and asks what is the idiomatic Fortran (post 90) way to reproduce Python's for-else structure, there are answers here to that too. 如果这个问题更笼统,并问到什么是惯用的Fortran(后90版)方式来重现Python的for-else结构,那么这里也有答案。

There is no direct equivalent to that python construct. 没有直接等效于python构造的东西。

Note though, that early termination of a do loop with a counted loop control can be detected by examining the value of the do variable after the loop. 但是请注意,可以通过检查循环后的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

An exit statement can also jump out of more than just do loops: 退出语句还可以跳出循环之外:

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

and a cycle statement can cycle any do construct that the statement is nested within: 并且cycle语句可以循环嵌套该语句的任何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

GO TO statements allow arbitrary jumps. GO TO语句允许任意跳转。 In particular, you write your for loop followed by the else block, followed by a labeled continue. 特别是,您先编写for循环,然后再是else块,再加上一个标记为Continue的代码。 Within the loop, if the condition is true then jump to the labeled continue. 在循环内,如果条件为true,则跳至标记为继续。 Otherwise the for loop will terminate normally, the else block will be executed and then the continue, exactly matching the semantics of python's for...else construct. 否则,for循环将正常终止,else块将被执行,然后继续执行,完全匹配python for ... else构造的语义。

For example: 例如:

        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

Produces 产生

       3           1           0           2           3

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? 由于Python的for-else块的else部分仅在处理完所有元素后才执行,因此仅对最后一个元素使用if语句怎么办? 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: 另一种方法可能是使用标记的block构造,例如:

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). 根据第20.1.7节:“ 现代Fortran解释中的 “几乎从任何结构退出”(由Metcalf等人)以及F2008标准第8.1.10节 (从此处获得),可以从任何标记的结构退出像blockifassociate等,但是我们可能需要一个相对较新的编译器(gfortran-6为我工作)。 The IBM man page for exit is also useful. 用于退出的IBM手册页也很有用。

To the best of my knowledge, Python is the only (or one of the very few) languages that has a for-else statement. 就我所知,Python是仅有的(或少数几种)具有for-else语句的语言。 No, Fortran does not have it. 不,Fortran没有。

Sometimes GOTO is good. 有时GOTO很好。 A WHERE ELSEWHERE may be useful... 在其他地方可能会有用...

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))

声明:本站的技术帖子网页,遵循CC BY-SA 4.0协议,如果您需要转载,请注明本站网址或者原文地址。任何问题请咨询:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM