A need for a proposal for an enforced INTENT(IN)?

The intent(out) attribute means that the value of the argument after
invoking the procedure is entirely the result of executing that procedure.

intent(in) is just literally indicating the intent of the programmer.

As has come up before, the compilers are free to try and report when an
intent(in) value has been changed, but it is hard to detect. Although
the programmer can avoid the problems this can produce by making a copy
before the call or in the called procedure that defeats the purpose
most programmers have in specifying the attribute in the first place.

Should the standard provide some alternate attribute that ensures the
value is copied if necessary so that there is a strict enforceable
meaning like with intent(out)?

I keep finding what can be a subtle bug (especially when the value is
only conditionally changed) that the longer example program illustrates,
(and at least three compilers do not seem able to detect) as an example
of a real-world mistake that I keep seeing, partly because the word
INTENT is not being taken literally; but the fact an intent(out) does
always have a predictable action really makes it non-intuitive that
intent(in) does not.

One of the strengths of the Fortran language are parts of the design specifically make it hard to make errors commonly found in codes written in other languages. It seems like it missed the mark, even though I am sure there was good intent :wink: .

program intent_out
integer,allocatable :: i(:)

   if(allocated(i))deallocate(i)
   allocate(i(10))
   i=123
   write(*,*)'I allocation before=',allocated(i)
   call out(i)
   write(*,*)'I allocation after=',allocated(i)

contains

subroutine out(j)
integer,allocatable,intent(out) :: j(:)
   write(*,*)'J allocation=',allocated(j)
end subroutine out

end program intent_out
 I allocation before= T
 J allocation= F
 I allocation after= F
Example code
program testit
implicit none
integer  :: array(20,50)
integer  :: i, x, y, c

! fill an array with blocks of integer values that are an
! ADE (ASCII decimal equivalent of a printable character (ie. 32 to 126)
   array(:,:)=61 ! pre-fill array
! Fill array with rectangles of values
   array(  5:15,  4:45) = 43 
   array( 10:12,  3:35) = 45 
   array( 13:18,  2:45) = 45 
   array(  2:10, 26:49) = 45 
   array(  3: 8, 30:44) = 42 
   array(  2: 2,  2:14) = 45 
! print the array assuming the values can be printed as characters
   write (*, fmt = '(50a1)') (char(array(i,:)),i=1,size(array,dim=1))

! pick a point <10,17> and flood fill starting at the point with value 35
   x=10
   y=17
   c=array(10,17)
#ifdef ADD_BUG
   ! NOTE: DO NOT DO THIS INSTEAD:
   write(*,*)'BAD'
   call flood_fill(array,y,x,array(10,17),35)
   ! you would be passing in a value that will be changed during the
   ! recursion!
#else
   write(*,*)'GOOD'
   call flood_fill(array,y,x,c,35)
#endif

! print the array to show the change
   write(*,'(a)')
   write (*, fmt = '(50a1)') (char(array(i,:)),i=1,size(array,dim=1))

contains

recursive subroutine flood_fill(array,y,x,old_attr,new_attr)
integer             ::  array(:,:)
integer,intent(in)  :: y, x, old_attr, new_attr
integer             :: test_attribute
! Stack-based recursive flood-fill (Four-way)
   test_attribute=array(y,x)
!     prevent loop changing A to A     Found something of the old color
   if(test_attribute.ne.new_attr .and. test_attribute.eq.old_attr)then
      array(y,x)=new_attr
      if(x.gt.1)                call flood_fill(array,y,x-1,old_attr,new_attr)
      if(x.lt.size(array,dim=2))call flood_fill(array,y,x+1,old_attr,new_attr)
      if(y.gt.1)                call flood_fill(array,y-1,x,old_attr,new_attr)
      if(y.lt.size(array,dim=1))call flood_fill(array,y+1,x,old_attr,new_attr)
   endif
end subroutine flood_fill

end program testit

good output

GOOD output
GOOD
==================================================
=-------------===========------------------------=
=========================----***************-----=
=========================----***************-----=
===++++++++++++++++++++++----***************-----=
===++++++++++++++++++++++----***************-----=
===++++++++++++++++++++++----***************-----=
===++++++++++++++++++++++----***************-----=
===++++++++++++++++++++++------------------------=
==###############--------------------------------=
==#################################++++++++++=====
==#################################++++++++++=====
=############################################=====
=############################################=====
=############################################=====
=############################################=====
=#########-----------------------------------=====
=--------------------------------------------=====
==================================================
==================================================

bad output

BAD output
 BAD

==================================================
=-------------===========------------------------=
=========================----***************-----=
=========================----***************-----=
===++++++++++++++++++++++----***************-----=
===++++++++++++++++++++++----***************-----=
===++++++++++++++++++++++----***************-----=
===++++++++++++++++++++++----***************-----=
===++++++++++++++++++++++------------------------=
==###############--------------------------------=
==#################################++++++++++=====
==#################################++++++++++=====
=############################################=====
=############################################=====
=############################################=====
=############################################=====
=#########-----------------------------------=====
=--------------------------------------------=====
==================================================
==================================================

I believe this is not standard conforming, as youā€™re aliasing an intent(out) (although itā€™s unspecified) argument with and intent(in) argument.

But to answer your question to be explicit about making a copy on input, you could consider using the value attribute.

2 Likes

+1

My thoughts exactly.

1 Like

There are definitely ways to fix the code, including the method shown. The VALUE attribute is a good one but I think it just points out that INTENT(IN) is more like a pragma that does not necessarily change the way the code performs, while INTENT(OUT) has a defined behavior that changes results. I think anyone first seeing INTENT(IN) expects it to be enforced. The asymmetry points to something missing in my opinion.

There are a LOT of restrictions on the VALUE attribute, so it would work nicely here with a scalar, but what about a simple case where the value is an array? for example.

The implications of INTENT(OUT) often trip up programmers who are transitioning from old Fortran (F77 and earlier) or from another language to modern Fortran. The meaning of INTENT(OUT) could have been: ā€œfor this argument the prior value is not used in the subprogram, and the subprogram may update the value before returningā€. In other words, if no update occurred, the value prior to entry would remain unchanged. According to the Fortran standard, however, the prior value is replaced by ā€˜undefinedā€™ as soon as the subprogram is entered. Most compilers, on the other hand, do not enforce this unless a suitable error-checking compiler flag is specified.

I think that this destructive feature (undefined unless defined in subprogram) is less useful than ā€˜update or preserve, do not useā€™. The language forces the programmer to save and restore the value using another variable, or change the intent to INOUT or unspecified, if it is desired to ā€˜update or preserveā€™.

What is your experience in this regard?

Here is a pseudo-code sketch:

ā€¦
istat = 1 ! 1 means ā€˜converging slowlyā€™
call sub(ā€¦, istat)
select case(istat)
case(1)
print *,ā€˜Converged slowlyā€™
case (2)
print *,ā€˜Failed to convergeā€™
stop
end select
ā€¦
subroutine sub(ā€¦, istat)
integer, intent(out) :: istat
ā€¦
if (iters > iterlim) istat = 2 ! 2 means failure

A benefit of the current behavior is that one knows that an allocatable intent(out) is deallocated, as are the allocatable components of a derived type, so for such arguments code such as

if (allocated(foo)) deallocate (foo)

is not needed.

I agree, but this is a special case, and it is less frequently used than specifying intent for arguments that do not have the ā€˜allocatableā€™ attribute or whose allocation status is not subject to change in the subroutine.

There is often confusion regarding whether the intent applies to the allocation status or to the contents of the variable.

1 Like

I think it would be useful to specify INTENT(OUT) separately for data and for allocation status. If a compiler or tool is tracing data flow through a code, a routine which allocates an object but does set a value could cause problems.

In house, we forbid INTENT specifications except where they are mandated by the standard. This because:

i. We have measured the reliability of INTENT specifications in many large codes. Typically the error rate, where INTENT(IN) objects are actually changed, is over 2%.

ii. The current specification is not adequate for dataflow analysis. We need to know, for example, whether an INTENT(OUT) object is always assigned or sometimes assigned.

iii. We have tools which find INTENT reliably by analysing the code.

Fortran has a range of different intents, at least:

i. Label argument
ii. Subroutine argument
iii. Function argument.
iv. Data INTENT(IN) This can be subdivided into always and sometimes, but we havenā€™t found this useful (yet).
v. Data INTENT(INOUT) (Again, this could be sub-divided
vi Data INTENT(Always OUT)
vii. Data INTENT(Sometimes OUT)
viii Allocation status INTENT(IN)
ix - xi. Allocation status as Data v-vii.
xii. Attribute (IN) - e.g. array bounds, size, etc.

I am not sure how much specifying all this would contribute to the language. We do use this information internally in analysing code and analysis tools may be the best place for it.

We have examined compilers for their response to INTENT violations. For example, we stripped all of the INTENT specifications from WRF and ran the example cases. The results did not change by a single bit under ifort and gfortran. However, there are cases where INTENT specifications can improve efficiency in passing array sections.

For the most part, INTENT specifications reveal the programmersā€™ belief about what will happen, and that is useful.

Best wishes,

John

3 Likes

I agree with @urbanjost, my understanding until recently was that intent(in) values in a function/subroutine behave like a parameter. And to me, this is still the way I would like it to be.

Actually, with -Wall, gfortran gives an error if one tries to write to an intent(in) variable. :clap:

It would be interesting to know why intent(in) must not be enforced. Maybe it is just too hard to implement (e.g. when using pointers or procedures that have dummy variables without intent specification) and enforcing it makes it impossible to write standard-conforming compilers. There is some similarity with pure procedures which are not allowed to print to screen until someone writes an interfaces for a function that does it ā€¦

In contrast, intent(out) does what I expect. It needs to be defined in the function or subroutine. gfortran with -Wall reminds me to do that. For good reasons this reminder is a warning, not an error.

1 Like

Problems with enforcing intent(in) is that intent of some procedure calls is not known to the compiler. This occurs when calling old style (F77) Fortran codes, or codes defined using C interoperability with pointer arguments. Codes whose documentation doesnā€™t completely describe their behavior.

Thereā€™s a few ways one can circumvent an intent(in) statement and cause surprising behaviour. Off the top of my head I can think of the following ways (see bottom of post for examples):

  1. Calling procedures without an explicit interface
  2. Using pointers
  3. Using global (module) variables
  4. Manually specifying an incorrect interface
  5. Having multiple arguments with different intents that (partially) share the same location in memory

Items 1, 2 and 3 Iā€™m not too concerned about. They can be avoided by declaring procedures pure. Eliminating these pitfalls are actually a good motivation to use pure!

Item 4 is difficult to guard against as long as this is permitted. In my opinion, any language needs some way of letting the programmer tell the compiler ā€œtrust me, I know what Iā€™m doingā€ even though they might be misused. Perhaps this is one such feature in Fortran?

I think item 5 is the most common way that unexpected behaviour with Ƭntent(in) can happen. When working with multiple different slices of the same array throughout multiple layers of procedures it is easy to cause this at some point. The only way I can think of to guard against this is to have a system like Rustā€™s borrow checker. This is essentially a system where the programmer has to prove at compile time that there is no inconsistent use of memory. I donā€™t think this should be top priority for Fortran, but itā€™s a very interesting solution to this sort of problems for sure!

Examples:

module global
    integer :: global_value
end module

program main
    implicit none

    integer :: val

    val = 42
    call using_legacy_routines(val)

    val = 42
    call using_pointer(val)

    block
        use global, only: global_value
        global_value = 42
        call using_global_variables(global_value)
    end block

    val = 42
    call using_fake_interfaces(val)

    val = 42
    call using_overlapping_arguments(val, val)

contains


    subroutine using_legacy_routines(i)
        integer, target, intent(in) :: i

        write(*,*) 'Before: ', i
        call without_interface(i)
        write(*,*) 'After: ', i
    end subroutine

    subroutine using_pointer(i)
        integer, target, intent(in) :: i

        integer, pointer :: j

        write(*,*) 'Before: ', i
        j => i
        j = 123
        write(*,*) 'After: ', i
    end subroutine

    subroutine using_global_variables(i)
        use global, only: global_value
        integer, intent(in) :: i

        write(*,*) 'Before: ', i
        global_value = 123
        write(*,*) 'After: ', i
    end subroutine

    subroutine using_fake_interfaces(i)
        integer, intent(in) :: i

        interface
            subroutine fake_interface_sub(i)
                integer, intent(in) :: i
            end subroutine
        end interface

        write(*,*) 'Before: ', i
        call fake_interface_sub(i)
        write(*,*) 'After: ', i
    end subroutine

    subroutine using_overlapping_arguments(i, j)
        integer, intent(in) :: i
        integer, intent(inout) :: j

        write(*,*) 'Before: ', i
        j = 123
        write(*,*) 'After: ', i
    end subroutine
end program


subroutine without_interface(i)
    integer, intent(inout) :: i

    i = 123
end subroutine


subroutine fake_interface_sub(i)
    integer, intent(inout) :: i

    i = 123
end subroutine
3 Likes

I just tweeted about #5. In the caller you could put parentheses around the arguments that are intent(in) in the procedure and check that the code gives the same results (but probably more slowly).

2 Likes

I think your compiler is generating interfaces for you. This is a feature typically used to detect potential errors in legacy code.

The example compiles with no warnings using the latest ifort version. Iā€™d expect it would fail if I were to use the -warn interfaces flag though. This flag - ironically for itā€™s name - causes ifort to emit an error when interface errors are detected. It rarely works reliably for anything but trivial examples though, but thatā€™s a different discussion.

If you put the external procedures in separate files (like is usually done), even the latest version of gfortran still wonā€™t detect this. gfortran has the nice extension of doing interface checking if everything is in the same file, but it doesnā€™t have to to be standards conforming.

Yep. Iā€™m not trying to suggest that programmers should do this as a workaround to write code like this (Iā€™m of the opinion you should never use implicit interfaces), just pointing out that most projects wonā€™t be structured in a way that allows the compiler to check the interfaces if theyā€™re not explicit. Thus saying that gfortran will catch this is misleading for most cases, and does not address OPā€™s concerns. And since other compilers donā€™t check the interfaces, it would be bad advice to suggest that programmers rely on it.