Preserving non-default array bounds in dummy arguments

I want to pass an array with non-default bounds to a subprogram and to somehow make the body of the subprogram “see” those bounds. Here’s a quick program to show why this doesn’t “just work”.

program test
implicit none

integer :: a(-3:6)

print *, lbound(a, 1), ubound(a, 1)  ! -3, 6
print *, bnds(a)                     ! 1, 10

contains

function bnds(x)
  integer, intent(in) :: x(:)
  integer :: bnds(2)
  bnds(1) = lbound(x, 1)
  bnds(2) = ubound(x, 1)
end function bnds

end program test

Basically, by declaring the dummy argument assumed shape x(:), the body of the function must be written as if the lower bound is 1. I know that if I instead declare

function bnds(x, lbd) 
  integer, intent(in) :: lbd
  integer, intent(in) :: x(lbd:)
  integer :: bnds(2)
  ! ...
end function bnds

and call bnds(x, lbound(x, 1), then it would produce the expected behavior. This works, but feels clumsy. An alternative is to wrap the array in a derived type, which will preserve the bounds on entry to procedures. That has the downside of making the array more difficult to use.

I wonder if I have overlooked some other programming approach or language feature for passing non-default bounds information to procedures.

3 Likes

You can make the array with non-default bounds a module variable and USE it in procedures.

@nshaffer,

Not sure if this is something you’ve considered and dismissed, but a programming approach you can consider is to “parametrize” your code with named constants toward the lbound(s) and sizes of your array(s):

program test
   implicit none

   integer, parameter :: lbd_a = -3
   integer, parameter :: size_a = 10
   integer :: a( lbd_a : size_a+lbd_a-1 )

   print *, lbound(a, 1), ubound(a, 1)  ! -3, 6
   print *, bnds(a)                     ! -3, 6 now; default 1, 10

contains

   function bnds(x)
      integer, intent(in) :: x(lbd_a:)
      integer :: bnds(2)
      bnds(1) = lbound(x, 1)
      bnds(2) = ubound(x, 1)
   end function bnds

end program test

Oh, nice! I didn’t know that property of pointers. Indeed, if I revise the example to

program test
implicit none

integer, pointer :: a(:)
allocate (a(-3:6))

print *, lbound(a, 1), ubound(a, 1)  ! -3, 6
print *, bnds(a)                     ! -3, 6

contains

function bnds(x)
  integer, pointer, intent(in) :: x(:)
  integer :: bnds(2)
  bnds(1) = lbound(x, 1)
  bnds(2) = ubound(x, 1)
end function bnds

end program test

Then the function bnds “sees” the lower and upper bounds of its actual argument.

I agree declaring the bounds as parameters is the cleanest and safest approach when the bounds are known at compile time, as in this minimal example. That’s unfortunately not the case in the application at hand.

That’s a nice touch! Thanks again for this tip. Pointer semantics (especially across procedure boundaries) have always been a weak point for me…

You can also declare the array to be allocatable. This avoids some of the optimization issues with pointers.