This feature will be more useful if rank is allowed to be allocatable. For example, it can be used for generalizing ‘reduce/fold’ functions as shown below. (I have left some details for brevity.)
pure function general_reduce(binary_op,x,dim) result (r)
real ,intent(in) :: x(..)
integer,intent(in) :: dim
real,allocatable :: r(..)
integer :: i, x_shape(RANK(x)), idx(RANK(x)), idr(RANK(x)-1)
interface
real pure function binary_op(x,y)
real,intent(in) :: x, y
end function binary_op
end interface
x_shape = SHAPE(x)
r = ALLOCATE(r([x_shape(:dim-1),x_shape(dim+1:)]))
do i = 1,PRODUCT(x_shape)
idx = counter_to_tuple(i)
idr = [idx(:dim-1),idx(dim+1:)]
if(idx(dim)==1) then
r(@idr) = x(@idx)
else
r(@idr) = binary_op(r(@idr),x(@idx))
end if
end do
contains
pure function counter_to_tuple(n) result (t)
! find index tuple from 1D counter. e.g. 1->(1,1,1), 2->(2,1,1) etc
integer,intent(in) :: n
integer :: t(RANK(x))
...
end function counter_to_tuple
end function general_reduce
One can still achieve this Fortran by:
a) Using PACK and RESHAPE. But, this will require memory duplication.
b) Defining an array type. This can be as close to the proposed syntax as x.AT.[1,2,1] etc.