Proposal: IMPLICIT NONE (INTENT)

Fortran 2018 introduced IMPLICIT NONE (EXTERNAL), which induces me to hope that compilers will soon enable external procedure calls to be checked that the proedure actual arguments as well as return type (if the procedure is a function) are consistent with the declations of the types of the function and its arguments.

In this note I wish to make the case for IMPLICIT NONE (INTENT). Intent declarations are not required, and the default intent is INTENT(IN OUT). When a programmer writes explicit INTENT declarations instead of relying on the default, the programmer would appreciate help from the compiler (when requested with an option flag) to check that the declared intents are correct. In the case of the NRL/NASA code HWM14, about which I opened a separate thread a few weeks ago, there are some instances where the declared intent is wrong, and there is no way that I can see to get the compilers to detect and tell me about that error The opinion has been stated that compilers usually ignore intent declarations completely. In the case of HWM14, I was able to pinpoint the errors in the stated intents only by turning on the C=UNDEFINED option of the NAG compiler. To understand the issues better, I went back to the HWM14 source files, and removed all the intent declarations (the correct ones as well as the incorrect ones). The result, when compiled with or without optimization, was: surprise, no change in the output results. Are we to conclude that writing intent declarations, without help available for checking those declarations, is a waste of time?

1 Like

I think the default intent should be intent(in), so that you don’t accidentally modify the arguments and because I think that’s the most common.

1 Like

My experience, admittedly only with the DEC/Intel compilers. is that INTENT is checked for violations of language rules. Generated code changes are more subtle, and only with INTENT(IN).

The default is no INTENT specified, which is not the same as INTENT(INOUT). INTENT(INOUT) specifies the argument is definable, so technically you could not pass an expression, for example.

INTENT(OUT) means I am going to specify the value on return but do not need the current value, INTENT(INOUT) means I need the current value and am going to set the value on return and no INTENT means no such assumptions. So both
INTENT(OUT) and INTENT(INOUT) imply the argument passed is definable and should not be a constant or expression, for example.

You might get the same answer if you remove all the INTENT attributes and they were done correctly but perhaps not the same optimizations. Passing an argument that the compiler decides to do a gather/scatter on would not need to do the scatter if INTENT(IN) is specified, for example. The standard leaves nearly everthing up to the compiler but nothing prevents the compiler from enforcing INTENT, it is just very difficult to enforce.

NOTE 4 in section 8.5.10 gives perhaps the best condensed description; although the behavior with pointer arguments is a bit harder to digest.

Obviously at least one compiler actually uses the INTENT(OUT) description as it caused the bug you described; so it is not like INTENT always has no effect; but the machine code produced is often the same whether the option is there or not; partly because the compiler can be smart enough to draw the same conclusion; perhaps because the compiler treats it merely as a comment mostly useful to someone maintaining the code in the future.

Because of the very bug you describe that can be introduced I have seen several discussions where people say they remove all the INTENT attributes, but I find it useful myself.

 8.5.10      INTENT attribute
          NOTE4
           Argument intent specifications serve several purposes in addition to documenting the intended use of dummy
           arguments. A processor can check whether an INTENT (IN) dummy argument is used in a way that could
           redefine it. A slightly more sophisticated processor could check to see whether an INTENT (OUT) dummy
           argument could possibly be referenced before it is defined. If the procedure’s interface is explicit, the processor
           can also verify that actual arguments corresponding to INTENT (OUT) or INTENT (INOUT) dummy argu-
           ments are definable. A more sophisticated processor could use this information to optimize the translation of
           the referencing scoping unit by taking advantage of the fact that actual arguments corresponding to INTENT
           (IN) dummy arguments will not be changed and that any prior value of an actual argument corresponding to
           an INTENT (OUT) dummy argument will not be referenced and could thus be discarded.
           INTENT (OUT) means that the value of the argument after invoking the procedure is entirely the result of
           executing that procedure. If an argument might not be redefined and it is desired to have the argument retain its
           value in that case, INTENT (OUT) cannot be used because it would cause the argument to become undefined;
           however, INTENT (INOUT) can be used, even if there is no explicit reference to the value of the dummy
           argument.

           INTENT (INOUT) is not equivalent to omitting the INTENT attribute. The actual argument corresponding
           to an INTENT (INOUT) dummy argument is always required to be definable, while an actual argument
           corresponding to a dummy argument without an INTENT attribute need be definable only if the dummy
           argument is actually redefined.

I wish it was enforced more often, and I wish it was implemented on the procedure header itself and optionally on the call as well, so it looked like

subroutine(a>,b>,<c>,<c) or (a>,b>,c<>,d<). If that notation meant a call had to use matching notation it would be easier for a compiler to enforce, but that would mean if you changed the routine you would have to change all the calls and is perhaps too burdensum a syntax.

I think the default being anything but the current lack of intent would be problematic for a subroutine, but I do wish functions defaulted to everything being INTENT(IN) as well, but that is somewhat a personal taste I suppose ( I really like to avoid changing input values with a function, but admit to doing it occasionally with an optional error code parameter).

2 Likes

That sentence and the one following it in your quotation are very much relevant and helpful.
The original programmers of the HWM14 code, I guess, added intent declarations in order to be helpful to people who used their code years later. Despite their good intentions, a bug was introduced into the code – a bug that has survived for12 years.

I hit a similar bug a while ago which is where I first learned how IINTENT(OUT) could optionally undefine the current values. One compiler used a new undefined array at the beginning of the procedure, but the procedure did not always set all the values but another compiler treated it just like no intent was specified (and worked) . It was a Netlib package but I do not immediately remember which one. It is unfortunate the attribute can cause new bugs and does not always catch old ones; making its use more problematic than it originally appears. I know when I initially saw it I thought it would always be an improvement to use it but found out in practice that is not the case.

With large arrays there can be significant overhead in initializing an array, but if I suspect intent is causing a problem I remove them all or for all INTENT(OUT) arrays put ā€œARRAY_NAME=NANā€ for floats and ARRAY_NAME=(-huge(0)) for whole numbers at the very top of the procedures.

Not sure if it is a common enough problem to justify a compiler having a ā€œā€“ignore intentā€ switch, but there are times it would be nice.

It is one of those classes of bugs where once you see and understand it you remember because it took so much effort to resolve, and subsequently spot it pretty quickly. But definitely a lesson I wish was not needed.

1 Like

More than that, if the intent(out) argument is a derived type with initializers, they will be initialized:

program intent_out_test
  implicit none

  type xyzzy_t
    integer :: i=42, j=-42
  end type

  type (xyzzy_t) :: x

  x%i = 10
  x%j = 11
  call sub (x)
  print *, 'main: ', x%i, x%j

contains

  subroutine sub (t)
    type (xyzzy_t), intent(out) :: t

    print *, 'sub : ', t%i, t%j

  end subroutine

end program
$ lfortran intent_out.f90
sub :     42    -42
main:     42    -42
$

Yes. Older codes tend not to use user-defined types but a common thing in the old codes is passing the same parameter multiple times. The two combined is indeed a perplexing combination. I was not sure at all what
a modified version of your demonstrator would produce or if it would compile…

program intent_out_test
  implicit none

  type xyzzy_t
    integer :: i=42, j=-42
  end type

  type (xyzzy_t) :: x

  x%i = 10
  x%j = 11
  print *, 'main: before', x%i, x%j
  call sub (x,x,x)
  print *, 'main: after', x%i, x%j
 
contains

  subroutine sub (s,t,u)
    type (xyzzy_t), intent(in) :: s
    type (xyzzy_t), intent(out) :: t
    type (xyzzy_t), intent(inout) :: u

    print *, 'sub : ', t%i, t%j
    print *, 'sub : ', u%i, u%j
    t%i=t%i+10
    u%j=u%j+100

  end subroutine

end program

so the result was a little anti-climatic given my pessimism! Only tried it
with gfortran though.

Others have pointed out that the default intent is not exactly the same as INOUT. Consider this program:

program intent
   implicit none
   integer :: a, b, c
   call sub( 1, 2, 3 )  ! error in third argument
contains
   subroutine sub( a, b, c )
      integer :: a   ! no intent
      integer, intent(in) :: b
      integer, intent(inout) :: c
      b = b + 1  ! should be an error.
   end subroutine sub
end program intent

$ gfortran intent.f90
intent.f90:10:7:

   10 |       b = b + 1  ! should be an error.
      |       1~
Error: Dummy argument 'b' with INTENT(IN) in variable definition context (assignment) at (1)
intent.f90:4:19:

    4 |    call sub( 1, 2, 3 )  ! error in third argument
      |                   1
Error: Non-variable expression in variable definition context (actual argument to INTENT = OUT/INOUT) at (1)

It is allowed to pass the literal value 1 as the first argument with default intent, but not the literal value 3 as the third argument with INTENT(INOUT).

Also note that the modification of the second dummy argument with INTENT(IN) is recognized by the compiler as an error.

Changing the meaning of default INTENT would be problematic because of the 70 year legacy of fortran arguments. It would have been problematic if it had been changed in f90 too (when INTENT was introduced into the language), but perhaps even more so now some 35 years later.

There are some other cases where intent(out) requires some kind of active action by the compiler: 1) an allocatable actual argument (or derived type component) must be deallocated, and 2) intent(out) can trigger a finalizer call. Are there any others?