更改Fortran中的数组维度

17

在Fortran 90/95中,将数组传递给子程序基本上有两种方法:

PROGRAM ARRAY
INTEGER, ALLOCATABLE :: A(:,:)
INTEGER :: N
ALLOCATE(A(N,N))
CALL ARRAY_EXPLICIT(A,N)
! or
CALL ARRAY_ASSUMED(A)
END PROGRAM ARRAY

SUBROUTINE ARRAY_EXPLICIT(A,N)
INTEGER :: N
INTEGER :: A(N,N)
! bla bla
END SUBROUTINE ARRAY_EXPLICIT

SUBROUTINE ARRAY_ASSUMED(A)
INTEGER, ALLOCATABLE :: A(:,:)
N=SIZE(A,1)
! bla bla
END SUBROUTINE ARRAY_ASSUMED

在第二种情况下,通常需要使用模块来获得显式接口。

从FORTRAN77开始,我习惯于使用第一种选择,并且我读到如果传递整个数组,则这也是最有效的方法。

显式形状的好处是我还可以调用子例程并将数组视为向量而不是矩阵:

SUBROUTINE ARRAY_EXPLICIT(A,N)
INTEGER :: N
INTEGER :: A(N**2)
! bla bla
END SUBROUTINE ARRAY_EXPLICIT

我想知道是否有一种好的方法可以使用第二个假定形状接口来完成这种操作,而不需要复制它。


"不复制它。" 不复制什么? - Wildcat
2
我认为@steabert的意思是在原地改变数组的形状,而不是将其复制到一个一维数组中。 - M. S. B.
感谢 @M. S. B. 的澄清,那就是我想表达的意思。所以不是下面提到的 reshape 内在解决方案。 - steabert
1
@ M. S. B. 我就猜到了。那么重新塑造内在并不是一个解决方案。嗯,我认为这件事情在很大程度上取决于故事中的“!bla,bla”部分。=)你总是可以使用循环将你的二维数组迭代为一维数组。 - Wildcat
1
@kemiisto,没错,你总是可以控制如何索引这个东西,但我想知道这种“手动”处理是否是唯一的方法。比如说,我有一个子程序接受一个NxN矩阵,而我想传递的矩阵最容易使用4个索引循环在MxMxMxM形状上填充,那么我可以优雅地使用一个显式形状的虚拟参数。 - steabert
6个回答

13

参考RESHAPE内置函数,例如:

http://gcc.gnu.org/onlinedocs/gfortran/RESHAPE.html

或者,如果您想避免复制(在某些情况下,优化编译器可能能够进行重塑而不复制,例如,如果RHS数组之后没有被使用,但我不会指望它),从Fortran 2003开始,您可以使用bounds remapping将指针分配给不同秩的目标。例如,类似于以下内容:

program ptrtest
  real, pointer :: a(:)
  real, pointer :: b(:,:)
  integer :: n = 10
  allocate(a(n**2))
  a = 42
  b (1:n, 1:n) => a
end program ptrtest

1
+1,然而,你的例子在我的情况下不起作用,我使用ifort 11进行编译。报告的b的大小是2*n**2,是a大小的两倍。 - steabert
4
只有最新的Fortran 2003编译器才支持指针边界重映射这一特性。我认为gfortran 4.6但不是4.5,Intel 12但不是11.1。 - M. S. B.
@M. S. B. 谢谢!顺便说一下,确实是 ifort 12,而不是 11。但我仍然无法让它工作,非常奇怪。有人能用 ifort 12 检查一下吗? - steabert
我刚刚使用英特尔的Fortran编译器在Mac OSX 10.11.6 (ifort 17.0.7 20180403)上测试了上面的ptrtest程序。我一次编译时使用了以下标志:debug all -g -traceback -gen-interfaces -warn interfaces -check bounds -check arg_temp_created -check uninit -check all, noarg_temp_created。无论是哪种情况,都可以编译和运行而没有任何警告或错误。 - jvriesem

8
我正在尝试做同样的事情,看到了这个讨论。没有一种解决方案符合我的要求,但是我发现如果你正在使用当前fortran 90/95编译器通常支持的fortran 2003标准,可以使用iso_c_binding来重新调整数组而不复制数据。我知道这个讨论已经过时了,但是为了其他人的利益,我认为我应该添加我所想出的东西。
关键是使用函数C_LOC将数组转换为数组指针,然后使用C_F_POINTER将其转换回具有所需形状的fortran数组指针。使用C_LOC的一个挑战是,C_LOC仅适用于具有直接指定形状的数组。这是因为在fortran中,具有不完整大小规范的数组(即某些维度使用:)除了包含数组数据外还包括数组描述符。C_LOC不提供数组数据的内存位置,而是提供描述符的位置。因此,可分配的数组或指针数组不适用于C_LOC(除非您想要编译器特定的数组描述符数据结构的位置)。解决方法是创建一个子程序或函数,将数组作为固定大小的数组接收(大小实际上并不重要)。这会导致函数(或子例程)中的数组变量指向数组数据的位置,而不是数组描述符的位置。然后,您可以使用C_LOC获取指向数组数据位置的指针,并使用C_F_POINTER将此指针转换回具有所需形状的数组。必须将所需形状传递到此函数以与C_F_POINTER一起使用。以下是示例:
program arrayresize
  implicit none
  integer, allocatable :: array1(:)
  integer, pointer :: array2(:,:)

  ! allocate and initialize array1
  allocate(array1(6))
  array1 = (/1,2,3,4,5,6/)

  ! This starts out initialized to 2
  print *, 'array1(2) = ', array1(2)

  ! Point array2 to same data as array1. The shape of array2
  ! is passed in as an array of intergers because C_F_POINTER
  ! uses and array of intergers as a SIZE parameter.
  array2 => getArray(array1, (/2,3/))

  ! Change the value at array2(2,1) (same as array1(2))
  array2(2,1) = 5

  ! Show that data in array1(2) was modified by changing
  ! array2(2,1)
  print *, 'array(2,1) = array1(2) = ', array1(2)

contains

  function getArray(array, shape_) result(aptr)
    use iso_c_binding, only: C_LOC, C_F_POINTER
    ! Pass in the array as an array of fixed size so that there
    ! is no array descriptor associated with it. This means we
    ! can get a pointer to the location of the data using C_LOC
    integer, target :: array(1)
    integer :: shape_(:)
    integer, pointer :: aptr(:,:)

    ! Use C_LOC to get the start location of the array data, and
    ! use C_F_POINTER to turn this into a fortran pointer (aptr).
    ! Note that we need to specify the shape of the pointer using an
    ! integer array.
    call C_F_POINTER(C_LOC(array), aptr, shape_)
  end function
end program

1
这类似于janneb的回答:“自Fortran 2003以来,您可以将指针分配给不同秩的目标”,它还依赖于F2003功能,但更加复杂... - steabert

6

@janneb已经回答了关于RESHAPE的问题。RESHAPE是一个函数,通常在赋值语句中使用,因此会有复制操作。也许可以使用指针来避免复制。除非数组很大,否则最好使用RESHAPE。

我对显式形状数组比隐式形状数组更有效率持怀疑态度,就运行时间而言。我的倾向是使用Fortran >=90语言的特性,并使用隐式形状声明...这样你就不必麻烦地传递维度。

编辑: 我用ifort 11、gfortran 4.5和gfortran 4.6测试了@janneb的示例程序。其中只有gfortran 4.6能够正常工作。有趣的是,要将1-D数组连接到现有的2-D数组,需要Fortran 2008的另一个新特性——“连续”属性,至少根据gfortran 4.6.0 20110318如此。如果在声明中没有这个属性,就会出现编译时错误。

    program test_ptrs

   implicit none

   integer :: i, j

   real, dimension (:,:), pointer, contiguous :: array_twod
   real, dimension (:), pointer :: array_oned

   allocate ( array_twod (2,2) )

   do i=1,2
      do j=1,2
         array_twod (i,j) = i*j
      end do
   end do

   array_oned (1:4) => array_twod

   write (*, *) array_oned

   stop

end program test_ptrs

是的,我知道reshape函数,但正如你所说,对于巨大的数组来说存在问题,例如如果其中2个数组不适合内存。显式形状更有效的事实,我在这里http://software.intel.com/file/6397的第40-41页上读到了。你关于使用Fortran>=90的新功能是正确的,这就是为什么我想要为dummys使用假定形状并使用显式接口。这就是为什么我想知道关于重塑的事情,是否可以原地进行。 - steabert

1
你可以使用假定大小数组,但这可能意味着多层包装器程序。
program test

  implicit none

  integer :: test_array(10,2)

  test_array(:,1) = (/1,   2,  3,  4,  5,  6,  7,  8,  9, 10/)
  test_array(:,2) = (/11, 12, 13, 14, 15, 16, 17, 18, 19, 20/)

  write(*,*) "Original array:"
  call print_a(test_array)

  write(*,*) "Reshaped array:"
  call print_reshaped(test_array, size(test_array))

contains

  subroutine print_reshaped(a, n)
  integer, intent(in) :: a(*)
  integer, intent(in) :: n
  call print_two_dim(a, 2, n/2)
  end subroutine

  subroutine print_two_dim(a, n1, n2)
  integer, intent(in) :: a(1:n1,1:*)
  integer, intent(in) :: n1, n2
  call print_a(a(1:n1,1:n2))
  end subroutine

  subroutine print_a(a)
  integer, intent(in) :: a(:,:)
  integer :: i
  write(*,*) "shape:", shape(a)
  do i = 1, size(a(1,:))
      write(*,*) a(:,i)
  end do
  end subroutine

end program test

0

我正在使用ifort 14.0.3和2D到1D转换,我可以使用可分配数组来处理2D数组,使用指针数组来处理1D数组:

integer,allocatable,target :: A(:,:)
integer,pointer :: AP(:)

allocate(A(3,N))
AP(1:3*N) => A

正如 @M.S.B 所提到的,如果 A 和 AP 都具有指针属性,则我必须对 A 使用连续属性以保证转换的一致性。

0

Gfortran 对接口有点过于谨慎。它不仅想知道参数的类型、种类、秩和数量,还想知道形状、目标属性和意图(尽管我同意意图部分)。我遇到了类似的问题。

使用 gfortran,有三种不同的维度定义:
1. 固定
2. 变量
3. 假设大小

对于 ifort,类别 1 和 2 被视为相同,因此您可以在接口中将任何维度大小定义为 0,它就能正常工作。

program test

  implicit none

  integer, dimension(:), allocatable :: ownlist

  interface
    subroutine blueprint(sz,arr)
      integer, intent(in) :: sz
      integer, dimension(0), intent(in) :: arr
      ! This zero means that the size does not matter,
      ! as long as it is a one-dimensional integer array.
    end subroutine blueprint
  end interface

  procedure(blueprint), pointer :: ptr

  allocate(ownlist(3))
  ownlist = (/3,4,5/)
  ptr => rout1
  call ptr(3,ownlist)
  deallocate(ownlist)

  allocate(ownlist(0:10))
  ownlist = (/3,4,5,6,7,8,9,0,1,2,3/)
  ptr => rout2
  call ptr(3,ownlist)
  deallocate(ownlist)

contains

  ! This one has a dimension size as input.
  subroutine rout1(sz,arr)
    implicit none
    integer, intent(in) :: sz
    integer, dimension(sz), intent(in) :: arr
    write(*,*) arr
    write(*,*) arr(1)
  end subroutine rout1

  ! This one has a fixed dimension size.
  subroutine rout2(sz,arr)
    implicit none
    integer, intent(in) :: sz
    integer, dimension(0:10), intent(in) :: arr
    write(*,*) "Ignored integer: ",sz
    write(*,*) arr
    write(*,*) arr(1)
  end subroutine rout2

end program test

Gfortran 抱怨接口。将0更改为“ sz”可以解决'rout1'的问题,但无法解决'rout2'的问题。

然而,您可以欺骗gfortran并说dimension(0:10 + 0 * sz)而不是dimension(0:10),gfortran编译并提供与ifort相同的结果。

这是一个愚蠢的技巧,它依赖于可能不存在的整数“ sz”的存在。另一个程序:

program difficult_test

  implicit none

  integer, dimension(:), allocatable :: ownlist

  interface
    subroutine blueprint(arr)
      integer, dimension(0), intent(in) :: arr
    end subroutine blueprint
  end interface

  procedure(blueprint), pointer :: ptr

  allocate(ownlist(3))
  ownlist = (/3,4,5/)
  ptr => rout1
  call ptr(ownlist)
  deallocate(ownlist)

  allocate(ownlist(0:10))
  ownlist = (/3,4,5,6,7,8,9,0,1,2,3/)
  ptr => rout2
  call ptr(ownlist)
  deallocate(ownlist)

contains

  subroutine rout1(arr)
    implicit none
    integer, dimension(3), intent(in) :: arr
    write(*,*) arr
    write(*,*) arr(1)
  end subroutine rout1

  subroutine rout2(arr)
    implicit none
    integer, dimension(0:10), intent(in) :: arr
    write(*,*) arr
    write(*,*) arr(1)
  end subroutine rout2

end program difficult_test

这个在ifort下可以工作,原因和之前的例子一样,但是gfortran会抱怨接口。我不知道该如何修复它。

我想告诉gfortran的唯一事情是“我还不知道维度大小,但我们会解决它”。但这需要一个备用整数参数(或其他可以转换为整数的东西)来欺骗gfortran。


虽然这句话很长,但我不确定你是否回答了楼主实际提出的问题。 - Vladimir F Героям слава

网页内容由stack overflow 提供, 点击上面的
可以查看英文原文,
原文链接