Implied-do array constructor, type specs, and differences between GFortran, Intel, and LFortran

I am a complete newbie when it comes to Fortran, but I was thinking that this should be a valid program:

program array_constructor
    implicit none
    real :: a(10)

    a = [real :: (i*2.5, integer :: i = 1,10)]  ! potential syntax error
    
    print *, a

end program array_constructor

This is accepted by the Intel compilers: ifort and ifx. Unfortunately, GFortran (v. 13.2.0) complains of a syntax error:

array_constructor.f90:5:24:

    5 |     a = [real :: (i*2.5, integer :: i = 1,10)] ! causes syntax error
      |                        1
Error: Expected a right parenthesis in expression at (1)

…similarly, LFortran says it is also a syntax error:

syntax error: Token '::' is unexpected here
 --> input:5:34
  |
5 |     a = [real :: (i*2.5, integer :: i = 1,10)] ! causes syntax error
  |                                  ^^ 

The relevant section of the draft 2023 Fortran Standard looks to be “7.8 Construction of array values” that starts on page 99 (PDF page 113). It seems like GFortran and LFortran aren’t liking the optional type specification for the loop do-variable. Which seems odd, since I’ve been under the impression that implicit none is a recommended common practice. Am I overlooking something?

Thanks!

1 Like

Hi, @GregB. Welcome to the forum. As of version 13, you have encountered a missing feature implementation in gfortran. Intel, Cray, and NAG are the compilers with a fully or nearly complete implementation of Fortran 2018. The GNU developers always appreciate and look for new volunteers if you can help improve gfortran.

4 Likes

Thanks @GregB for reporting this unimplemented feature, I created an issue for it: Allow optional types in implied do loops · Issue #4033 · lfortran/lfortran · GitHub. If you or others want to help, we always welcome PRs. This feature shouldn’t be too difficult to implement for a newcomer.

1 Like

This is a new syntax that gfortran apparently does not yet support. The older way is to declare integer :: i in the subprogram declarations rather than within the implied do loop.

2 Likes

I wish this would be possible:
a = 2.5 * [1:10]

5 Likes

Are the draft versions of previous Fortran standards available? So that I could figure out which standard this came from?

This url https://wg5-fortran.org/ has a popup window that I think has links to the final drafts of the standard dating back to f90. Before that, the pdfs of the final standards are available at no cost.

However, even with these documents, it requires much effort to determine exactly when a feature became standard in the language. A feature cross-reference with this information would be useful for both programmers and compiler writers. This might be a good crowd-source project for our community.

I think the current array constructor syntax is much more powerful and flexible. This limited syntax would be a step backwards.

However, there is a useful addition to the current syntax that might be considered. One disadvantage of the current syntax is that the programmer does not control whether the statement is intended to be evaluated at compile time or at run time. It is now the compiler (e.g. with optimization level options) that determines this. If there is a backwards-compatible way that the programmer could tell the compiler which he intends, that would be useful.

The committee will yawn at this (most in private given the PC environment) and think the Fortranner should be satisfied with the following:

    ..
    block
       real, parameter :: n(*) = 2.5 * real( [( i, integer :: i = 1, size(a) )], kind=kind(a) )
       a = n
    end block
    ..

Ok, I could agree that this is one way to “force” computation at compile time. But what about the other extreme, where the programmer wants the computation to occur at run time (e.g. to make the compiled object file small)?

Then, either

   ..
   forall ( integer :: i=1:size(a) ) a(i) = 2.5 * real( i, kind=kind(a) )
   ..

or the old-fashioned + new (due to the stupid situation with DO but where it’s still better to localize the type specification of loop index)

   ..
    block 
       integer :: i
       do i = 1, size(a)
          a(i) = 2.5 * real( i, kind=kind(a) )
       end do
    end block
   ..

Well, it would not aim at replacing the current constructor (which is here for eternity anyway), but at providing a much shorter and more readable syntax that would fit 95% of the usage cases.

5 Likes

Each revision of the standard (since F2008, anyway) has a section in the Introduction identifying changes. Some of the changes might be difficult to represent in a table. The optional type for an array constructor first appeared in Fortran 2018.

2 Likes

@FortranFan

a(i) = 2.5 * real( i, kind=kind(a) )

Why decorating with the unnecessary code ?

is “a(i) = 2.5 * i” any different ?

Surely, more unnecessary decoration is just a receipt for coding bugs.

It generalizes and future-proofs the code. It does not matter for this particular expression, but other general expressions can benefit from the explicit kind=kind(a) conversion when kind(a) is some nondefault real kind. Otherwise, the expression might first narrow to the default kind, losing accuracy, and then convert to the final kind=kind(a).

This is often spelled range. I.e.

function range(i)
  integer, intent(in) :: i
  integer :: range(i)
  range = [(j, j = 1, i)]
end function

I use it pretty regularly, so I wouldn’t be opposed to having it added as an intrinsic.

1 Like

There is already an intrinsic called range with a very different meaning, and so @everythingfunctional’s suggested new one would have to be called something else. Perhaps between(m,n) defined by

  function between(m,n)
    integer,intent(in) :: m,n
    integer between(n-m+1), j
    between = [(j, j = m,n)]
  end function between

(This produces an empty array if n<m. So does @everythingfunctional’s range(i) if i<1. What ought to happen in those cases?)

Just

[n:m:p] (:p being optional)

would be just perfect, as a shortcut to the current constructor

[(i, integer :: i = n, m, p)].

No need to give a name…

5 Likes

One can define a binary operator .to. so that i.to.j gives what you intend with i:j, for example

module m
implicit none
interface operator(.to.)
   module procedure to
end interface
contains
pure function to(i, j) result(vec)
integer, intent(in) :: i, j
integer             :: vec(j-i+1)
integer             :: k
vec = [(k, k=i,j)]
end function to
end module m

program main
use m, only: operator(.to.)
implicit none
print*,2.5 * [1.to.4]
end program main

giving output

2.50000000 5.00000000 7.50000000 10.0000000

4 Likes

Indeed. A name doesn’t immediately come to mind, but I’m sure one could be found.

I was somewhat basing the idea off the python equivalent (and given a simple expected implementation) that it would give a zero-sized array. I.e.

>>> print(list(range(3)))
[0, 1, 2]
>>> print(list(range(0)))
[]
>>> print(list(range(-1)))
[]

Using a placeholder name, I would expect something like

interface range
  module procedure range_without_start
  module procedure range_with_start
end interface

function range_without_start(finish, increment) result(list)
  integer, intent(in) :: finish
  integer, optional, intent(in) :: increment
  integer :: list(finish/(present(increment) ? increment : 1))
  list = [(i, integer :: i = 1, finish, (present(increment) ? increment : 1))]
end function

function range_with_start(start, finish, increment) result(list)
  integer, intent(in) :: start
  integer, intent(in) :: finish
  integer, optional, intent(in) :: increment
  integer :: list((finish-start+1)/(present(increment) ? increment : 1))
  list = [(i, integer :: i = start, finish, (present(increment) ? increment : 1))]
end function

Although now that I’ve typed it out, it is an ambiguous interface. :thinking:

I get the feeling there’s some syntactic ambiguity hiding in here somewhere, but if not it seems reasonable.