Open PierUgit opened 2 months ago
Extending the (re)allocation behavior of intrinsic assignment to also apply to defined assignment would be unambiguous and safe from invaliding existing code (which I insist that we should still care about) in the case of a defined assignment generic that comprised only ELEMENTAL
subroutines, as an elemental procedure may not have an ALLOCATABLE
dummy argument, and the application of the specific elemental subroutine to an assignment with a deallocated allocatable LHS or allocatable LHS with distinct shape is an error case.
For defined assignment generics comprising non-ELEMENTAL
subroutines, it would be nice to have a means for including specific procedures that differed only in having the ALLOCATABLE
attribute on the LHS dummy argument. This is not conforming today(*) in the general case, but for ASSIGNMENT(=)
generics it could be carved out as a conforming exception, again without invalidating existing code.
(*) It is not conforming to define a single defined assignment generic comprising two subroutines whose characteristics differ only in the presence of the ALLOCATABLE
attribute on a dummy argument. But it's unclear whether it is conforming to create such a (non-type-bound) generic via combination of USE associations, so long as each actual call can be unambiguously resolved to a specific procedure.
It should actually work without breaking anything for any type bound defined assignment, as the passed object cannot be allocatable. It also has to be a scalar, regardless the procedure is elemental or not.
A defined assignment in a generic interface may have the allocatable attribute on the first argument (which may be an array if the procedure is not elemental), in which case it's the responsability of the writer of the procedure to take care of the allocation status.
The only ambiguous configuration is a defined assignment in a generic interface, with a procedure that is not elemental, and with the first argument which is an array.
It looks quite difficult to make the (re)allocation on assignment work with any kind of defined assignment, but at least for a given derived type, the developer should be able to provide a safe defined assignment in place of the intrinsic assignment for this type.
The code snippet below illustrates 5 cases of defined assignments where the left hand size is an allocatable object.
It seems that most of time the compilers could easily determine the shape of the LHS from the interface of the procedure that is used. The only impossible cases is when the procedure is not elemental and the dummy argument for the LHS is an assumed size/shape array.
module aoda_m
implicit none
type ta
integer :: i = 0
contains
procedure :: ta_assign1, ta_assign2, ta_assign3
generic :: assignment(=) => ta_assign1, ta_assign2, ta_assign3
end type
type tb
integer :: i = 0
end type
interface assignment(=)
module procedure :: tb_assign4, tb_assign5
end interface
interface possibly_realloc
module procedure :: possibly_realloc_a0, possibly_realloc_a1, possibly_realloc_b1
end interface
contains
elemental subroutine ta_assign1(this,that)
class(ta), intent(inout) :: this
type(ta), intent(in) :: that
this%i = that%i
end subroutine
elemental subroutine ta_assign2(this,that)
class(ta), intent(inout) :: this
integer, intent(in) :: that
this%i = that
end subroutine
subroutine ta_assign3(this,that)
class(ta), intent(inout) :: this
type(ta), intent(in) :: that(:)
this%i = sum(that(:)%i)
end subroutine
subroutine tb_assign4(this,that)
type(tb), intent(inout) :: this(:)
integer, intent(in) :: that
this(1:that)%i = that
end subroutine
subroutine tb_assign5(this,that)
type(tb), allocatable, intent(inout) :: this(:)
type(tb), intent(in) :: that(:)
call possibly_realloc(this,size(that))
this(:)%i = that(:)%i
end subroutine
subroutine possibly_realloc_a0(x)
type(ta), intent(inout), allocatable :: x
if (.not.allocated(x)) allocate(x)
end subroutine
subroutine possibly_realloc_a1(x,s)
type(ta), intent(inout), allocatable :: x(:)
integer, intent(in) :: s
if (allocated(x)) then
if (size(x) /= s) deallocate(x)
end if
if (.not.allocated(x)) allocate(x(s))
end subroutine
subroutine possibly_realloc_b1(x,s)
type(tb), intent(inout), allocatable :: x(:)
integer, intent(in) :: s
if (allocated(x)) then
if (size(x) /= s) deallocate(x)
end if
if (.not.allocated(x)) allocate(x(s))
end subroutine
end module aoda_m
program aoda
use aoda_m
! type bound ta_assign1() is used; it is elemental and overloads the intrinsic assignment,
! so (re)allocation on assignment could work, based on the shape of the RHS
CASE1: BLOCK
type(ta), allocatable :: lhs(:)
type(ta) :: rhs(5) = ta(5)
call possibly_realloc( lhs, size(rhs) )
lhs = rhs(:)
print*, lhs%i
END BLOCK CASE1
! type bound ta_assign2() is used; it is elemental,
! so (re)allocation on assignment could work, based on the shape of the RHS
CASE2: BLOCK
type(ta), allocatable :: lhs(:)
integer :: rhs(3) = [1, 2, 3]
call possibly_realloc( lhs, size(rhs) )
lhs = rhs(:)
print*, lhs%i
END BLOCK CASE2
! type bound ta_assign3() is used; it is not elemental but the output is always a scalar,
! so (re)allocation on assignment could work, based on the ta_assign3() interface
CASE3: BLOCK
type(ta), allocatable :: lhs
type(ta) :: rhs(3) = [ta(1), ta(2), ta(3)]
call possibly_realloc( lhs )
lhs = rhs(:) ! gfortran <= 14 is bugging on this one
! call lhs%ta_assign3(rhs) ! instead
print*, lhs%i
END BLOCK CASE3
! module procedure tb_assign4() is used; the output is an array
! so (re)allocation on assignment could not work
! (well, actually it could, by examining the interface of tb_assign4() in the case
! where the first dummy argument has an explicit shape)
CASE4: BLOCK
type(tb), allocatable :: lhs(:)
integer :: rhs = 3
call possibly_realloc(lhs,rhs)
lhs = 3
print*, lhs%i
END BLOCK CASE4
! module procedure tb_assign5() is used; the output is an ALLOCATABLE array
! so the procedure takes care of the (re)allocation of the output as needed
CASE5: BLOCK
type(tb), allocatable :: lhs(:)
type(tb) :: rhs(2) = [tb(2), tb(2)]
lhs = rhs(:)
print*, lhs%i
END BLOCK CASE5
end
For defined assignment generics comprising non-
ELEMENTAL
subroutines, it would be nice to have a means for including specific procedures that differed only in having theALLOCATABLE
attribute on the LHS dummy argument. This is not conforming today(*) in the general case, but forASSIGNMENT(=)
generics it could be carved out as a conforming exception, again without invalidating existing code.
This would actually be desirable, and not only for assignment(=)
. Is there a reason why you would restrict it to this case?
F2003 has introduced (re)allocation on assignment, but as mentioned on the Fortran Discourse it will work only on intrinsic assignment, not on defined assignment (overloaded assignment of a derived type).
For, the standard says "The interpretation of a defined assignment is provided by the subroutine that defines it", and in the example above the procedure
assign
is called with an unallocated actual argument for a non allocatable and non optional dummy argument, which is illegal.To me, it looks like a serious caveat... One could accept the limitation, but the compiler has no way to catch the problem, and the problem appears at runtime only (at best with a crash, at worst with a silent undefined behavior).
Is there any way to fix the problem in the standard? Is there a technical reason why the (re)allocation on assignment has not been extended to the defined assignment in the first place?