Question on compiler runtime errors over pointer deallocation

Hi all,
I’m struggling with Sec. 9.7.3.3.2 of the standard (document 24-007) regarding deallocation of pointers. The code below compiles and runs without problem with all recent version of gfortran, NAG, ifort, ifx, but when using the very recent git version of flang-new (which is a great development, by the way!), this throws a runtime error: DEALLOCATE of a pointer that is not the whole content of a pointer ALLOCATE
(which is the content of Sec. 9.7.3.3.2 of the standard. Now the object current that was allocated below is of the extended type t_entry_t, and then a DT-component of type t_t is pointing to the subobject current%t_t, and then the DT-component t_t is deallocated. Am I reading this correctly that this runtime error message can be thrown by the compiler, but doesn’t have to (as the standard says “shall”), and is the code below non-conformant? Any comments are highly appreciated.
Cheers,
Juergen

program m
  implicit none

  type :: t_t
  end type t_t

  type, extends (t_t) :: t_entry_t
     type(t_entry_t), pointer :: next => null ()
  end type t_entry_t  
  
  type :: r_t
     type(t_t), pointer :: t => null ()
  end type r_t

  type(r_t), target :: global
  type(t_entry_t), pointer :: current
  allocate (current)
  global%t => current%t_t
  current => null ()
  deallocate (global%t)
end program m

@jr_reuter , I suggest you also communicate with the J3 mailing list and seek comments and feedback there, perhaps even inquire whether the so-called “Interp” workflow is warranted in this case.

Because the matter involves the whole of an object and what exactly is meant by that, arguably the standard document is inadequate in revealing this aspect.

For whatever it’s worth, my own read is the processor detecting and diagnosing the issue is right in doing so, the instruction deallocate (global%t) in the program shown in the original post does not conform because I surmise the target current%t_t is not the “whole of the object”.

I will admit that

If a pointer appears in a DEALLOCATE statement, it shall be associated with the whole of an object that was created by allocation.

should probably be more precise. The whole of current%t_t (the target of the pointer global%t that appears in the deallocate statement), was created by allocation, but I don’t believe that is what the intent of that sentence in the standard is. Rather, the intent of the standard is that the target of the pointer must be the whole of the entity identified in an allocate statement.

Perhaps, add “that is given as the argument to DEALLOCATE()” before “must be …” ? I think that is what you meant.

The NAG compiler does give some indication that all is not well, if you use the memory tracer and the runtime memory analyzer.

The object in DEALLOCATE is of type t_t but the object allocated was of type t_entry_t.

Standard: If a pointer appears in a DEALLOCATE statement, it shall be associated with the whole of an object that was created by allocation.

Is the relevant t_t object the whole of the t_entry_t object? We don’t have a definition of this in the Standard, but we have a definition of subobject (9.4.2 p5 “Structure Components” and NOTE1) and if A has a subobject X but B doesn’t, then (I argue that) B can’t be the whole of A. So, the shall clause fails and the program is non-conforming.

$ cat -n  /tmp/jr.f90 && nagfor -quiet -mtrace=all /tmp/jr.f90 && ./a.out |& nagfmcheck
     1  program m
     2    implicit none
     3
     4    type :: t_t
     5    end type t_t
     6
     7    type, extends (t_t) :: t_entry_t
     8       type(t_entry_t), pointer :: next => null ()
     9    end type t_entry_t
    10
    11    type :: r_t
    12       type(t_t), pointer :: t => null ()
    13    end type r_t
    14
    15    type(r_t), target :: global
    16    type(t_entry_t), pointer :: current
    17    allocate (current)
    18    global%t => current%t_t
    19    current => null ()
    20    deallocate (global%t)
    21  end program m
Questionable: /tmp/jr.f90, line 21: Variable GLOBAL set but never referenced
 DEALLOCATE: record 4 WRONG SIZE (allocate=8, deallocate=0) at line 20 of /tmp/jr.f90
 4 allocations
 No memory leaked
2 Likes

Yes, that’s what I meant.

We discussed this in our team and indeed we agree that the code above (a simplified version from our software) is not standard-compliant. Consequently, we promoted the type(t_t) to class(t_t), allowing to avoid the pointer assigment to the base-type component. Thanks for all the comments.