Derived data type component as do loop index

(gfortran v13 on Linux)
According to my 4th edition of Chapman:
“Each component in a variable of a derived data type can be addressed independently, and can be used just like any other variable of the same type.”

program iderive
implicit none

type loopcounter
  integer :: i
end type loopcounter

type(loopcounter) :: lc

do lc%i = 1, 10
  write (*, *) lc%i
end do

end program iderive

In this over-simplified example I get an ‘Unclassifiable statement’ compile error at the start of the do loop.

What have I missed?

2 Likes

ifx, nvfortran, and AMD flang give the following errors

t4.f90(10): error #5082: Syntax error, found ‘%’ when expecting one of: =
do lc%i = 1, 10
-----^
t4.f90(12): error #6099: An ENDDO statement occurred without a corresponding DO or DO WHILE statement.
end do
^
compilation aborted for t4.f90 (code 1

nvfortran:

NVFORTRAN-S-0106-DO index variable must be a scalar variable (t4.f90: 10)
0 inform, 0 warnings, 1 severes, 0 fatal for iderive

AMD flang

F90-S-0106-DO index variable must be a scalar variable (t42.f90: 16)
0 inform, 0 warnings, 1 severes, 0 fatal for iderive

nvfortran and AMD flang are both based on “classic” flang so they give essentially the same error message.

gfortran 14 gives the same error as 13.

However if you modify your original code as follows:

program iderive
implicit none

type loopcounter
  integer :: i
end type loopcounter

type(loopcounter) :: lc

associate(i=>lc%i)
  do i = 1, 10
    write (*, *) lc%i
  end do
end associate

end program iderive

All of the compilers above give the expected results

1 Like

With NAG Fortran:

> nagfor test_loop_counter.f90
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
Error: test_loop_counter.f90, line 10: Syntax error
       detected at LC@%
Error: test_loop_counter.f90, line 12: ENDDO without DO
       detected at END DO@<end-of-statement>
[NAG Fortran Compiler pass 1 error termination, 2 errors]

With @rwmsu introduction of associate I get the following message instead: :slight_smile:

> nagfor test_loop_counter.f90
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
Questionable: test_loop_counter.f90, line 11: DO index variable I is an associate-name
[NAG Fortran Compiler normal termination, 1 warning]

Since the four most widely used compilers (at least on workstations), give errors for the original code, the question becomes why?. lc%i is clearly a scalar (at least from the programmers perspective). A second question is do compilers treat loop indices different than standard integers and would this factor into the errors. Since its illegal to jump into a loop after modifying the loop index, I assume that loop indicies are treated as purely local data and can’t have a global extent which is what embedding it in a derived type might imply. Just guessing but maybe one of the standards folks can clarify what is happening here. Are loops considered a different “scoping unit”?

Most of the compilers above fail in the parsing stage.

Definitely in the fixed-form parsing the spaces are removed so you have doi=1 and there is special logic to distinguish and assignment doi = 1 and loop do i = 1, 10 from just doi=1 by looking if there is a comma or not. Probably it could be extended to handle derived types also, however then it could also be things like do a%b(3,1)%e(4)%i = 1, 10, I don’t know if there could be some fundamental ambiguities or not.

Assuming you can parse it, then it becomes a question of semantics, if a loop variable should just be a local variable or associated variable. I don’t know what the standard says.

For the record, LFortran behaves like this:

$ lfortran a.f90
syntax error: Token '%' is unexpected here
  --> a.f90:10:6
   |
10 | do lc%i = 1, 10
   |      ^

And the associate version above also works in LFortran.

I’m wonder if this case is addressed at all in the standard. If not, this might be a good candidate for an interpretation request.

Edit:

So to summarize above, this is a parsing issue because current parsers are looking for either a fixed form where spaces are not significant or a free form where the only characters allowed between the do and the index variable name are spaces (and at least one space is required). Therefore if the parser sees any character other than a space it will throw an error. Makes sense. I guess the only characters allowed after it finds the loop index is a space or an =.

I see this

C1121 (R1124) The do-variable shall be a variable of type integer.

but I do not know if this precludes a derived type component. I think the “shall” means that the compiler must detect violations.

The key rule here in the standard is:

R1124 do-variable is scalar-int-variable-name

A component is not a variable name. This is a syntax rule.

5 Likes

Ok, now I’m really confused. How can a variable name not be a variable name just because its a component in a derived type. Why isn’t the full reference to the component (lc%i) the unique identifier (ie variable name) for the component. Why should the compiler at least at the programmer level care. At the syntax level how is this really any different than writing:

integer :: lc_i

do lc_i=1,10

The only difference is I guess the scope of the variable. Sorry but this seems to me to be a contradiction to what I would define a “scalar-int-variable-name”. I think at least the standard should spell out in plain language (something its not very good at in my opinion) why this corner-case is not allowed. Yes it’s obvious why once you really dig into the syntax rules but the average Joe Programmer will see the component as just an integer and could care less if " A component is not a variable name". I use derived types a lot in cases that before f90 I would use a COMMON block. Just another way to group related data into one storage construct. My point is, if:

common /lc/ i

do i=1,10

works, then having i as a component of derived type lc should also work.

The restriction that the do-variable must be a named variable is in the standard since at least F90 —but back then, it could be real besides integer.

I’m just speculating but since the values the do-variable takes are not controlled by the programmer directly, it makes sense to avoid the whole “does it belong to a regular derived type or a sequence one?” (“does the DT have the bind(C) attribute?”).

There are some other places where that behavior is similar —e.g., in a select-type-stmt the selector must either be a named variable or be replaced by an associate-name, since the actual type will be controlled by the type-guards.

(</end-of-speculation>)

May I ask the reason to have a non-local do-variable?

I personally wouldn’t use a non-local do variable but the OP apparently has a reason. I have seen do variables saved in common blocks or local data statements in a lot of old code usually something like interpolation routines where you are trying to find the bounding interval for the desired interpolation value. Saving the index of the last found interval in a search to use in successive calls to the interpolation routines was standard practice.

1 Like

Thanks to everyone for the responses.
My original code, in essence, was:

program iderive
implicit none

integer :: i, j
type coordinates
  integer :: x
  integer :: y
end type coordinates
type(coordinates) :: cp

do i = 1, 10
  cp%x = i
  do j = 1, 10
    cp%y = j
     ! do something with cp%x and cp%y
  end do
end do

end program iderive

It seemed a good idea to use cp%x and cp%y directly as the loop indices…