Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

clarification of protected?

10 views
Skip to first unread message

Jared Ahern

unread,
Oct 21, 2010, 3:47:28 PM10/21/10
to
I'm just checking out a lingering issue that I had with protected
module variables. I get different results from gfortran and g95, and
I suspect neither is correct (although it would be nice if gfortran
was). And my machine with ifort is down temporarily...

! gfortran 4.6.0 20100409 (experimental) [trunk revision 158144]
! g95 (GCC 4.1.1 (g95 0.93!) Jun 16 2010)

MODULE amod
IMPLICIT NONE
TYPE foo
INTEGER :: i = 4
INTEGER, POINTER :: j => NULL()
END TYPE foo
TYPE(foo), SAVE, PROTECTED :: a
TYPE(foo), SAVE, PROTECTED, POINTER :: b
INTEGER, SAVE, PROTECTED :: i = 5
INTEGER, SAVE, PROTECTED, POINTER :: j => NULL()
END MODULE amod

PROGRAM test
USE mymod
IMPLICIT NONE
INTEGER, TARGET :: k
TYPE(foo), TARGET :: c
k = 2
c%i = 9

! all below give gfortran errors
i = k
j => k
j = 3 ! no g95 error (ok if j associated?)
a = c
a%i = k
a%j => k
a%j = 5 ! (ok if a%j associated?)
b => c
b%i = k ! no g95 error
b%j => k
b%j = 5 ! no g95 error (ok if b%j associated?)

END PROGRAM test

The above works if I remove the protected attributes. As far as I
understand, I shouldn't be able to alter the value of a protected
module variable, or association of a protected module pointer, but
changing a protected pointer target value is allowed. (I reread
5.3.15 in N1830, but I wasn't 100% clear). Here, gfortran flags
everything as disallowed (which would be nice, but not consistent with
my potentially incorrect understanding), and g95 seems to miss
things. Are they both wrong? (I tried gfortran with and without --
std=f2003 .)

- Jared

steve

unread,
Oct 21, 2010, 3:52:25 PM10/21/10
to
On Oct 21, 12:47 pm, Jared Ahern <jared.ah...@gmail.com> wrote:
> PROGRAM test
>    USE mymod

I suspect all compilers fail to compile your code
unless the compiler comes with a crystal ball.

--
steve

Jared Ahern

unread,
Oct 21, 2010, 4:14:05 PM10/21/10
to

Good call - bad copy/paste. That should read "USE amod". I had a
couple modules that I was experimenting with.

Richard Maine

unread,
Oct 21, 2010, 4:43:44 PM10/21/10
to
Jared Ahern <jared...@gmail.com> wrote:

> As far as I
> understand, I shouldn't be able to alter the value of a protected
> module variable, or association of a protected module pointer, but
> changing a protected pointer target value is allowed.

I believe your interpretation to be correct. Anyway, I read it the same
way.

As an unrelated aside, do note that your "amod" module name is the same
as that of a standard specific intrintrinsic. (That's not related to the
mymod vs amod, which you already explained).

It ought to work anyway, as long as you don't use your module and the
specific intrinsic name in the same scope. And that specific intrinsic
is not one that I'd use in new code anyway ("new" starting with f77 in
this case). So it isn't necessarily a problem. Just thought I would
point it out in case you do have a policy of avoiding conflicts with
standard intrinsic names.

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain

Dick Hendrickson

unread,
Oct 21, 2010, 5:20:19 PM10/21/10
to
On 10/21/10 3:43 PM, Richard Maine wrote:
> Jared Ahern<jared...@gmail.com> wrote:
>
>> As far as I
>> understand, I shouldn't be able to alter the value of a protected
>> module variable, or association of a protected module pointer, but
>> changing a protected pointer target value is allowed.
>
> I believe your interpretation to be correct. Anyway, I read it the same
> way.
>

Does it depend on what the meaning of "should" should be? You certainly
shouldn't do it, but you might be able to in a non-conforming program..

The problem, as I read it, is that the constraints only apply in regions
where the compiler can see the PROTECTED attribute via a USE statement.
The attribute does not flow down a call tree. If you pass a protected
variable into a subroutine, it's up to you to not define the variable,
the compiler isn't required to give an error message.

Dick Hendrickson

Tobias Burnus

unread,
Oct 21, 2010, 5:33:48 PM10/21/10
to
Jared Ahern wrote:
> I'm just checking out a lingering issue that I had with protected
> module variables. I get different results from gfortran and g95, and
> I suspect neither is correct
>
> ! gfortran 4.6.0 20100409 (experimental) [trunk revision 158144]

Note: There were some bugfixes regarding variable-definition checks on
2010-09-23; see below for the results with the newer version.


> The above works if I remove the protected attributes. As far as I
> understand, I shouldn't be able to alter the value of a protected
> module variable, or association of a protected module pointer, but
> changing a protected pointer target value is allowed.

I think that your understanding is correct (as thinks Richard Maine :-).


Trying 6 compilers, I get the following result. The OK/Invalid is based
on my understanding. If a compiler name appears in a line, the compiler
shows an error for that line. (For the [bug] lines the error "Invalid
reference to target of null pointer constant" is shown. Note that PGI
compiles the program without any error/warning.)


MODULE amod
IMPLICIT NONE
TYPE foo
INTEGER :: i = 4
INTEGER, POINTER :: j => NULL()
END TYPE foo
TYPE(foo), SAVE, PROTECTED :: a
TYPE(foo), SAVE, PROTECTED, POINTER :: b
INTEGER, SAVE, PROTECTED :: i = 5
INTEGER, SAVE, PROTECTED, POINTER :: j => NULL()

contains
subroutine alloc()
allocate(b,j)
end subroutine alloc
END MODULE amod

PROGRAM test
USE amod


IMPLICIT NONE
INTEGER, TARGET :: k
TYPE(foo), TARGET :: c

k = 2 ! local
c%i = 9 ! local

call alloc()

! In parentheses: compiler gives error for that line
! gfortran 4.6/Oct, g95 Aug 2010, NAG 5.1, ifort 11.1,
! pathf95 3.2.99, PGI 10.5 (compiles without error), crayftn
i = k ! Invalid 1 (gfortran NAG g95 ifort pathf95 cray)
j => k ! Invalid 2 (gfortran g95 ifort pathf95 cray)
j = 3 ! OK 1 ( ifort pathf95 cray)
a = c ! Invalid 3 (gfortran NAG g95 ifort pathf95 cray)
a%i = k ! Invalid 4 (gfortran NAG g95 ifort pathf95 cray)
a%j => k ! Invalid 5 (gfortran NAG g95 ifort pathf95 cray)
a%j = 5 ! OK 2 ( g95 ifort pathf95 cray)
b => c ! Invalid 6 (gfortran g95 ifort pathf95 cray)
b%i = k ! OK 3 (gfortran ifort [bug] cray)
b%j => k ! OK 4 (gfortran g95 ifort [bug] cray)
b%j = 5 ! OK 5 ( ifort [bug] cray)

END PROGRAM test


Tobias

PS: I have filled a bugreport against gfortran as it wrongly flags the
OK3 and OK4 tests as invalid; cf.
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46122

Jared Ahern

unread,
Oct 21, 2010, 6:16:23 PM10/21/10
to
> As an unrelated aside, do note that your "amod" module name is the same
> as that of a standard specific intrintrinsic. (That's not related to the
> mymod vs amod, which you already explained).
>
> It ought to work anyway, as long as you don't use your module and the
> specific intrinsic name in the same scope. And that specific intrinsic
> is not one that I'd use in new code anyway ("new" starting with f77 in
> this case). So it isn't necessarily a problem. Just thought I would
> point it out in case you do have a policy of avoiding conflicts with
> standard intrinsic names.

Thanks for pointing that out - I typically do try to avoid clashes for
clarity. I really just need to come up with a new set of generic
names, since I tend to use foo, bar, spam, & eggs a bunch. :)

Jared Ahern

unread,
Oct 21, 2010, 6:26:32 PM10/21/10
to
> Does it depend on what the meaning of "should" should be?  You certainly
> shouldn't do it, but you might be able to in a non-conforming program..
>
> The problem, as I read it, is that the constraints only apply in regions
> where the compiler can see the PROTECTED attribute via a USE statement.
>   The attribute does not flow down a call tree.  If you pass a protected
> variable into a subroutine, it's up to you to not define the variable,
> the compiler isn't required to give an error message.

I have encountered instances of a compiler generating an error for
things such as passing a protected variable accessed via use into an
intent(inout) subroutine, which would seem to avoid at least some of
the issues you raise. Whether that behavior is correct or not, I am
not sure, but I think this follows as that would be a "variable
definition context" as defined in the standard, from which protected
variables are prohibited.

Jared Ahern

unread,
Oct 21, 2010, 6:38:21 PM10/21/10
to
> PS: I have filled a bugreport against gfortran as it wrongly flags the
> OK3 and OK4 tests as invalid; cf.http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46122

Thanks! If you are following up on this, it might be useful to still
provide a warning in all of OK 1-5. I would actually prefer to know
if anything in a protected variable is altered, even though it is
allowed by the standard.

In my view though, I would tend to think that OK3 and OK4 should
actually be errors. Since b is protected, b%i and b%j have the
protected attribute. Wouldn't the same restrictions apply to them
then? Or is there a distinction between the original object marked as
protected and the ultimate components (or other subobjects)? I
wouldn't think that it would matter whether the %i and %j components
are held by a pointer or a regular variable...

Wolfgang Kilian

unread,
Oct 21, 2010, 5:58:45 PM10/21/10
to
On 10/22/2010 12:38 AM, Jared Ahern wrote:

> In my view though, I would tend to think that OK3 and OK4 should
> actually be errors. Since b is protected, b%i and b%j have the
> protected attribute. Wouldn't the same restrictions apply to them
> then? Or is there a distinction between the original object marked as
> protected and the ultimate components (or other subobjects)? I
> wouldn't think that it would matter whether the %i and %j components
> are held by a pointer or a regular variable...

There could be another pointer pointing to the same object - the
contents of b are not 'held' by the pointer, they are just pointed to,
so they can't be 'protected' in a literal sense ... I guess that's why
these cases are ok. To make them invalid, use allocatable components
instead of pointers, these should inherit the PROTECTED attribute.

-- Wolfgang

--
E-mail: firstnameini...@domain.de
Domain: yahoo

Richard Maine

unread,
Oct 21, 2010, 7:06:42 PM10/21/10
to
Jared Ahern <jared...@gmail.com> wrote:

Yes, intent(inout) is covered ok. Unspecified intent is not. My personal
style avoids unspecified intent to the extent practical in f95, but the
standard does still allow it.

Jared Ahern

unread,
Oct 21, 2010, 7:40:07 PM10/21/10
to
> There could be another pointer pointing to the same object - the
> contents of b are not 'held' by the pointer, they are just pointed to,
> so they can't be 'protected' in a literal sense ... I guess that's why
> these cases are ok.  To make them invalid, use allocatable components
> instead of pointers, these should inherit the PROTECTED attribute.

I would agree. Actually, I don't believe I've ever tried to use a
protected pointer. But I was a bit surprised to find that their
targets are not protected. It would seem useful to disallow other
pointers to point to them, and prevent them from being passed to
procedures in manners that allow them to change, etc. Of course, if
that target data is available by some other means (e.g. the target is
public in the same module and is not protected), all bets are off; but
this can be avoided if desired (since you would only be able to change
its association from within the originating module.)

There's probably some aspect of this that's not occurring to me at the
moment which makes this protection impractical. Richard Maine
mentioned procedure arguments with unspecified intent - those I just
try to avoid, so I hadn't really considered them.

Richard Maine

unread,
Oct 21, 2010, 9:05:11 PM10/21/10
to
Jared Ahern <jared...@gmail.com> wrote:
[quoting Wolfgang]

> > There could be another pointer pointing to the same object - the
> > contents of b are not 'held' by the pointer, they are just pointed to,
> > so they can't be 'protected' in a literal sense ... I guess that's why
> > these cases are ok. To make them invalid, use allocatable components
> > instead of pointers, these should inherit the PROTECTED attribute.
>
> I would agree. Actually, I don't believe I've ever tried to use a
> protected pointer. But I was a bit surprised to find that their
> targets are not protected.

I guess I don't understand why their targets would be protected. As
Wolfgang wrote, other pointers could access the same target. I'd like to
state that more emphatically in that the target is really a completely
different thing than the pointer. It is more than just that other
pointers might happen to also point to it, but that no pointer "owns" a
target, even if it hapens to be the only way to access the target at the
moment. This is one of my "mantras" in explaining Fortran pointers -
that the pointer and the target are completely different entities. If
you are thinking that protecting the pointer should protect its target,
then I suspect you are too much in the mode of thinking of the pointer
and target as being more closely related than they are; this will
probably bite you elsewhere as well. For a closely related case,
consider the intent attribute for a pointer dummy argument; that also
applies to the association status of the pointer - not to its target.

You can't reasonably expect to associate a pointer with some random
target - possibly a target not even in the same module - and then
declare that the pointer has just "claimed" that target and nobody else
is allowed to modify it. That's pretty fundamentally opposed to the way
pointers are. You might say that some particular cases of pointer usage
might not fit that mold, but attributes are generally designed to apply
broadly rather than to one particular style of use.

Note that if you had a pointer to a target and the value of the target
isn't allowed to change, there isn't much reason to have used a pointer
at all; might as well just have copied the value to a non-pointer
variable. I seem to recall arguments something like that when intent for
dummy pointers was introduced. I don't recall the details as well for
the case of the protected atribute and pointers, but I suspect it might
have been modeled after INTENT.

Jared Ahern

unread,
Oct 22, 2010, 12:17:46 PM10/22/10
to
> It is more than just that other
> pointers might happen to also point to it, but that no pointer "owns" a
> target, even if it hapens to be the only way to access the target at the
> moment.

Absolutely. It's clear that in the general case, the target of a
pointer could be anything (that meets the proper criteria), and the
target data itself could be accessible by multiple means.

> You might say that some particular cases of pointer usage
> might not fit that mold, but attributes are generally designed to apply
> broadly rather than to one particular style of use.
>
> Note that if you had a pointer to a target and the value of the target
> isn't allowed to change, there isn't much reason to have used a pointer
> at all; might as well just have copied the value to a non-pointer
> variable.

I generally agree with you, which is why I haven't had much cause to
use protected pointer variables. However, I do think that there are
simple reasons to use a pointer whose target's value is fixed. The
first example that comes to mind is (a "particular case", and perhaps
not optimal):

MODULE grid
IMPLICIT NONE
TYPE vector
REAL :: x, y, z
END TYPE vector
TYPE(vector), ALLOCATABLE, TARGET, PROTECTED :: nodes(:)
REAL, POINTER, PROTECTED :: xvals(:,:,:)
CONTAINS
! Setup called elsewhere to initiate proper module use
SUBROUTINE Setup(ni,nj,nk)
INTEGER, INTENT(IN) :: ni, nj, nk
ALLOCATE(nodes(ni*nj*nk))
xvals(1:ni,1:nj,1:nk) => nodes%x
END SUBROUTINE Setup
END MODULE grid

There may well be a better way to do it, but this this uses pointer
bounds remapping and scalar-part/component arrays (correct
terminology?) to access subtypes. I believe that this is valid F03:
F08 allows even more options. It's not possible with just an
allocatable (or parameter, or equivalence, or another module;
others?). However, we see that "nodes" can be altered via "xvals",
even with the protected attribute.

Depending on your code design, features like this could be useful - it
might be that different external output code requires data in
different forms, but organized in a consistent manner, and you'd like
to avoid copying or changes outside of the defining module. But you
are right - it is up to the module designer to ensure that the
necessary data is properly insulated from arbitrary changes. Given
all the potential ways to get oneself into trouble, it's
understandable that the present form of PROTECTED was defined. I just
hadn't thought about it much before, since the last time I started a
new large project it was not a well-supported feature.

Wolfgang Kilian

unread,
Oct 22, 2010, 1:26:15 PM10/22/10
to
On 10/22/2010 06:17 PM, Jared Ahern wrote:

> There may well be a better way to do it, but this this uses pointer
> bounds remapping and scalar-part/component arrays (correct
> terminology?) to access subtypes.

This is a simplified version (without remapping or derived types):

module foo
implicit none
integer, protected, target :: i = 1
integer, pointer, protected :: ptr => null ()
contains
subroutine init ()
ptr => i
end subroutine init
end module foo

program main
use foo
implicit none
call init ()
ptr = 2 ! (*)
print *, i
end program main

My nagfor 5.2 accepts this program, and it prints '2'.

The assignment (*) doesn't alter the association status, so the
PROTECTED attribute of ptr does not apply.

What puzzles me is that the 'backdoor' opened by associating ptr with i
allows to modify the protected variable i in the main program. Is this
program standard-conforming?

In the F2003 standard (draft) I read

5.1.2.12 PROTECTED attribute
Other than within the module in which an entity is given the PROTECTED
attribute, (1) if it is a nonpointer object, it is not definable [...]

So i is not definable in the main program.

7.4.1.2 Intrinsic assignment statement
[...]
If variable is a pointer, it shall be associated with a definable target
such that the type, type parameters, and shape of the target and expr
conform.

In (*), ptr is a pointer, and it is associated with i which is not a
definable target. So the assignment is not allowed by the standard,
correct?

If the program is not standard-conforming, it might still be that the
compiler is unable to detect this fact.

Message has been deleted

Wolfgang Kilian

unread,
Oct 22, 2010, 5:38:10 PM10/22/10
to
On 10/22/2010 11:38 PM, Richard Maine wrote:
>> In (*), ptr is a pointer, and it is associated with i which is not a
>> definable target. So the assignment is not allowed by the standard,
>> correct?
>
> Hmm. I don't think so, but I can certainly see the ambiguity in the
> wording. I think what it should have said is something more like that
> the target had to be definable at the point where the association was
> made. That was in the module, where i was definable.

This may be the intention of the statement. I just couldn't find a
definition of 'definable' in the standard that made this clear (to me).

Such an indirect write access to the protected variable is likely
impossible to detect at compile time, in the general case. And I don't
think that the PROTECTED information even exists in the program at
runtime. So it probably makes no sense to disallow this in the
standard, although it would be a logical possibility.

0 new messages