Set array's rank at runtime

二次信任 提交于 2019-11-28 11:45:51
steabert

I once asked something similar, i.e. how to treat a two-dimensional array as one dimension, see here: changing array dimensions in fortran.

The answers were about the RESHAPE instrinsic of pointers, however there seems to be no way to use the same array name unless you use subroutine wrappers, but then you need callbacks to have the eventual subroutine with only one name, so the problems get larger.

program test
    real, allocatable :: data(:)
    allocate(data(n_data))
    ! read stuff, set is_2d and sizes
    if (is_2d) then
        call my_sub2(data, nX, nY)
    else
        call my_sub3(data, nX, nY, nZ)
    end if
end program test

subroutine my_sub2(data, nX, nY)
    real :: data(nx,nY)
    ! ...
end subroutine my_sub2

subroutine my_sub3(data, nX, nY, nZ)
    real :: data(nx,nY,nZ)
    ! ...
end subroutine my_sub3

EDIT: as an alternative, set the third rank to 1:

program test
    real, allocatable, target:: data(:)
    real, pointer:: my_array(:,:,:)
    logical is_2d
    n_data = 100
    allocate(data(n_data))
    ! read stuff, determine is_2d and n
    if (is_2d) then
        i=n
        j=n
        k=1
    else
        i=n
        j=n
        k=n
    end if
    my_array(1:i,1:j,1:k) => data
    write(*,*) my_array
end program test

Then you handle the 2D case as a special 3D case with third dimension 1.

EDIT2: also, beware when passing non-contiguous arrays to subroutines with explicit-shape arrays: http://software.intel.com/sites/products/documentation/hpc/compilerpro/en-us/fortran/lin/compiler_f/optaps/fortran/optaps_prg_arrs_f.htm

If I understand correctly, you read in data in and 1-D array and want to assign it to 2D or 3D arrays, which you know only after reading the file. Why not declare both 2D and 3D arrays as allocatable arrays, and allocate only one of them base on your data shape? You could use the intrinsic function RESHAPE to do this conveniently.

REAL,DIMENSION(:,:),  ALLOCATABLE :: arr2d
REAL,DIMENSION(:,:,:),ALLOCATABLE :: arr3d
...
! Read data into 1-D array, arr1d;
...
IF(L2d)THEN
  ALLOCATE(arr2d(im,jm))
  arr2d=RESHAPE(arr1d,(/im,jm/))
ELSEIF(L3d)THEN
  ALLOCATE(arr3d(im,jm,km))
  arr3d=RESHAPE(arr1d,(/im,jm,km/))
ENDIF

You could use the EQUIVALENCE statement like this:

Program ranks
    integer a_1d(12)
    integer a_2d(2, 6)
    integer a_3d(2, 2, 3)

    equivalence (a_1d, a_2d, a_3d)

    ! fill array 1d
    a_1d = (/1,2,3,4,5,6,7,8,9,10,11,12/)

    print *, a_1d

    print *, a_2d(1,1:6)
    print *, a_2d(2,1:6)

    print *, a_3d(1,1,1:3)
    print *, a_3d(2,1,1:3)
    print *, a_3d(1,2,1:3)
    print *, a_3d(2,2,1:3)

end program ranks

You can write a subroutine for different ranks of array and create an interface Here in example I have shown that how to populate an array of different array using interface statement `

program main 
    use data 
    implicit none 
    real,dimension(:,:,:),allocatable::data 
    integer::nx,ny,nz
    nx = 5
    ny = 10
    nz = 7
    call populate(nx,ny,nz,data)
    print *,data
end program main `

data module is here

module data  
  private 
  public::populate
  interface populate 
      module procedure populate_1d 
      module procedure populate_2d 
      module procedure populate_3d 
  end interface
 contains 
   subroutine populate_1d(x,data)
       implicit none 
       integer,intent(in)::x
       real,dimension(:),allocatable,intent(out):: data
       allocate(data(x))
       data=rand()
   end subroutine populate_1d 
   subroutine populate_2d(x,y,data)
       implicit none 
       integer,intent(in)::x,y
       real,dimension(:,:),allocatable,intent(out):: data
       allocate(data(x,y))
       data=rand()
   end subroutine populate_2d 
   subroutine populate_3d(x,y,z,data)
       implicit none 
       integer,intent(in)::x,y,z
       real,dimension(:,:,:),allocatable,intent(out):: data
       allocate(data(x,y,z))
       data=rand()
   end subroutine populate_3d 
end module data 

There is an interface to populate 1d, 2d and 3d arrays. you can call populate interface instead of calling individual subroutines. It will automatically pick the relevant one.

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!