Custom operators in extended type

Hi,

this is my first post. Thanks to the group for sharing insights!

What is the correct way to define an operator in a base derived type and then extend that definition in an extended type? Much clearer with an example.

This is my base type definition:

module mod_baseType
  implicit none 
  private 

  type :: baseType 
    integer :: myInt
  contains 
    procedure, pass(self) :: baseEquality
    generic :: operator(==) => baseEquality    
  end type baseType

  public :: baseType
contains 

  pure function baseEquality(self, b) result(res)
    class(baseType), intent(in) :: self, b
    logical :: res

    res = self%myInt == b%myInt
  end function baseEquality

end module mod_baseType

And this is the extended type:

module mod_extendedType
  use mod_baseType, only: baseType
  implicit none 
  private 

  real, parameter :: tol = 1e-5

  type, extends(baseType) :: extendedType
    real :: myReal
  contains 
    procedure, pass(self) :: extendedEquality
    generic :: operator(==) => extendedEquality
  end type extendedType

  public extendedType
contains

  pure function extendedEquality(self, b) result(res)
    class(extendedType), intent(in) :: self, b
    logical :: res

    res = self%myInt==b%myInt .and. abs(self%myReal-b%myReal) < tol 
  end function extendedEquality
end module mod_extendedType

This code does not compile with gfortran:
Error: 'extendedequality' and 'baseequality' for GENERIC '==' at (1) are ambiguous

And I have not managed to figure the right way of providing an operator for the extended type and keep the inheritance from the baseType (so that I can compare an extendedType to a baseType based on the inherited operator). Surely there must be one…

1 Like

@ludnic ,

Welcome to the forum!

Re: your quoted question, now there’s no single nor a straightforward answer to it!!

For the sake of brevity, I too will show you some code where you will see the generic binding is “extended” with an additional specific procedure in the subclass. You will notice the extension of the generic binding essentially involves unambiguous “signatures” (interfaces in Fortran parlance) of each of the specific procedures in the binding i.e., baseEquality and extendedEquality. By the way, you may consider a stylistic option with the visibility attribute with the procedures and the type.

module mod_baseType
  implicit none 
  private 

  type, public :: baseType 
    integer :: myInt
  contains
    private 
    procedure, pass(self) :: baseEquality
    generic, public :: operator(==) => baseEquality    
  end type baseType

contains 

  pure function baseEquality(self, b) result(res)
    class(baseType), intent(in) :: self
    type(baseType), intent(in)  :: b
    logical :: res

    res = self%myInt == b%myInt
  end function baseEquality

end module mod_baseType

module mod_extendedType
  use mod_baseType, only: baseType
  implicit none 
  private 

  real, parameter :: tol = 1e-5

  type, extends(baseType), public :: extendedType
    real :: myReal
  contains
    private 
    procedure, pass(self) :: extendedEquality
    generic, public :: operator(==) => extendedEquality    
  end type extendedType

contains

  pure function extendedEquality(self, b) result(res)
    class(extendedType), intent(in) :: self
    type(extendedType), intent(in)  :: b
    logical :: res

    ! check base equality first 
    res = (self%baseType == b%baseType)
    if ( res ) then
       ! additional checks for the extended type here
       res = abs(self%myReal-b%myReal) < tol 
    end if
  end function extendedEquality
end module mod_extendedType
2 Likes

Thanks @FortranFan that makes sense and solves the question! Also good point on hiding procedures within the type.

1 Like

@ludnic It also helps me this problem has solved by you guys. Thanks for doing this well job. :slightly_smiling_face:

1 Like