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?