Type bound generic procedures

I wish to understand how does type bound generic procedures work. Here, it seems to be working fine with the subroutine but not with the function.

  1. Below is the module containing subroutine for type bound generic procedure
module genmod
    
    type:: gen
        real:: x,y
        contains
        
        generic :: g=>p1,p2
        procedure, pass :: p1, p2
    end type
    
    contains
    
    subroutine p1(a,b)
        class(gen), intent(in):: a
        real, intent(out)     :: b
        b=a%x**2+a%y**2
    end subroutine
    
    subroutine p2(a,b)
        class(gen), intent(in)::a
        integer,intent(out)   ::b
        b=a%x+a%y
    end subroutine
    
end module genmod

with the main program

program generic_test
    use genmod
    type(gen)  :: x=gen(2.0,3)
    integer    :: c
    real       :: d
    
    call x%g(d) 
    print *, d
    
    call x%g(c) 
    print *,c
    
end program
  1. Here is the module containing function. It shows the error

Error: ‘p1’ and ‘p2’ for GENERIC ‘g’ at (1) are ambiguous

module genmod
    
    type:: gen
        real:: x,y
        contains
        
        generic :: g=>p1,p2
        procedure, pass :: p1, p2
    end type
    
    contains
    
    function p1(a)
        class(gen), intent(in):: a
        real                  :: p1
        p1=a%x**2+a%y**2
    end function
    
    function p2(a)
        class(gen), intent(in)::a
        integer               ::p2
        p2=a%x+a%y
    end function
    
end module genmod

The function type is different here; one is integer and the other is real. So I was expecting it to be working due to different data types. This raises the question, does it work only with different number of arguments in case of functions? For example, if I change the number of arguments - shown below, there is no compilation error !

    function p2(a,b)
        class(gen), intent(in)::a,b
        integer               ::p2
        p2=a%x+a%y
    end function

That’s expected. When you call the generic function, how can the compiler know which actual function you really want? The type of the result does not help, because a function result is evaluated on its own, independently of the expression where it appears.

2 Likes

Some languages that offer overloading (and strong typing) also offer syntax to select a function based on the type of result, for example:

a = g(x)@Integer

Fortran does not.

2 Likes

If you allow me to hijack this thread, I have a related question. I am writing a module that wraps the NetCDF procedures to make them a little less verbose and I am stuck at the design of the read routine. What I would like to achieve is to have a single read routine that handles under the hood all the possible cases. And if I were designing this as a generic procedure, all would be simple and easy, write the routines for all the cases you need (in the following example, single and double precision for both one and two dimensional arrays), wrap them around an interface and everything is done. Moreover, if I understood correctly the procedure check is done at compile time so it should be as fast in execution as calling the actual procedure.

However, how can I achieve a similar result for a derived data type? The following MWE should illustrate the structure I would like to follow.

module test
    !!   This module contains...
   use, intrinsic :: iso_fortran_env, only: real32, real64
   implicit none
   private

   integer, parameter :: sp = real32
   integer, parameter :: dp = real64

   type, public :: grid
      integer :: file_id
   contains
      procedure :: read_1D_sp
      procedure :: read_2D_sp
      procedure :: read_1D_dp
      procedure :: read_2D_dp
   end type grid

   ! This is how generics work for non type-bound procedures
   public :: read
   interface read
      module procedure read_1D_sp
      module procedure read_2D_sp
      module procedure read_1D_dp
      module procedure read_2D_dp
   end interface

contains

   subroutine read_1D_sp(self, arrayOut)
      class(grid)           , intent(in   ) :: self
      real(sp),  allocatable, intent(inout) :: arrayOut(:)
      !
      if (.not.allocated(arrayOut)) allocate(arrayOut(10))
   end subroutine read_1D_sp

   subroutine read_2D_sp(self, arrayOut)
      class(grid)           , intent(in   ) :: self
      real(sp),  allocatable, intent(inout) :: arrayOut(:,:)
      !
      if (.not.allocated(arrayOut)) allocate(arrayOut(10,10))
   end subroutine read_2D_sp

   subroutine read_1D_dp(self, arrayOut)
      class(grid)           , intent(in   ) :: self
      real(dp),  allocatable, intent(inout) :: arrayOut(:)
      !
      if (.not.allocated(arrayOut)) allocate(arrayOut(10))
   end subroutine read_1D_dp

   subroutine read_2D_dp(self, arrayOut)
      class(grid)           , intent(in   ) :: self
      real(dp),  allocatable, intent(inout) :: arrayOut(:,:)
      !
      if (.not.allocated(arrayOut)) allocate(arrayOut(10,10))
   end subroutine read_2D_dp

end module test

program testgrid
   use, intrinsic :: iso_fortran_env, only: real32, real64
   use test
   implicit none
   type(grid) :: ggrid
   real(real32), allocatable :: single_1D(:)
   real(real32), allocatable :: single_2D(:,:)
   real(real64), allocatable :: double_1D(:)
   real(real64), allocatable :: double_2D(:,:)

   print *, allocated(single_1D)
   call read(ggrid, single_1D) ! This is good!
   print *, allocated(single_1D)

   print *, allocated(single_2D)
   call ggrid%read_2D_sp(single_2D) ! This is less good
   print *, allocated(single_2D)   

   ! What I desire is to have something like
   !call ggrid%read(single_2D)
end program

I don’t understand how tho structure the code to arrive at something like

call ggrid%read(single_1D)

instead of having to call the specific routine read_1D_sp and what would be the rationale for that structuring. Thanks

I guess you are looking for generic type-bound procedures:

module test
    !!   This module contains...
   use, intrinsic :: iso_fortran_env, only: real32, real64
   implicit none
   private

   integer, parameter :: sp = real32
   integer, parameter :: dp = real64

   type, public :: grid
      integer :: file_id
   contains
      generic, public :: read => read_1D_sp, read_2D_sp, read_1D_dp, read_2D_dp
      procedure, private :: read_1D_sp
      procedure, private :: read_2D_sp
      procedure, private :: read_1D_dp
      procedure, private :: read_2D_dp
   end type grid

contains

   subroutine read_1D_sp(self, arrayOut)
      class(grid)           , intent(in   ) :: self
      real(sp),  allocatable, intent(inout) :: arrayOut(:)
      !
      if (.not.allocated(arrayOut)) allocate(arrayOut(10))
   end subroutine read_1D_sp

   subroutine read_2D_sp(self, arrayOut)
      class(grid)           , intent(in   ) :: self
      real(sp),  allocatable, intent(inout) :: arrayOut(:,:)
      !
      if (.not.allocated(arrayOut)) allocate(arrayOut(10,10))
   end subroutine read_2D_sp

   subroutine read_1D_dp(self, arrayOut)
      class(grid)           , intent(in   ) :: self
      real(dp),  allocatable, intent(inout) :: arrayOut(:)
      !
      if (.not.allocated(arrayOut)) allocate(arrayOut(10))
   end subroutine read_1D_dp

   subroutine read_2D_dp(self, arrayOut)
      class(grid)           , intent(in   ) :: self
      real(dp),  allocatable, intent(inout) :: arrayOut(:,:)
      !
      if (.not.allocated(arrayOut)) allocate(arrayOut(10,10))
   end subroutine read_2D_dp

end module test

program testgrid
   use, intrinsic :: iso_fortran_env, only: real32, real64
   use test
   implicit none
   type(grid) :: ggrid
   real(real32), allocatable :: single_1D(:)
   real(real32), allocatable :: single_2D(:,:)
   real(real64), allocatable :: double_1D(:)
   real(real64), allocatable :: double_2D(:,:)

   ! What I desire is to have something like
   call ggrid%read(single_2D)
end program

There are a couple of implementations using this design pattern in stdlib that I’m aware of, you might draw some inspiration out of them: