Type-bound procedures -- motivation for PASS and NOPASS attributes

I am studying type-bound procedures (TBP) by reading Leair and Metcalf/Reid/Cohen and have questions about the motivations of some features.

By default, a TBP will have a passed-object dummy argument (PODA) that is the first argument. A benefit of TBP is that

use mod, only: some_type

will import all the procedures bound to some_type. With regular procedures that have arguments of type(some_type), their names would need to be exported separately.

With the PASS attribute the PODA need not be the first argument – this is more flexible. But why would you need that flexibility?. With NOPASS there is no PODA. When would this be used? One application I can think of is to return information about the type rather than an instance of a type. Here is a small program I wrote to try out TBPs with attributes.

module date_mod
implicit none
type date
  integer :: year, month, day
  contains
    procedure             :: init
    procedure, pass(this) :: init_pass
    procedure, nopass     :: init_nopass
    procedure             :: disp
    procedure, nopass     :: disp_format
end type date
contains
!
impure elemental subroutine disp(this)
class(date), intent(in) :: this
write (*,"(i4.4,2('-',i2.2))") this%year, this%month, this%day
end subroutine disp
!
impure elemental subroutine disp_format()
write (*,"('yyyy-mm-dd')") 
end subroutine disp_format
!
impure elemental subroutine init(this,year,month,day)
integer    , intent(in)  :: year, month, day
class(date), intent(out) :: this 
this%year  = year
this%month = month
this%day   = day
end subroutine init
!
impure elemental subroutine init_pass(year,month,day,this)
integer    , intent(in)  :: year, month, day
! "this" can be later argument since pass(this) specified
class(date), intent(out) :: this 
this%year  = year
this%month = month
this%day   = day
end subroutine init_pass
!
impure elemental subroutine init_nopass(this,year,month,day)
class(date), intent(out) :: this 
integer    , intent(in)  :: year, month, day
this%year  = year
this%month = month
this%day   = day
end subroutine init_nopass
end module date_mod
!
program test_type_bound_procedure
use date_mod, only: date
implicit none
type(date) :: d
call d%disp_format() ! yyyy-mm-dd
d = date(2022,1,20) ! use the default constructor to initialize
call d%disp() ! 2022-01-20
call d%init(2000,12,31) ! use a type-bound procedure to initialize
call d%disp() ! 2000-12-31
call d%init_pass(1999,10,1)
call d%disp() ! 2000-12-31
! use TBP with nopass binding attribute
! this use requires an extra argument and has no benefit that I see
call d%init_nopass(d,2020,12,15) 
call d%disp() ! 2020-12-15
end program test_type_bound_procedure
1 Like

I’ve used TBP extensively for many years now. Very, very rarely have I ever found the need to use either NOPASS or PASS.
One case where I have used NOPASS are for TBP that return type bound data. Fortran has no real notion of TBD, but this could be a (private) module parameter associated with the type, or hard-coded data like your format. The other case is to make available utility procedures through the type that don’t depend on components of the type. These could just as easily be simple module procedures that a user imports separately from the type. I do find that I use NOPASS much more often for procedure components (which I don’t often use) of a DT, but that’s a different question.
The only occasion I recall for using PASS to specify a different argument than the first is for procedures that define an assignment operator. There are rules on the order of the arguments and sometimes it is more natural for the passed dummy object to not be the first.

2 Likes

I have never used TBDs without any explicit or implicit PASS attribute in Fortran. However, I use @staticmethod and @classmethod in Python which is roughly equivalent. A good explanation is given on Class method vs Static method in Python - GeeksforGeeks.

The idea is to couple related functionality to an object even if the method does not need access to the internal state of the object. In that context, I find the Fortran term type bound procedure a little bit misleading: A type bound procedure having a variable with the PASS attribute is bound to the instance, not to the type of the object.

3 Likes

One can suppose the terminology with the Fortran standard is not to be taken too literally considering the scope is mostly limited to the standard document and the intended audience - until very recently times - has been predominantly those working with processors (compiler developers) - and given other challenges with arriving at consensus on what will be viewed as more important matters in standard bodies where there is only so much energy and effort the standard bearers can bring toward discussion on terminology.

Nonetheless, in case of “type bound procedure”, there is some evidence the thought behind it is how the binding is applied with the “use association” semantics of subprogram entities, that it comes “along” with the importing of the type definition. When placed in the context of this detail, the use of the term TBP appears not too unreasonable.

1 Like