It is hard to chisel an API in stone when the library is undergoing rapid development. For example one would like to add optional arguments to a procedure without breaking existing users of it. Fortran supports both positional and by-keyword actual arguments. So if someone is using positional arguments, and a new optional argument gets added, the code could break. (Unless one takes the approach that any new argument always be placed at the end of the argument list.)
What we did in ESMF was to require any optional argument use keywords. We enforced it by using a ‘keyword enforcer’ argument between the required arguments and optional ones. The ‘keyword enforcer’ is a private type, so end users can not specify it. With it in place, optional arguments can be added without API breakage.
For example:
In some module, define a keyword enforcer type within the library. The type is public within the library, but not publicized to outside callers. For example:
module myutil_mod
implicit none
private
! This type is public within the library, but will never be publicized outside it.
type myutil_keywordenforcer_t
private
integer :: quiet
end type
public :: myutil_keywordenforcer_t
! These will be used both inside and outside the library
integer, parameter, public :: mysuccess = 1, myfail = 0
end module
Another module within the library can then use these:
module mytype_mod
use myutil_mod
implicit none
private
type mytype_t
character(20) :: myname
integer :: myvals
end type
public :: mytype_t
public :: myprint
public :: mysuccess, myfail
contains
subroutine myprint (this, keywordEnforcer, printstyle, errcode)
type(mytype_t), intent(in) :: this
type(myutil_keywordEnforcer_t), optional :: keywordEnforcer
character(*), intent(in), optional :: printstyle
integer, intent(out), optional :: errcode
if (present (printstyle)) then
select case (printstyle)
case('titled')
print *, 'name, value:'
case ('untitled', ' ')
case default
if (present (errcode)) then
errcode = myfail
return
end if
end select
end if
print *, this%myname, this%myvals
if (present (errcode)) then
errcode = mysuccess
end if
end subroutine
end module
Finally, in the main program the method is called in a couple different ways. But all optional arguments must use keyword=value:
program main
use mytype_mod
implicit none
type(mytype_t) :: something
integer :: err
something = mytype_t('xyzzy', 42)
call myprint (something)
! Note that since the keyword enforcer type was never publicized, we are forced to
! use keyword=value arguments for printstyle and errcode:
call myprint (something, printstyle='titled')
call myprint (something, errcode=err)
end program
With this in place, one can add all the optional arguments one wants, and in any order, without breaking existing code.