Evading intent(in)

Intel Fortran, gfortran, and g95 all compile and run the following program, which changes an intent(in) argument, giving output 4.

module m
implicit none
contains
subroutine foo(i)
integer, intent(in) :: i
call increment(i)
end subroutine foo

subroutine increment(i)
integer :: i
! integer, intent(in out) :: i ! will not compile if this line uncommented
i = i+1
end subroutine increment
end module m

program main
use m, only: foo
implicit none
integer :: i
i = 3
call foo(i)
print*,i
end program main

When argument intents were introduced in Fortran 90, should there have been a restriction that an intent(in) argument can only be passed to other procedures as an intent(in) argument? Maybe this was not done because it would have prevented code using intent(in) from calling Fortran 77 code in many cases. Can this now be fixed by saying that passing an intent(in) variable to a procedure as an argument that is not intent(in) is obsolescent? Compilers would be required to warn about this, and users could turn such warnings into errors.

4 Likes

@Beliavsky , I suggest you also post this at GitHub - j3-fortran/fortran_proposals: Proposals for the Fortran Standard Committee. It is worth a good consideration. Thanks,

2 Likes

Related to this is:

  • What is the difference between intent(inout) and “unspecified intent” ?

I know we have discussed it somewhere, but I couldn’t find it, and had to figure out out on my own: the difference is that unspecified intent can be any of: intent(in), intent(out) and intent(inout). So for example if we change every unspecified intent as intent(inout), then the following code will not work anymore I think:

subroutine sub(i)
integer :: i
! integer, intent(in out) :: i ! will not compile if this line uncommented
print *, i
end subroutine

...
call sub(5)

If this analysis is correct, then one (as a human or a compiler) must examine every unspecified intent and see if the function writes to it or reads from it, and using this information figure out the exact intent. So the sub function above would become intent(in), but your increment function would become intent(inout).

1 Like

No, at least not by default. All I am saying is that unless I am mistaken, if foo does not modify i, then the example you gave is equivalent to integer, intent(in) :: i.

Yes, that is my point also: if we can’t determine if foo modifies i, then we can’t determine the correct intent, it can be intent(in), intent(out) or intent(inout). So no warning by default.

Agree with @kargl and @certik . intent is more of a promise by the developer than a dragon guarding the hoard of gold. There are various ways you can evade the language’s blade guards, and the use of unspecified intent is one of them. The language does the best it reasonably can to catch misuses of intent(in) dummies, but it can’t see all of them.

2 Likes

The OP example does show this producing a bug; so it would be nice to have some way to prevent it or warn of it. Since the compiler does catch use of the intent(in) variable on the LHS, it seems use as an argument is the (only?) case were it is not caught. It might be an expensive run-time check but it does seem possible a compiler could compare any intent(in) value on return to its’ original value or after an external call and warn if the value changed. I was thinking if an INTENT(IN) value was always passed by value to any external it would be better than the current case; but that does not catch the opposite type of bug where the value “should” be changed by the external call. I have certainly used debuggers that can watch for a change in a value, so it seems if that has been done that an optional run-time warning must be feasible; I assume the debugger watches an address instead of duplicating the potentially large amount of memory that could be required to check for a change on return, but really not sure. I just helped locate a bug that suffered from a somewhat similiar problem where there was a use of the variable J as a DO counter in a routine with a contained procedure called in the loop that set the value of the variable J but did not declare J as local, so it ended up inadvertently changing the value of the counter, producing an incomplete execution of the loop in that case. Not sure all compilers would generate the same bug, actually suspect they wouldn’t, but it was interesting because it also corrupted the debugger they were using so it was hiding itself well. Some old-fashioned PRINT statements found it in a few minutes. Sometimes the oldies are still goodies.

I was also surprise to see this behavior, my expectation was that variables with intent(in) would behave like a parameter for all subsequent calls.

The following examples shows how to protect the variable:

module m
implicit none
contains

subroutine foo(i)
  integer, intent(in) :: i
  call increment(i)
end subroutine foo

subroutine increment(i)
  integer :: i
  i = i+1
  print*, 'i in function', i
end subroutine increment

end module m

program main
  use m, only: foo
  implicit none
  integer :: i
  i = 3
  call foo((i))  ! force 'call by value'
  print*, 'i in main', i
end program main
module m
implicit none
contains

subroutine foo(i)
  integer, intent(in) :: i
  call increment((i))  ! force 'call by value'
end subroutine foo

subroutine increment(i)
  integer :: i
  i = i+1
  print*, 'i in function', i
end subroutine increment

end module m

program main
  use m, only: foo
  implicit none
  integer :: i
  i = 3
  call foo(i)
  print*, 'i in main', i
end program main
module m
implicit none
contains

subroutine foo(i)
  integer, intent(in) :: i
  call increment(i)
end subroutine foo

subroutine increment(i)
  integer :: i
  i = i+1
  print*, 'i in function', i
end subroutine increment

end module m

program main
  use m, only: foo
  implicit none
  integer, parameter :: i = 3
  call foo(i)
  print*, 'i in main', i
end program main

With gfortran, the first two program runs and the third crashes.

I don’t think the first two code examples in the prior message are valid Fortran but don’t know which compilers catch the problem. As stated on Stack Overflow,

[I]n the absence of a pointer result, the result of evaluating an expression is a value, not a variable. You are not permitted to redefine a value . Conceptually, it makes it no sense to say "I am going to change the meaning of the value 2 ", or "I am going to change the meaning of the result of evaluating 1 + 1 ".

When you use such an expression as an actual argument, it must not be associated with a dummy argument that is redefined inside the procedure.

Inside the subroutine change , the dummy argument that is associated with the value of the expression (a) is redefined. This is non-conforming.

I agree. But I though changing the value of an intent(in) variable is equally forbidden.
For the parameter, I get at least an segmentation fault.

The following contrived user error is interesting in that nvfortran goes through the loop the expected ten times, gfortran and ifortran go though it once (as indicated by M) but everyone compiled and ran without a warning

program usererr
implicit none
integer :: i,j,m
   j=20
   m=0
   do i=1,10
      call oops(j)
      m=m+1
   enddo
   write(*,*)i,j,m
contains
subroutine oops(k)
integer :: k
!integer :: i  !!USER FORGOT THIS
   i=k*k
   write(*,*)i,k
end subroutine oops
end program usererr

I enjoy your analogies :slight_smile: .

For pure and elemental procedures, the language is “tougher”. A pure procedure can only call procedures that are declared pure or elemental. It is not enough that those procedures satisfy the properties of pure procedures. I am suggesting that the requirements for intent(in) be similarly strengthened so that passing an intent(in) to a procedure where it has unspecified intent be obsolescent and trigger a compiler warning. Programmers would decide whether to have such warnings shown and whether to add intents to old procedures that lack them.

It’s good that Fortranners can now specify argument intents and that compilers will give error messages for intent(in) arguments that are explicitly changed in a procedure, but an intent(in) declaration that can be easily evaded means that they cannot be completely relied upon, or worse, that a programmer may see an intent(in) declaration and get a false sense of security.

1 Like

@Beliavsky 's original post with the comment, “Can this now be fixed by saying that passing an intent(in) variable to a procedure as an argument that is not intent(in) is obsolescent?” is a good premise for a proposal consideration toward the evolution of the language.

The original post hints well at the struggles and give-and-take during the difficult 1980s with the subsequent revision to FORTRAN 77 and how to approach Fortran 8X and to how get the newfangled code with additional guardrails to work with legacy code full of myriad extensions, all with unspecified dummy argument INTENTs of course. Compromises had to be made.

Nearly 30 years after the landmark Fortran 90 publication, it will be good for the Community to start discussing at least how to bring about better (perhaps stricter) guards and protections for modern code, in the case of this thread with INTENT(IN). And this does seem viable given some attention and care and guidance by compiler implementations. Hence my suggestion to @Beliavsky to also post it at GitHub proposals site where the targeted feedback and discussions toward a future enhancement to the standard can be captured.

2 Likes

It is now Make passing an intent(in) argument to a procedure with unspecified intent obsolescent, #228.

4 Likes

On Windows, GNU Fortran (GCC) 12.0.0 20210718 from equation.com is new enough and gives the above error.

Where the user runs it is unlikely he will get a production upgrade for a while, and it also ran with two other compilers, but that is good to hear. The particular code where something similar happened is always compiled with all available compilers during development; perhaps a 12.0 version might be allowed for testing/development and that is certainly a good reason why. The actual bug did not always change I and so only occasionally caused the wrong number of iterations and was more subtle than the little reproducer so it went unnoticed for too long. Seeing a compiler catch it is very appealing after having several not. The use case for Fortran in my experience often involves it being a language it is harder to make errors in so it is always good to see improvements like this, whether in the standard or in popular compilers.

I just tested the above code with GCC GFortran 9.3.0 and 10.3.0 on Ubuntu Linux 20.04 LTS. Both compile without any problem, and gives the following output:

         400          20
         401          20           1

Looks like GFortran 11.2 on Debian unstable won’t compile it. It gave me the same error message:

$ gfortran-11 looperr.f90 
looperr.f90:15:9:

    7 |     call oops(j)
      |                2
......
   15 |     i=k*k
      |         1
Error: Index variable 'i' redefined at (1) in procedure 'oops' called from within DO loop at (2)

I am surprised by Beliavsky’s example because increment is visible in the module compilation unit. The compilers can see that increment changes its argument.

In the situation where sub-programs are separately compiled, analyses of several large programs (e.g. WRF and TELEMAC) show about a 2% error rate in INTENT(IN) specifications. We experimented with removing all of the INTENT specifications and found absolutely no change in the program outputs. However I think that compilers do use INTENT in determining whether to input or output arrays in some circumstances. We found that INTENT is always checked within the routine where it is specified, but not when an INTENT(IN) argument is passed down into other routines.

fpt (http://simconglobal.com) will catch errors like this because it reads all of the routines in a program and analyses the uses. However this is not trivial. In particular it is difficult to catch INTENT(OUT) violations because this involves tracing all control paths through the code to prove that an INTENT(OUT) argument is always assigned. We are revising our handling of this at the moment.

Best wishes,

John

4 Likes

Thanks for the information. Does fpt have the ability to analyze a Fortran-77-style code without INTENTs and rewrite the code, adding INTENTs, while giving the same results as the original code? Adding intents manually is one of the first things I do when trying to understand an old code.

1 Like

INTENT(INOUT) requires that the associated actual argument is definable. This is not the same as the rules for no intent specified. The first sentence is why you cannot use an INTENT(IN) argument as an actual argument corresponding to a dummy with INTENT(INOUT).

2 Likes