Dummy pointers to actual non-pointers allocatable targets

Hello everyone :slight_smile:

so, it has been said few times, here and on other platforms as well, that if one could avoid the use of pointers in Fortran, then maybe it should, and live a good and safe life with allocatables.
Indeed, pointers have their advantages, provided the fact that the user knows exactly in which case he/she is using them, and how. Otherwise, I see no reason for them to be part of the language features.

Now, consider this:

program main
   implicit none
   integer, target, allocatable :: ivar(:)

   call sub(null())
   call sub(ivar)
   ivar = [1, 2, 3, 4, 5]
   call sub(ivar)

contains

   subroutine sub(ivar)
      integer, intent(in), pointer, contiguous, allocatable :: ivar(:)
      
      if (associated(ivar)) then
         if (allocated(ivar)) then
            print '(*(i0, " "))', ivar
         else
            print *, ' Target not allocated !'
         endif
      else
         print *, ' Pointer not associated !'
      endif
   end subroutine
end program

GFortran does not compile at all, saying that pointer attribute is not compatible with allocatable.
While both ifort and ifx do compile, but the treat the first call sub(ivar) as call sub(null()).

Basically, you cannot have a pointer to an allocatable variable, keeping the two ā€œconceptsā€ distinct.

For GFortran, I think because you could allocate a pointer, i.e. allocate(ivar) in the subroutine, which makes ivar associated with an anonymous variable.

ifort and ifx they implement it as ivar being not associated (in the subroutine). (NOTE: in such case, one might argue that it does not change the expected behavior, finally. Though itā€™s not exactly ā€œmyā€ expected one, still GFortran does not compile it. So, yes, it still remain a concern.)

Here it sound back the voice saying ā€œif you could avoid usign pointers, do it, and use allocatables insteadā€.
Well, of course one could. But, assuming that sub() is a procedure exposed in an API, the use of allocatables would force the user to anyway declare that allocatable actual argument, which might or might not be allocated, to be able to make the procedure call. This cancels out the possibility of avoiding declaring it and passing null() in those cases when it knows for sure it will not need that entry in the procedure call.

Another important thing that one might argue on, is the line if (allocated(ivar)) in sub().
Here, it would makes NO sense to inquire for allocation status of a pointer dummy argument. Because pointers can only be associated, right? But, here is where it would kick in the implicit pointer dereferentiation that exist in Fortran. So that it would implicitly mean if (allocated(ivar->target)). At this point, if the actual argument is not actually an allocatable, then thow a (compile-time?) error. Otherwise, inquiry for its allocation status.
(NOTE: well, this is what actually happens with ifort and ifx, but only when the actual argument is allocated. Otherwise, they threat the dummy pointer as not being associated)

At this point, I donā€™t have in mind any workaround for obtaining the same desired (cross-compiler compliant) outcome.

If youā€™d have any suggestion, please kindly let me know :smiley:

This is the version using allocatables:

program main
   implicit none
   integer, allocatable :: ivar(:)

   call sub(null())
   call sub(ivar)
   ivar = [1, 2, 3, 4, 5]
   call sub(ivar)

contains

   subroutine sub(ivar_)
      integer, intent(in), allocatable :: ivar_(:)

      if (allocated(ivar_)) then
         print '(*(i0, " "))', ivar_
      else
         print *, ' Target not allocated !'
      endif
   end subroutine
end program

Actually, I might like this solution more, but GFortran does not compile due to call sub(null()).

So, to conclude, it seems to me that ifort and ifx they somehow do the work, even though not as one would expect.

gfortran just refuses all of this.

Becuase, Iā€™d bet, this is not proper Standard Fortran.

You can pass an allocatable to a pointer. You just canā€™t assign an allocatable attribute to the dummy pointer argument in the receiving subroutine. Pointers by there nature are implicitly ā€œallocatableā€. However, if the allocatable array is not allocated when passed you might see an error with gfortran.

The following works with ifort 2021.7

program main
   implicit none
   integer, target, allocatable :: ivar(:)

   call sub(null())
   call sub(ivar)
   ivar = [1, 2, 3, 4, 5]
   call sub(ivar)

contains

   subroutine sub(ivar)
      integer, intent(in), pointer, contiguous :: ivar(:)

      if (associated(ivar)) then
        print '(*(i0, " "))', ivar
      else
         print *, ' Pointer not associated !'
      endif
   end subroutine
end program

However, gfortran 11.0 gives the following error.

    5 |    call sub(null())
      |            1
Error: Actual argument to contiguous pointer dummy ā€˜ivarā€™ at (1) must be simply contiguous

Not sure who is correct here (intel or gfortran) but just make sure the allocatable array is allocated before being passed (something you should always do anyway). Iā€™m not familiar enough with the new simply contiguous rules to know if the value that is returned by null is suppose to be a scalar and if scalars are considered simply contiguous (I would think they would be)

@mEm ,

Per the standard, the received argument cannot both have allocatable and pointer attributes. So bug reports appear due here.

You may want to consider a generic interface here for your sub, possibly like so where the processor can resolve the two different attributes of the objects:

module m
   .
   generic :: sub => sub_a, sub_p
   .
contains
    .
    subroutine sub_a( ivar )
       integer, allocatable, intent(in) :: ivar(:)
    .

    subroutine sub_p( ivar )
       integer, pointer, contiguous, intent(in) :: ivar(:)

But you mentioned APIs in your original post and note if you are really concerned about authoring highly general and clear APIs in Fortran or making unambiguous use of APIs from third party where they may not be really on top on all the intricacies with Fortran, then your worries are well-founded. The above design too has a flaw that can trip an unsuspecting user, moreover it may be a long, long while before all your compilers may work reliably with the possible semantics.

As things stand, Fortran is really in a bad place when it comes to both authoring libraries and consuming other parties libraries, way too much care is needed to write proper code and keep everything kosher.

And compilers still have ways to go before they can be good guides for the practitioners.

1 Like

I was pretty much sure to remember this, that it was not allowed. Wanted to double check from the Standard document itself, but couldnā€™t find it right away. My fault, since I just now realise it is very easily accessible via Fortran Lang Learn web page. My apologies!

Thanks for the suggestion, didnā€™t come to my mind. And how you state, solves the problem, but not structurally.

What I also wanted to say via this thread is ā€œsimplyā€ this:
ā€œwouldnā€™t have this been avoidable if the Standard permitted to have pointers to allocatables?ā€. By saying that they represent two completely different things, and that allocation and association could live together since theyā€™d refer to (again) completely different entities?

For sake of clearance, something like:

program test

   implicit none
   integer, target :: ivar(10)
   integer, target, allocatable :: ivar_all(:)
   integer, pointer :: iptr(:) => null()

contains

   subroutine sub1(dummy)
      integer :: dummy(:)
   end subroutine

   subroutine sub1_bis(dummy)
      integer, allocatable :: dummy(:)
   end subroutine

   subroutine sub2(dummy)
      integer, intent(in) :: dummy(:)
   end subroutine

   subroutine sub2_bis(dummy)
      integer, intent(in), allocatable :: dummy(:)
   end subroutine

   subroutine sub3(dummy)
      integer, pointer :: dummy(:)
   end subroutine

   subroutine sub4(dummy)
      integer, pointer, intent(in) :: dummy(:)
   end subroutine

   subroutine sub4_bis(dummy)
      integer, pointer, intent(in), allocatable :: dummy(:)
   end subroutine

   !> Here, neither the pointer nor the target could be changed.
   subroutine sub4_ter(dummy)
      integer, pointer, intent(in), allocatable, intent(in) :: dummy(:)
   end subroutine
   
end program

Also, the utopic version sub4_ter() would avoid many unwanted bugs when it come to usage of pointers in Fortran.

This just to remark that to me, those cases should be uniquely and separately one from each other. Because thay intrinsically mean different expected situations, i.e. behaviours, without any hidden surprise.

Does all this make sense? To make it clear, itā€™s just for me to deeply understand the matter. Maybe I am loosing a quite as small as important detail which would clarify things out. That is, maybe there exist a Standand Compliant solution to the pointer, allocatable duality that I am trying to argue in here, which I am not seeing.

@rwmsu thanks for your answer :smiley: I had actually forgotten (though had some souvenirs) of that rule (pointer. allocatable being forbidden). Should have checked the standard before postingā€¦

However,

thatā€™s also part of the (cause) problem which I wanted to raise implicitly with this thread.
Indeed, just as a matter of open discussion.
No bad intentions or tones at all in all this, just to clarify!

To me, this exact statement should not hold. Nevertheless, this would not imply that one could not allocate a pointer.

That is absolutely 100% untrue. An entity can have both allocatable and target attributes, which then means that a pointer is allowed to point to some or all of that entity. This is a standard programming situation that all fortran programmers use daily. The pointer can even point to a slice within the allocatable (i.e. some subset of elements, with a stride). With the recent fortran standards (I forget which was the first), one can even have 2D, 3D, etc. pointers that point to a 1D allocatable, which makes for some very flexible programming options.

One feature that I think is ā€œmissingā€ is all of this is the ability to do shallow copies between pointers and allocatables. One way to do this would be to allow pointer arguments to the move_alloc() intrinsic. In the pointer-to-allocatable case, there might need to be some restrictions regarding contiguous elements for this to make sense. In the allocatable-to-pointer case, the allocatable would be ā€œdeallocatedā€ afterwards, but the contents would still be available through the pointer entity ā€œas ifā€ it had been allocated originally through the pointer. These shallow copies are cheap to execute because no data is actually moved, only the metadata is affected (rank, upper and lower bounds, addresses, etc.).

I think if the dummy argument is optional, then null() is allowed as an actual argument. On the subroutine side, you test for this with present().

It is a very normal thing to pass an unallocated entity as an actual argument, and then have the subroutine perform the allocation internally. All of the upper and lower bounds are returned to the calling program, which makes this a very useful feature.

@RonShepard ,
we all the due respect, I donā€™t think I alluded in any way at using such tones from my side. I donā€™t then see why you should use them. This does not mean I donā€™t accept critics/comments/etc., but I do strongly believe there are ways and ways to express the same idea.
After all, we (almost) all are here in order to learn from most knowledged people in the field.

That said, I feel we are referring to two different problems. As other posters have also pointed out, as I hadnā€™t checked that out carefully, a pointer, allocatable dummy argument simply is not Standard possible.
What I wanted to mean, is a ā€œconceptā€ of a dummy pointer (associated with a non-pointer target actual entity) being aware of the target whether being allocatable or not. Which, this, I think is not possible.

Thanks anyway for your reply!

@RonShepard. Yes if both the actual and dummy arguments have an allocatable attribute. If the dummy argument is a pointer, I think you are asking for trouble if you leave the actual argument unallocated prior to calling the subroutine. Also, just a reminder (if I remember correctly), in order to pass an allocatable actual argument to a dummy pointer argument, the calling program must be able to see an explicit interface to the subroutine. This is another issue with pointer arguments that Iā€™ve seen novice programmers get tripped up by.

Thanks for the hint. However, still would not compile with gfortran, sign that it does not like the association of a dummy allocatable with the intrinsic null().

It is absolutely a bug in IFORT/IFX that no error is given when a dummy argument has both POINTER and ALLOCATABLE. I have reported this to Intel as case 05752678.

F2008 allows an OPTIONAL dummy argument that is neither POINTER nor ALLOCATABLE to correspond to an actual argument that is an unallocated allocatable or disassociated pointer, in which case the argument is deemed to be ā€œnot presentā€.

Thanks for the clarification. @RonShepard Iā€™m sorry for not having understood your second answer in the first place, donā€™t know why I got the idea that I had to add OPTIONAL instead of just declaring it as such. Thanks to both for the useful comments.

I did not mean any kind of personal offense. It was just that the statement I quoted was untrue in very way possible, so I thought it was appropriate to point out that, in fact, that is a typical thing that programmers do all the time, it is supported by the standard, and as far as I know, all compilers support it without error.

The combination of pointer, allocatable is not allowed for any entity, dummy argument or otherwise. As for the concept of having pointers point to allocatable entities, as I said above, that is allowed by the standard, supported by all known compilers, and it is a common programming practice.

My memory was a little off about the details of this feature. Iā€™m glad someone posted the right combinations that work.

Here is a little program that demonstrates the various combinations. Iā€™m unsure about the last one, but it does work at least with gfortran and nagfor.

program ptr
   real, allocatable, target :: a(:)
   real, pointer :: apt(:) => null()
   call sub('unallocated a', a)
   call sub('apt=>null()', apt)
   a=[1.0,2.0,3.0]
   call sub('allocated a', a)
   apt=>a(1:3:2)
   call sub('apt=>a(1:3:2)', apt)
   call sub('null()', null() )
contains
   subroutine sub( text, b )
      character(*), intent(in) :: text
      real, optional :: b(:)
      write(*,*) text, present(b)
      if(present(b)) write(*,*) 'b=', b
      return
   end subroutine sub
end program ptr