Hello! I’m having troubles overloading operators functions in a parametrized derived type and I’m not sure if it’s a limitation of PDTs that I couldn’t find information on, or if I’m doing something wrong.
I have a minimal working example of the problem here.
If I do this, without PDTs, there is no problem:
module pdt
implicit none
type :: pdtype
real :: x(5)
contains
private
procedure :: ladd
generic, public :: operator (+) => ladd
end type
contains
pure function ladd(self, x) result(y)
class(pdtype), intent(in) :: self
real, intent(in) :: x
real :: y(5)
y = self%x + x
end function ladd
end module pdt
program main
use pdt
implicit none
type(pdtype) :: a
real :: b, c(5)
a = pdtype([1,2,3,4,5])
b = 5
c = a + b
print *, c
end program main
But then, when I do the same thing with PDTs I get the errors:
pdt.f90:9:17:
9 | procedure :: ladd
| 1
Error: Argument ‘self’ of ‘ladd’ with PASS(self) at (1) must be of the derived-type ‘pdtype’
pdt.f90:10:42:
10 | generic, public :: operator (+) => ladd
| 1
Error: Undefined specific binding ‘ladd’ as target of GENERIC ‘+’ at (1)
pdt.f90:27:9:
module pdt
implicit none
type :: pdtype(n)
integer, len :: n
real :: x(n)
contains
private
procedure :: ladd
generic, public :: operator (+) => ladd
end type
contains
pure function ladd(self, x) result(y)
class(pdtype(:)), intent(in) :: self
real, intent(in) :: x
real :: y(size(self%x))
y = self%x + x
end function ladd
end module pdt
I was able to get over this error with an interface, but this won’t work if I use, only: pdtype
in my code
type :: pdtype(n)
integer, len :: n
real :: x(n)
end type
interface operator(+)
module procedure :: ladd
end interface
Am I missing something? Or is this the only way to overload operators with PDTs?