Silverfrost Forums

Welcome to our forums

Optional arrays arguments

22 Sep 2015 3:23 #16817

I believe that it is part of the Fortran standard that optional arguments can be passed as optional arguments to other routines without having to check whether they are present - their present status is passed automatically.

But consider the following code, which does not work in either FTN95 or NAGWare. My understanding is that the call to s2 should definitely work, but what about the call to s3 at line 11? This generates an error message indicating that the optional arguments are undefined. Indeed the optional arguments are not passed to s1, but given that they are optional in s3 surely that should not matter.

PROGRAM m
!
 CALL s1 ()
!
CONTAINS
!
 SUBROUTINE s1 (i,j)
  INTEGER,               INTENT(IN), OPTIONAL :: i
  INTEGER, DIMENSION(2), INTENT(IN), OPTIONAL :: j
  CALL s2 (i1=i)
  CALL s3 (j1=j(1),j2=j(2))
 END SUBROUTINE s1
!
 SUBROUTINE s2 (i1)
  INTEGER, INTENT(IN), OPTIONAL :: i1
  IF (PRESENT(i1)) THEN
     PRINT *, i1
  ELSE
     PRINT *, 'N/A'
  END IF
 END SUBROUTINE s2
!
 SUBROUTINE s3 (j1,j2)
  INTEGER, INTENT(IN), OPTIONAL :: j1
  INTEGER, INTENT(IN), OPTIONAL :: j2
  IF (PRESENT(j1)) THEN
     PRINT *, j1
  ELSE
     PRINT *, 'N/A'
  END IF
  IF (PRESENT(j2)) THEN
     PRINT *, j2
  ELSE
     PRINT *, 'N/A'
  END IF
 END SUBROUTINE s3
END PROGRAM m
22 Sep 2015 12:49 #16818

This is an example that justifies one's sitting on the fence with a copy of the Fortran standard, but here is my take: Line 11 of your code tries to split a hair that is not present, so the code is not valid. Whether a compiler should detect the violation at compile time or at run time is a separate question.

Let us look at the question from an implementation perspective, as well. When j is used as an argument, whether present or not, its address is passed; a NULL gets passed if it is not present. However, you want to pass j(1) and j(2) as arguments, and that cannot be done unless you start treating NULLs in the same way as infinity, i.e., half a NULL equals a NULL, etc.

I am open to arguments supporting the claim that the opposite should be true.

P.S.: After writing my reply above, I tested your code with the Sun Fortran compiler 12.4 on Linux. The run-time error was:

 ******  FORTRAN RUN-TIME SYSTEM  ******
 Attempting to use a missing optional dummy 'J'
 Location:  line 11 column 15 of 'pres.f90'
Aborted

It is worth noting that Line-11, Column 15 is where we have 'j(1)...'.

28 Sep 2015 8:56 #16854

I thought the problem here was that the actual arguments are arrays but the dummy arguments are scalars?

Generally speaking, if a subprogram 'A' has optional dummy arguments there is no need to test using present() if they are simply passed and associated to optional dummy arguments in another subprogram 'B'.

So, if A and B have explicit interfaces, there is no need to write

subroutine A(x)
   integer, optional :: x
   if (present(x)) then
      call B(x)
   else
      call B()
   end if
end subroutine A

subroutine B(x)
   integer, optional :: x
   if (present(x)) then
      ! ... may reference x
   end if
end subroutine B

Instead you can just say:

subroutine A(x)
   integer, optional :: x
   call B(x)
end subroutine A

subroutine B(x)
   integer, optional :: x
   if (present(x)) then
      ! ... may reference x
   end if
end subroutine B

I think this works ok in FTN95. But mixing array/non-array arguments may confuse the compiler.

30 Sep 2015 2:19 #16862

DavidB, only the optional second argument of Subroutine S1 is an array. In the only call of S1 in the example, this argument is absent.

The main issue is: if an optional argument is an array (or structure), in an instance where it is not present, how should array elements (or structure components) be treated? I think that consistency requires that if J is an optional array arguments, both J(1), J(2), etc., should all be seen as absent.

Here is a second example to make this clear.

PROGRAM absent
type pair
  integer first,second
end type
!          
 CALL s1 () 
! 
CONTAINS 
! 
 SUBROUTINE s1 (j) 
  type(pair), INTENT(IN), OPTIONAL :: j
!
 CALL s2 (j1=j%first,j2=j%second) 
 END SUBROUTINE s1 
! 
 SUBROUTINE s2 (j1,j2) 
  INTEGER, INTENT(IN), OPTIONAL :: j1, j2
  write(*,10)loc(j1),loc(j2)
10 format('Subroutine s2, argument addresses: ',4x,Z8.8,4x,Z8.8)
  IF (PRESENT(j1)) THEN 
  	  PRINT *, 'j1 seems to be present'
     PRINT *, 'j1 = ',j1 
  ELSE 
     PRINT *, 'j1 is not present' 
  END IF 
  IF (PRESENT(j2)) THEN 
  	  PRINT *, 'j2 seems to be present'
     PRINT *, 'j2 = ',j2 
  ELSE 
     PRINT *, 'j2 is not present' 
  END IF 
 END SUBROUTINE s2 
END PROGRAM absent 

This code prints

Subroutine s2, argument addresses:     F0F0F0F0    F0F0F0F4
 j1 is not present
 j2 seems to be present

and then it crashes.

The signature F0F0F0F0 appears to have been adopted as the representation for Optional, Not Present. On the other hand, F0F0F0F4 has no special significance and causes the crash when dereferenced.

Please login to reply.