Allocatable arrays and lower bounds

A question on the Fortran newsgroup started a discussion on what is and is not allowed syntax for setting lower bounds on an allocatable array, and how that would be affected by the LHS using X(:)= versus X= and we disagreed even after reading the 2018 standard so we “asked the compilers” and got three different results with three compilers :>. At least we are not the only ones confused. Wondering if anyone agrees or disagrees with the following minimal code being standard (f2018) and what the results should be. The idea is how you can change the lower bound to a value other than one
on an allocatable array and when or if the lower bound gets reset on an assignment:

program testit
integer, allocatable :: X(:)
integer,dimension(-2:2) :: b, c
integer :: isize
! allocate it
isize=size(b)+size(c)
allocate(x(0:isize-1))
x(:)=[b,c];               call show()
x=[b,c];                  call show()
! what should it change to?
x(:)=[11,22,33];          call show()
x=[1,2,3];                call show()
x(1:)=[10,20];            call show()

!oops -- apparently not legal but wish it was (thought it was -- need to look this one up). 
!X=[integer,dimension(0:isize-1) :: b,c];  call show()

contains
subroutine show()
   write(*,gen)X,'bounds',lbound(x),ubound(x)
end subroutine show
end program testit

typing this not pasting it, so forgive any inadvertent syntax errors. What I hope to have typed compiled and ran without warning on all the compilers with default flags (at least).

2 Likes

dimension(-2,2) makes b and c have zero size. Did you mean (-2:2)?

Yes. Corrected example. Thanks.

So if the allocate set the lower bounds to zero, x(:slight_smile: should not change that, but the next x= keeps it the same size and type. One compiler changed LBOUND to 1, another left it at 0. Another left it at 0 on this one, but when the size changed it to 1; but the other one that left it at 0 left it at 0 again. So I agree that the first x(:)= should leave it at 0; after seeing the compiler results not sure when the size and type is not changed in the first x=. At least at first glance, it seemed one compiler left it at 0 once set in the allocate() until explicitly deallocated; another left it at 0 unless the size changed, the other changed it to 1 on the first X= even though type and size had not changed. So it the LBOUND should have changed on the first x= ?

So size can change and the bound should stay the same. Trying to sort out the bug reports to file. So with gfortran(9.2, will try a newer one when I get the chance) the X=[b,c] kept the bounds at 0, but X=[b,c,b] which changed the size but not the type or shape set the lower bound to 1. Wrong, I believe (now). ifort for one, left it at 0. Note that both changed UBOUND so the size was 15 for the case where LBOUND changed, so gfortran bounds became 1:15, ifort bounds became 0:14.

Ahh, OK. Need to use “shape” as defined in the standard.

Noticed it is often used in reference to “programming environment” or something akin to that. Definitely confusing for such a word with a well-established common meaning. That might show how far back the origins of the standard go. Before computers a “processor” meant “that which processes something”; sort of like not too long before the origins of Fortran a “computer” was generally a person.

Probably one of the reasons I personally avoid using anything but default bounds is some of this behavior. Would be nice if you could declare one bound fixed for an allocatable array in a declaration or allocate statement. I actually prefer the ifort behavior. Something like

integer,allocatable  :: arr1(LBOUND:),  arr2(:UBOUND)

where you could set one end and it would stay fixed unless explicitly deallocated.

1 Like

Indeed, just like @urbanjost and @pmk said, I also mostly just use the default lower bounds because it’s confusing when the lower bound gets lost. It’s unfortunate.

Is there a way to improve the situation at this point? Or is it too late.

1 Like

This doesn’t look accurate; to me, unless I’m misunderstanding the standard, there’s not much of a mystery e.g., section 8.5.8.4 Deferred-shape array explains the situation with objects that have POINTER and ALLOCATABLE attributes including when said objects are dummy arguments.

37 5 The bounds of each dimension of an associated array pointer, and hence its shape, may be specified

40 • if it is a dummy argument, by argument association with a nonpointer actual argument or an associated
41 pointer effective argument.

Consider the simple-minded example below:

module m
contains
   subroutine sub( a )
      integer, pointer, intent(in) :: a(:)
      print *, "In sub: lbound(a) = ", lbound(a, dim=1)
   end subroutine 
end module
   use m
   integer, target :: x(-2:2)
   x = 0
   call sub( x )
end

It’ll be a struggle to find a compiler that doesn’t the output the following and should there be one, the case is a reproducer toward their immediate bug resolution task:

C:\Temp>ifort /standard-semantics a.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.2.0 Build 20210228_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.28.29337.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:a.exe
-subsystem:console
a.obj

C:\Temp>a.exe
In sub: lbound(a) = -2

C:\Temp>

1 Like

It seems very cumbersome and inconsistent to have to have to use a pointer or pass the bounds as arguments. Has there ever been any discussion of something similiar to INTENT(), as in perhaps something called BOUNDS() that would let you specify that dummy arguments have their bounds retained? So instead of something like

module m
contains
   subroutine sub( a ,b,c,i,j)
      integer, pointer, intent(in) :: a(:)
      integer,intent(in) :: b(:)
      integer,intent(in) :: c(i:j)
      print *, "In sub: lbound(a) = ", lbound(a, dim=1)
      print *, "In sub: lbound(b) = ", lbound(b, dim=1)
      print *, "In sub: lbound(c) = ", lbound(c, dim=1)
   end subroutine 
end module
   use m
   integer, target :: x(-2:2)
   integer         :: y(-2:2)
   x = 0
   call sub( x ,y,y,lbound(y,dim=1),ubound(y,dim=1))
end

you could have

integer,intent(in),bounds(in) :: c

and not have to pass the bounds? Or is there another way I have missed?

2 Likes

An array being passed could be a whole array x(0:4), or an array section x(2:4), or an array section with a stride other than 1 x(2:4:2), or an array with a vector subscript x([2,4,3]). It’s simple to remember that the array when passed to a procedure has lower bound 1, and this allows more modularity. The procedure called says “you gave me an array with N reals, that I will index from 1 to N. How you dimensioned them in the caller is not my concern.” The array can be made a component of a derived type if one wants to pass it while preserving the bounds.

Yes, since the 1980s toward the eventual publication of the next revision: so, Fortran 90 onwards, the optional [ lower-bound ] in the assumed-shape array dummy argument has allowed that to be a specification-expr that then allows code like the following to be standard-conforming since Fortran 90:

module m
contains
   subroutine sub( a, lb )
      integer, intent(in) :: lb
      integer, intent(in) :: a(lb:)
      print *, "In sub: lbound(a) = ", lbound(a, dim=1)
   end subroutine 
end module
   use m
   integer :: x(-2:2)
   x = 0
   call sub( x, lbound(x, dim=1) )
end

C:\Temp>f90 a.f90
Compaq Visual Fortran Optimizing Compiler Version 6.6 (Update C)
Copyright 2003 Compaq Computer Corp. All rights reserved.

a.f90
Microsoft (R) Incremental Linker Version 6.00.8447
Copyright (C) Microsoft Corp 1992-1998. All rights reserved.

/subsystem:console

/out:a.exe

C:\Temp>a.exe
In sub: lbound(a) = -2

C:\Temp>

1 Like

Yes, this is how you pass in lower bounds currently:

But it seems inconsistent to me, since the upper bound is implicit, but the lower bound must be passed in as the lb argument. Does anyone know what the motivation for this is? It would feel natural to just do:

subroutine sub(a)
integer, intent(in), bounds(in) :: a(:)
print *, "In sub: lbound(a) = ", lbound(a, dim=1)
end subroutine 

Bounds, plural, implies that the lower and upper bounds are preserved. So if x(-2:4) is passed you want the bounds to be -2,4 in the called subroutine. What if x(4:-2:-2) or x([2,1,3]) is passed? I suggested earlier that one should pass a derived type with an array component if one wants the exact bounds preserved.

Reopening after 10 months, but here is something I just learned: the bounds of an allocatable array intent(in) or intent(in out) dummy argument are the same as those of the actual argument in the caller. Here is a short code showing what the bounds are for an
(1) assumed-shape dummy argument, declared as (:) – lbound = 1
(2) assumed-shape dummy argument, declared as (0:) – lbound = 0
(3) allocatable, intent(in) or intent(in out) argument – lbound = lbound of actual argument in caller
(4) assumed-shape dummy argument, declared as (lb:), where lb is an argument – lbound = lb

module m
implicit none
character (len=*), parameter :: fmt = "(a35,*(1x,i4))"
contains
!
subroutine print_bounds(x1,x2,x3,x4,lb)
integer, intent(in)              :: lb
real   , intent(in)              :: x1(:)
real   , intent(in)              :: x2(0:)
real   , intent(in), allocatable :: x3(:)
real   , intent(in)              :: x4(lb:)
print "(a)","entered print_bounds"
print fmt,"x1 bounds =",lbound(x1),ubound(x1)
print fmt,"x2 bounds =",lbound(x2),ubound(x2)
print fmt,"x3 bounds =",lbound(x3),ubound(x3)
print fmt,"x4 bounds =",lbound(x4),ubound(x4)
end subroutine print_bounds
end module m
!
program test_bounds
use m
real, allocatable :: x(:)
allocate (x(-2:3))
print fmt,"x bounds =",lbound(x),ubound(x)
call print_bounds(x,x,x,x,8)
end program test_bounds
! output:
!                          x bounds =   -2    3
! entered print_bounds
!                         x1 bounds =    1    6
!                         x2 bounds =    0    5
!                         x3 bounds =   -2    3
!                         x4 bounds =    8   13
3 Likes

Your variable x3 has rather peculiar properties, one of which you have described.

Since you specified INTENT(IN) for x3, its allocation status cannot be altered in the subroutine, so the rather odd effect/purpose of specifying the attribute ALLOCATABLE in the subroutine is to preserve/transmit the bounds with which it was allocated in the caller!

3 Likes

Allocatable dummy parameters always receive the descriptor of the actual argument, including the bounds (if allocated). This holds also for array pointers. Not for assumed shape arrays. See sect. 6.9 of MFE 2018.
Edit: I’ve tried to find the relevant paragraph in the Standard, to no success :frowning:

1 Like

Interesting, I didn’t know that either. So my “proposal” from above:

subroutine sub(a)
integer, intent(in), bounds(in) :: a(:)
print *, "In sub: lbound(a) = ", lbound(a, dim=1)
end subroutine 

Can in fact be written as:

subroutine sub(a)
integer, intent(in), allocatable :: a(:)
print *, "In sub: lbound(a) = ", lbound(a, dim=1)
end subroutine 

But it only works for allocatable arrays.

1 Like

It does take some digging. The relevant words are in 8.5.8.4p4 (Deferred shape array):

4 The bounds of each dimension of an allocated allocatable array are those specified when the array is allocated or, if it is a dummy argument, when it is argument associated with an allocated effective argument.

In your example, x3 is allocatable so the bounds are that of the “associated effective argument”. (p5 has related words for a POINTER dummy argument.)

x1, however, is an assumed-shape array, covered by 8.5.8.3 (emphasis mine):

3 The extent of a dimension of an assumed-shape array dummy argument is the extent of the corresponding dimension of its effective argument. If the lower bound value is d and the extent of the corresponding dimension of its effective argument is s, then the value of the upper bound is s + d − 1. If lower-bound appears it specifies the lower bound; otherwise the lower bound is 1.

1 Like