What is PROTECTED supposed to protect for a pointer?

Following a discussion on Stack Overflow I am a bit puzzled with what the protected attribute is supposed to protect when applied to a pointer. Intuitively, I have been thinking that it would prevent changing the pointer assignment from outside the module. In practice it seems that instead it prevent writing to the target… Code example:

module foo
implicit none

private

integer, target,  protected :: a(5) = 1
integer, pointer            :: pn(:)
integer, pointer, protected :: pp(:)

public :: pn, pp, assoc

contains 

subroutine assoc()
pp => a
pn => a
end subroutine assoc

end module foo


program bar
use foo
implicit none

integer, target :: b(5) = 2

call assoc()
pn(:)  = 10    ! this one if OK, although the target is protected
!pp(:) = 20     ! this one gives a compilation error because "pp" is protected
write(*,*) pn(:)
write(*,*) pp(:)
pn => b        ! this one is OK
pp => b        ! this one is OK, although "pp" is protected
pn(:)  = 10    ! this one if OK
!pp(:) = 20     ! this one gives a compilation error because "pp" is protected
                ! and although the target is not protected
write(*,*) pn(:)
write(*,*) pp(:)

end program bar

Both ifort (19) and gfortran (12) produce a compilation error on the instructions I have commented out. So either both compilers have the same flaw, which is unlikely, or my understanding was wrong. But I’m not the only one…

I have found an old (2013) discussion on the Intel forum, where this behavior was reported as a compiler bug: Bug with protected pointer - Intel Communities . However, since it is has not been corrected since then, it is apparently not considered as a bug at all by the compiler developers.

What do you think ?

This is for readers generally that the standard for Fortran provides rather limited guardrails with the PROTECTED attribute in the language:

  • the PROTECTED attribute applies to MODULE entities,
  • in the case of entities with the PROTECTED attribute, the standard stipulates via a numbered constraint, “A pointer that has the PROTECTED attribute and is accessed by use association shall not appear in a pointer association context.

The standard then goes on to explain the pointer association status of such an entity cannot be changed via USE associated objects i.e., a conforming processor shall include the ability to detect and report any instruction to change such a pointer association. Though it explains how the pointer may become undefined due to actions on the TARGET.

Thus the programmer, especially the library authors, would need to think through their needs it if they are really seeking “protection” in a broader sense of the term, a rather simple but by no means a foolproof or comprehensive case would be PROTECTED and PRIVATE (and often ALLOCATABLE) targets and also only PROTECTED pointers to such targets

How should it be interpreted in practice? Why is pp(:)=20 rejected by the compiler, while pp => b is not?

Edit: the error message from ifort is “error #7986: A use associated object that has the PROTECTED attribute shall not appear in a variable definition context. [PP]”

Compiler bug.

Editing (deleting out) my earlier comment which doesn’t apply here upon further review of the standard.

There are two bugs here! The pointer assignment pp => b should be rejected and the intrinsic assignment pp(:) = 20 accepted. NAG Fortran gets this right. I’ll file a bug report with Intel; perhaps someone else will do it for gfortran.

I’ll add that the standards committee discussed/argued quite a bit when PROTECTED was being added, with some members insisting that it should protect the target and others the pointer. In the end, protecting the pointer won, but for F2023 WG5 added a work item to come up with a way to specify that the target could not be redefined. Unfortunately, that was not completed in time, so it goes on the potential list for the next revision (that we are calling F202Y for now.)

2 Likes

Note that pp(:) = 20, pp(1) = 20, pp(1:2) = 20, are all rejected by the compiler.

pp = 20 is accepted (and it really modifies the target)

Please explain it further.

The Standard says:

C857 A nonpointer object that has the PROTECTED attribute and is accessed by use association shall not appear in a variable definition context (19.6.7) or as a data-target or initial-data-target.

So obviously trying to redefine protected a array outside the foo module would violate standard. Should it not exactly the same if someone tries to redefine the protected array through a pointer that is associated with it?

The constraint you cite says “nonpointer object” and pp is a pointer, so this constraint does not apply. The constraint that DOES apply is C858.

C858 A pointer that has the PROTECTED attribute and is accessed by use association shall not appear in a pointer association context (19.6.8).

The statement in question is intrinsic assignment and not a “pointer association context”. Follow the link to 19.6.8 to see that this means “a syntactic context that would imply alteration of the pointer association status”, such as pointer assignment.

Again, that PROTECTED for pointers doesn’t protect the target was a choice made earlier, and some recognize the need for a way to protect the target from redefinition. The language doesn’t have that yet.

I agree with your comments on the Standard. Still, we have a problem here: what to do in a situation like in OP’s code. A nonpointer object in a module is given protected attribute which, according to C857 should protect it from redefining outside the module. Using a pointer to do that should, IMHO, be disabled as well.

The current solution is to not use pointers to refer to objects for which redefinition is not allowed.

See https://j3-fortran.org/doc/year/18/18-144r1.txt

@sblionel, not sure what the direct relevance of the J3 paper is to this context?!

That J3 paper is of course indirectly to a ton of issues affecting safe and sound practice of Fortran in scientific and technical computing which is

  1. the practitioners of Fortran, especially those authoring compute libraries to help advance a variety of fundamental and societal needs, require a certain set of crucial facilities in the language like “yesterday”, however the ground reality with WG5, and J3, and compiler implementations is too little, too slow. Enhanced PROTECTED attribute aspects with module entities as well as derived type components are one such. Bottom-line: the resource constraints have ruled the roost,
  2. those constraints cannot be better illustrated than with the paper you reference which was US worklist for Fortran 202X (now 2023) with /DATA subgroup. However the paper that got passed by J3 and approved by WG5 was too short, it limited itself to “dummy argument” context whereas the actual work discussions in the /DATA subgroup immediately revealed broader use cases including derived type components, module entities and local objects. However that proved problematic because the chair of the /DATA subgroup was constrained by time, so the worklist item got deferred and was not included in Fortran 2023. Once deferred, the resource constraints around the J3/WG5 workflow mean ongoing failure of imagination and there is not the attention, the project management, the discipline, the time, etc. to promptly bring the worklist item back and get it worked on for a subsequent release.
  3. The way things are with the language standard development, when it comes to language facilities that are in the ambit of the so-called /DATA subgroup, there is in effect only one person who can work out the details. What this person develops usually gets voted in, when this person doesn’t like or approve the work of anyone else in /DATA even it voted in during their absence, it doesn’t make it in. The shamefully shoddy product which is two types of enum’s/enumerator types in Fortran 2023, neither of which come close to meeting the needs of actual practitioners, is a perfect example of the problem. This person is severely constrained when it comes to time, has multiple responsibilities on the Fortran language committee itself, in addition to a full-time job that is likely 2 or 3 jobs’ worth of effort. Fortran in effect has “all its eggs in one basket” when it comes to primary language development.
  4. There is a severe need for succession planning and knowledge transfer to bring on board more and especially younger members to language development. There has been tremendous improvement in this regard, especially thanks to @certik, but there are major gaps and they are pronounced when it comes to standard worklist items in the /DATA subgroup. Nothing can be or will be done to address this in the near future, Fortran is tied to that one person and that is high risk.

So as things stand, there is nothing the language standard and the compiler implementations can do if a library author desires additional security to prevent inadvertent (or intentional by a consumer) redefinition of a PROTECTED target if it were to get pointer associated, the practitioner has to figure out means other than Fortran under the circumstances to author safe code:

module m
   integer, protected, target :: a(2)
   integer, protected, pointer :: b(:) => a
end module
   use m
   b = 42 !<-- redefinition allowed, no protection available
end 

Fortran, which verily should remain as the “lingua franca” of scientific and technical computing deserves better; alas, that is not the case.

The relevance is that it’s the paper where the requested feature was being proposed. It will be taken up again for F202Y.

I brought a certain younger member onto the committee long before @certik did… What we really need, though, is more members who actually work on language development and not just sit back and criticize the work others do. Nearly all of the development papers are written by the same few (and older) members. I would like to see that change.

2 Likes

There is plenty of language development happening both at this Discourse page as well as the J3 proposals incubator github page, done by many young members. Precisely the change you want to see. All you have to do is to be inclusive of all these efforts, and not dismissive with statements like these:

Steve, instead of pulling me down like this, why aren’t you more encouraging and try to figure out how to incorporate all this effort with the committee?

Hi Ondrej,

I do indeed include this group and the Proposals github in discussions and planning. See 22-176r5.pdf (j3-fortran.org) for example. I was sorry that you missed the October J3 meeting.

The problem remains that we’re not short of ideas - we’re short of committee members doing the grunt work of participating in the formal development process, specifically drafting specs/syntax/edit papers. This is what gets features in the standard, and fewer than a handful of members do this with any frequency. We’re not a large committee to begin with and having the brunt of the work on the backs of only a few people remains the biggest obstacle to progress.

1 Like

Steve, thanks for the reply. Actually I didn’t miss the October meeting, but we might have participated on different days, so we didn’t see each other. I was there on the first day for example.

You are right that only very few people submit papers using the current process. I recommend you change the process and organize things differently, so that more people will participate.

1 Like

Yes, but I also agree that the focal point in this sentence should be on “papers”. The community is what it is (i.e. small). And to me is totally natural that only a fraction has the experience and skill to bring meaningful contributions to the standard evolution. Working with a fraction of an already small pool it is really paramount to maximize accessibility to the development workflow for the standard. The same and older few members are the ones that are already accustomed to the established workflow, they have no barrier to contribute so they keep doing. New people have a barrier: of course it cannot be lowered to zero, but the smoother the workflow becomes, the better yield of new active contributors. The only real problem is that the Fortran community has small numbers, the only reasonable way to go in order to still get enough workforce for the standard is to device the best ergonomic and accessible flow to join the effort.

I don’t expect people not on the standards committee to write papers. I DO expect people who have been on the committee for even a year or two to volunteer to write simple papers (and there are some of those) to get a feel for the process, and then to be willing to dive in to write syntax and edit papers. I went through this when I started in 2008, even wrote the edits for the G0.d format back then. There are members who have been on the committee for five years who have yet to write a single paper - that just makes it harder for the rest of us.

Those of us who do the work get annoyed when those who don’t complain that we’re not moving fast enough.

Steve, writing papers is only the last step. What the committee needs help with is to actually discuss and design Fortran features. For example the generics subgroup has spent dozens and dozens of hours designing the feature (myself included!). Writing the actual paper is only the very last step. So one big problem is that you do not seem to recognize any such contributions, besides actually writing papers. (Which I have done quite a few times actually also.)

The current process does not allow to have such a discussion of new ideas; the current process only allows discussion of pre-approved ideas, such as generics. I have tried to bring new ideas from the J3 github repository at the plenary, and you were not against (thank you!). But you have not personally pushed for this process to continue and I can’t do this all on my own without the support of the leadership, which is you.

Thus my recommendation: please improve the process to allow participation of the wider community, which is interested to help.

2 Likes

I would say this is an oversight since a glaring hole in the protection is visible once one has a concrete example to demonstrate it. I think it should be rectified or mitigated for the upcoming 2023 standard.

In this example there is a protected target and two pointers with one protected all in the same module. My expected behavior is:

  1. The contents of the protected target array cannot be modified directly or indirectly through an internal pointer when outside the module.

  2. The protected pointer cannot be re-associated with any other target (or pointer) from outside the module.

  3. The internal unprotected pointer can be associated with any other target or pointer but the contents of a protected target (or pointer) should not be modifiable.

  4. An external pointer cannot be associated with a protected target or pointer in another module or its contents cannot be modified.

These rules would give all that one wants while remaining compatible with the existing rules by just adding more constraints. The intent is to simply have read-only access for protected objects in a module when outside the module.

All of this can be enforced at compile time with this example. Other restrictions may be required to make it completely general without adding too much complexity. The intent is simple.

Thanks. Dan.

@certik’s contributions are truly multifaceted, the list is too long, and they are immeasurably impactful all-around for the advancement of Fortran.

In the context of papers mentioned in the quoted comment above with the language standard and the committee and with PROTECTED, one can notice immediately the sea change brought out by @certik whereby @certik brought on board to the committee from the representing organization a new, young member who immediately started writing papers to advance the language which disproves the above assertion:

https://j3-fortran.org/doc/year/21/21-169r2.txt

Unfortunately none of the above work is going to make it to Fortran 2023 revision, the ball got dropped, and there are now sorry excuses.

There are some real deep-rooted problems starting with:

  1. the attitude of minor revisions only leading toward utterly minimalist positions, wanting to do the least, defer anything appears somewhat complicated, let the compilers “catch up” when only one or two are putting in real effort to do so, kick the can down the road, etc. The two worklist items from the original Fortran 2023 project around PROTECTED semantics are casualties of this.
  2. what gets worked on and what doesn’t on the language standard development comes across as a function of who is asking for what and also, how so. There have been too many papers and proposals submitted with Fortran over the years, including very recently, that get ignored or overlooked and the true reasons are non-technical. These are indications of tremendous organizational implicit bias and worse. There are no efforts in the actual two institutions to really grow beyond such old traits. All in all, it is not at all a welcoming and inclusive workflow for the truly global nature of Fortran practice with people of all backgrounds who are stakeholders of the language.

On the other hand, with the broader aspects of J3 Fortran proposals site and fortran-lang org and with specific aspects such as the work on Generics, the contributions by @certik to be welcoming and inviting and encouraging and facilitating contributions globally and most positively crowd-sourcing the advancement of Fortran with enthusiastic and energized minds all over the world is an indescribably positive example for WG5 and J3 committees to follow, it should be a real eye-opener - just take a look at these:

1 Like