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