Pure procedure and intent(out) polymorphic pointer argument

module bugmod

   implicit none

   type value_t
   end type

contains

   pure subroutine fetch_ptr(ptr)
      class(value_t), intent(out), pointer :: ptr
   end subroutine

end module

gfortran fails to compile this code with:

Error: INTENT(OUT) argument ‘ptr’ of pure procedure ‘fetch_ptr’ at (1) may not be polymorphic

ifx:

bug.f90(10): warning #9000: An INTENT(OUT) dummy argument of a pure subroutine must not be polymorphic or have a polymorphic allocatable ultimate component.   [PTR]
   pure subroutine fetch_ptr(ptr)
-----------------------------^

But why? The restriction was imposed specifically to prevent the possibility of non-pure finalizers being invoked when the actual argument to intent(out) is being deallocated. But why is that a problem for a pointer? In this case no finalizer would be called, as far as my understanding of Fortran goes. It seems that there is no reason that this should not be allowed? Is this a compiler bug or bug in the standard?

Have a good day!

Dominik

nagfor agrees with gfortran on this one.

Fortran 2018 has the constraints:
“C1586 An INTENT (OUT) dummy argument of a pure procedure shall not be such that finalization of the actual argument would reference an impure procedure.
C1587 An INTENT (OUT) dummy argument of a pure procedure shall not be polymorphic or have a polymorphic allocatable ultimate component.”

I just happened to have the F2018 standard open. I am sure that there are similar contraints from F2003 onwards.

Have a good day yourself!

Paul

https://wg5-fortran.org/N2101-N2150/N2121.txt, interp F08/0143

Also, F2023 (J3/24-007), 15.7 Pure procedures,

C15106 A statement that might result in the deallocation of a polymorphic entity is not permitted in a pure procedure.

Yes, I am aware of that. However, in case of pointer, there is no deallocation. Therefore this statement should be permitted.

But the pointer can act as a “substitute” for allocatable (in fact, if you change the pointer to allocatable in your code sample, there should be a similar error).

The compiler shouldn’t be expected to analyze your implementation just to determine if the pointer is acting as an alias or if the allocate|deallocate statements will be involved.

And you can always just remove the pure prefix or change class to type and move on.

Pointer and allocatables are completely different and not intechangeable. This restriction is imposed because intent(out) with allocatable involves deallocation but not with pointer. There is no analysis required here.

Not “completely different”. The most significant differences are the automatic deallocation when going out of scope (for allocatable), and the pointing to a target (for pointer).

Assuming your “finalizer not involved” premise, the following would be problematic:

use bugmod
implicit none
type(value_t), pointer :: a, b
allocate (a)
b => a
call fetch_ptr(a)
call fetch_ptr(b)
end

Does your code involve any deallocation? Maybe my understanding of Fortran is wrong (which is totally possible since I am still learning), but I thought there is no auto-deallocation of any kind for pointers.

call fetch_ptr(a) will involve resetting the pointer to undefined status —which, without a final procedure to do the actual deallocation, is a memory leak.

The point is that the compiler has no way of knowing if your code will be used only for the “b” case and not for the “a” case.

I think I am confused. When using pointers the programmer is responsible for memory management and deallocation. The object could be deallocated at a later time and another scope. You mentioned that

but according to my understanding no finalizer should be called when pointer is pointed to a target – programmer is responsible for that?

Whenever there’s an intent(out), a finalizer will be invoked if it exists. The intent(out) means “this argument should be in an initial state”.

In case of pointer arguments, intent applies to the association status and not the target. It’s surprising. See this discussion: Meaning of the intent for pointer dummy arguments

As to the original question, you can find some discussion on this constraint here:

Also for one manual page:
https://www.ibm.com/docs/en/xl-fortran-linux/16.1.1?topic=attributes-intent#intent

If you specify a nonpointer, nonallocatable dummy argument, the INTENT attribute will have the following characteristics:

  • INTENT(OUT) specifies that the dummy argument must be defined before it is referenced within the subprogram. Such a dummy argument might not become undefined on invocation of the subprogram.

If you specify a pointer dummy argument, the INTENT attribute will have the following characteristics:

  • INTENT(OUT) specifies that at the execution of the procedure, the association status of the pointer dummy argument is undefined

If you specify an allocatable dummy argument, the INTENT attribute will have the following characteristics:

  • INTENT(OUT) specifies that at the execution of the procedure, if the associated actual argument is allocated it will be deallocated.

and also some possibly related discussions (although for allocatable in the 2nd link):

Given that the intent(out) applies to the association status of the pointer argument (not the status of the target) and deallocation is not performed automatically upon entry, the error might be to prohibit (or reduce the chance of) possible deallocation of polymorphic variables in the procedure body (because it might involve “impure” finalization via those polymorphic variables). But then, intent(inout), pointer for polymorphic pointer variables also has such a possibility (while it is not prohibited), I feel the error for intent(out), pointer seems strange… I guess the rule for non-pointer allocatable dummy polymorophic arguments (involving automatic deallocation upon entry) is just used also to pointer dummy arguments as well, which seems not reasonable to me also… (maybe the same as Gronki).

I think this is exactly the wording that I should have used to express my concern. I guess I am still not that good with Fortran phraseology. But yeah, this is the reason why these errors surprised me, although I could not put it so nicely.

Just curious, is there any reason why you can’t simply use a function?

module bugmod
    implicit none
    type value_t
    end type
    type(value_t), target :: foo
contains
    function fetch_ptr() result(ptr)
        class(value_t), pointer :: ptr
        ptr => foo
    end function
end module

program test
    use bugmod
    associate(tmp => fetch_ptr())  ! (bug?!)
       print *, associated(tmp,foo)
    end associate
end program

I absolutely can, or I can change to

class(value_t), intent(inout), pointer :: ptr

and my problem will be fixed. :slight_smile:

But if something should be permissible and the compiler (or even worse, the standard itself) throws a tantrum at me I like to find the issue and highlight it, perhaps it can be corrected. :slight_smile: Unless I am the one in the wrong, as it often turned out to be! I already filed a bug against gfortran.

In one of my replies, I mentioned that there could be a memory leak precisely because of that —the intent(out) applies to the pointer, so the target is still there, but if the target is anonymous (i.e., done through allocation of that pointer), then there’ll be no way to access it anymore.

The pure prefix implies a lot of rules, mostly related to the general concept of pure function, with some restrictions specific to Fortran (like the ones you stumbled upon).

One of the great things about Fortran 2003 and 2008, is that pointers could be completely avoided and allocatables could be used instead —except for those rare cases where only a pointer would do, like rotating binary trees and such.

You should check if you really need the pure prefix or the pointer attribute, or even if the subroutine could be a function instead.

I am working on a parser and I deal with a lot of data structures, therefore I consciously choose to use pointers to avoid copies (typically they are pointers to allocatables actually, but that is out of the topic).

I just find it very helpful to ask the questions about “edge cases”, since there are three possible outcomes and each of them is beneficial:

  • (most often) my knowledge in Fortran fails me and I do something obviously stupid → I learn
  • (sometimes) there is a compiler error and I can file a bug report → Fortran tooling improves
  • (rare but not impossible) there is something not considered or poorly worded in a standard and this can get clarified → Fortran as a whole improves

Regarding the use of pure, I like to use it wherever possible, until I really need to get things “impure” :slight_smile: In this case, it just clashed with my understanding of why the restriction for polymorphic intent(out) arguments is imposed – I felt like there is no reason for the case of pointer.

Actually I also misread your question and the answers in this thread. The error that compilers return isn’t because of the pointer attribute. You get the same errors without it: Compiler Explorer

Looking into MFE (the 2023 version), it states:

Declaring a procedure to be pure is an assertion that the procedure

  • if a function, does not alter any dummy argument, unless it has the value attribute (Section 20.8);
  • does not alter any part of a variable accessed by host or use association;
  • contains no local variable with a save attribute;
  • performs no operations on an external file (Chapters 10 and 12);
  • contains no stop statement
  • cannot cause the exectuion of an image control statement
  • does not reference an impure procedure

To ensure that these requirements are met and that a compiler can easily check that this is so, there are the following further rules:

  • any dummy argument that is a procedure, and any procedure referenced, is pure;
  • the intent of a dummy argument is declared unless it is a procedure, a pointer, or has the value attribute (Section 20.8), and this intent must be in in the case of a function;
  • any internal procedure is pure;
  • the procedure do not reference an impure procedure through finalization (Section 15.11) of its function result or an intent out dummy argument;
  • the procedure does not have an intent out dummy argument that is polymorphic or has a polymorphic allocatable ultimate component;
  • for a function, the result is not polymorphic and allocatable, and does not have a polymorphic allocatable component; and

So the issue here, is that if you had a finalizable type, that finalizer could be impure. This may not be obvious, but finalization

… also occurs (in the called procedure) when the object is passed to an intent out dummy argument, …

just like you clarified in the original post.

Bringing us back to your question, why isn’t a polymorphic pointer intent out dummy argument permitted, or why can’t the constraint C1587 (see @PaulT’s post) be relaxed? The target hasn’t been modified, so why would this be somehow impure?

Maybe the answer lies in what @septc says,

If you specify a pointer dummy argument, the INTENT attribute will have the following characteristics:

  • INTENT(OUT) specifies that at the execution of the procedure, the association status of the pointer dummy argument is undefined

and as @jwmwalrus spelled out:

I mentioned that there could be a memory leak precisely because of that —the intent(out) applies to the pointer, so the target is still there, but if the target is anonymous (i.e., done through allocation of that pointer), then there’ll be no way to access it anymore.

Making a pointer became undefined means changing a descriptor. The actual type would become lost on entry. It could invalidate other variables in your program. In contrast intent inout asserts you’ll be taking control of the pointers association status and target, and and you’re fully aware how. Just one way of reasoning about this.

1 Like

Nevertheless, this is allowed for non-polymorphic types without polymorphic allocatable components:

   pure subroutine fetch_ptr(ptr)
      integer, intent(out), pointer :: ptr
      ! ...
   end subroutine

So this doesn’t seem to be the issue in @gronki’s case. It’s because of the polymorphic type (class(value_t)) and C1587 that it doesn’t work.