Just say no to non-default lower bounds

I am officially declaring all use of non-default array bounds as evil forevermore. If one is writing code strictly for one’s own use and if you’re confident that you won’t need to modify the code ever again, maybe it’s ok, but if you have to return to the code years later or if anyone other than you has to work with it, then I think the byzantine rules around when the bounds will or won’t be preserved are sufficiently complicated and nuanced as to make seemingly simple code modifications problematic. I first noticed this issue four years ago when a related bug essentially killed my chances of delivering on a project just weeks before the deadline because of all the time lost in debugging a related issue. I henceforth abandoned non-default bounds and wrote some code that generates a table describing a few cases mostly as a cheat sheet for myself if I ever encountered non-default bounds again. The table is here. The code that generates the table is described and posted here. But now that I’m working with some inherited code with non-default bounds, I just realized for the first time four years later that the first row in the table is only sometimes true. The code that I just wrote to demonstrate the problem that I just discovered is as follows:

% cat bounds.f90 
program main
 implicit none
 integer, allocatable :: a(:), b(:), c(:), d(:)
 a = [2,2,2]
 allocate(b(0:size(a)-1)) ! size(b) == size(c)
 allocate(c(0:1)) ! size(c) < size(a)
 b = a
 c = a
 print *, lbound(a), ubound(a)
 print *, lbound(b), ubound(b)
 print *, lbound(c), ubound(c)
end program
% gfortran bounds.f90 
% ./a.out
           1           3
           0           2
           1           3

Notice that after the assignment b=a , the array b retains its lower bound of 0 because it was already correctly sized for the assignment and therefore didn’t need to be reallocated during the assignment. By contrast, the assignment c=a resets the lower bound of c to 1 because c was initially too small to hold a copy of a so the assignment reallocates c and gives it the default lower bound of 1 in the process. So b=a really does put an exact copy of a into b – bounds and all – whereas c=a only copies the values and shape but not the bounds.

I imagine there could be plenty of people who were already aware of such rules so a great deal of this comes down to habits. If one is used to coding in a certain way but is unaware of the implicit assumptions involved in what they are doing, it can be a painful process when discovering the cases in which those assumptions are violated. I fear for anyone who is new to contributing to a code that uses non-default array bounds.

7 Likes

This is not a feature I have ever used intentionally, and seems to be of dubious benefit. I’m not convinced that a language having the ability to change its array indexing scheme is particularly useful, especially if it’s not preserved in all cases…

@rouson’s example to me is as much an issue with allocate on assignment as it is with bounds. That’s why I’m very careful to not let allocate on assignment occur when I don’t really need it. I agree though that if you don’t know what your are doing and don’t take great care its best not to change from the default bounds. One exception I’ve used is with dummy arguments in a routine I’m trying to translate from C code. I will change the dummy argument bounds to something like a(0:). Of course if we need to blame someone for this mess, then lets blame the computer science community who for some reason never learned that when you count things you start with 1 not 0.

2 Likes

I have found arbitrary lower array bounds extremely useful on many occasions, and a strength of the language from my perspective. It can significantly simplify index calculations that would otherwise create other kinds of bugs. The only tricky cases I encountered were with allocatable arrays.

1 Like

I am genuinely curious which occasions you are actively looking to change array bounds? Mentioned upthread was starting at 0 to do easier translation of algorithms from (almost every other programming language).

There are also situations involving dummy arguments where sometimes the actual argument bounds are retained and sometimes not.

I don’t know the answer to these complications. I certainly do not advocate that all arrays must have lower bounds of 1. There are too many situations where it is better for the bounds to fit the problem that is being solved, rather than to have a fixed lower bound.

There is also this ambiguous situation. Your compiler chose to keep the original bounds and (presumably) the original storage of b(:). It is not required to do that, it could choose to reallocate this array too. The fortran standard allows either behavior. If you want to force the original storage to be retained, then the assignment should be b(:)=a; reallocation is not allowed in that case.

4 Likes

In my experience, I’ve only used non-default bounds for two purposes. The first is the one I mentioned above because it makes translating C indexing to Fortran a lot easier. Another is in Finite Volume or Finite Difference CFD codes where you have a halo of “ghost cell” or boundary condition cells around your main computational grid. For a grid with say 50 cells where you have two layers of halo cells appended in each direction, allocating say the x dimension to x(-1:52) greatly simplifies accessing data in the ghost cells.

4 Likes

Non-default array bounds are an elegant approach to global (as opposed to local) indexing in parallel domain decomposition. I think I’ve only used this feature for that purpose, and I’d use it again (in addition to Richard’s great point about halo cells). It’s unfortunate that coarrays don’t support different bounds across images, but I understand that it would complicate things at both language and implementation levels.

5 Likes

The rule that I have kept in mind by experience is that array bounds are never transferred, except when both sides involved are allocatable. I can only remember two such cases where bounds are transferred, in the language, 1) passing an allocatable actual argument to an allocatable dummy argument, 2) in move_alloc() intrinsic.

1 Like

It looks like there are more cases, than I mentioned above, for example with assignment.

Bounds are also transferred with pointer assignment and with pointer dummy arguments, although in these cases the syntax allows the lower bound to be specified directly too. With allocatables, I think the lower bound can be specified directly only with an allocate() statement.

1 Like

Damian’s table is an excellent summary. I reproduce it here for the sake of better visibility:

Bounds-preserving Fortran feature
True intrinsic assignment
True source allocation without specified bounds
True allocatable, assumed-shape dummy argument
True associate name
False non-allocatable, assumed-shape dummy argument
False function result
2 Likes

I use it for

  1. MPI ranks, which start at 0 because the implementation is in C. In that case, don’t forget to loop only to worldsize-1.
  2. base64 encoding where it simplifies some of the math.
  3. Polynomial evaluation where the constant term has zero order

For indexing operations that involve modulo operations it can also be handy.

1 Like

I rarely use non-default lower bounds, but I when I do, they make things somewhat “easier”. Cubic splines comes in mind, where most books/papers tabulate interpolation points as x0, x1, ... , xn. Another case is Runge-Kutta-something algorithms, where you have vectors of coefficients in a Butcher’s tableau, such as C(2), C(3), etc, and C(1) makes no sense. Not that it’s hard to implement all that in Fortran code without non-default array bounds, but it’s still a convenience to be able to define arrays with lower bound being 0, or 2, or whatever.

Granted, it’s not a feature many people will want desperately, but it’s good to be there for whenever it’s “needed”. In the end, if someone doesn’t like it, then they shouldn’t use it.

As was already mentioned above, non-default array bounds make life so much easier when programming parallel grid methods (FD/FV /DG …) and are widely used in such codes. This is one of the Fortran language features that I miss in Python and Matlab.

I maintain a program to calculate US and state income tax liability from taxpayer data for any year since 1960 (1977 for state tax). I keep features of the tax systems in arrays indexed by year. So I have lots of arrays with a lower bound of 1960 or 1977. It is a really nice feature of Fortran that I can do that. Of course, Fortran is Turing complete without that feature, so it is unnecessary, but the same could be said for every new feature since Fortran II.

2 Likes

In signal processing arbitrary lower bounds are quite useful. A zero phase signal is typically stored in a a(-n:n) array, an anticausal filter in a(-m:0), etc…

5 Likes

I may be misunderstanding something, but doesn’t c=a preserve bounds, rather than “default bounds (= 1-based)” are used for c? (Here, my meaning of “preserve” is that the bounds of an array on RHS is copied to that on LHS.) I’m wondering what happens for other compilers.

program main
    implicit none
    integer, allocatable :: a(:), b(:), c(:)

    !! Realloc on assignment with default bounds.
    a = [2,2,2]                  !! index =  1..3, size = 3

    !! Sourced allocation with explicit bounds.
    allocate( b( -1:1 ), source=1 )  !! index = -1..1, size = 3
    allocate( c(  0:1 ), source=0 )  !! index =  0..1, size = 2

    print *, "before:"
    print *, "a:", lbound(a), ubound(a), "  val =", a
    print *, "b:", lbound(b), ubound(b), "  val =", b
    print *, "c:", lbound(c), ubound(c), "  val =", c

    b = a + b
    c = b

    print *, "after:"
    print *, "b:", lbound(b), ubound(b), "  val =", b
    print *, "c:", lbound(c), ubound(c), "  val =", c
end program

$ gfortran-11 test.f90 && ./a.out

 before:
 a:           1       3   val =       2       2       2
 b:          -1       1   val =       1       1       1
 c:           0       1   val =       0       0
 after:
 b:          -1       1   val =       3       3       3
 c:          -1       1   val =       3       3       3
1 Like

I believe you can see the intrinsic assignment as something like:

if (allocated(c) .and. (size(c)==size(a))) then 
   c(:) = a ! do not change c bounds
else
  if (allocated(c)) deallocate(c)
  allocate(c(lbound(a,1):ubound(a,1)),source=a)
endif
2 Likes

Yes, that was my understanding, so a bit confused about the code in the first post… (possibly, does it mean that this behavior is not desirable?) (BTW, I also think the rules are pretty complicated and error-prone.)

1 Like