An unallocated variable passed as an argument is not PRESENT

The code below, lightly modified from this, surprised me. I did not know that you can pass an array or scalar variable that is not allocated to a procedure as an optional argument and ask there whether it is present. If not allocated it is not present. This language feature was discussed at the Intel Forum, where the last post, by Bálint_A_, gives its motivation.

module m
  implicit none
  contains
  pure integer function mysize(x)
    class(*), intent(in), optional :: x(..)
    mysize = -1
    if (present(x)) mysize = size(x)
  end function mysize
!
  pure integer function mysize_vec(x)
    integer, intent(in), optional :: x(:)
    mysize_vec = -1
    if (present(x)) mysize_vec = size(x)
  end function mysize_vec
end module m

program main
use m, only: mysize, mysize_vec
implicit none
integer, allocatable :: a(:), b(:), i
allocate(a(10))
print*, mysize(a), mysize(b)
print*, mysize_vec(a), mysize_vec(b)
print*, mysize(i)
allocate(i)
print*, mysize(i)
end program main

output:

          10          -1
          10          -1
          -1
           1
4 Likes

Woah! I never knew that!

Note the motivation in that Intel forum thread is the same as in Modern Fortran Explained, by Metcalf et al., 7th Edition published back in year 2011, nearly a decade ago. In section 20.14.3 Denoting absent arguments, the authors offer what they themselves term as a somewhat contrived situation involving several optional dummy arguments that the consumer may want to use with ALLOCATABLE or POINTER variables only if allocated or associated which can then lead to a combinatorial explosion of IF constructs without this facility.

Language purists are likely to scoff at such features, especially the one with ALLOCATABLE objects that can indeed come across as orthogonal to the notion in the language of not referencing such an object when unallocated. But these features are otherwise rather useful for the practitioners of Fortran.

My view is the long lag time with compiler implementations of such miscellaneous “goodies” adversely impacts awareness and adoption, cue the reactions upthread. If these facilities can be seen instead as “low-hanging fruit” by compiler developers and implemented with eagerness at short notice, that can be a boon for Fortranners.

I also learned this recently, and here on Discourse: Overloading functions with optional arguments - #18 by ashe.

This is really one of my favorite features in Fortran. I’m using it on a regular basis and it makes the code so much more readable, especially when combined with the automatic LHS allocation. While it is a less well known feature, I made the positive experience that it is quite self-explanatory for users who encounter it for the first time in a code base.

I indeed learned about this from Bálint (@aradi) when I started contributing to the DFTB+ project.

Surprisingly, in the 2018 edition of MFE this feature is addressed as a depcrecated feature; see section A.9.4 on page 454. I was never aware of it, but will therefore not start to remember it!
Robert

Deprecated is not an attribute used in the standard, but only by authors of MFE. There is only obsolete and deleted if I recall correctly. Some of the deprecated features have valid use cases which are not available in the current standard otherwise, therefore I would be hesitant do discard a feature based on this classification.

1 Like

I don’t have MFE at hand now, so I don’t know, why they don’t suggest its usage any more. For the cases discussed above, one can indeed often use the allocatable attribute instead of optional and still obtain the same behavior. So, this may seem redundant. However, if the argument is intent(out), the allocatable solution does not work. Compare:

subroutine  calc_properties(prop1, prop2)
  real, intent(out) :: prop1(:,:)
  real, intent(out), optional :: prop2(:,:)

  ...
  ! Make heavy calculation for prop2, if needed
  if (present(prop2)) then
    prop2(:,:) = ...
  end if

end subroutine calc_properties

versus

subroutine  calc_properties(prop1, prop2)
  real, intent(out) :: prop1(:,:)
  ! This does not work, as intent(out) alloctable is deallocated at entry
  ! We have no information, whether it was allocated by the caller or not
  real, intent(out), allocatable :: prop2(:,:)

  ...
  ! Useless, as prop2 is always unallocated
  if (allocated(prop2)) then
    prop2(:,:) = ...
  end if

end subroutine calc_properties

where the 2nd version does not work as intended. You may work around by declaring prop2 allocatable, intent(inout), instead. But that would allow the subroutine to change the allocation status of prop2, which is it not supposed to. For this case optional offers the only satisfying solution IMO.

2 Likes

They have section A.9

A.9 Fortran 2008 deprecated features
In this section we describe features that were new in Fortran 2008, but are considered by us
to be redundant.

which lists the following features:

A.9.1 The sync memory statement, and atomic_define and atomic_ref
A.9.2 Components of type c_ptr or c_funptr
A.9.3 Type declarations
A.9.4 Denoting absent arguments
A.9.5 Alternative form of complex constant

The following section is

B. Obsolescent and deleted features
B.1 Features obsolescent in Fortran 95
The features of this section are described by the Fortran 95 standard to be obsolescent. Their
replacements are described in the relevant subsections.

I think it is unlikely that the committee would remove a feature introduced as recently as 2008 unless it were an outright bug.

In section A.9.4, the authors give an example of absent optional denotation:

subroutine top(x, a, b)
real :: x
real, optional, target :: a(:), b(:)
real, allocatable :: worka(:), workb1(:), workb2(:)
real, pointer :: pivotptr
! (Code to conditionally allocate worka etc. elided.)
call process_work(x, worka, workb1, workb2, pivot)
end subroutine
subroutine process_work(x, wa, wb1, wb2, pivot)
real :: x
real, optional :: wa(:), wb1(:) , wb2(:), pivot

and show that without the feature, calling process_work would be awkward:

if (allocated(worka)) then
  if (allocated(workb1)) then
    if (allocated(workb2)) then
      if (associated(pivot)) then
        call process_work(x, worka, workb1, workb2, pivot)
      else
        call process_work(x, worka, workb1, workb2)
      end if
    else if (associated(pivot)) then
      call process_work(x, worka, workb1, pivotptr=pivot)
    else
      call process_work(x, worka, workb1)
    end if
! (Remainder of huge nested if construct elided.)

@m_b_metcalf , in case this has not been noted already, FIgure A.4 in the Eighth Edition of Modern Fortran Explained has typos related to pivotptr variable since Figure A.3 in indicated as the basis: the following is suggested.


Figure A.4 Huge unreadable nested if constructs


if ( allocated(worka) ) then
   if ( allocated(workb1) then
      if ( allocated(workb2) ) then
         if ( associated(pivotptr) ) then
            call process_work( x, worka, workb1, workbb2, pivotptr )
         else
            call process_work( x, worka, workb1, worbk2 )
         end if
      else if ( associated(pivotptr) ) then
         call process_work( x, worka, workb1, pivot=pivotptr )
      else
         call process_work( x, worka, workb1 )
      end if
.
. ( Remainder of large nested if coonstruct elided
.

On this, see comments by @jacobwilliams here (“Make it a class and put the work arrays in the class”) and here ("… the object-oriented interface is the real one…").

Should one pay heed to the deprecation by the authors of MFE of the feature mentioned in the original post, an OO approach would make sense. And indeed it’s a pattern preferred in some domains, particularly in industry whereby consumers never directly allocate and use work areas such as worka, workb1, workb2 or deal with pivots, to state the obvious they navigate at a high level using helper procedures for the same (usually type-bound) that do the needful in terms of setting up the components of the derived type (the class) suitably and the method invocation to do some work is always with the same i.e., with a consistent API, say

call process%work( x )  ! or call work( process, x )

Thus making the feature in question inoperative.

Technically the standard uses the term “obsolescent” rather than “obsolete”. There are also “deleted” features, though that list expands more slowly because it affects backwards compatibility and compiler vendors rarely actually delete the feature in practice anyway.

Note that an optional dummy argument that corresponds to an actual allocatable argument that is not allocated is seen as “not present” only if the dummy argument is not also allocatable. If the dummy is allocatable, then it is reasonable for the actual argument (required to be allocatable) to not be allocated on entry. The procedure being called could very well want to allocate the dummy (and hence the actual) argument.

1 Like

Thanks. Illustrating this:

module m
implicit none
contains
!
function is_present(ivec) result(tf)
integer, intent(in out), optional :: ivec(:)
logical                           :: tf
tf = present(ivec)
end function is_present
!
function is_present_alloc(ivec) result(tf)
integer, intent(in out), allocatable, optional :: ivec(:)
logical                                        :: tf
tf = present(ivec)
end function is_present_alloc
end module m
!
program main
use m
implicit none
integer, allocatable :: ivec(:)
print*,is_present(ivec),is_present_alloc(ivec) ! gives F T
end program main

I will refrain from changing the thread title to “An unallocated variable passed as an argument that is not allocatable is not PRESENT” :slight_smile: . If I used this clever feature of modern Fortran in my code, I would probably document it.

Thanks for pointing out these typos. They’ll be corrected in a later printing.

Regards,

Mike