Pointer to a page of a 3D array

Fortran produces a 2D pointer with different lower index bounds, depending on the syntax of the assignment. Consider:

real(4), target:: D(-10:10, -10:10)
read(4) pointer P(:,: ), Q(:,: )
P => D
Q => D(:,: )

P will have extents (-10:10, -10,10)
Q will have extents(1,21: 1:21)

Even though Q is pointed to the entire array D, the presence of dimension specification in the target D produces a pointer.with all lower index bounds of 1

I had a 3D array

real(4), target:: F(-10:-10, -10:10, 5)

I need to point to a particular 2D page of F and have the pointer maintain the array bounds (-10:10, -10:10). A simple pointer assignment such as

Q => f(:,:, n)

yields a pointer with the wrong array bounds and can be used in subsequent code. Does anyone know a way to accomplish this?

1 Like

A minus too many?

Mike

Welcome, @dldl, to the forum. See the following solution to this bounds problem:

Q(-10:10,-10:10) => F(:,:,1)

to get at the first “plane” with the right lower/upper bounds. Note, that if you pass the array/pointer to the array to a subroutine or function, the lower bound reverts to 1 again.

I’ve tweeted

A pointer can be used to map an array to an array of the same type and size but a different shape, rank, or bounds, for example

real, target  :: y(6)
real, pointer :: p(:,:)
p(-1:1,1:2) => y ! map y(:) to 3x2 matrix with LB -1, 1

with sample program

program pointer_remap_array
implicit none
integer, parameter :: n = 6
integer, target    :: a1d(n)
integer, pointer   :: a2d(:,:)
integer            :: i,i1,iter
a1d = [(10*i,i=1,n)]
print "('a1d =',/,*(i4))",a1d
do iter=1,2
   print*
   if (iter == 1) then 
! map a1d to array with lower bounds 1, 1
      a2d(1:3,1:2) => a1d
      print*,"a2d(1:3,1:2) => a1d"
   else
! map a1d to array with lower bounds -1, 1
      a2d(-1:1,1:2) => a1d 
      print*,"a2d(-1:1,1:2) => a1d"
   end if
   print "(' shape(a2d) =',*(1x,i4))",shape(a2d)
   print "('lbound(a2d) =',*(1x,i4))",lbound(a2d)
   print "('ubound(a2d) =',*(1x,i4))",ubound(a2d)
   print "(/,'a2d =')"
   do i1=lbound(a2d,1),ubound(a2d,1)
      print "(*(i4))",a2d(i1,:)
   end do
   ! changes to pointer affect the pointee
   if (iter == 2) a2d(-1,1) = a2d(-1,1)*10
end do
print "(/,'a1d =',/,*(i4))",a1d
end program pointer_remap_array
! output:
! a1d =
!   10  20  30  40  50  60
!  
!  a2d(1:3,1:2) => a1d
!  shape(a2d) =    3    2
! lbound(a2d) =    1    1
! ubound(a2d) =    3    2
! 
! a2d =
!   10  40
!   20  50
!   30  60
!  
!  a2d(-1:1,1:2) => a1d
!  shape(a2d) =    3    2
! lbound(a2d) =   -1    1
! ubound(a2d) =    1    2
! 
! a2d =
!   10  40
!   20  50
!   30  60
! 
! a1d =
!  100  20  30  40  50  60
1 Like

@dldl ,

Welcome to this forum, hopefully you find the comments on this forum also useful to build on what you posted yesterday at the Intel Fortran forum in this thread where I advised you to also post here.

Re: your question “A simple pointer assignment such as … yields a pointer with the wrong array bounds,”

  • know that with pointer assignments to array slices of a target, the shape and the bounds is what the coder wants it to be.

Consider again the simple example I showed you at the Intel forum, here is a modified one and look at the line for the pointer assignment:

   integer, target :: F(-2:2,-2:2,2)
   integer, pointer :: P(:,:)
   F = reshape( source=[( i, integer :: i = 1, size(F) )], shape=shape(F) ) 

   P(-2:2,-2:2) => F(:,:,2)  !<-- coder can specify the bounds and the shape of LHS

   print *, "lbound(P,dim=1) = ", lbound(P,dim=1), "expected is -2"
   print *, "lbound(P,dim=2) = ", lbound(P,dim=2), "expected is -2"
   print *, "P(-1,1) = ", P(-1,1), "expected is ", F(-1,1,2)
end
C:\temp>ifort /standard-semantics t.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.6.0 Build 20220226_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.

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

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

C:\temp>t.exe
 lbound(P,dim=1) =  -2 expected is -2
 lbound(P,dim=2) =  -2 expected is -2
 P(-1,1) =  42 expected is  42

Ah! Just what I needed. Many thanks.