Operator overloading in parametrized derived type

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?

Use * to specify “assumed length” instead of : to specify “deferred length”. I.e.

class(pdtype(*)), intent(in) :: self

Thanks, but that didn’t change anything :frowning:
Asides from that, I’ve read somewhere on Chapman that using * shouldn’t be used since it can lead to memory reference problems (or something like that, sorry, I’m still new to some details of Fortran). That advice was related to assumed shape arrays, with PDTs it won’t be a problem?

Anyways, if someone could point me to an explanation of why use * or : I’ll be very grateful!

Which compiler are you using? Intel ifort can compile your code (with everythingfunctional’s correction). The GNU compiler’s implementation of PDTs is incomplete.

1 Like

Ohh, that’s it then, I’m using gnufortran (v12). Thanks!

There’s a good point in there, but it’s more subtle than just “avoid *”. The real thing is “avoid assumed-size array arguments”. So

subroutine sub(arr)
  integer :: arr(*)
...

is bad, but

subroutine sub(str)
  character(len=*) :: str
...

is good. That’s called “assumed length” and it’s different from assumed size.

Note, the modern replacement for assumed size is assumed shape (i.e. use : instead of * in the above array example). I’ve talked about that in various places around the forum.

Chapman may have said you should use : not * but that is for arrays not character variables. Character variable lengths are declared with * if they are dummy arguments of functions or subroutines. You might even declare a dummy 2-D array argument of type character with character(*),intent(in):: c(:,:) where the : tell the compiler to pick up the shape of the array and the * tell it to pick up the length of each element from the actual argument.

Thanks for both answers! I’ve understand it more clearly now :slight_smile: