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.
- 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
- 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