Simple/effective way to "attach" function to derived type

I am sorry for the obvious lack of clarity of the title of this post, but I guess my inability to formulate the question in proper terms is a significant part of the problem itself.
I would like to build a derived type having a component that holds (points to) a function, say f(x,y), to be supplied by the package user. This function is employed by a type-bound procedure to do some math.
After looking for some inspiration on the web, I noticed that some programmers employ the following approach:
typefun.f90 (1.3 KB)

module funtype
   implicit none
   private
   public :: typewithfun

   type ::typewithfun
      procedure(fncstyle), pointer :: fnc ! Define pointer to function with explicit interface
   contains
      procedure, pass(self) :: init
      procedure, pass(self) :: domath
   end type

   abstract interface
      integer function fncstyle(self, x, y)
         import :: typewithfun
         class(typewithfun), intent(inout) :: self  ! I would really like to get rid of this
         integer, intent(in) :: x, y
      end function
   end interface

contains

   subroutine init(self, fnc)
      class(typewithfun), intent(inout) :: self
      procedure(fncstyle) :: fnc
      self%fnc => fnc
   end subroutine

   integer function domath(self) result(res)
      class(typewithfun), intent(inout) :: self
      res = self%fnc(2, 2)
   end function

end module

program main
   use funtype, only: typewithfun
   implicit none

   type(typewithfun) :: some_typewithfun

   call some_typewithfun%init(somefnc)
   print *, some_typewithfun%domath()

contains

   integer function somefnc(self, x, y)
      class(typewithfun), intent(inout) :: self ! I would really like to get rid of this
      integer, intent(in) :: x, y
      somefnc = x + y
   end function

end program

This works well, but it forces the user to (re)define the function to include the derived type as first (dummy) argument. I find this very intrusive, because it somehow prevents the user to employ the function in its “natural” form. So, the question is:

  • Is there some alternative coding approach that allows to achieve the same result without having the requirement class(typewithfun), intent(inout) :: self ?

Thanks.

You mean adding nopass?

module funtype
   implicit none
   private
   public :: typewithfun

   type ::typewithfun
      procedure(fncstyle), nopass, pointer :: fnc ! Define pointer to function with explicit interface
   contains
      procedure, pass(self) :: init
      procedure, pass(self) :: domath
   end type

   abstract interface
      integer function fncstyle(x, y)
         integer, intent(in) :: x, y
      end function
   end interface

contains

   subroutine init(self, fnc)
      class(typewithfun), intent(inout) :: self
      procedure(fncstyle) :: fnc
      self%fnc => fnc
   end subroutine

   integer function domath(self) result(res)
      class(typewithfun), intent(inout) :: self
      res = self%fnc(2, 2)
   end function

end module

program main
   use funtype, only: typewithfun
   implicit none

   type(typewithfun) :: some_typewithfun

   call some_typewithfun%init(somefnc)
   print *, some_typewithfun%domath()

contains

   integer function somefnc(x, y)
      integer, intent(in) :: x, y
      somefnc = x + y
   end function

end program
3 Likes

Adding to @awvwgk answer, nopass is the Fortran keyword for static methods

3 Likes

Thanks, spot on! If one does not know what to look for, not even google can help! :slight_smile:
In case another lost soul lands here, maybe reading about nopass will help.

1 Like