I have tagged this as “compilers” but it could be a hole in the language spec. Consider the appended program, in that with gfortran
the reshape
and pack
result in the lower bound of the assigned-to array to be 0 in the x
to x
and x
to y
cases, but 1 for in the x
to z
case; I would expected the lower bound to be 1 in every case.
Put another way my impression is that at least in gfortran
if reshape
and pack
do not require a copy the lower bound of the assigned-to array is not changed, but it is changed if the operation requires a copy.\
Is this is according to the language specification? Is this a bug in the compiler?
program main
character(len=*), parameter:: f1 = "(A,I2,I2,A,A16,$)"
character(len=*), parameter:: f2 = "(A,I2)"
integer, allocatable:: x(:)
integer, allocatable:: y(:)
integer, allocatable:: z(:)
block
integer:: nbc
integer,dimension(-1:1):: b,c
nbc = size(b)+size(c)
b = 2
c = 3
allocate(x(0:nbc-1))
allocate(y(0:nbc-1))
allocate(z(2:nbc))
x(:) = [b,c]; call px("x(:)=[b,c]")
x = [b,c]; call px("x=[b,c]")
print *
end block
x = [x]; call px("x=[x]")
x = pack(x,.true.); call px("x=pack(x)")
x = reshape(x,[size(x)]); call px("x=reshape(x)")
x = reshape(x(:),[size(x)]);call px("x=reshape(x(:))")
x = reshape([x],[size(x)]); call px("x=reshape([x])")
print *
y = [x]; call py("y=[x]")
y = pack(x,.true.); call py("y=pack(x)")
y = reshape(x,[size(x)]); call py("y=reshape(x)")
y = reshape(x(:),[size(x)]);call py("y=reshape(x(:))")
y = reshape([x],[size(x)]); call py("y=reshape([x])")
print *
z = [x]; call pz("z=[x]")
z = pack(x,.true.); call pz("z=pack(x)")
z = reshape(x,[size(x)]); call pz("z=reshape(x)")
z = reshape(x(:),[size(x)]);call pz("z=reshape(x(:))")
z = reshape([x],[size(x)]); call pz("z=reshape([x])")
print *
z = [1,2,3]; call pz("z=[1,2,3]")
z(:) = [4,5,6]; call pz("z(:)=[4,5,6]")
print *
deallocate(z)
deallocate(y)
deallocate(x)
contains
! The array to print must not be passed as an argument
subroutine px(m)
character(len= *), intent(in):: m
print f1,'bounds: ',lbound(x),ubound(x)," ",m; print *,"; x: ",x
end subroutine px
subroutine py(m)
character(len= *), intent(in):: m
print f1,'bounds: ',lbound(y),ubound(y)," ",m; print *,"; y: ",y
end subroutine py
subroutine pz(m)
character(len= *), intent(in):: m
print f1,'bounds: ',lbound(z),ubound(z)," ",m; print *,"; z: ",z
end subroutine pz
end program main