TRANSFER of type with ultimate ALLOCATABLE component

TRANSFER of type with ultimate ALLOCATABLE component

This is intended as a discussion with any language lawyers, rather than a request for help.

I have recently become aware of what I think is a bug, or flaw in the standard. Consider the following code snippet:

    type mytype
     real, allocatable, dimension(:) :: c
    end type mytype
	
    type(mytype) :: a, b

    allocate(a%c(8))
	
    b = transfer(a, b)

    write(*,*) 'Storage (as integer) of a = ', storage_size(a)/storage_size('a')
    write(*,*) 'Storage (as integer) of b = ', storage_size(b)/storage_size('a')
		
	print *, 'Allocation status(a,b)=', allocated(a),allocated(b)
	if( allocated(b%c)) deallocate(b%c)
	print *, 'Allocation status(a,b)=', allocated(a),allocated(b)
	if( allocated(a%c)) deallocate(a%c)

I can find no language in the description of the TRANSFER intrinsic in the standard nor in Modern Fortran Explained which would flag this as non-conforming code. And yet it is clearly wrong. What does it mean to transfer the bits of an allocatable array descriptor to another variable, but not the actual? (Invariably as the storage for ‘a%c’ is dynamically allocated from the heap.) By contrast to the rules for an EQUIVALENCE statement clearly state that a structure with an ultimate allocatable component is not allowed.

In practice some testing with different compilers and valgrind reveals a range of interesting undefined behaviours. In all cases except NAG, ALLOCATED(b%c) becomes TRUE following the transfer and DEALLOCATE(b%c) does not change the allocated status of a%c.

NAG:
raises a compile-time ERROR

GNU:
b appears to become a “shallow” copy of a, and changing b%c(i) results in a similar change in a%c(i). DEALLOCATE(b%c) followed by DEALLOCATE(a%c) results in a double-free error.

FLANG(new) and CRAYFTN:
a%c becomes deallocated following the transfer - at least the storage is freed, although the ALLOCATED flag remains true. (Presumably an unintended side-effect of the optimisation following deallocation of the TRANSFER function result). DEALLOCATING both a%c and b%c results in a double-free detected" error from the C runtime.
IFX and NVFORTRAN:

These compilers appear to b as a “deep” copy of a, despite STORAGE_SIZE(b) being too small to contain the data. The address of the first element of a%c does not appear to point at the same storage as b%c. Valgrind reveals no implicit deallocation or out-of-bounds access. Presumably this arises from treading the assignment to “b” using the F2003 rules without attempting to optimise along with the deallocation of the “transfer” result.

By contrast if the type contains a pointer instead of an allocatable, everything compiles and works as expected with all six compilers; following the TRANSFER, b becomes a shallow copy of a, with b%c associated with a%c.

It seems that this must be an oversight in the standard; this issue only arose when allocatable components of a derived type were added in Fortran 2003. Previously there was no such issue. However the issue does not appear to have been resolved, or even discussed for Fortran 2008, 2013, 2018, 2023 and I was unable to find any discussion on the J3 documents website. The only reference to any discussion I was able to find was a 2011 thread on comp.lang.fortran where Richard Maine was of the opinion that this usage might be forbidden by the “catch-all” clause that if the standard did not specify the behaviour of a construct then it is non-conforming!

If anyone as a suggestion of how to draw this to the committee’s attention I would be grateful.

It seems like there are two separate issues here. The first is what is the value of the expression transfer(a,b). I think this could also be written as transfer(a,a), right? I guess the issue is whether the allocatable component of the result is a shallow copy or a deep copy.

Then the second question is what happens with the intrinsic assignment, b=expression. I think this must be a deep copy, regardless of how the first question is answered. So the end result, whether b is a deep copy or a shallow copy, should be the same regardless of how the first question is answered, it should always be a deep copy with a newly allocated component.

If b already had an allocated component prior to the assignment, then the result should always be a deep copy, but whether the existing allocation should be used or whether a newly allocated component should be created has the same ambiguity as any other allocatable assignment as discussed recently in Optimizing vectorized array operations. As you can see in that discussion, there is some disagreement about what the standard says and also whether that was the intended meaning of the intrinsic assignment.

The text of standard is quite vague about the interpretation of the result of the TRANSFER function.

One should consider that the result is undefined and that the values are not usable, even if the destination type is the same as the source type. It would better if it was clearly written (with a note or whatever).

TRANSFER copies the “physical representation” of the source. In the example case, the memory occupied by things of type mytype is what gets copied - for allocatable, pointer and/or array components (and some other things too), this will typically be some descriptors and not the value as you might understand it. The end result is unpredictable and could likely lead to data corruption down the road.

I would agree that some additional words are needed. I’d at least add something in 19.6.6 (Events that cause variables to become undefined), and possibly a note in the description of TRANSFER.

2 Likes

I think the answer to your first question has to be a shallow copy. TRANSFER() just copies bit patterns, which has to mean that the result variable of the TRANSFER has to contain an identical copy of any array descriptor, including its allocation status and any pointer/address to the actual data.

I disagree with your answer to your second question. There is a provision for memory associated with a function result not to be deallocated until after any assignment to the LHS variable. The “as if” provision then allows for optimisation by re-using the result variable without performing a full assignment.

I note as a matter of implementation detail that gfortran does perform this optimization, generating a shallow copy. Flang on the other hand does not, and in deallocating the result variable, also deallocates the input variable!

According to this comment, and also the @sblionel response above, if the component is a normal array, without the allocatable attribute, then the transfer() result is allowed to be a shallow copy. That is, just the array metadata is copied by transfer(), and not the array data itself.

For an assignment, I think that might work, since the intrinsic assignment itself requires a deep copy, so the lhs of the expression will end up with a deep copy of the array. But what if the transfer() is used in other ways, is that shallow copy still allowed? Consider this case

call mysub( a, transfer(a,a) )

and suppose further that the first dummy argument has intent(inout) and is modified. Here the difference between a shallow copy and a deep copy would have observable consequences. In the shallow copy case, the array components would be aliased by the argument association, while with a deep copy the two arguments would have distinct arrays with the same values. I think modification of the first dummy arguments would not be allowed in the former case but would be allowed in the latter case. Again, I’m talking about the normal array case here, not the allocatable case.

If the derived type component has the allocatable attribute, then there should be no hidden aliases to that array (at least with no target attribute anywhere). I think in this case, the same restrictions would apply to the dummy arguments above. That is, the allocatable components of the two dummy arguments must be distinct, and if the first argument is modified, then the arrays cannot be shallow copies to the same storage locations in memory.

The description of intrinsic assignment when the lhs is allocatable is itself ambiguous in this case when the lhs is already allocated with the correct extents. I think this also applies to the situation where the lhs is a derived type with an allocatable array component. The shallow copy operation is not explicitly prohibited, explicitly required, or explicitly allowed, it is totally ambiguous. In the other situations (the lhs is previously allocated with the wrong extents, or the lhs is unallocated), the standard requires the appropriate deallocation and allocation of the lhs array, followed by the deep copy (or at least, the “as if” deep copy). This behavior has observable consequences within the language (pointers lose their association, finalization should occur, c_loc() results change, etc.), so it cannot entirely hide behind the “as if” provision.

I had a discussion about this with Malcolm. He tells me that the NAG compiler will give you an error if you try to use TRANSFER where either the source or mold has a descriptor in it. I suggested to him that the standard could use some words either specifying that this was not allowed or that the results are implementation-dependent - I have not yet seen a response to that.

TRANSFER never does a deep copy, and shouldn’t. That’s what assignment (intrinsic or defined) is for.

2 Likes

This is really useful information. I thought that transfer() was defined for normal arrays, including derived types that have normal array components. Is that not true?

I have been testing the NAG compiler (alongside others). It issues the error when a derived type contains an allocatable component, but not for a fixed-size array or a pointer.

It occurs to me that I have not (yet) tested a parameterised derived type, which may be an additional case or complication.

1 Like

A “normal” array component (i.e. an array of fixed size that is known at compile time) doesn’t have to have a descriptor (I would even say that it must not have a descriptor). It is just a memory area having the appropriate length inside the derived type.

Normal, fixed-size arrays don’t have descriptors, so they’re OK. Problem cases would be if the type has an ultimate component that is deferred-shape, deferred-length, allocatable, paramaterized (I think), polymorphic, or has type-bound procedures. There may be other cases I have not thought of.

My problem with this is that the standard doesn’t disallow these cases but also doesn’t say what the behavior would be. Some cases might be harmless, but an allocatable component certainly wouldn’t be. Pointer components might work, but then you break any attempt to track pointers, which some compilers do.

1 Like

I would think that a normal array would have a descriptor that describes its rank, bounds, and strides, in addition to its memory address and maybe whether it lives in the stack or the heap. An allocatable array would have the same metadata, in addition to its allocation status. A pointer array would have the same information, along with some kind of association information.

Further, when a normal array is passed as an argument, then that descriptor information must be passed (or copied) during the argument association for assumed shape dummy arguments (and maybe some of the other cases too).

Is this just a compiler-specific implementation detail, or is this described somewhere in the standard?

It could be, but it’s not like that in practice. All the information about the array (rank, bounds…) is just internal to the compiler and not stored in the compiled binary.

I think that descriptors wouldn’t work well with legacy implicit interfaces by the way: when an array is passed as an actual argument, the caller doesn’t know what is the rank, size, etc, of the dummy argument, so it can only pass the base address. That’s also why it has always been possible to interoperate C and Fortran (and just handle a pointer on the C side).

I can’t tell if all of this is clearly detailed in the standard…

A part of the answer… The following code is conforming. The pointer association would not work if the %a component was primarily stored as a descriptor, because x(:)%a(5) would not be guaranteed to have a constant stride.

type foo
    integer :: a(10)
end type

type(foo), target :: x(100)
integer, pointer :: p(:)

p => x(:)% a(5)   ! conforming code

end

I don’t know what is the implementation status of the PDTs in nagfor, but their implementation is (unfortunately) incomplete and/or flawed in most of the compilers around.

EDIT: demonstration with modified version of the above snippet (Compiler Explorer):

type foo(n)
    integer, len :: n
    integer :: a(n)
end type

type(foo(10)), target :: x(7)
integer, pointer :: p(:)

do i = 1, size(x) 
    x(i)% a(:) = i
end do

p => x(:)% a(5)   ! conforming code ?

print "(7(I0,X))", p(:)   ! should print "1 2 3 4 5 6 7"

end

gfortran 14.2: internal compiler error: in gfc_get_dataptr_offset, at fortran/trans-array.cc:7508

ifx 2024.0: /app/example.f90(13): error #8868: Pointer assignments where the target is a PDT component reference to the right of a non-scalar part reference are not yet implemented. [A] p => x(:)% a(5)

flang-trunk: error: loc("/app/example.f90":1:6): /root/llvm-project/flang/lib/Lower/ConvertType.cpp:483: not yet implemented: parameterized derived types

nvfortran 25.1: actually compiles! But prints garbage:
1 3 5 811275488 0 0 0

I agree that the code is conforming, and I would also agree that the pointer p(:) is treated within the language as a normal integer type. I would also say that the array x(m)%a is treated in the language as a normal integer array. Nonetheless, I think that a compiler would still store the metadata for the arrays x, x(m)%a, and p in array descriptors of the appropriate type. The intrinsic functions size(), shape(), lbound(), ubound(), etc. would access the appropriate metadata from those descriptors, and it would be those descriptors that are passed as actual arguments to assumed shape dummy arguments.

Perhaps a relevant question is how many array descriptors are required for p(m)%a? Is it 100 (for m=1:100), or just 1 (stored as part of the derived type metadata)? Obviously, the base address of each of those arrays can be determined from the array descriptor for p, and the other metadata (size, lbound, etc.) is all shared. Maybe this is just an implementation detail for the internal workings of the compiler.

With your PDT example in nagfor:

> nagfor pdt.f90 
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
Error: pdt.f90, line 15: No spacing specified for X edit descriptor
[NAG Fortran Compiler error termination, 1 error]

After changing the spacing to 1X it functions as expected:

> nagfor pdt.f90 
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
[NAG Fortran Compiler normal termination]
> ./a.out
1 2 3 4 5 6 7
1 Like

See this one:

type foo_static
    integer :: a(10)
end type

type foo_alloc
    integer, allocatable :: a(:)
end type

type(foo_static), target :: x(100)
type(foo_alloc), target :: y(100)
integer, pointer :: p(:)

allocate( y(1)% a(10) )

p => x(:)% a(5)   ! conforming code

print "(2Z16)", loc(x(1)),       loc(y(1))
print "(2Z16)", loc(x(1)%a),     loc(y(1)%a)
print "(2I16)", storage_size(x), storage_size(y)

end

Output with gfortran (this is similar with ifx):

    7FFE8A43C6C0          404080
    7FFE8A43C6C0         41AF910
             320             512

This clearly shows that when the %a component is a fixed size array, the whole array is directly stored within the type variable itself, without any descriptor (size is exactly 32 bits x 10 elements, and the address of x(1) is also the address of x(1)%a). In contrast, the allocatable array component is stored with a descriptor (the gfortran, as expected.

Still, I agree that even in the fixed size case, it’s not obvious that the standard really disallows a storage with descriptors. The compiler could allocate a contiguous block of 100*10=1000 elements, and make the 100 descriptors point to the relevant parts of this block. Would look overly complicated, though…

What is the nagfor output of print*, storage_size(x) in the PDT example?

Gfortran fails with the PDT. Here is the nag output.

program pdt
   implicit none
   type foo(n)
      integer, len :: n
      integer :: a(n)
   end type foo
   type(foo(10)), target :: x(7)
   integer, pointer :: p(:)
   integer :: i
   character(*), parameter :: cfmt='(*(i0,1x))'
   
   do i = 1, size(x) 
      x(i)% a(:) = i
   end do

   p => x(:)%a(1)
   print cfmt, p(:)   ! should print "1 2 3 4 5 6 7"
   p => x(4)%a
   print cfmt, p(:)
   print cfmt, storage_size(x(1)%a(1)), storage_size(x(1)), storage_size(x)

end program pdt

$ nagfor pdt.f90 && a.out
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
[NAG Fortran Compiler normal termination]
1 2 3 4 5 6 7
4 4 4 4 4 4 4 4 4 4
32 320 320
1 Like