Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Generic assignment(=) in conjunction with allocation upon assignment and class(*)

Martin1
New Contributor I
834 Views

I got confused, when I tried to assign some derived type variable, for which there is a generic assignment(=) defined, to a "class(*), allocatable" variable. gfortran allocates upon assignment, but does not call the assignment routine. ifort complains with an "If the actual argument is unlimited polymorphic, the corresponding dummy argument must also be unlimited polymorphic" error. Which compiler got it right, or are both wrong?

Moreover, using an allocate with source does not do the job, as it does not call the assignment routine, which I guess is correct behaviour? There is a cumbersome work-around (involving a select type block), commented in the code below.

module mod

implicit none
private

type, public :: t
   integer :: i = 3
contains
   generic, public :: assignment(=) => set
   procedure, private :: set
end type t

contains

subroutine set(x, y)
   class(t), intent(out) :: x
   type(t), intent(in) :: y
   x%i = y%i + 1
end subroutine set

end module mod



program alloc_assign

use mod
implicit none

class(*), allocatable :: x
class(*), allocatable :: y
type(t) :: z

! this fails
x = t(5)
! work around
!allocate(x, mold=t())
!select type (x)
!type is (t)
!   x = t(5)
!end select

! should this call the assignment routine set? it doesn't
allocate(y, source=t(5))

! works as expected
z = t(5)

! expected output: "6, 5, 6" (or: "6, 6, 6" if allocate with source should call assignment procedure)
select type (x)
type is (t)
   print *,x%i
class default
   print *,'???'
end select

select type (y)
type is (t)
   print *,y%i
class default
   print *,'???'
end select

print *,z%i

end program alloc_assign

 

0 Kudos
14 Replies
Martin1
New Contributor I
834 Views

Side node: If  I declare "type(t), allocatable :: z" (allocatable attribute added), then both ifort as well as gfortran crash at the assignment "z=t(5)". If the generic assignment is commented out, then both compilers succeed. This is probably a bug in both compilers...

0 Kudos
Juergen_R_R
Valued Contributor I
834 Views

Hi Martin,

I think what happens is that the compiler sees t(5) as a structure constructor and not as your user-defined assignment. This happens for the middle case where the allocate statement assources that y has the same type as t, as well as for the first case because the compiler does not know the type of x, so it cannot match this to the assignment. It then evaluates the RHS via structure constructor and so the outcome is 5, not 6. You can compare this via a print statement, which only shows up for the third case. The assignment is also used in the first case with your workaround. Both gfortran and nagfor agree with this. PGI fortran and Intel both reject the first code. So apparently the latter two try to match the statement x = t(5) as user-defined assignment for which the LHC must not be unlimited polymorphic, while nagfor and gfortran evaluate the RHS as structure constructor and then do an assignment which is not defined at all. Difficult.

0 Kudos
Steve_Lionel
Honored Contributor III
834 Views

1) ALLOCATE(SOURCE=) does not invoke defined assignment.

2) The ifort error message looks strange until you realize that a defined assignment turns into a call to your assignment procedure. So in this case x = t(5) becomes:

call set(x, (t(5))

You now run afoul of the language restriction mentioned by the compiler:

The actual argument shall be polymorphic if and only if the associated dummy argument is polymorphic, and either both the actual and dummy arguments shall be unlimited polymorphic, or the declared type of the actual argument shall be the same as the declared type of the dummy argument.

since x is unlimited polymorphic but the dummy argument in set is class(t).

0 Kudos
FortranFan
Honored Contributor II
834 Views

Martin wrote:

Side node: If  I declare "type(t), allocatable :: z" (allocatable attribute added), then both ifort as well as gfortran crash at the assignment "z=t(5)". If the generic assignment is commented out, then both compilers succeed. This is probably a bug in both compilers...

Re: "This is probably a bug in both compilers.." - no, again this is per the standard which states objects with the ALLOCATABLE attribute "shall not be referenced" if the status of the object is unallocated.  And without referencing the object 'z', the compiler cannot invoke the generic binding provided for the defined assignment with the dynamic type of 'z' which is t.  Hence some instruction to have the object 'z' attain a status of 'allocated' (say allocate(z)) is required before 'z=t(5)' assignment.

This issue doesn't occur when you comment out the defined assignment.  In that case, intrinsic assignment comes into play; the expression on right-hand side gets evaluated first using the structure constructor for 't(5)' instruction and the result gets assigned to the variable on left-hand side i.e., 'z'.

0 Kudos
Steve_Lionel
Honored Contributor III
834 Views

I agree - there is no bug here, at least for ifort.

0 Kudos
Martin1
New Contributor I
834 Views

Thanks for the detailed and enlightening answers. I have not seen allocation upon assignment as part of the (intrinsic) assignment, but something which happens before (like transform it into "allocate(lhs, mold=rhs); call set(lhs, rhs)").

Of course, I could put the allocate part into the assignment myself by adding another method (with pass(y) attribute) to the generic interface:

subroutine set_alloc(x, y)
   class(t), allocatable, intent(out) :: x
   class(t), intent(in) :: y
   allocate(x, mold=y)
   x%i = y%i + 1
end subroutine set_alloc

But this will in general conflict (as in this case) with the standard assignment method because of ambiguous interfaces. Or it might not be possible if I need y to be of type integer instead.

It looks like that user defined assignment and allocation upon assignment do not go well together.

BTW, for the class(*) case, an easier way to achieve the goal is to use move_alloc, as in

type(t), allocatable: aux
class(*), allocatable: x
allocate(aux)
aux = t(5)
call move_alloc(aux, x)

Or are there shorter, more elegant ways to achieve this?

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
834 Views

FF (and Steve)

With regard to FF's #5 argument (statement of facts)

When Fortran introduced realloc lhs this permitted:

real, allocatable :: lhs(:), rhs(:)
allocate(rhs(123))
lhs = rhs

IOW the compiler would know lhs is an allocatable, and the runtime would know to test the array descriptor for allocation status and size compatibility. Then take appropriate action or inaction to perform the copy. The runtime system would get the necessary information from the array descriptor. 

With the introduction of class(*) there is (must be) a descriptor that behaves like an analog to the array descriptor that (I assume) contains an attribute that is a signature of the class, as well as other attributes (allocatable, ranks, ...). It would appear to be completely reasonable that the runtime system can (could) make the correct decision in encoding x = t(5) where x is allocatable class(*) that is unallocated and/or allocated (same functionality as realloc lhs). IOW make the lhs conform to the requirements of rhs.

RE:  the standard which states objects with the ALLOCATABLE attribute "shall not be referenced" if the status of the object is unallocated

In the case of x=t(5), the lhs variable x is not actually referenced to make the determination, the descriptor is referenced. This is just as the array descriptor would be referenced in the case of a real array, unallocated, being assigned with an allocated array, yet having the same  '"shall not be referenced" if the status of the object is unallocated'.

The only reason I can think of why it doesn't is lack of consensus in the committee.

Jim Dempsey

0 Kudos
Steve_Lionel
Honored Contributor III
834 Views

Jim, you misrepresent the standard here. It's perfectly fine to have x = t(5) if x is class(*). The issue in the original post related to the use of defined assignment. If you take that out of the picture, it's fine. Going on your snippet:

D:\Projects>type t.f90
class(*) , allocatable :: lhs(:)
real, allocatable :: rhs(:)
allocate(rhs(123))
lhs = rhs
select type (lhs)
  type is (real)
    print *, size(lhs)
end select
end
D:\Projects>ifort t.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 19.0.1.144 Build 20181018
Copyright (C) 1985-2018 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.16.27026.1
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:t.exe
-subsystem:console
t.obj

D:\Projects>t.exe
         123

Yes, there is a descriptor with the type information and it gets filled in as needed. This bit about "shall not be referenced" is a red herring, it isn't relevant to the question at hand.

0 Kudos
Steve_Lionel
Honored Contributor III
834 Views

And here it is closer to the original test case:

D:\Projects>type t.f90
class(*) , allocatable :: x
type t
  integer :: i
  end type t
x = t(5)
select type (x)
  type is (t)
    print *, x%i
end select
end
D:\Projects>ifort t.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 19.0.1.144 Build 20181018
Copyright (C) 1985-2018 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.16.27026.1
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:t.exe
-subsystem:console
t.obj

D:\Projects>t.exe
           5

 

0 Kudos
FortranFan
Honored Contributor II
834 Views

jimdempseyatthecove (Blackbelt) wrote:

FF (and Steve)

With regard to FF's #5 argument (statement of facts).. 

The only reason I can think of why it doesn't is lack of consensus in the committee.

Jim Dempsey

Jim,

Please note my comments in Quote #5 were specifically in reference to OP's suggestion of a compiler bug in Quote #2 with respect to the scenario presented therein and where defined assignment comes into play.  As discovered by OP and noted with statements such as "If the generic assignment is commented out", the kind of issues mentioned in this thread do not arise with intrinsic assignment with polymorphic variables, even unlimited poiymorphic or otherwise.

0 Kudos
jimdempseyatthecove
Honored Contributor III
834 Views

Thank you for the clarifications

0 Kudos
FortranFan
Honored Contributor II
834 Views

Martin wrote:

.. It looks like that user defined assignment and allocation upon assignment do not go well together.

Yep, employ user-defined assignment option only if it's really needed; rely on intrinsic assignments as much as possible

Martin wrote:

BTW, for the class(*) case, an easier way to achieve the goal is to use move_alloc, ..

Or are there shorter, more elegant ways to achieve this?

Well, as you found, you can just do the short 'x = t(5)' by *doing away* with user-defined assignments,

But if you really, really do need user-defined assignments, then you may want to consider making things much easier by not employing unlimited polymorphism - this is what complicates things further with the code in the original post.

0 Kudos
Martin1
New Contributor I
834 Views

FortranFan wrote:

But if you really, really do need user-defined assignments, then you may want to consider making things much easier by not employing unlimited polymorphism - this is what complicates things further with the code in the original post.

But in this case, you can replace class(*) with some parent of t (assuming that t is extended from some other type) and still have the same problem. Anyway, the assignment was in conjunction with a string class, where user-defined assignment improves readability a lot. Moreover the rational for class(*) is mostly to be able to implement generic containers. And this problem occured trying to transfer a string into such a container. At least, class(*) helps to avoid copy-and-paste (to some extend). And class(*) does not leak much into the normal code which uses the generic containers, so I am fine with it.

0 Kudos
FortranFan
Honored Contributor II
834 Views

Martin wrote:

.. in this case, you can replace class(*) with some parent of t (assuming that t is extended from some other type) and still have the same problem. Anyway, the assignment was in conjunction with a string class, where user-defined assignment improves readability a lot. Moreover the rational for class(*) is mostly to be able to implement generic containers. And this problem occured trying to transfer a string into such a container. At least, class(*) helps to avoid copy-and-paste (to some extend). And class(*) does not leak much into the normal code which uses the generic containers, so I am fine with it.

Given how complicated one's design for a 'string' class or a generic container becomes (with the former being kinda doable considering the facilities in the current Fortran standard whereas the latter is mostly a pursuit fueled by inefficiency due to insufficient support for generics in the language), one can overdo the defined operations but that's besides the context of the original post.  Considering what's shown thus far, it's the instructions such as 'x = t(5)' that are akin to assignments whereas 'z = t(5)' is more like a structure construction.  By treating them as such and keeping the simplicity of both the library code as well as consuming code in mind, one will find use cases can be satisfied more readily by eschewing unlimited polymorphism with current Fortran.

0 Kudos
Reply