Search code examples
fortranoperator-overloadinggfortranallocationintel-fortran

Overload assignment operator and ELEMENTAL assignment operator in Fortran


I am trying to overload the assignment operator for a custom type, and I want it to be able to use automatic allocation. I read this thread, and wrote the following:

module overload_op
  implicit none
  PUBLIC ASSIGNMENT(=)

  TYPE, PUBLIC :: my_type
    real :: real_member
  END TYPE my_type

  INTERFACE ASSIGNMENT (=)
    MODULE PROCEDURE assign_my_type_my_type_elem
    MODULE PROCEDURE assign_my_type_my_type
  END INTERFACE

  contains
    ELEMENTAL SUBROUTINE assign_my_type_my_type_elem (var1, var2)
      TYPE(my_type), INTENT(OUT) :: var1
      TYPE(my_type), INTENT(IN) :: var2
      var1%real_member = var2%real_member
    END SUBROUTINE assign_my_type_my_type_elem

    SUBROUTINE assign_my_type_my_type (var1, var2)
      TYPE(my_type), ALLOCATABLE, INTENT(OUT) :: var1(:)
      TYPE(my_type), ALLOCATABLE, INTENT(IN) :: var2(:)
      if (.not.allocated(var1)) allocate(var1(size(var2)))
      ! Call the elemental assignment subroutine for gfortran, fail for Intel
      var1(:) = var2(:)
    END SUBROUTINE assign_my_type_my_type   
end module overload_op

program main

  use overload_op
  implicit none
  TYPE(my_type) :: a(3), b(3)
  TYPE(my_type), allocatable :: c(:), d(:)
  b = a
  allocate(d(3))
  c = d

end program main

In my understanding the code should call assign_my_type_my_type for allocatable arrays and the elemental for defined shape array (like arrays with (:) specification) or simple my_type variables.

And this works as I intended with gfortran up to version 10.0.1 (latest to which I have access). But when I try to compile with ifort ( up to intel/2020.1) I get first the following error:

error #6437: A subroutine or function is calling itself recursively. [ASSIGN_MY_TYPE_MY_TYPE] var1(:) = var2(:)

And when I change the code for

call assign_my_type_my_type_elem(var1(:), var2(:))

I get an error on variables a, b of the main program not having the allocatable attribute.

An allocatable dummy argument may only be argument associated with an allocatable actual argument.

So my question is: is my implementation totally wrong and by using the notation (:) I am not calling the elemental assignment operator? In other word does gfortran has a bug and Intel is right or the other way around?


Solution

  • Your implementation is incorrect, but it's not easily fixed.

    The subroutine assign_my_type_my_type defines the defined assignment a=b whenever a and b are rank-1 arrays of type(my_type). assign_my_type_my_type_elem consequently never defines defined assignment for rank-1 arrays: an elemental subroutine only defines assignment if no other subroutine does.

    Deciding whether a subroutine defines a particular assignment (Fortran 2018 10.2.1.4) there is no distinction made for allocatable arguments or non-allocatable arguments. (As I said elsewhere "there is no requirement which states that defined assignment requires the chosen subroutine to be callable!")

    Inside assign_my_type_my_type the assignment

    var1(:) = var2(:)
    

    is still defined by assign_my_type_my_type itself, even though var1(:) is not allocatable. This would be recursive if it could happen (it can't happen because the actual argument isn't allocatable).

    Your attempt to use

    call assign_my_type_my_type_elem(var1(:), var2(:))
    

    instead of the defined assignment does work in the sense that it correctly points to the elemental (non-recursive) subroutine. It fails, as you note, because in the main program's defined assignment

    b = a
    

    you attempt to call the subroutine assign_my_type_my_type with non-allocatable arguments. You call this subroutine because, again, that's the one that defines the assignment of rank-1 arrays of that type. Callable or not.

    Which leads to why this isn't easily fixed: it is not possible to create a generic where two specifics differ only by the allocatable nature of one of the arguments. And it is not possible to select "elemental if non-elemental is not callable".

    You must choose to support allocatable left-hand side or non-allocatable left-hand side. Or use a "wrapper" type.


    There is an easily fixed issue with assign_my_type_my_type: var2 being allocatable means that the subroutine can never be directly invoked through defined assignment. In any case, that argument doesn't need to be allocatable in your use, so remove that attribute.

    Finally, a conceptual note about this implementation of "automatic allocation". With the first argument allocatable, intent(out) the left-hand side always gets deallocated before the assignment. This is different from the case of automatic allocation on intrinsic assignment.

    In intrinsic assignment the left-hand side is deallocated only if there is a mismatch with the right-hand side in some way, most commonly in size. If you want consistent behaviour in your defined assignment you will need to have intent(inout) and do the various tests for deallocation.