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

Bounds for array pointer dummy argument

678 views
Skip to first unread message

Thomas Koenig

unread,
Jul 8, 2017, 8:37:35 AM7/8/17
to
What should the following program print? 0 or 1?

PROGRAM X
TYPE T
INTEGER :: I
REAL :: X
END TYPE T
TYPE(T), TARGET :: T1(0:3)
INTEGER, POINTER :: P(:)

P => T1%I
CALL Z(P)
CONTAINS
SUBROUTINE Z(Q)
INTEGER, POINTER :: Q(:)
print *,lbound(q)
END SUBROUTINE Z
END PROGRAM X

gfortran and ifort agree that the output is 1, but it is not clear
that this is indeed correct.

paul.rich...@gmail.com

unread,
Jul 8, 2017, 10:01:33 AM7/8/17
to
Specifically, from the F2003 standard:
C.9.6

If a dummy argument is declared to be a pointer, it may be matched only by an actual argument that also is a pointer, and the characteristics of both arguments shall agree. A model for such an association is that descriptor values of the actual pointer are copied to the dummy pointer.... snip....

If this latter is followed, the output should be zero.

Paul

Damian Rouson

unread,
Jul 8, 2017, 11:38:01 AM7/8/17
to
On Saturday, July 8, 2017 at 8:01:33 AM UTC-6, paul.rich...@gmail.com wrote:
>
> If this latter is followed, the output should be zero.
>

I agree with this reading of the C.9.6 in the Fortran 2003 standard -- although I haven't found any similar language in Fortran 2008 or the February draft of the Fortran 2015 standard. I assume that constraint C.10.4 in the 2008 and 2015 standards are the descendants of Fortran 2003 C.9.6 -- at least the titles match -- but the 2008/2015 C.10.4 are written very differently from 2003 C.9.6 and I can't discern any vestiges of the quoted language from C.9.6. Does anyone know if that language appears somewhere else or was dropped intentionally?

Damian

spectrum

unread,
Jul 8, 2017, 12:01:10 PM7/8/17
to
I have tried printing the bounds of array pointer P(:) as

PROGRAM X
implicit none
TYPE T
INTEGER :: I
REAL :: X
END TYPE T
TYPE(T), TARGET :: T1( 0:3 )
INTEGER, POINTER :: P(:)

P => T1 % I
print *,"main:", lbound( P ), ubound( P ) ! added this line

CALL Z( P )

CONTAINS
SUBROUTINE Z( Q )
INTEGER, POINTER :: Q(:)
print *,"sub:", lbound( Q ), ubound( Q )
END SUBROUTINE Z
END PROGRAM X

and I get the results:

[ gfortran-7.1 ]
main: 0 3
sub: 1 4

[ ifort-16 (with and without -standard-semantics)]
main: 1 4
sub: 1 4

[ oracle studio 12.5 ] ! may not be fully compliant to the latest standards yet
main: 1 4
sub: 1 4

[ pgfortran-2017.4 ] ! may not be fully compliant to the latest standards yet
main: 1 4
sub: 1 4

If I change the line of pointer association in the main program as

P => T1(:) % I

then gfortran-7.1 gives

main: 1 4
sub: 1 4

In my understanding (up to now), pointer association preserves bounds
when the right-hand side has no colon (:), while it loses bounds info when
colon (:) is used (as in the second case). Is this not true for this kind of
type components <--> array pointer association?

# On the other hand, my assumption is that
the association of actual-dummy array pointers always preserves bounds (correct?)

paul.rich...@gmail.com

unread,
Jul 8, 2017, 2:10:38 PM7/8/17
to
There seems to be a double problem of interpretation, as far as I can tell.

(i) Pointer assignment: I think that F2008 5.3.14 is clear enough about this:
"If a data pointer is associated, the values of its deferred type parameters are the same as the values of the corresponding type parameters of its target."

From which I conclude that gfortran has it right.

(ii) Argument association: From 12.5.2.5: "The values of assumed type parameters of a dummy argument are assumed from the corresponding type parameters of its effective argument."

From which I conclude that gfortran has it wrong.

This problem arose in trying to fix bug pr34640. The fix that is compliant with 12.5.2.5 caused the above test(subref_array_4.f90) from the testsuite to fail. "Fixing" this caused another test(char_result_4.f90) to fail.

The fix that I had prepared is compliant with (i) and (ii) above. I am perfectly prepared to be guided if I have it all wrong :-)

Cheers

Paul



rbader

unread,
Jul 8, 2017, 5:23:20 PM7/8/17
to
Hello Paul,

deferred type parameters are not bounds (even though the pointer is said to have deferred shape). For POINTER dummies argument association works according to 12.5.2.3 para 2; I believe 5.3.8.4 para 5 implies that the bounds are taken from the actual argument. And for pointer assignment 7.2.2.3 para 10 applies as far as the bounds are concerned.

Cheers
Reinhold

rbader

unread,
Jul 8, 2017, 5:40:22 PM7/8/17
to
I got the reference for the argument association wrong for the case of a pointer actual: it is described in 12.5.2.3 para 5. Sorry.

campbel...@gmail.com

unread,
Jul 8, 2017, 8:56:39 PM7/8/17
to
I am not as familiar with F03 or F08 as with F90/95 but isn't this a more general problem in Fortran, where the lower bound of an assumed size array is not transferred and it is generally assumed that:
lbound (Q) = 1
ubound (Q) = size (Q)

I would expect this for either of the cases below, even though both require a CONTAINS or INTERFACE:

> SUBROUTINE Z( Q )
> INTEGER, POINTER :: Q(:)
> print *,"sub:", lbound( Q ), ubound( Q )
> END SUBROUTINE Z

or
SUBROUTINE Z( Q )
INTEGER :: Q(:)
print *,"sub:", lbound( Q ), ubound( Q )
END SUBROUTINE Z

The only attribute being transferred is the size of each array dimension.
The examples presented by Spectrum appear to support this.

Can anyone identify where this is not the case when "INTEGER, POINTER :: Q(:)" or "INTEGER :: Q(:)" is being used ?

campbel...@gmail.com

unread,
Jul 8, 2017, 9:08:21 PM7/8/17
to
Apologies; I should have referred to "Assumed-Shape" rather than "Assumed-Size" arrays.
My understanding is that in the case above of SUBROUTINE Z, the lower bound property of array Q is defined in SUBROUTINE Z, rather than from where it was called, while the SIZE of array Q is defined by the CALL.
Does this still apply for F08 ?

paul.rich...@gmail.com

unread,
Jul 9, 2017, 5:20:49 AM7/9/17
to
Hi Rheinhold,

Thanks! I did a search on 'pointer' in the F2008 standard and visted every single mention. Somehow, I failed to pick up the meaning 7.2.2.3 para 10. I guess that I had just had enough by then!

I conclude, therefore, that gfortran has it right in picking up the lbound of 'T1' but that it should pass the descriptor unmolested to the dummy 'Q'.

Good, it means that I have to do no more to the patch :-)

Thanks

Paul

chinoun...@gmail.com

unread,
Jul 9, 2017, 5:46:32 AM7/9/17
to
when replacing the derived-type array by a simple integer array all the compilers ( gfortran, ifort, pgfortran ) give the same result : 0

PROGRAM X
INTEGER, TARGET :: T1(0:3)
INTEGER, POINTER :: P(:)

P => T1
CALL Z(P)
CONTAINS
SUBROUTINE Z(Q)
INTEGER, POINTER :: Q(:)
print *,lbound(q)
END SUBROUTINE Z
END PROGRAM X

So the problem arise when the pointer point to a component of a derived-type.

Ron Shepard

unread,
Jul 9, 2017, 2:06:45 PM7/9/17
to
On 7/8/17 7:56 PM, campbel...@gmail.com wrote:
> I am not as familiar with F03 or F08 as with F90/95 but isn't this a more general problem in Fortran, where the lower bound of an assumed size array is not transferred and it is generally assumed that:
> lbound (Q) = 1
> ubound (Q) = size (Q)

No, there are some situations in which the lower bound of the actual
argument is transferred to the dummy and other situations in which the
lower bound is not transferred. The POINTER attribute of the dummy
argument is one of the situations in which the lower bound information
is transferred.

program tp
integer, target :: a(-1:1)
integer, pointer :: p(:)
p => a
print *,"a:", lbound( a ), ubound( a )
print *,"p", lbound( p ), ubound( p )
call z(a)
call z(p)
call zp(p)
contains
subroutine z( q )
integer :: q(:)
print *,"z:", lbound( q ), ubound( q )
end subroutine z
subroutine zp( q )
integer, pointer :: q(:)
print *,"zp:", lbound( q ), ubound( q )
end subroutine zp
end program tp


The gfortran output is:

a: -1 1
p -1 1
z: 1 3
z: 1 3
zp: -1 1

The assumed type nature of the actual argument appears to make this
situation even more complicated, and that is an issue with the original
post in this thread.

$.02 -Ron Shepard

campbel...@gmail.com

unread,
Jul 9, 2017, 10:49:54 PM7/9/17
to
Ron,

Thanks for your example, which does give information on the lower bound for p => a.

However gFortran 6.3.0 does appear to give incorrect results at line 14 for the following merged example if lines 16 and 17 are not commented out. This looks to be a strange problem with gFortran

PROGRAM X
integer, target :: a(-1:1)
INTEGER, POINTER :: P(:)
TYPE T
INTEGER :: I
REAL :: X
END TYPE T
TYPE(T), TARGET :: T1(0:3)

call report_compiler_version

P => a
call z(p, 'P => a')
CALL Zp(P, 'P => a')

! P => T1%I
! CALL Zp(P, 'P => T1%I')

CONTAINS
subroutine z( q, description )
integer :: q(:)
character*(*) description
print *,"z:", lbound( q ), ubound( q ), ' : ',description
end subroutine z

SUBROUTINE Zp(Q, description)
INTEGER, POINTER :: Q(:)
character*(*) description
print *,"zp:", lbound(q), ubound(q), ' : ',description
END SUBROUTINE Zp
END PROGRAM X

subroutine report_compiler_version
use iso_fortran_env
!
write (*,*) compiler_version ()
end subroutine report_compiler_version

Themos Tsikas

unread,
Jul 10, 2017, 7:30:25 AM7/10/17
to
It is clear that gfortran produces wrong code for this case. I tried

GNU Fortran (GCC) 4.9.2 20150212
GNU Fortran (GCC) 7.1.1 20170516
pgfortran 17.4-0 64-bit target on x86-64 Linux
Intel(R) Fortran Intel(R) 64 Compiler [...] Version 17.0.4.196 Build 20170411
NAG Fortran Compiler Release 6.1(Tozai) Build 6137

on the program (which shows how to make a zero-based pointer to an array of the integer components).

!begin
Module formats
Character (*), Parameter :: form = '(A4,3I4)'
End Module formats

Program x
Use formats, Only: form
Type t
Integer :: i
Real :: x
End Type t
Type (t), Target :: t1(0:3)
Integer, Pointer :: p(:), s(:), r(:)

Write (*, Fmt=form) 't1 ', lbound(t1), ubound(t1), size(t1)
Write (*, Fmt=form) 't1%I', lbound(t1%i), ubound(t1%i), size(t1%i)
p => t1%i
Write (*, Fmt=form) 'p ', lbound(p), ubound(p), size(p)
Call z(p)
r =>t1(0:)%i
Write (*, Fmt=form) 'r ', lbound(r), ubound(r), size(r)
Call z(r)
s(lbound(t1,dim=1):) => t1%i
Write (*, Fmt=form) 's ', lbound(s), ubound(s), size(s)
Call z(s)
Contains
Subroutine z(q)
Integer, Pointer :: q(:)

Write (*, Fmt=form) 'q ', lbound(q), ubound(q), size(q)
End Subroutine z
End Program x
!end

The correct output (all but GNU produced this)

t1 0 3 4
t1%I 1 4 4
p 1 4 4
q 1 4 4
r 1 4 4
q 1 4 4
s 0 3 4
q 0 3 4


The GNU output

t1 0 3 4
t1%I 1 4 4
p 0 3 4
q 1 4 4
r 1 4 4
q 1 4 4
s 0 3 4
q 1 4 4


Themos Tsikas, NAG Ltd

paul.rich...@gmail.com

unread,
Jul 10, 2017, 1:35:30 PM7/10/17
to
Hi Themos,

While I am not over enthusiastic about democratic resolutions of this kind of question, it is clear that the majority in this case had read the standard description of LBOUND carefully and that whoever implemented pointer assignment in gfortran did not :-)

The key here is that for the bounds of the target to be transmitted to the pointer, the reference must be a WHOLE ARRAY. Otherwise LBOUND must be 1.

Many thanks for your test and for doing it on such a wide range of compilers. I will fix gfortran accordingly. I have already fixed the passing of pointer arrays to dummy pointers.

In fact, thanks to all of you who contributed to this thread. You have helped to get it right.

Paul

herrman...@gmail.com

unread,
Jul 10, 2017, 4:54:19 PM7/10/17
to
On Monday, July 10, 2017 at 10:35:30 AM UTC-7, paul.rich...@gmail.com wrote:

(snip)

> While I am not over enthusiastic about democratic resolutions
> of this kind of question, it is clear that the majority in this
> case had read the standard description of LBOUND carefully and
> that whoever implemented pointer assignment in gfortran did not :-)

> The key here is that for the bounds of the target to be
> transmitted to the pointer, the reference must be a WHOLE ARRAY.
> Otherwise LBOUND must be 1.

And no comment on a language definition so complicated that
you have to refer to the standard, and read it so carefully,
to get this right.

For comparison purposes only, note that the PL/I array convention
always uses the declared array bounds. There is nothing like assumed
size in PL/I. This might be inconvenient. You can't add, or even
assign, arrays with different LBOUND, without a loop. Subroutines
always need to use LBOUND and UBOUND to loop over the whole array,
except in cases where array expressions work.

Not so convenient, but nice and consistent. You only need to
learn one rule, and always apply that rule.

There are many PL/I rules that are inconvenient for compiler
writers, but convenient for users. One not so obvious, and
maybe Fortran users forget what happens in this case, when
using ENTRY, the return value is converted to the appropriate
type for the ENTRY point used. For those who forgot, Fortran
EQUIVALENCEs all the function return variables.

No, I am not writing this in hopes that people will start
using PL/I. But consider that if the rules are so complicated
that it takes this much discussion, they are likely to lead to
program bugs when users forget them.

Someone might have an assumed shape array, but then realize
that they need an ALLOCATABLE or POINTER instead. nice simple
change, and maybe in the beginning the lower bound is 1 in
testing, but then later on, another lower bound is used, and
the program fails. Or maybe the other was, someone doesn't
like using POINTER where it isn't needed, and makes the change.

Fragile programs lead to hard to find bugs. In larger programs,
they get even harder to find.

Gary Scott

unread,
Jul 10, 2017, 8:53:45 PM7/10/17
to
Oh come on, you KNOW that PL/I is the bestest!

robin....@gmail.com

unread,
Jul 10, 2017, 9:59:48 PM7/10/17
to
On Tuesday, July 11, 2017 at 6:54:19 AM UTC+10, herrman...@gmail.com wrote:
> On Monday, July 10, 2017 at 10:35:30 AM UTC-7, paul.rich...@gmail.com wrote:
>
> (snip)
>
> > While I am not over enthusiastic about democratic resolutions
> > of this kind of question, it is clear that the majority in this
> > case had read the standard description of LBOUND carefully and
> > that whoever implemented pointer assignment in gfortran did not :-)
>
> > The key here is that for the bounds of the target to be
> > transmitted to the pointer, the reference must be a WHOLE ARRAY.
> > Otherwise LBOUND must be 1.
>
> And no comment on a language definition so complicated that
> you have to refer to the standard, and read it so carefully,
> to get this right.
>
> For comparison purposes only, note that the PL/I array convention
> always uses the declared array bounds.

That's because the array bounds are passed in a descriptor,
which contains the upper and lower bounds, as well as the address
of the array.

> There is nothing like assumed size in PL/I.

What? Dummy arguments in Fortran are defined with * for each bound.
That is how the corresponding facility in PL/I is used.

> This might be inconvenient. You can't add, or even
> assign, arrays with different LBOUND, without a loop.

But most programmers choose a consistent lower bound, such as 0 or 1.

> Subroutines
> always need to use LBOUND and UBOUND to loop over the whole array,
> except in cases where array expressions work.

That's the same in Fortran.

> Not so convenient, but nice and consistent. You only need to
> learn one rule, and always apply that rule.

Indeed.

herrman...@gmail.com

unread,
Jul 11, 2017, 1:34:34 AM7/11/17
to
On Monday, July 10, 2017 at 6:59:48 PM UTC-7, robin....@gmail.com wrote:

(snip, previous discussion said)
> > > The key here is that for the bounds of the target to be
> > > transmitted to the pointer, the reference must be a WHOLE ARRAY.
> > > Otherwise LBOUND must be 1.

(then I said)
> > For comparison purposes only, note that the PL/I array convention
> > always uses the declared array bounds.

> That's because the array bounds are passed in a descriptor,
> which contains the upper and lower bounds, as well as the address
> of the array.

Fortran assumed shape are passed by descriptor, too, but
with different information. The descriptor might just pass
the extent if each subscript. In the called routine,
the array will have lower bound of 1, and appropriate
upper bound.

> > There is nothing like assumed size in PL/I.

> What? Dummy arguments in Fortran are defined with * for each bound.
> That is how the corresponding facility in PL/I is used.

Assumed size, along with explicit shape, does not pass bounds
information, (or if it does, it is ignored). The dummy array
can have different rank, and/or different extent of each
dimension, as long as it stays within the number of element
of the actual array. Even more, one can pass an array element,
and the called routine can use any array element from that one,
to the end of the array. There is no such feature in PL/I.

(It would be interesting to see what the Fortran to PL/I
converter did with this one.)

> > This might be inconvenient. You can't add, or even
> > assign, arrays with different LBOUND, without a loop.

> But most programmers choose a consistent lower bound, such as 0 or 1.

In that case, there is no problem. Sometimes, one wants to
use a routine written by someone else. But even consider:

dcl (a(-2:3), b(0:5), c(2:7)) float bin(23);

you can't:

a=b+c;

or even:

a=c;

because the bounds don't match. On the other hand:

real a(-2:3), b(0:5), c(2:7)

(and assuming that they have appropriate values)

a=b+c

the six elements of b will be added to the six element
of c, and the sum assigned to a.

> > Subroutines
> > always need to use LBOUND and UBOUND to loop over the whole array,
> > except in cases where array expressions work.

> That's the same in Fortran.

No. In most cases, the case in this thread being a
counterexample, the called routine can:

do i=1, size(a,1)
a(i)=a(i)+1
enddo

> > Not so convenient, but nice and consistent. You only need to
> > learn one rule, and always apply that rule.

> Indeed.

Even more interesting, the descriptor defined for VAX in
the 1970's is appropriate for calling between Fortran and PL/I.

For the PL/I calling convention, you don't need the address
of the first element of the array, you need the address of
the virtual origin, the element with all subscripts zero
(which may or may not be inside the array). For the Fortran
assumed shape case, you can find all the array elements with
the address of the first element, and the extents of each.

The VAX descriptor passes the actual origin, virtual origin,
upper and lower bounds, and extent for each dimension.
Fortran programs can call PL/I, or PL/I programs call Fortran.

(snip of unrelated features)


robin....@gmail.com

unread,
Jul 11, 2017, 6:38:23 AM7/11/17
to
On Tuesday, July 11, 2017 at 3:34:34 PM UTC+10, herrman...@gmail.com wrote:
> On Monday, July 10, 2017 at 6:59:48 PM UTC-7, robin....@gmail.com wrote:
>
> (snip, previous discussion said)
> > > > The key here is that for the bounds of the target to be
> > > > transmitted to the pointer, the reference must be a WHOLE ARRAY.
> > > > Otherwise LBOUND must be 1.
>
> (then I said)
> > > For comparison purposes only, note that the PL/I array convention
> > > always uses the declared array bounds.
>
> > That's because the array bounds are passed in a descriptor,
> > which contains the upper and lower bounds, as well as the address
> > of the array.
>
> Fortran assumed shape are passed by descriptor, too, but
> with different information.

But Fortran does not pass the upper and lower bounds of the argument.
It's then necessary to pass the lower bound as a separate argument.

> The descriptor might just pass
> the extent if each subscript. In the called routine,
> the array will have lower bound of 1, and appropriate
> upper bound.

The "appropriate" upper bound can exceed the size of an integer.

> > > There is nothing like assumed size in PL/I.
>
> > What? Dummy arguments in Fortran are defined with * for each bound.
> > That is how the corresponding facility in PL/I is used.
>
> Assumed size, along with explicit shape, does not pass bounds
> information, (or if it does, it is ignored). The dummy array
> can have different rank, and/or different extent of each
> dimension, as long as it stays within the number of element
> of the actual array.

That's a good way to introduce bugs into a program.

> Even more, one can pass an array element,

An array element is not passed.
The address of it is passed.

> and the called routine can use any array element from that one,
> to the end of the array.

Another "feature" waiting to show up as a bug.

> There is no such feature in PL/I.

And you would not want such a bug-prone "feature" in PL/I.
As I said, looping over the array is precisely the same in PL/I.
Of course, for this trivial example, in PL/I you can write
a = a + 1;

And what happens when array A is defined as
real a(-2147483647:2147483647) ?

> > > Not so convenient, but nice and consistent. You only need to
> > > learn one rule, and always apply that rule.
>
> > Indeed.
>
> Even more interesting, the descriptor defined for VAX in
> the 1970's is appropriate for calling between Fortran and PL/I.
>
> For the PL/I calling convention, you don't need the address
> of the first element of the array, you need the address of
> the virtual origin, the element with all subscripts zero
> (which may or may not be inside the array).

You are assuming something that is not true, in general.

spectrum

unread,
Jul 11, 2017, 8:02:56 AM7/11/17
to
The ASSOCIATE construct for referencing type components (as an array)
also seems to have a similar dependence on compilers,
so it may also need attention (maybe a similar origin?). For example,

PROGRAM X
implicit none
TYPE T
INTEGER :: I
END TYPE T
TYPE(T), TARGET :: T1( 0:3 )

associate( P => T1 % I )
print *, "P : ", lbound(P), ubound(P)
endassociate

associate( P2 => T1(:) % I )
print *, "P2 : ", lbound(P2), ubound(P2)
endassociate

associate( Q => T1 )
print *, "Q : ", lbound(Q), ubound(Q)
endassociate

associate( Q2 => T1(:) )
print *, "Q2 : ", lbound(Q2), ubound(Q2)
endassociate

END PROGRAM X

[ gfortran-7.1 ]
P : 0 3
P2 : 1 4
Q : 0 3
Q2 : 1 4

[ ifort-16 ]
P : 1 4
P2 : 1 4
Q : 0 3
Q2 : 1 4

[ PGI 2017.4 ] ! may not be fully compliant to F2003/08 yet
P : 1 4
P2 : 1 4
Q : 0 3
Q2 : 1 4

[ Oracle studio 12.5 ]
(... cannot compile ...)

spectrum

unread,
Jul 11, 2017, 8:23:33 AM7/11/17
to
Dear Glen and Robin,

I think the comparison with PL/I is interesting (with respect to the treatments
of array bounds), but I guess it would be more convenient and interesting
(for the reader) and focused (for posters) if we make a separate thread
for comparison of the treatment of array bounds in other languages.
This is particularly so because the topic is pretty broad and it might be better
to keep this thread "focused" on the specific issue (though it is probably
very broadly related to the underlying design). Indeed, comparison with
not only PL/I, but also with Pascal, Ada, Nim, Julia, Chapel (or any other
languages that allow arbitrary bounds) seem interesting.

# Personally, I wanted Fortran to preserve the bounds for the case
"P => T1 % I", but it may be too late to say this (looking at other compilers).
Very personally, I feel Fortran is becoming more and more "oriented"
toward 1-based arrays, because there are more cases that lose bounds
than keeping them. (Maybe the only "safe (or safer)" way is to include
an array pointer into a type?)

Ron Shepard

unread,
Jul 11, 2017, 11:33:43 AM7/11/17
to
On 7/11/17 7:23 AM, spectrum wrote:
> # Personally, I wanted Fortran to preserve the bounds for the case
> "P => T1 % I", but it may be too late to say this (looking at other compilers).
> Very personally, I feel Fortran is becoming more and more "oriented"
> toward 1-based arrays, because there are more cases that lose bounds
> than keeping them. (Maybe the only "safe (or safer)" way is to include
> an array pointer into a type?)

I have had that same feeling since f90, where either the wrong default
seemed to have been chosen, or where it was not possible for the
programmer to maintain a lower bound convention in a simple way. At
least many of these situations were corrected in f2003 when the lower
bound could be set/reset on the lhs during pointer assignment. I still
have lots of code written before 2010 that has clunky workarounds
(possibly not strictly standard conforming) due to this faulty design
choice.

The ability for the programmer to set the lower bounds in arrays has
been in the language since f77. That is one of the features that sets
fortran apart from lesser languages such as C and its ilk. Whenever a
new feature is added to the language, I think this ability should be
maintained in a natural and straightforward way.

$.02 -Ron Shepard

spectrum

unread,
Jul 11, 2017, 6:16:04 PM7/11/17
to
Dear Glen and Robin,

I'm sorry if my post above looks like an attempt to "enforce" or "control" your future posts toward different threads (than this one). Rather, my intention was that I would like to hear practical experiences of such array handling in other languages (incl. PL/I)
in a more "dedicated" thread. But there's no such moderation/rules in this forum,
so please don't take my post above too seriously...

Best regards,
S

spectrum

unread,
Jul 11, 2017, 6:34:14 PM7/11/17
to
On Wednesday, July 12, 2017 at 12:33:43 AM UTC+9, Ron Shepard wrote:
> I have had that same feeling since f90, where either the wrong default
> seemed to have been chosen, or where it was not possible for the
> programmer to maintain a lower bound convention in a simple way. At
> least many of these situations were corrected in f2003 when the lower
> bound could be set/reset on the lhs during pointer assignment. I still
> have lots of code written before 2010 that has clunky workarounds
> (possibly not strictly standard conforming) due to this faulty design
> choice.
>
> The ability for the programmer to set the lower bounds in arrays has
> been in the language since f77. That is one of the features that sets
> fortran apart from lesser languages such as C and its ilk. Whenever a
> new feature is added to the language, I think this ability should be
> maintained in a natural and straightforward way.
>

Indeed, assumed-shape arrays have the default lower bound of 1, and we need
to pass other variables separately to set the lower bound via variables
(correct?). Because I felt it very tedious to pass such bounds info separately,
I usually sticked to the default lower bound = 1 almost in all my programs up to now.
But, there are cases where I do want to use bounds other than 1, but I felt
some dilemma there. I even considered changing all allocatable arrays to
array pointers to keep bounds automatically, but this has also some drawbacks.

Because I guess array descriptors are passed internally to assumed-shape arrays,
I think it would be more convenient to just keep all the info of the actual
descriptor (and bounds), while allowing the user to decide whether to
"discard the bounds or not (in a scope)" depending on their needs.
This is because it is easy to lose information at any time, while
retrieving it needs more efforts (e.g., by passing bounds info separately via arguments).

Nevertheless, setting the lower bound to 1 for dummy arrays
makes a subroutine conceptually simpler, so probably there are pros & cons...

herrman...@gmail.com

unread,
Jul 11, 2017, 7:41:29 PM7/11/17
to
On Tuesday, July 11, 2017 at 3:16:04 PM UTC-7, spectrum wrote:

> I'm sorry if my post above looks like an attempt to "enforce"
> or "control" your future posts toward different threads
> (than this one).

No, I wasn't bothered by that.

> Rather, my intention was that I would like to hear practical
> experiences of such array handling in other languages (incl. PL/I)
> in a more "dedicated" thread. But there's no such moderation/rules
> in this forum, so please don't take my post above too seriously...

I suppose I was asking about that, but more I was asking about
the rules that are confusing and inconsistent.

I don't know that it was intentional, but it always seemed
to me that PL/I was designed to keep rules consistent.

Some have been fixed by now. Until Fortran 77, WRITE statements
could only have variables, including array elements, but not
constants or general expressions.

Using internal procedure names as actual arguments took some
time, but I believe is now allowed. If I remember, though,
nesting of internal procedures is still not allowed. This makes
a complicated rule, saying where you can and can't (inside other
internal procedures) have one. Sometimes there are good reasons,
but other times it just seems to be to make it harder for users.

Another example, why no REAL variables for DO loops. Yes I know
that they can cause problems for users, but that is for users
to understand. Every other language that I can think of allows them.
They were added in Fortran 77, and later removed, so it isn't
likely that they are hard to implement. It adds one more
restriction on users, and something else for compilers to check.

Some rules are needed to prevent ambiguities, and other things
that just don't make much sense, but not always.

FortranFan

unread,
Jul 11, 2017, 8:16:57 PM7/11/17
to
On Tuesday, July 11, 2017 at 6:34:14 PM UTC-4, spectrum wrote:

> ..
>
> Indeed, assumed-shape arrays have the default lower bound of 1, and we need
> to pass other variables separately to set the lower bound via variables
> (correct?). Because I felt it very tedious to pass such bounds info separately,
> I usually sticked to the default lower bound = 1 almost in all my programs up to now.
> But, there are cases where I do want to use bounds other than 1, but I felt
> some dilemma there. I even considered changing all allocatable arrays to
> array pointers to keep bounds automatically, but this has also some drawbacks.
> ..


Hopefully one or more current/future members of the standards committee will make a good note of such issues in this thread and also be aware of this other discussion a couple of months ago

https://groups.google.com/d/msg/comp.lang.fortran/gNJGmqn3I9s/6hy7UmkMAwAJ

where the idea of ASSUMEBOUNDS (PASSBOUNDS originally) as a dummy argument attribute was brought up.

The committee needs to give additional attention to this matter and come up with some reasonable solution in the next revision (Fortran 202X) for the benefit of coders using Fortran.

Clive Page

unread,
Jul 12, 2017, 5:14:43 AM7/12/17
to
On 12/07/2017 00:41, herrman...@gmail.com wrote:
>
> I suppose I was asking about that, but more I was asking about
> the rules that are confusing and inconsistent.
>
> I don't know that it was intentional, but it always seemed
> to me that PL/I was designed to keep rules consistent.
>
> Some have been fixed by now. Until Fortran 77, WRITE statements
> could only have variables, including array elements, but not
> constants or general expressions.

I'd like to echo your concern about this. An awful lot of the current Fortran Standard is
taken up with exceptions to general rules. For example: in the I/O list of a WRITE
statement you can use any general expression except that you can't use a user-written
function which itself does I/O (except in a few cases you can).

Maybe a good way of improving Fortran for the next standard would be for people to look
through the exceptions to general rules and see whether it would be easy to get rid of
them. In some cases, of course, this would involve compiler-writers in a huge amount of
work or it would change Fortran in a way that would invalidate existing programs. But my
guess is that some exceptions could be removed without too much trouble, and that
programmers would benefit hugely from a cleaned-up language.

In particular the current rules about lower-bounds is a real pain, and as others have
said, it means that Fortran programmers have a strong incentive to stick to the default of
1 unless they are prepared to take a lot of effort.

We often criticise the C language for having a broken array system because when you pass
an array to a function it degrades into a pointer. It seems to me that Fortran's array
system is somewhat broken too in that if you define a lower-bound to an array and you pass
it to a procedure it degrades into a dummy array with a lower-bound of 1 (except in cases
in which it doesn't). I realise it's going to be hard to fix this without making existing
software incompatible, but would it be impossible?

--
Clive Page

Gary Scott

unread,
Jul 12, 2017, 9:46:04 AM7/12/17
to
Isn't that just descriptor content? Doesn't sound difficult.

Jos Bergervoet

unread,
Jul 12, 2017, 1:21:21 PM7/12/17
to
So the only question is whether the (original) statement
P => T1%I
counts as an *expression*. If so, then its result is an array
with default lower-bound, 1, if not then it preserves the
existing lowerbound, 0. So here we go:

program x
type t
integer :: i
end type t

type(t) :: t1(0:3)

print *, lbound(t1%i) ! gfortran prints 1
end

Apparently, gfortran believes t1%i to be an expression (it
knows very well that lbound(t1) is 0). I leave it to the
language lawyers to decide whether t1%i indeed is expression..

--
Jos

Jos Bergervoet

unread,
Jul 12, 2017, 1:25:30 PM7/12/17
to
Or perhaps the implementer believed that t1%i is an expression

[see my other post. Of course we can have a democratic process
to resolve this expression question, but my preference was to
leave that to the language lawyers! Where are they?]



>
> The key here is that for the bounds of the target to be transmitted to the pointer, the reference must be a WHOLE ARRAY. Otherwise LBOUND must be 1.

Yes, but whole array would be t1, whereas t1%i is an expression,
perhaps (or perhaps not).

> Many thanks for your test and for doing it on such a wide range of compilers. I will fix gfortran accordingly.

Are you sure you will not have to fix it back?

--
Jos

Themos Tsikas

unread,
Jul 12, 2017, 1:42:08 PM7/12/17
to
Hello,

The entertaining thing is that my version of the 2003 standard says

R739 data-target is variable or expr

2008 says

R737 data-target is variable

and draft 2015 says , you guessed it

R1037 data-target is expr

Themos Tsikas, NAG Ltd


On Wednesday, 12 July 2017 18:21:21 UTC+1, Jos Bergervoet wrote:

paul.rich...@gmail.com

unread,
Jul 12, 2017, 2:40:53 PM7/12/17
to
On Wednesday, 12 July 2017 18:42:08 UTC+1, Themos Tsikas wrote:
> Hello,
>
> The entertaining thing is that my version of the 2003 standard says
>
> R739 data-target is variable or expr
>
> 2008 says
>
> R737 data-target is variable
>
> and draft 2015 says , you guessed it
>
> R1037 data-target is expr
>
> Themos Tsikas, NAG Ltd
>

Hi Themos,

I don't want to know about this :-) I have just spent an unreasonable amount of time producing a patch to push gfortran in the direction of the 'democratic choice', which is the correct one by F2008. The section on pointer assignment in F2008 is, I was going to say clear enough, but, once the definition of "whole array" was absorbed by this Bear-of-little-brain, it is at least unambiguous!

Thanks for your testcase - it helped. I have even put right the associate problem....

Cheers

Paul

Jos Bergervoet

unread,
Jul 12, 2017, 3:53:03 PM7/12/17
to
On 7/12/2017 8:40 PM, paul.rich...@gmail.com wrote:
> On Wednesday, 12 July 2017 18:42:08 UTC+1, Themos Tsikas wrote:
>> Hello,
>>
>> The entertaining thing is that my version of the 2003 standard says
>>
>> R739 data-target is variable or expr
>>
>> 2008 says
>>
>> R737 data-target is variable
>>
>> and draft 2015 says , you guessed it
>>
>> R1037 data-target is expr
>>
>> Themos Tsikas, NAG Ltd
>>
>
> Hi Themos,
>
> I don't want to know about this :-) I have just spent an unreasonable
> amount of time producing a patch to push gfortran in the direction of the
> 'democratic choice',

I'm sorry to hear that. (It's much appreciated!)

> .. which is the correct one by F2008. The section
> on pointer assignment in F2008 is, I was going to say clear enough, but, once
> the definition of "whole array" was absorbed by this Bear-of-little-brain,
> it is at least unambiguous!

The meaning of unambiguous could then perhaps use some patching up
as well. At least to some it might seem that if t1(0:3) is *not* a
whole array even though it is the whole content, then t1%i should
also *not* be the whole array (since it leaves out the reals!)

program x ! testing gfortran
type t
integer :: i; real :: r
end type t

type(t) :: t1(0:3)

print *, lbound( t1 ) ! prints 0, is whole array
print *, lbound( t1(0:3) ) ! prints 1
print *, lbound( t1%i ) ! prints 1, will change to 0(?)
end

Nevertheless, I have nothing against it personally. Still, if the
J3 committee or another form of Supreme Court could give its fiat,
that would be, well, reassuring!

--
Jos

Themos Tsikas

unread,
Jul 12, 2017, 5:23:45 PM7/12/17
to
Hello,

The final word of the 2008 standard should be the one that includes the Corrigenda and you can find in document N2122

(linked from page http://www.nag.co.uk/sc22wg5/docs.html )


Subclause 7.2.2.2
In syntax rule R737, add new production:
or expr

which restores the 2003 text. That is a WG5 document intended for internal use. I understand that this is not official ISO/IEC standard until it is properly published as such.

Also, latest 2015 Draft Just a few days old!), document N2137, contains the wording

R1037 data-target is expr
C1025 (R1037) The expr shall be a designator that designates a variable with either the TARGET or POINTER attribute and is not an array section with a vector subscript, or it shall be a reference to a function that returns a data pointer.
C1026 (R1037) A data-target shall not be a coindexed object.
R901 designator is object-name
or array-element
or array-section
or coindexed-named-object
or complex-part-designator
or structure-component
or substring
R913 structure-component is data-ref
R911 data-ref is part-ref [ % part-ref ] ...
R912 part-ref is part-name [ ( section-subscript-list ) ] [ image-selector ]

So, I think that the intention and effect of all this is that t1%i in the context of data-target of pointer-assignment-stmt is NOT a general expression as understood elsewhere. In any case the LBOUND of p should be the same as LBOUND of t1%i (this is where gfortran came up short) as stated
"If bounds-spec-list appears, it specifies the lower bounds; otherwise, the lower bound of each dimension is the result of the intrinsic function LBOUND (16.9.109) applied to the corresponding dimension of the pointer target."
But I am not convinced now that all the other compilers get it right either or even if the standard establishes an interpretation! Time to talk to the Editor...

Themos Tsikas, NAG Ltd

On Wednesday, 12 July 2017 18:42:08 UTC+1, Themos Tsikas wrote:

Dick Hendrickson

unread,
Jul 12, 2017, 9:15:27 PM7/12/17
to
I don't think so. What should ti(I:J) be? Should it be a whole array
if I and J happen to be 0 and 3 and not a whole array otherwise. A run
time decision? Fortran made the choice that whole arrays are arrays
without subscript expressions and not-whole-arrays are arrays with
subscript expressions. Fortran generally doesn't distinguish between
simple expressions and complicated expressions. The rule is, mostly, if
you want the whole array write the array name; if you want part of the
array, write some subscript bounds. The compiler won't take a peek at
the bounds to see which you meant.

Similarly, several posts in this thread have implicitly assumed that
actual arguments are simple array names; they aren't, actual argumnts
can be expressions. Given something like
dimension a(-10:5)
maybe
call sub(a)
should somehow pass the -10 and 5 as hidden arguments?
but what about
call sub(a(I:J:K))
call sub(a + a(5:-10:-1))
call sub(a(-2)) !remember F77 storage association :(

Dick Hendrickson

campbel...@gmail.com

unread,
Jul 12, 2017, 11:35:25 PM7/12/17
to
On Thursday, July 13, 2017 at 11:15:27 AM UTC+10, Dick Hendrickson wrote:
> but what about
> call sub(a(I:J:K))
> call sub(a + a(5:-10:-1))
> call sub(a(-2)) !remember F77 storage association :(
>
> Dick Hendrickson

If we are not discussing a pointer array, then lbound is not transferred. For "Integer, pointer :: Q(:)", wouldn't sub be contained or have an interface when it is expecting an assumed shape argument ?
...
CONTAINS
SUBROUTINE sub(Q)
INTEGER, POINTER :: Q(:)
...

I suspect the 3rd example would give a compile error and I don't know what would happen with the other two.

Ron Shepard

unread,
Jul 13, 2017, 2:17:34 AM7/13/17
to
On 7/12/17 8:15 PM, Dick Hendrickson wrote:
> call sub(a(I:J:K))
> call sub(a + a(5:-10:-1))
> call sub(a(-2)) !remember F77 storage association :(

It might be a little confusing to lump these all together as
"expressions". The first (array slice) and the last (array element)
allow the subroutine to modify the dummy argument, whereas the second
(which is an actual arithmetic expression) does not allow the dummy
argument to be modified. If sub() has an explicit interface with intent
attributes, then the compiler is likely to catch mismatches like this
between the actual and dummy arguments at compile time. Otherwise, it is
entirely up to the programmer to keep things straight.

The question in this thread is what is the lower bound of the dummy
argument within sub(), and in all three of these cases it would be the
default 1, unless declared otherwise in some explicit way. So in that
way, all three share the same feature.

The three cases also differ regarding pointer assignment. Assuming a(:)
is a legal target, then only the first is a legal target for a rank 1
pointer, and only the last is a legal target for a scalar pointer. So
this is another way that the three "expressions" differ.

$.02 -Ron Shepard

Jos Bergervoet

unread,
Jul 13, 2017, 2:24:29 AM7/13/17
to
On 7/13/2017 8:17 AM, Ron Shepard wrote:
> On 7/12/17 8:15 PM, Dick Hendrickson wrote:
>> call sub(a(I:J:K))
>> call sub(a + a(5:-10:-1))
>> call sub(a(-2)) !remember F77 storage association :(
>
> It might be a little confusing to lump these all together as
> "expressions". The first (array slice) and the last (array element)
> allow the subroutine to modify the dummy argument, whereas the second
> (which is an actual arithmetic expression) does not allow the dummy
> argument to be modified. If sub() has an explicit interface with intent
> attributes, then the compiler is likely to catch mismatches like this
> between the actual and dummy arguments at compile time. Otherwise, it is
> entirely up to the programmer to keep things straight.
>
> The question in this thread is what is the lower bound of the dummy
> argument within sub(),

Actually the sub is irrelevant in OP's example code, you see the
different lowerbounds *already* if, for the different cases, you
just use:
print *, lbound( ... )

But of course you could argue that print is the "subroutine" here.
Anyway no reason to wrap it inside another one. (Your additional
issue of F77 storage association of course does require a subroutine
to be involved.)

--
Jos

Jos Bergervoet

unread,
Jul 13, 2017, 2:31:21 AM7/13/17
to
My point is not that ti(I:J) should be a whole array! It is that
since ti(I:J) is *not* a whole array, perhaps ti%comp would *also*
not be a whole array. At least one would not be sure without
consulting the standard.

The discussion here seems to focus on the wrong question (What the
subroutine does with its argument) whereas the only real (new)
problem that needs to be addressed is whether a component selection
of a whole array is still a whole array.

[Actually my preference would be "yes", and that also is the answer
that has been reached, so there is no problem left. It was only about
the logic in analyzing the question!]

--
Jos

Themos Tsikas

unread,
Jul 13, 2017, 6:31:22 AM7/13/17
to
Well,

"A whole array is a named array or a structure component whose final part-ref is an array component name; no subscript list is appended."

Since i is a scalar component, t1%i cannot be whole array and LBOUND specifies

Case (i): If DIM is present, ARRAY is a whole array, and either ARRAY is an assumed-size array of rank DIM or dimension DIM of ARRAY has nonzero extent, the result has a value equal to the lower bound for subscript DIM of ARRAY. Otherwise, if DIM is present, the result value is 1.

Case (ii): LBOUND (ARRAY) has a value whose i^th element is equal to LBOUND (ARRAY, i), for i = 1, 2,. . . , n, where n is the rank of ARRAY. LBOUND (ARRAY, KIND=KIND) has a value whose i^th element is equal to LBOUND (ARRAY, i, KIND), for i = 1, 2, . . . , n, where n is the rank of ARRAY.

so, LBOUND(t1%i,1) = 1 and LBOUND(t1%i) = the array [1]

That is my current understanding of it.

Themos Tsikas, NAG Ltd.

paul.rich...@gmail.com

unread,
Jul 13, 2017, 8:13:46 AM7/13/17
to
Dear Themos,

Thanks to you that is my understanding too and why I now think that gfortran had it wrong and the others were right.

In respect of tweaks to the standard, appearing in F2015, I think that it would be a mistake to change from this understanding.

Cheers

Paul

FortranFan

unread,
Jul 13, 2017, 9:40:47 AM7/13/17
to
On Wednesday, July 12, 2017 at 5:23:45 PM UTC-4, Themos Tsikas wrote:

> ..
>
> So, I think that the intention and effect of all this is that t1%i in the context of data-target of pointer-assignment-stmt is NOT a general expression as understood elsewhere. In any case the LBOUND of p should be the same as LBOUND of t1%i (this is where gfortran came up short) as stated
> "If bounds-spec-list appears, it specifies the lower bounds; otherwise, the lower bound of each dimension is the result of the intrinsic function LBOUND (16.9.109) applied to the corresponding dimension of the pointer target."
> But I am not convinced now that all the other compilers get it right either or even if the standard establishes an interpretation! Time to talk to the Editor...
>
> ..

@Themos Tsikos,

I hope you will "talk to the Editor" (should be much easier for you to do so than anyone else, right!? :-). And please report back here any findings.

Can you please elaborate further on your comment, "I am not convinced now that all the other compilers get it right either"? What exactly in the wording changes from revision to revision (2003 to 2008 to 2015) seems to materially affect anything in the context of this thread or the pointer assignment in the original post? Are not the facts still that

a) T1%I is not a "whole array" PER Fortran standard definition of what a whole array is, regardless of how T1%I may appear to some of the readers here.

b) One piece of verbiage that has consistently appeared in the standard revisions in question is the one about "otherwise, the lower bound of each dimension is the result of the intrinsic function LBOUND (16.9.109) applied to the corresponding dimension of the pointer target." and which is precisely what gfortran deviated from whereas other compilers didn't.

So it is troublesome and worrying to read of your concern now about other compilers. It will be good to understand where you are coming from on this.

Thanks much,

Themos Tsikas

unread,
Jul 13, 2017, 12:18:31 PM7/13/17
to
Hello,

In retrospect I should have probably kept my attempts to make sense of everything I was reading to myself and not post late at night! The Editor communicated to me that the language definition regarding pointer assignment (including what happens to lower bounds) has not changed although the wording had to accommodate new features.

One more example code, showing the difference between whole-array and parenthesised whole-array.

!begin
type t
real::x(2)
integer::i(3:5)
integer::j
end type
type(t), target :: ta(0:10)
print *,"lbound(ta)",lbound(ta) !whole array: 0
print *,"lbound((ta))",lbound((ta)) !expression: 1
print *,"lbound(ta(0)%x)",lbound(ta(0)%x)!whole array: 1
print *,"lbound(ta(0)%i)",lbound(ta(0)%i)!whole array: 3
print *,"lbound(ta%j)",lbound(ta%j) !not whole : 1
end
!end

Out of my earlier list of compilers, only the PGI one gets the expression case wrong (returns 0).

Themos Tsikas, NAG Ltd.

FortranFan

unread,
Jul 13, 2017, 2:20:13 PM7/13/17
to
On Thursday, July 13, 2017 at 12:18:31 PM UTC-4, Themos Tsikas wrote:

> .. The Editor communicated to me that the language definition regarding pointer assignment (including what happens to lower bounds) has not changed although the wording had to accommodate new features.
>
> One more example code, ..

Hello Themos,

Thanks much for your response, greatly appreciated.

By the way, it's extremely, extremely valuable to have your (and thus NAG Ltd's) contributions on this forum, it enriches the platform tremendously. Hope more and more Fortran compiler and language experts will start to follow your example.

Thanks and regards,
just a Fortran enthusiast

jfh

unread,
Jul 13, 2017, 5:27:55 PM7/13/17
to
I'm also glad to see NAG here. My notes for f77->f95 conversion say "There is a newsgroup called comp.lang.fortran for discussions on the language; its signal-to-noise ratio is higher than most, and some real experts frequently contribute (e.g. past or present members of the committee revising the Fortran standard, a Fortran textbook writer, and senior members of major computer companies' Fortran teams.)"

Gary Scott

unread,
Jul 13, 2017, 8:32:25 PM7/13/17
to
higher? I think the S/N ratio is much lower than most on clf.

Jos Bergervoet

unread,
Jul 14, 2017, 2:12:34 PM7/14/17
to
On 7/14/2017 2:32 AM, Gary Scott wrote:
> On 7/13/2017 4:27 PM, jfh wrote:
..
..
>> I'm also glad to see NAG here. My notes for f77->f95 conversion say
>> "There is a newsgroup called comp.lang.fortran for discussions on the
>> language; its signal-to-noise ratio is higher than most, and some real
>> experts frequently contribute (e.g. past or present members of the
>> committee revising the Fortran standard, a Fortran textbook writer,
>> and senior members of major computer companies' Fortran teams.)"
>
> higher? I think the S/N ratio is much lower than most on clf.

Do you think the signal content is particularly low or the noise
is high?! Anyhow, with the right coding, even a negative S/N ratio
does not prohibit information transfer!
<http://en.wikipedia.org/wiki/Turbo_code>

--
Jos

Jos Bergervoet

unread,
Jul 14, 2017, 2:24:09 PM7/14/17
to
On 7/13/2017 2:13 PM, paul.rich...@gmail.com wrote:
> On Thursday, 13 July 2017 11:31:22 UTC+1, Themos Tsikas wrote:
>> Well,
>>
>> "A whole array is a named array or a structure component whose final part-ref is an array component name; no subscript list is appended."
>>
>> Since i is a scalar component, t1%i cannot be whole array and LBOUND specifies
>>
>> Case (i): If DIM is present, ARRAY is a whole array, and either ARRAY is an assumed-size array of rank DIM or dimension DIM of ARRAY has nonzero extent, the result has a value equal to the lower bound for subscript DIM of ARRAY. Otherwise, if DIM is present, the result value is 1.
>>
>> Case (ii): LBOUND (ARRAY) has a value whose i^th element is equal to LBOUND (ARRAY, i), for i = 1, 2,. . . , n, where n is the rank of ARRAY. LBOUND (ARRAY, KIND=KIND) has a value whose i^th element is equal to LBOUND (ARRAY, i, KIND), for i = 1, 2, . . . , n, where n is the rank of ARRAY.
>>
>> so, LBOUND(t1%i,1) = 1 and LBOUND(t1%i) = the array [1]
>>
>> That is my current understanding of it.
...
> Thanks to you that is my understanding too and why I now think that gfortran had it wrong and the others were right.

But gfortran had it right if you agree with Themos!
Version 4.8.1 gives 1 for lbound(t1%i), just like
described above. So what problem are you referring to?
Are there newer gfortran version that actually print 0?

--
Jos

FortranFan

unread,
Jul 14, 2017, 2:59:36 PM7/14/17
to
On Friday, July 14, 2017 at 2:24:09 PM UTC-4, Jos Bergervoet wrote:

> ..
>
> But gfortran had it right if you agree with Themos!
> ..

Read this post upthread, please:
https://groups.google.com/d/msg/comp.lang.fortran/QbMFCNP_DuY/2eg_o4WHAAAJ

Gary Scott

unread,
Jul 14, 2017, 9:28:29 PM7/14/17
to
noise is lower

Jos Bergervoet

unread,
Jul 16, 2017, 2:25:34 PM7/16/17
to
That post confirms what Themos wrote (that LBOUND(t1%i) = 1)
and that gfortran had that one right!

It also shows that gfortran did mess up, but on two other
things (so thanks for the pointer, Fortranfan).

--
Jos

David Thompson

unread,
Aug 21, 2017, 2:46:11 PM8/21/17
to
On Tue, 11 Jul 2017 16:41:25 -0700 (PDT), herrman...@gmail.com
wrote:
<snip>
> I don't know that it was intentional, but it always seemed
> to me that PL/I was designed to keep rules consistent.
>
> Some have been fixed by now. <snip>
> Another example, why no REAL variables for DO loops. Yes I know
> that they can cause problems for users, but that is for users
> to understand. Every other language that I can think of allows them.
> They were added in Fortran 77, and later removed, so it isn't
> likely that they are hard to implement. It adds one more
> restriction on users, and something else for compilers to check.
>
Pascal requires the 'for' var be 'ordinal' type (integer or enum which
includes char and bool), although that started as pedagogical which is
arguably a special case. I have a feeling other Wirth languages
followed suit but haven't used them myself.

Ada requires 'discrete' in the original 'for x in subrange' form,
although Ada12 adds a generalized 'for x in iteration' form intended
to handle arrays and opaque containers equally (much like Java for
(elem in array_or_container) -- surprise?) but which I _think_
(without actually trying) can be bent to handle real numbers.

0 new messages