I discovered type-bound procedures and was wondering how I could use them. I have this code which is working as expected:
module utils
implicit none
type TypeParam
integer :: val
contains
procedure :: initval => initI
procedure :: writeval => writeI
end type TypeParam
contains
!---------------------------
subroutine initI(this,val)
class(TypeParam),intent(inout)::this
integer,intent(in) :: val
this%val=val
end subroutine initI
!---------------------------
subroutine writeI(this)
class(TypeParam),intent(inout)::this
print*,this%val
end subroutine writeI
!---------------------------
end module utils
program testtypebound
use utils
implicit none
type(TypeParam) :: TP(2)
call TP(1)%initval(3)
call TP(2)%initval(5)
call TP(1)%writeval() ! Returns 3
call TP(2)%writeval() ! Returns 5
end program testtypebound
Now I do not know how, if it makes any sense at all, to assign initval and writeval at runtime. Having them point to null() and assign them in the main program as TP(1)%initval=>othersubroutine.
The following code, which does not use type-bound procedure, does what I want, not sure though if it the way to go. Are there any pitfalls to the second approach ?
Many thanks
module utils
implicit none
type TypeParam
integer :: val
procedure(InitValInteger), pointer :: initval => null()
procedure(WriteValInteger), pointer :: writeval => null()
end type TypeParam
interface
subroutine InitValInteger(this,val)
import TypeParam
class(TypeParam),intent(inout)::this
integer,intent(in) :: val
end subroutine InitValInteger
subroutine WriteValInteger(this)
import TypeParam
class(TypeParam),intent(inout)::this
end subroutine WriteValInteger
end interface
contains
!---------------------------
subroutine initI(this,val)
class(TypeParam),intent(inout)::this
integer,intent(in) :: val
this%val=val
end subroutine initI
!---------------------------
subroutine writeI(this)
class(TypeParam),intent(inout)::this
print*,this%val
end subroutine writeI
!---------------------------
end module utils
program testtypebound
use utils
implicit none
type(TypeParam) :: TP(2)
TP(1)%initval =>initI
TP(1)%writeval=>writeI
TP(2)%initval =>initI
TP(2)%writeval=>writeI
call TP(1)%initval(3)
call TP(2)%initval(5)
call TP(1)%writeval() ! Returns 3
call TP(2)%writeval() ! Returns 5
end program testtypebound
Clarification
As pointed out in the comments, the previous examples may not be useful. Here is a code which I think does what I want and could be extended to my real code:
module utils
implicit none
type TypeParam
integer :: val
procedure(UseValue), pointer :: useval => null()
end type TypeParam
interface
real*8 function UseValue(this,i)
import TypeParam
class(TypeParam),intent(inout)::this
integer,intent(in) :: i
end function UseValue
end interface
contains
!---------------------------
real*8 function useval1(this,i)
class(TypeParam),intent(inout)::this
integer,intent(in) :: i
useval1=this%val i
end function useval1
!---------------------------
real*8 function useval2(this,i)
class(TypeParam),intent(inout)::this
integer,intent(in) :: i
useval2=this%val**2 i
end function useval2
!---------------------------
end module utils
program testtypebound
use utils
implicit none
integer :: i
type(TypeParam) :: TP
write(*,*) "Enter version 1 or 2"
read(*,*) i
if(i==1)then
TP%val=2
TP%useval =>useval1
elseif(i==2)then
TP%val=1
TP%useval =>useval2
else
write(*,*) "Version unknown (1 or 2)"
stop
endif
print*, TP%useval(2) ! Returns 4 if i=1 and 3 if i=2
end program testtypebound
But before I start to implement this, does this code have drawbacks, flaws? Can it be made simpler/more compact using type-bound procedures ? In real life, TP will be an array, such that each component of the array will hold different procedures depending on user input.
CodePudding user response:
Type-bound procedures are "bound to a derived type and referenced via an object of that type" (Fortran 2018, 3.112.6). Being bound to a type and not an object means that two objects of the same type result in the same reference. (Further, the definition of a type cannot change during execution.)
A procedure pointer component is different: it's a component of the type and each object instance of the type can have its own value and, for a variable, its value can change during execution.
Which mechanism best suits a use case depends on what is required. If you want two objects of the same type to resolve to different procedure references, or want the referenced procedure to vary during execution, you'll be using procedure pointer components.
A procedure pointer can be not-associated and there's no equivalent state for a type-bound procedure. This means you have a responsibility to ensure that call a%s()
has the s
procedure pointer component pointer associated with a target, but also allows you to do logic like if (ASSOCIATED(a%s)) ...
(if it's of defined association status). You're also responsible for ensuring it always points to the place you want it to point (note also that one can't PROTECT components) and for ease you may well end up writing a structure constructor.
Equally, a procedure pointer component can be used in ways a binding name cannot be: call run(a%s)
is allowed for a procedure pointer component, but not for a type-bound procedure.
That said, the use case of referencing based on a run-time condition can be addressed even using type-bound procedures:
type t
logical :: use_a = .TRUE.
contains
procedure :: selector
end type t
where selector
is a wrapper like
subroutine selector(this, val)
class(t), intent(in) :: this
integer, intent(in) :: val
if (this%use_a) then
call A(this, val)
else
call B(this, val)
end if
end subroutine selector