数组的属性和特性#

合并#

名称#

merge(3) - [ARRAY:CONSTRUCTION] 合并变量

概要#

    result = merge(tsource, fsource, mask)
     elemental type(TYPE(kind=KIND)) function merge(tsource,fsource,mask)

      type(TYPE(kind=KIND)),intent(in) :: tsource
      type(TYPE(kind=KIND)),intent(in) :: fsource
      logical(kind=**),intent(in)   :: mask
      mask** : Shall be of type logical.

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • tsource 可以是任何类型,包括用户定义类型。

  • fsource 应与tsource具有相同的类型和类型参数。

  • mask 应为逻辑类型。

  • 结果将与tsource具有相同的类型和类型参数。

描述#

元素函数merge(3)根据逻辑掩码从两个数组或标量中选择值。当mask的对应元素为.true.时,结果等于tsource的一个元素;当其为.false.时,结果等于fsource的一个元素。

支持多维数组。

请注意,merge(3)的参数表达式不需要短路,因此(例如)如果数组x在下面的语句中包含零值,则标准不会阻止生成浮点除以零;因为在使用掩码选择要保留的值之前,可能会对x的所有值计算1.0/x

      y = merge( 1.0/x, 0.0, x /= 0.0 )

请注意,编译器也可以自由地进行短路或生成无穷大,因此这在许多编程环境中可能有效,但不建议这样做。

对于此类情况,可以使用where结构通过掩码赋值来代替

      where(x .ne. 0.0)
         y = 1.0/x
      elsewhere
         y = 0.0
      endwhere

而不是更模糊的

      merge(1.0/merge(x,1.0,x /= 0.0), 0.0, x /= 0.0)

选项#

  • tsource

    可以是任何类型,包括用户定义类型。

  • fsource

    应与tsource具有相同的类型和类型参数。

  • mask

    应为逻辑类型。

请注意,(目前)字符值必须具有相同的长度。

结果#

如果mask.true.,则结果由tsource的一个元素构建;否则,由fsource构建。

由于tsourcefsource需要具有相同的类型和类型参数(对于声明类型和动态类型),因此当且仅当tsourcefsource都是多态的时,结果才是多态的。

示例#

示例程序

program demo_merge
implicit none
integer :: tvals(2,3), fvals(2,3), answer(2,3)
logical :: mask(2,3)
integer :: i
integer :: k
logical :: chooseleft

   ! Works with scalars
   k=5
   write(*,*)merge (1.0, 0.0, k > 0)
   k=-2
   write(*,*)merge (1.0, 0.0, k > 0)

   ! set up some simple arrays that all conform to the
   ! same shape
   tvals(1,:)=[  10, -60,  50 ]
   tvals(2,:)=[ -20,  40, -60 ]

   fvals(1,:)=[ 0, 3, 2 ]
   fvals(2,:)=[ 7, 4, 8 ]

   mask(1,:)=[ .true.,  .false., .true. ]
   mask(2,:)=[ .false., .false., .true. ]

   ! lets use the mask of specific values
   write(*,*)'mask of logicals'
   answer=merge( tvals, fvals, mask )
   call printme()

   ! more typically the mask is an expression
   write(*, *)'highest values'
   answer=merge( tvals, fvals, tvals > fvals )
   call printme()

   write(*, *)'lowest values'
   answer=merge( tvals, fvals, tvals < fvals )
   call printme()

   write(*, *)'zero out negative values'
   answer=merge( tvals, 0, tvals < 0)
   call printme()

   write(*, *)'binary choice'
   chooseleft=.false.
   write(*, '(3i4)')merge([1,2,3],[10,20,30],chooseleft)
   chooseleft=.true.
   write(*, '(3i4)')merge([1,2,3],[10,20,30],chooseleft)

contains

subroutine printme()
      write(*, '(3i4)')(answer(i, :), i=1, size(answer, dim=1))
end subroutine printme

end program demo_merge

预期结果

 >     mask of logicals
 >      10   3  50
 >       7   4 -60
 >     highest values
 >      10   3  50
 >       7  40   8
 >     lowest values
 >       0 -60   2
 >     -20   4 -60
 >     zero out negative values
 >       0 -60   0
 >     -20   0 -60
 >     binary choice
 >      10  20  30
 >       1   2   3

标准#

Fortran 95

另请参见#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

打包#

名称#

pack(3) - [ARRAY:CONSTRUCTION] 将数组打包成秩为一的数组

概要#

    result = pack( array, mask [,vector] )
     TYPE(kind=KIND) function pack(array,mask,vector)

      TYPE(kind=KIND),option(in) :: array(..)
      logical  :: mask(..)
      TYPE(kind=KIND),option(in),optional :: vector(*)

特性#

  • array 是任何类型的数组

  • mask 一个逻辑标量以及与array一致的数组。

  • vectorarray具有相同的种类和类型,并且秩为一

  • 返回值与array具有相同的种类和类型

描述#

pack(3)将array的元素存储在秩为一的数组中。

结果数组的开头由mask等于.true.的元素组成。之后,剩余位置将填充从vector中获取的元素

选项#

  • array

    此数组中的数据用于填充结果向量

  • mask

    逻辑掩码必须与array的大小相同,或者也可以是逻辑标量。

  • vector

    一个与array类型相同的数组,秩为一。如果存在,vector中的元素数量应等于或大于mask中真元素的数量。如果mask是标量,则vector中的元素数量应等于或大于array中的元素数量。

vector的元素数量应至少与array中的元素数量相同。

结果#

结果是一个秩为一且与array类型相同的数组。如果存在vector,则结果大小为vector的大小,否则为mask.true.值的个数。

如果mask是值为.true.的标量,则结果大小为array的大小。

示例#

示例程序

program demo_pack
implicit none
integer, allocatable :: m(:)
character(len=10) :: c(4)

 ! gathering nonzero elements from an array:
   m = [ 1, 0, 0, 0, 5, 0 ]
   write(*, fmt="(*(i0, ' '))") pack(m, m /= 0)

 ! Gathering nonzero elements from an array and appending elements
 ! from VECTOR till the size of the mask array (or array size if the
 ! mask is scalar):
   m = [ 1, 0, 0, 2 ]
   write(*, fmt="(*(i0, ' '))") pack(m, m /= 0, [ 0, 0, 3, 4 ])
   write(*, fmt="(*(i0, ' '))") pack(m, m /= 0 )

 ! select strings whose second character is "a"
   c = [ character(len=10) :: 'ape', 'bat', 'cat', 'dog']
   write(*, fmt="(*(g0, ' '))") pack(c, c(:)(2:2) == 'a' )

end program demo_pack

结果

 > 1 5
 > 1 2 3 4
 > 1 2
 > bat        cat

标准#

Fortran 95

另请参见#

merge(3)spread(3)unpack(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

扩展#

名称#

spread(3) - [ARRAY:CONSTRUCTION] 添加维度并复制数据

概要#

    result = spread(source, dim, ncopies)
     TYPE(kind=KIND) function spread(source, dim, ncopies)

      TYPE(kind=KIND)             :: source(..)
      integer(kind=**),intent(in) :: dim
      integer(kind=**),intent(in) :: ncopies

特性#

  • source 是任何类型的标量或数组。

  • dim 是一个整数标量

  • ncopies 是一个整数标量

描述#

spread(3)沿着指定的维度dim复制source数组。副本重复ncopies次。

因此,要向矩阵添加其他行,将使用dim=1,但要添加其他列,将使用dim=2,例如。

如果source是标量,则结果向量的大小为ncopies,并且结果的每个元素的值都等于source

选项#

  • source

    任何类型的标量或数组,秩小于十五。

  • dim

    范围从1n+1的附加维度值,其中n等于source的秩。

  • ncopies

    要生成的原始数据的副本数量

结果#

结果是与source类型相同的数组,秩为n+1,其中n等于source的秩。

示例#

示例程序

program demo_spread
implicit none

integer a1(4,3), a2(3,4), v(4), s

   write(*,'(a)' ) &
   'TEST SPREAD(3)                                      ', &
   '  SPREAD(3) is a FORTRAN90 function which replicates', &
   '  an array by adding a dimension.                   ', &
   ' '

   s = 99
   call printi('suppose we have a scalar S',s)

   write(*,*) 'to add a new dimension (1) of extent 4 call'
   call printi('spread( s, dim=1, ncopies=4 )',spread ( s, 1, 4 ))

   v = [ 1, 2, 3, 4 ]
   call printi(' first we will set V to',v)

   write(*,'(a)')' and then do "spread ( v, dim=2, ncopies=3 )"'
   a1 = spread ( v, dim=2, ncopies=3 )
   call printi('this adds a new dimension (2) of extent 3',a1)

   a2 = spread ( v, 1, 3 )
   call printi(' spread(v,1,3) adds a new dimension (1) of extent 3',a2)
   ! add more
   a2 = spread ( v, 1, 3 )
   call printi(' spread(v,1,3) adds a new dimension (1) of extent 3',a2)

contains
! CONVENIENCE ROUTINE; NOT DIRECTLY CONNECTED TO SPREAD(3)
subroutine printi(title,a)
use, intrinsic :: iso_fortran_env, only : stderr=>ERROR_UNIT,&
 & stdin=>INPUT_UNIT, stdout=>OUTPUT_UNIT
implicit none

!@(#) print small 2d integer scalar, vector, matrix in row-column format

character(len=*),parameter   :: all='(" ",*(g0,1x))'
character(len=*),intent(in)  :: title
character(len=20)            :: row
integer,intent(in)           :: a(..)
integer                      :: i

   write(*,all,advance='no')trim(title)
   ! select rank of input
   select rank(a)
   rank (0); write(*,'(a)')' (a scalar)'
      write(*,'(" > [ ",i0," ]")')a
   rank (1); write(*,'(a)')' (a vector)'
      ! find how many characters to use for integers
      write(row,'(i0)')ceiling(log10(real(maxval(abs(a)))))+2
      ! use this format to write a row
      row='(" > [",*(i'//trim(row)//':,","))'
      do i=1,size(a)
         write(*,fmt=row,advance='no')a(i)
         write(*,'(" ]")')
      enddo
   rank (2); write(*,'(a)')' (a matrix) '
      ! find how many characters to use for integers
      write(row,'(i0)')ceiling(log10(real(maxval(abs(a)))))+2
      ! use this format to write a row
      row='(" > [",*(i'//trim(row)//':,","))'
      do i=1,size(a,dim=1)
         write(*,fmt=row,advance='no')a(i,:)
         write(*,'(" ]")')
      enddo
   rank default
      write(stderr,*)'*printi* did not expect rank=', rank(a), &
       & 'shape=', shape(a),'size=',size(a)
      stop '*printi* unexpected rank'
   end select
   write(*,all) '>shape=',shape(a),',rank=',rank(a),',size=',size(a)
   write(*,*)

end subroutine printi

end program demo_spread

结果

   TEST SPREAD(3)
     SPREAD(3) is a FORTRAN90 function which replicates
     an array by adding a dimension.

    suppose we have a scalar S  (a scalar)
    > [ 99 ]
    >shape= ,rank= 0 ,size= 1

    to add a new dimension (1) of extent 4 call
    spread( s, dim=1, ncopies=4 )  (a vector)
    > [  99 ]
    > [  99 ]
    > [  99 ]
    > [  99 ]
    >shape= 4 ,rank= 1 ,size= 4

     first we will set V to  (a vector)
    > [  1 ]
    > [  2 ]
    > [  3 ]
    > [  4 ]
    >shape= 4 ,rank= 1 ,size= 4

    and then do "spread ( v, dim=2, ncopies=3 )"
    this adds a new dimension (2) of extent 3  (a matrix)
    > [  1,  1,  1 ]
    > [  2,  2,  2 ]
    > [  3,  3,  3 ]
    > [  4,  4,  4 ]
    >shape= 4 3 ,rank= 2 ,size= 12

     spread(v,dim=1,ncopies=3) adds a new dimension (1) (a matrix)
    > [  1,  2,  3,  4 ]
    > [  1,  2,  3,  4 ]
    > [  1,  2,  3,  4 ]
    >shape= 3 4 ,rank= 2 ,size= 12

标准#

Fortran 95

另请参见#

merge(3)pack(3)unpack(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

解包#

名称#

unpack(3) - [ARRAY:CONSTRUCTION] 使用掩码将向量的元素散布到数组中

概要#

    result = unpack(vector, mask, field)
     type(TYPE(kind=KIND)) unpack(vector, mask, field)

      type(TYPE(kind=KIND)),intent(in) :: vector(:)
      logical,intent(in)               :: mask(..)
      type(TYPE(kind=KIND)),intent(in) :: field(..)

特征#

  • vector 是任意类型的秩为一的数组

  • mask 是一个逻辑数组

  • fieldmask 兼容,具有与 VECTOR 相同的类型和类型参数。

  • 结果是一个与 vector 类型和类型参数相同,并且与 mask 形状相同的数组。

描述#

unpack(3) 将 vector 的元素分散到任意秩的数组 field 的副本中,使用 mask 中按数组元素顺序排列的 .true. 值来指定 vector 值的放置位置。

因此,会生成 field 的副本,其中选定的元素被替换为来自 vector 的值。这允许使用复杂的替换模式,而在使用数组语法或多个赋值语句时,这些模式将非常困难,尤其是在替换有条件时。

选项#

  • vector

    要放置到 field 中指定位置的新值。它应至少包含与 mask.true. 值一样多的元素。

  • mask

    应为一个数组,指定 field 中哪些值将被替换为来自 vector 的值。

  • field

    要更改的输入数组。

结果#

结果中对应于 mask 的第 i 个真元素(按数组元素顺序)的元素具有值 vector(i),其中 i = 1, 2, …, t,t 是 mask 中真值的个数。其他每个元素的值等于 **field* 如果 field 是标量,或者等于 **field 的对应元素如果它是一个数组。

结果数组对应于 field,其中 mask.true. 元素被来自 vector 的值(按数组元素顺序)替换。

示例#

可以使用以下方法将特定值“分散”到数组中的特定位置

                       1 0 0
    If M is the array  0 1 0
                       0 0 1

    V is the array [1, 2, 3],
                               . T .
    and Q is the logical mask  T . .
                               . . T
    where "T" represents true and "." represents false, then the result of

    UNPACK (V, MASK = Q, FIELD = M) has the value

      1 2 0
      1 1 0
      0 0 3

    and the result of UNPACK (V, MASK = Q, FIELD = 0) has the value

      0 2 0
      1 0 0
      0 0 3

示例程序

program demo_unpack
implicit none
logical,parameter :: T=.true., F=.false.

integer :: vector(2)  = [1,1]

! mask and field must conform
integer,parameter :: r=2, c=2
logical :: mask(r,c)  = reshape([ T,F,F,T ],[2,2])
integer :: field(r,c) = 0, unity(2,2)

   ! basic usage
   unity = unpack( vector, mask, field )
   call print_matrix_int('unity=', unity)

   ! if FIELD is a scalar it is used to fill all the elements
   ! not assigned to by the vector and mask.
   call print_matrix_int('scalar field',         &
   & unpack(                                     &
   & vector=[ 1, 2, 3, 4 ],                      &
   & mask=reshape([ T,F,T,F,F,F,T,F,T ], [3,3]), &
   & field=0) )

contains

   subroutine print_matrix_int(title,arr)
   ! convenience routine:
   ! just prints small integer arrays in row-column format
   implicit none
   character(len=*),intent(in)  :: title
   integer,intent(in)           :: arr(:,:)
   integer                      :: i
   character(len=:),allocatable :: biggest

      write(*,*)trim(title)
      ! make buffer to write integer into
      biggest='           '
      ! find how many characters to use for integers
      write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
      ! use this format to write a row
      biggest='("  [",*(i'//trim(biggest)//':,","))'
      ! print one row of array at a time
      do i=1,size(arr,dim=1)
         write(*,fmt=biggest,advance='no')arr(i,:)
         write(*,'(" ]")')
      enddo
   end subroutine print_matrix_int

end program demo_unpack

结果

   > unity=
   >  [ 1, 0 ]
   >  [ 0, 1 ]
   > scalar field
   >  [  1,  0,  3 ]
   >  [  0,  0,  0 ]
   >  [  2,  0,  4 ]

标准#

Fortran 95

另请参见#

merge(3)pack(3)spread(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

allocated#

名称#

allocated(3) - [数组:查询] 可分配实体的分配状态

概要#

    result = allocated(array|scalar)
     logical function allocated(array,scalar)

      type(TYPE(kind=**)),allocatable,optional :: array(..)
      type(TYPE(kind=**)),allocatable,optional :: scalar

特征#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • array 可以是任意类型的任何可分配数组对象。

  • scalar 可以是任意类型的任何可分配标量。

  • 结果是默认逻辑标量

描述#

allocated(3) 检查数组和标量的分配状态。

必须至少指定一个且仅指定一个 arrayscalar

选项#

  • 实体

    要测试的 可分配 对象。

结果#

如果参数已分配,则结果为 .true.;否则,返回 .false.

示例#

示例程序

program demo_allocated
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=sp), allocatable :: x(:)
character(len=256) :: message
integer :: istat
  ! basics
   if( allocated(x)) then
       write(*,*)'do things if allocated'
   else
       write(*,*)'do things if not allocated'
   endif

   ! if already allocated, deallocate
   if ( allocated(x) ) deallocate(x,STAT=istat, ERRMSG=message )
   if(istat.ne.0)then
      write(*,*)trim(message)
      stop
   endif

   ! only if not allocated, allocate
   if ( .not. allocated(x) ) allocate(x(20))

  ! allocation and intent(out)
   call intentout(x)
   write(*,*)'note it is deallocated!',allocated(x)

   contains

   subroutine intentout(arr)
   ! note that if arr has intent(out) and is allocatable,
   ! arr is deallocated on entry
   real(kind=sp),intent(out),allocatable :: arr(:)
       write(*,*)'note it was allocated in calling program',allocated(arr)
   end subroutine intentout

end program demo_allocated

结果

 >  do things if not allocated
 >  note it was allocated in calling program F
 >  note it is deallocated! F

标准#

Fortran 95。Fortran 2003 中添加了可分配标量实体。

另请参见#

move_alloc(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

is_contiguous#

名称#

is_contiguous(3) - [数组:查询] 测试对象是否连续

概要#

    result = is_contiguous(array)
     logical function is_contiguous(array)

      type(TYPE(kind=**)),intent(in) :: array

特征#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • array 可以是任何类型。它应该是一个数组或假定秩。如果它是指针,则应与其关联。

  • 结果是默认逻辑标量

描述#

is_contiguous(3) 当且仅当对象连续时返回 .true.

如果对象为以下情况,则对象为连续:

  • (1) 具有 CONTIGUOUS 属性的对象,

  • (2) 不是假定形状的非指针整个数组,

  • (3) 与连续数组进行参数关联的假定形状数组,

  • (4) 由 ALLOCATE 语句分配的数组,

  • (5) 与连续目标关联的指针,或

  • (6) 非零大小的数组节,前提是

    • (a) 其基本对象是连续的,

    • (b) 它没有向量下标,

    • (c) 该节的元素(按数组元素顺序)是按数组元素顺序连续的基本对象元素的子集,

    • (d) 如果数组的类型为字符并且出现子字符串范围,则子字符串范围指定父字符串的所有字符,

    • (e) 只有其最终部分引用具有非零秩,并且

    • (f) 它不是类型为复数的数组的实部或虚部。

如果对象是数组子对象,则对象不连续,并且

  • 对象具有两个或多个元素,

  • 对象中按数组元素顺序排列的元素在基本对象的元素中不连续,

  • 对象不是长度为零的字符类型,并且

  • 对象不是派生类型,该派生类型除了零大小的数组和

  • 长度为零的字符之外没有最终组件。

其他对象是否连续取决于处理器。

选项#

  • array

    要测试其是否连续的任何类型的数组。如果它是指针,则应与其关联。

结果#

如果 array 连续,则结果值为 .true.,否则为 .false.

示例#

示例程序

program demo_is_contiguous
implicit none
intrinsic is_contiguous
real, DIMENSION (1000, 1000), TARGET :: A
real, DIMENSION (:, :), POINTER       :: IN, OUT
   IN => A              ! Associate IN with target A
   OUT => A(1:1000:2,:) ! Associate OUT with subset of target A
   !
   write(*,*)'IN is ',IS_CONTIGUOUS(IN)
   write(*,*)'OUT is ',IS_CONTIGUOUS(OUT)
   !
end program demo_is_contiguous

结果

    IN is  T
    OUT is  F

标准#

Fortran 2008

另请参见#

****(3)

fortran-lang 内在描述

lbound#

名称#

lbound(3) - [数组:查询] 数组的下界

概要#

    result = lbound(array [,dim] [,kind] )
     elemental TYPE(kind=KIND) function lbound(array,dim,kind)

      TYPE(kind=KIND),intent(in)           :: array(..)
      integer(kind=**),intent(in),optional :: dim
      integer(kind=**),intent(in),optional :: kind

特征#

  • array 应为假定秩或任何类型的数组。它不能是未分配的可分配数组或未关联的指针。

  • dim 应为标量 integer。相应的实际参数不应是可选的虚拟参数、分离的指针或未分配的可分配参数。

  • kind 一个 integer 初始化表达式,指示结果的种类参数。

  • 返回值的类型为 integer,种类为 kind。如果省略 kind,则返回值为默认整数种类。如果存在 dim,则结果为标量;否则,结果为秩为一且大小为 n 的数组,其中 n 是 array 的秩。

  • 指定为 ** 的种类可以是该类型支持的任何种类。

描述#

result(3) 返回数组的下界,或沿 dim 维度的单个下界。

选项#

  • array

    应为任何类型的数组。

  • dim

    应为标量 integer。如果省略 dim,则结果为 array 的上界的数组。

  • kind

    一个 integer 初始化表达式,指示结果的种类参数。

结果#

如果省略 dim,则结果为 array 的下界的数组。

如果存在 dim,则结果为对应于该维度数组下界的标量。如果 array 是表达式而不是整个数组或数组结构组件,或者如果它沿相关维度具有零范围,则下界取为 1。

NOTE1

If **array** is assumed-rank and has rank zero, **dim** cannot be
present since it cannot satisfy the requirement **1 <= dim <= 0**.

示例#

请注意,在我看来,此函数不应在假定大小的数组或任何没有显式接口的函数中使用。如果未定义接口,则可能会发生错误。

示例程序

! program demo_lbound
module m_bounds
implicit none
 contains
    subroutine msub(arr)
       !!integer,intent(in) :: arr(*)  ! cannot be assumed-size array
       integer,intent(in) :: arr(:)
       write(*,*)'MSUB: LOWER=',lbound(arr), &
       & 'UPPER=',ubound(arr), &
       & 'SIZE=',size(arr)
    end subroutine msub
 end module m_bounds

 program demo_lbound
 use m_bounds, only : msub
 implicit none
 interface
    subroutine esub(arr)
    integer,intent(in) :: arr(:)
    end subroutine esub
 end interface
 integer :: arr(-10:10)
    write(*,*)'MAIN: LOWER=',lbound(arr), &
    & 'UPPER=',ubound(arr), &
    & 'SIZE=',size(arr)
    call csub()
    call msub(arr)
    call esub(arr)
 contains
subroutine csub
   write(*,*)'CSUB: LOWER=',lbound(arr), &
   & 'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
end subroutine csub
end

 subroutine esub(arr)
 implicit none
 integer,intent(in) :: arr(:)
    ! WARNING: IF CALLED WITHOUT AN EXPLICIT INTERFACE
    ! THIS WILL GIVE UNDEFINED ANSWERS (like 0,0,0)
    write(*,*)'ESUB: LOWER=',lbound(arr), &
    & 'UPPER=',ubound(arr), &
    & 'SIZE=',size(arr)
 end subroutine esub

!end program demo_lbound

结果

   MAIN: LOWER=         -10 UPPER=          10 SIZE=          21
   CSUB: LOWER=         -10 UPPER=          10 SIZE=          21
   MSUB: LOWER=           1 UPPER=          21 SIZE=          21
   ESUB: LOWER=           1 UPPER=          21 SIZE=          21

标准#

Fortran 95,带 KIND 参数 - Fortran 2003

另请参见#

数组查询:#

co_ubound(3)co_lbound(3)

状态查询:#

种类查询:#

位查询:#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

rank#

名称#

rank(3) - [数组:查询] 数据对象的秩

概要#

    result = rank(a)
     integer function rank(a)

      type(TYPE(kind=**)),intent(in) :: a(..)

特征#

  • a 可以是任何类型 TYPE 和秩。

  • 指定为 ** 的种类可以是该类型支持的任何种类。

描述#

rank(3) 返回标量或数组数据对象的秩。

数组的秩是它所具有的维度数(标量为零)。

选项#

  • a 是要查询其维度的数据对象。返回的秩可以是 0 到 16。

    参数 a 可以是任何数据对象类型,包括假定秩数组。

结果#

对于数组,返回其秩;对于标量,返回零。

示例#

示例程序

program demo_rank
implicit none

! a bunch of data objects to query
integer           :: a
real, allocatable :: b(:,:)
real, pointer     :: c(:)
complex           :: d

! make up a type
type mytype
   integer :: int
   real :: float
   character :: char
end type mytype
type(mytype) :: any_thing(1,2,3,4,5)

  ! basics
   print *, 'rank of scalar a=',rank(a)
   ! you can query this array even though it is not allocated
   print *, 'rank of matrix b=',rank(b)
   print *, 'rank of vector pointer c=',rank(c)
   print *, 'rank of complex scalar d=',rank(d)

  ! you can query any type, not just intrinsics
   print *, 'rank of any arbitrary type=',rank(any_thing)

  ! an assumed-rank object may be queried
   call query_int(10)
   call query_int([20,30])
   call query_int( reshape([40,50,60,70],[2,2]) )

  ! you can even query an unlimited polymorphic entity
   call query_anything(10.0)
   call query_anything([.true.,.false.])
   call query_anything( reshape([40.0,50.0,60.0,70.0],[2,2]) )

contains

subroutine query_int(data_object)
! It is hard to do much with something dimensioned
! name(..) if not calling C except inside of a
! SELECT_RANK construct but one thing you can
! do is call the inquiry functions ...
integer,intent(in) :: data_object(..)
character(len=*),parameter :: all='(*(g0,1x))'

   if(rank(data_object).eq.0)then
      print all,&
      & 'passed a scalar to an assumed rank,  &
      & rank=',rank(data_object)
   else
      print all,&
      & 'passed an array to an assumed rank,  &
      & rank=',rank(data_object)
   endif

end subroutine query_int

subroutine query_anything(data_object)
class(*),intent(in) ::data_object(..)
character(len=*),parameter :: all='(*(g0,1x))'
  if(rank(data_object).eq.0)then
    print all,&
    &'passed a scalar to an unlimited polymorphic rank=', &
    & rank(data_object)
  else
    print all,&
    & 'passed an array to an unlimited polymorphic, rank=', &
    & rank(data_object)
  endif
end subroutine query_anything

end program demo_rank

结果

    rank of scalar a=           0
    rank of matrix b=           2
    rank of vector pointer c=           1
    rank of complex scalar d=           0
    rank of any arbitrary type=           5
   passed a scalar to an assumed rank,   rank= 0
   passed an array to an assumed rank,   rank= 1
   passed an array to an assumed rank,   rank= 2
   passed a scalar to an unlimited polymorphic rank= 0
   passed an array to an unlimited polymorphic, rank= 1
   passed an array to an unlimited polymorphic, rank= 2

标准#

另请参见#

数组查询:#

状态查询:#

种类查询:#

位查询:#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

#

shape#

名称#

shape(3) - [ARRAY:INQUIRY] 确定数组或标量的形状

提要#

  result = shape( source [,kind] )
   integer(kind=KIND) function shape( source, KIND )

    type(TYPE(kind=**)),intent(in)       :: source(..)
    integer(kind=**),intent(in),optional :: KIND

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • source 是任何类型的数组或标量。如果 source 是指针,则它必须是关联的,并且可分配数组必须已分配。它不应是假定大小的数组。

  • KIND 是一个常量整数初始化表达式。

  • 如果存在 KIND,则结果是一个秩为一的整数数组,其大小等于 source 的秩,并且具有 KIND 指定的种类,否则它具有默认整数种类。

描述#

shape(3) 查询数组的形状。

选项#

  • source

    任何类型的数组或标量。如果 source 是指针,则它必须是关联的,并且可分配数组必须已分配。

  • kind

    指示结果的种类参数。

结果#

一个秩为一的整数数组,其元素数与 source 的维度数相同。

结果数组的元素对应于 source 沿各个维度的范围。

如果 source 是标量,则结果为空数组(大小为零的秩为一的数组)。

示例#

示例程序

program demo_shape
implicit none
character(len=*),parameter :: all='(*(g0,1x))'
integer, dimension(-1:1, -1:2) :: a
   print all, 'shape of array=',shape(a)
   print all, 'shape of constant=',shape(42)
   print all, 'size of shape of constant=',size(shape(42))
   print all, 'ubound of array=',ubound(a)
   print all, 'lbound of array=',lbound(a)
end program demo_shape

结果

   shape of array= 3 4
   shape of constant=
   size of shape of constant= 0
   ubound of array= 1 2
   lbound of array= -1 -1

标准#

Fortran 95;带 KIND 参数的 Fortran 2003

另请参见#

数组查询:#

状态查询:#

种类查询:#

位查询:#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

size#

名称#

size(3) - [ARRAY:INQUIRY] 确定数组的大小或一个维度的范围

提要#

    result = size(array [,dim] [,kind])
     integer(kind=KIND) function size(array,dim,kind)

      type(TYPE(kind=KIND),intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      integer(kind=**),intent(in),optional :: KIND

特性#

  • array 是任何类型的假定秩数组或数组,以及关联的种类。

    如果 array 是指针,则它必须是关联的,并且可分配数组必须已分配。

  • dim 是一个整数标量

  • kind 是一个标量整数常量表达式。

  • 结果是一个种类为 KIND 的整数标量。如果省略 KIND,则返回默认种类的整数

  • 指定为 ** 的种类可以是该类型支持的任何种类。

描述#

size(3) 返回数组中的元素总数,或者如果指定了 dim,则返回该维度上的元素数。

size(3) 确定沿指定维度 dimarray 的范围,或者如果省略 dim,则确定 array 中的元素总数。

选项#

  • array

    要测量其元素数的数组。如果**array*是假定大小的数组,则**dim**必须存在,其值小于**array**的秩。

  • dim

    值应在 1 到 n 的范围内,其中 n 等于 array 的秩。

    如果不存在,则返回整个数组的所有元素的总数。

  • kind

    一个 integer 初始化表达式,指示结果的种类参数。

    如果不存在,则返回的值的种类类型参数为默认整数类型。

    kind 必须允许 size 返回的幅度,否则结果未定义。

    如果省略 kind,则返回值为默认整数种类。

结果#

如果 dim 不存在且 array 是假定秩的,则结果的值等于 PRODUCT(SHAPE(ARRAY,KIND))。否则,结果的值等于 array 的元素总数。

如果 dim 存在,则返回该维度上的元素数,但如果 ARRAY 是假定秩的并且与假定大小的数组关联,并且 DIM 存在且其值等于 array 的秩,则该值为 -1。

注释 1

如果 array 是假定秩的并且秩为零,则 dim 不能存在,因为它无法满足要求

1 <= DIM <= 0。

示例#

示例程序

program demo_size
implicit none
integer :: arr(0:2,-5:5)
   write(*,*)'SIZE of simple two-dimensional array'
   write(*,*)'SIZE(arr)       :total count of elements:',size(arr)
   write(*,*)'SIZE(arr,DIM=1) :number of rows         :',size(arr,dim=1)
   write(*,*)'SIZE(arr,DIM=2) :number of columns      :',size(arr,dim=2)

   ! pass the same array to a procedure that passes the value two
   ! different ways
   call interfaced(arr,arr)
contains

subroutine interfaced(arr1,arr2)
! notice the difference in the array specification
! for arr1 and arr2.
integer,intent(in) :: arr1(:,:)
integer,intent(in) :: arr2(2,*)
   !
   write(*,*)'interfaced assumed-shape array'
   write(*,*)'SIZE(arr1)        :',size(arr1)
   write(*,*)'SIZE(arr1,DIM=1)  :',size(arr1,dim=1)
   write(*,*)'SIZE(arr1,DIM=2)  :',size(arr1,dim=2)

!  write(*,*)'SIZE(arr2)        :',size(arr2)
   write(*,*)'SIZE(arr2,DIM=1)  :',size(arr2,dim=1)
!
! CANNOT DETERMINE SIZE OF ASSUMED SIZE ARRAY LAST DIMENSION
!  write(*,*)'SIZE(arr2,DIM=2)  :',size(arr2,dim=2)

end subroutine interfaced

end program demo_size

结果

    SIZE of simple two-dimensional array
    SIZE(arr)       :total count of elements:          33
    SIZE(arr,DIM=1) :number of rows         :           3
    SIZE(arr,DIM=2) :number of columns      :          11
    interfaced assumed-shape array
    SIZE(arr1)        :          33
    SIZE(arr1,DIM=1)  :           3
    SIZE(arr1,DIM=2)  :          11
    SIZE(arr2,DIM=1)  :           2

标准#

Fortran 95,带 kind 参数 - Fortran 2003

另请参见#

数组查询:#

状态查询:#

种类查询:#

位查询:#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ubound#

名称#

ubound(3) - [ARRAY:INQUIRY] 数组的上界维度

提要#

    result = ubound(array [,dim] [,kind] )
     elemental TYPE(kind=KIND) function ubound(array,dim,kind)

      TYPE(kind=KIND),intent(in)           :: array
      integer(kind=**),intent(in),optional :: dim
      integer(kind=**),intent(in),optional :: kind

特性#

  • array 应为假定秩或任何类型的数组。它不能是未分配的可分配数组或未关联的指针。

  • dim 应为标量 integer。相应的实际参数不应是可选的虚拟参数、分离的指针或未分配的可分配参数。

  • kind 一个 integer 初始化表达式,指示结果的种类参数。

  • 返回值的类型为 integer,种类为 kind。如果省略 kind,则返回值为默认整数种类。如果存在 dim,则结果为标量;否则,结果为秩为一且大小为 n 的数组,其中 n 是 array 的秩。

  • 指定为 ** 的种类可以是该类型支持的任何种类。

描述#

ubound(3) 返回数组的上界,或沿 dim 维度的单个上界。

选项#

  • array

    要确定其上界的任何类型的假定秩数组或数组。如果可分配,则必须已分配;如果为指针,则必须是关联的。如果是假定大小的数组,则必须存在 dim

  • dim

    要确定其边界的 array 的特定维度。如果省略 dim,则结果是 array 的上界的数组。如果 array 是假定大小的数组,则需要 dim,在这种情况下,必须小于或等于 array 的秩。

  • kind

    指示结果的种类参数。如果省略,则返回默认种类的整数

结果#

返回值的类型为整数,种类为 kind。如果省略 kind,则返回值为默认整数种类。

如果省略 dim,则结果是 array 的每个维度的上界的数组。

如果 dim 存在,则结果是对应于该维度上数组的上界的标量。

如果 array 是表达式而不是整个数组或数组结构组件,或者如果它在相关维度上具有零范围,则上界被视为沿相关维度上的元素数。

注释 1 如果 ARRAY 是假定秩的并且秩为零,则 DIM 不能存在,因为它无法满足要求 1 <= DIM <= 0

示例#

请注意,此函数不应用于假定大小的数组或任何没有显式接口的函数中。如果未定义接口,则可能会发生错误。

示例程序

! program demo_ubound
module m2_bounds
implicit none

contains

subroutine msub(arr)
!!integer,intent(in) :: arr(*)  ! cannot be assumed-size array
integer,intent(in) :: arr(:)
   write(*,*)'MSUB: LOWER=',lbound(arr),'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
end subroutine msub

end module m2_bounds
!
program demo_ubound
use m2_bounds, only : msub
implicit none
interface
   subroutine esub(arr)
   integer,intent(in) :: arr(:)
   end subroutine esub
end interface
integer :: arr(-10:10)
   write(*,*)'MAIN: LOWER=',lbound(arr),'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
   call csub()
   call msub(arr)
   call esub(arr)
contains
subroutine csub
   write(*,*)'CSUB: LOWER=',lbound(arr),'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
end subroutine csub

end

subroutine esub(arr)
implicit none
integer,intent(in) :: arr(:)
   ! WARNING: IF CALLED WITHOUT AN EXPLICIT INTERFACE
   ! THIS WILL GIVE UNDEFINED ANSWERS (like 0,0,0)
   write(*,*)'ESUB: LOWER=',lbound(arr),'UPPER=',ubound(arr), &
   & 'SIZE=',size(arr)
end subroutine esub
!end program demo_ubound

结果

 >  MAIN: LOWER=         -10 UPPER=          10 SIZE=          21
 >  CSUB: LOWER=         -10 UPPER=          10 SIZE=          21
 >  MSUB: LOWER=           1 UPPER=          21 SIZE=          21
 >  ESUB: LOWER=           1 UPPER=          21 SIZE=          21

标准#

Fortran 95,带 KIND 参数的 Fortran 2003

另请参见#

数组查询:#

co_ubound(3)co_lbound(3)

状态查询:#

种类查询:#

位查询:#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

maxloc#

名称#

maxloc(3) - [ARRAY:LOCATION] 数组中最大值的所在位置

提要#

    result = maxloc(array [,mask]) | maxloc(array [,dim] [,mask])
     NUMERIC function maxloc(array, dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • NUMERIC 指定任何内在数值类型和种类。

描述#

maxloc(3) 确定数组中具有最大值的元素的位置,或者,如果提供了 dim 参数,则确定沿 dim 方向数组的每一行的最大元素的位置。

如果存在 mask,则仅考虑 mask.true.的元素。如果数组中有多个元素具有最大值,则返回的位置是这些元素中第一个在数组元素顺序中的元素的位置。

如果数组的大小为零,或 mask 的所有元素都为 .false.,则结果为零数组。类似地,如果提供了 dim 并且给定行中 mask 的所有元素都为零,则该行的结果值为零。

选项#

  • array

    应为整数实数字符类型的数组。

  • dim

    (可选) 应为整数类型的标量,其值介于 1 和 array 的秩之间(包括 1 和秩)。它不能是可选的哑元参数。

  • mask

    应为类型为logical的数组,且与array一致。

结果#

如果省略dim,则结果为一个秩为一的数组,其长度等于array的秩。如果存在dim,则结果为一个数组,其秩比array的秩小一,并且大小对应于array的大小,其中dim维度已删除。如果存在dimarray的秩为一,则结果为标量。在所有情况下,结果都为默认的integer类型。

返回值是从数组开头开始的偏移量的引用,如果数组下标不是从一开始,则不一定为下标值。

示例#

示例程序

program demo_maxloc
implicit none
integer      :: ii
integer,save :: i(-3:3)=[(abs(abs(ii)-50),ii=-3,3)]
integer,save :: ints(3,5)= reshape([&
   1,  2,  3,  4,  5, &
   10, 20, 30, 40, 50, &
   11, 22, 33, 44, 55  &
],shape(ints),order=[2,1])

    write(*,*) maxloc(ints)
    write(*,*) maxloc(ints,dim=1)
    write(*,*) maxloc(ints,dim=2)
    ! when array bounds do not start with one remember MAXLOC(3) returns
    ! the offset relative to the lower bound-1 of the location of the
    ! maximum value, not the subscript of the maximum value. When the
    ! lower bound of the array is one, these values are the same. In
    ! other words, MAXLOC(3) returns the subscript of the value assuming
    ! the first subscript of the array is one no matter what the lower
    ! bound of the subscript actually is.
    write(*,'(g0,1x,g0)') (ii,i(ii),ii=lbound(i,dim=1),ubound(i,dim=1))
    write(*,*)maxloc(i)

end program demo_maxloc

结果

 >     3       5
 >     3       3       3       3       3
 >     5       5       5
 >  -3 47
 >  -2 48
 >  -1 49
 >  0 50
 >  1 49
 >  2 48
 >  3 47

标准#

Fortran 95

另请参阅#

fortran-lang 内在描述

minloc#

名称#

minloc(3) - [ARRAY:LOCATION] 数组中最小值的所在位置

概要#

    result = minloc(array [,mask]) | minloc(array [,dim] [,mask])
     NUMERIC function minloc(array, dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • NUMERIC 是任何数值类型和种类。

描述#

minloc(3) 确定数组中具有最小值的元素的位置,或者,如果提供了dim参数,则确定数组沿dim方向每个行中最小元素的位置。

如果存在mask,则仅考虑masktrue.的元素。

如果数组中有多个元素具有最小值,则返回的位置是数组元素顺序中第一个此类元素的位置。

如果数组大小为零,或者mask的所有元素都为.false.,则结果为零数组。类似地,如果提供了dim并且给定行中mask的所有元素都为零,则该行的结果值为零。

选项#

  • array

    应为整数实数字符类型的数组。

  • dim

    (可选) 应为整数类型的标量,其值介于 1 和 array 的秩之间(包括 1 和秩)。它不能是可选的哑元参数。

  • mask

    应为类型为logical的数组,且与array一致。

结果#

如果省略dim,则结果为一个秩为一的数组,其长度等于array的秩。如果存在dim,则结果为一个数组,其秩比array的秩小一,并且大小对应于array的大小,其中dim维度已删除。如果存在dimarray的秩为一,则结果为标量。在所有情况下,结果都为默认的integer类型。

示例#

示例程序

program demo_minloc
implicit none
integer,save :: ints(3,5)= reshape([&
   4, 10,  1,  7, 13, &
   9, 15,  6, 12,  3, &
  14,  5, 11,  2,  8  &
],shape(ints),order=[2,1])
   write(*,*) minloc(ints)
   write(*,*) minloc(ints,dim=1)
   write(*,*) minloc(ints,dim=2)
   ! where in each column is the smallest number .gt. 10 ?
   write(*,*) minloc(ints,dim=2,mask=ints.gt.10)
   ! a one-dimensional array with dim=1 explicitly listed returns a scalar
   write(*,*) minloc(pack(ints,.true.),dim=1) ! scalar
end program demo_minloc

结果

 >        1       3
 >        1       3       1       3       2
 >        3       5       4
 >        5       4       3
 >        7

标准#

Fortran 95

另请参阅#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

findloc#

名称#

findloc(3) - [ARRAY:LOCATION] 沿维度DIM匹配目标值的ARRAY中第一个元素的位置

概要#

    result = findloc (array, value, dim [,mask] [,kind] [,back]) |
             findloc (array, value [,mask] [,kind] [,back])
     function findloc (array, value, dim, mask, kind, back)

      type TYPE(kind=KIND),intent(in)      :: array(..)
      type TYPE(kind=KIND),intent(in)      :: value
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)
      integer(kind=**),intent(in),optional :: kind
      logical(kind=**),intent(in),optional :: back

特性#

  • array 是任何内在类型的数组。

  • value 应为标量,但应与array类型一致,如运算符==或运算符.EQV.所指定。

  • dim 一个对应于array维度的integer。相应的实际参数不应为可选的虚拟参数。

  • mask 为逻辑类型,且应与array一致。

  • kind 标量整数初始化表达式(即常量)

  • back 逻辑标量。

  • 结果为默认种类或种类kindinteger(如果存在kind参数)。如果dim未出现,则结果为秩为一且大小等于array秩的数组;否则,结果为与array具有相同秩和形状的数组,但减少了维度dim

注意:指定为**的种类可以是该类型支持的任何种类

描述#

findloc(3) 返回array中沿维度dim第一个具有与value相等值的元素的位置,该元素由mask标识。

如果arrayvalue都是逻辑类型,则使用.eqv.运算符执行比较;否则,使用==运算符执行比较。如果比较结果为.true.,则array的该元素与value匹配。

如果只有一个元素与value匹配,则返回该元素的下标。否则,如果有多个元素与value匹配且back不存在或存在且值为.false.,则返回的元素是第一个此类元素,按数组元素顺序取。如果back存在且值为.true.,则返回的元素是最后一个此类元素,按数组元素顺序取。

选项#

  • array

    应为内在类型的数组。

  • value

    应为标量,且应与array类型一致。

  • dim

    应为整数标量,其值在范围1 <= DIM <= n内,其中n是array的秩。相应的实际参数不应为可选的虚拟参数。

  • mask

    (可选) 应为逻辑类型,且应与array一致。

  • kind

    (可选) 应为标量整数初始化表达式。

  • back

    (可选) 应为逻辑标量。

结果#

存在kind时,种类类型参数由kind的值指定;否则,种类类型参数为默认整数类型的种类。如果dim未出现,则结果为秩为一且大小等于array秩的数组;否则,结果为秩为n - 1且形状为

   [d1, d2, . . ., dDIM-1, dDIM+1, . . ., dn ]

其中

   [d1, d2, . . ., dn ]

array的形状。

结果#

  • 情况(i):findloc (array, value)的结果是一个秩为一的数组,其元素值为array中与value匹配的元素的下标值。如果存在这样的值,则返回的第i个下标位于范围1到ei内,其中ei是array的第i维的范围。如果没有元素与value匹配或array的大小为零,则结果的所有元素都为零。

  • 情况(ii):findloc (array, value, mask = mask)的结果是一个秩为一的数组,其元素值为array中与mask的真元素相对应的元素的下标值,其值与value匹配。如果存在这样的值,则返回的第i个下标位于范围1到ei内,其中ei是array的第i维的范围。如果没有元素与value匹配,array的大小为零,或者mask的每个元素的值都为false,则结果的所有元素都为零。

示例#

示例程序

program demo_findloc
logical,parameter :: T=.true., F=.false.
integer,allocatable :: ibox(:,:)
logical,allocatable :: mask(:,:)
  ! basics
   ! the first element matching the value is returned AS AN ARRAY
   call printi('== 6',findloc ([2, 6, 4, 6], value = 6))
   call printi('== 6',findloc ([2, 6, 4, 6], value = 6,back=.true.))
   ! the first element matching the value is returned AS A SCALAR
   call printi('== 6',findloc ([2, 6, 4, 6], value = 6,dim=1))
   call printi('== 6',findloc ([2, 6, 4, 6], value = 6,back=.true.,dim=1))

   ibox=reshape([ 0,-5,  7, 7, &
                  3, 4, -1, 2, &
                  1, 5,  6, 7] ,shape=[3,4],order=[2,1])

   mask=reshape([ T, T, F, T, &
                  T, T, F, T, &
                  T, T, F, T] ,shape=[3,4],order=[2,1])

   call printi('array is', ibox )
   call printl('mask  is', mask )
   print *, 'so for == 7 and back=.false.'
   call printi('so for == 7 the address of the element is', &
           & findloc (ibox, 7, mask = mask) )
   print *, 'so for == 7 and back=.true.'
   call printi('so for == 7 the address of the element is', &
           & findloc (ibox, 7, mask = mask, back=.true.) )

   print *,'This is independent of declared lower bounds for the array'

   print *, ' using dim=N'
   ibox=reshape([ 1,  2, -9,  &
                  2,  2,  6 ] ,shape=[2,3],order=[2,1])

   call printi('array is', ibox )
   ! has the value [2, 1, 0] and
   call printi('',findloc (ibox, value = 2, dim = 1) )
   ! has the value [2, 1].
   call printi('',findloc (ibox, value = 2, dim = 2) )
contains
! GENERIC ROUTINES TO PRINT MATRICES
subroutine printl(title,a)
implicit none
!@(#) print small 2d logical scalar, vector, matrix in row-column format
character(len=*),intent(in)  :: title
logical,intent(in)           :: a(..)

character(len=*),parameter   :: row='(" > [ ",*(l1:,","))'
character(len=*),parameter   :: all='(" ",*(g0,1x))'
logical,allocatable          :: b(:,:)
integer                      :: i
   write(*,all,advance='no')trim(title)
   ! copy everything to a matrix to keep code simple
   select rank(a)
   rank (0); write(*,'(a)')' (a scalar)'; b=reshape([a],[1,1])
   rank (1); write(*,'(a)')' (a vector)'; b=reshape(a,[size(a),1])
   rank (2); write(*,'(a)')' (a matrix)'; b=a
   rank default; stop '*printl* unexpected rank'
   end select
   do i=1,size(b,dim=1)
      write(*,fmt=row,advance='no')b(i,:)
      write(*,'(" ]")')
   enddo
   write(*,all) '>shape=',shape(a),',rank=',rank(a),',size=',size(a)
   write(*,*)
end subroutine printl

subroutine printi(title,a)
implicit none
!@(#) print small 2d integer scalar, vector, matrix in row-column format
character(len=*),intent(in)  :: title
integer,intent(in)           :: a(..)
character(len=*),parameter   :: all='(" ",*(g0,1x))'
character(len=20)            :: row
integer,allocatable          :: b(:,:)
integer                      :: i
   write(*,all,advance='no')trim(title)
   ! copy everything to a matrix to keep code simple
   select rank(a)
   rank (0); write(*,'(a)')' (a scalar)'; b=reshape([a],[1,1])
   rank (1); write(*,'(a)')' (a vector)'; b=reshape(a,[size(a),1])
   rank (2); write(*,'(a)')' (a matrix)'; b=a
   rank default; stop '*printi* unexpected rank'
   end select
   ! find how many characters to use for integers
   write(row,'(i0)')ceiling(log10(real(maxval(abs(b)))))+2
   ! use this format to write a row
   row='(" > [",*(i'//trim(row)//':,","))'
   do i=1,size(b,dim=1)
      write(*,fmt=row,advance='no')b(i,:)
      write(*,'(" ]")')
   enddo
   write(*,all) '>shape=',shape(a),',rank=',rank(a),',size=',size(a)
   write(*,*)
end subroutine printi
end program demo_findloc

结果

 >  == 6  (a vector)
 >  > [  2 ]
 >  >shape= 1 ,rank= 1 ,size= 1
 >
 >  == 6  (a vector)
 >  > [  4 ]
 >  >shape= 1 ,rank= 1 ,size= 1
 >
 >  == 6  (a scalar)
 >  > [  2 ]
 >  >shape= ,rank= 0 ,size= 1
 >
 >  == 6  (a scalar)
 >  > [  4 ]
 >  >shape= ,rank= 0 ,size= 1
 >
 >  array is  (a matrix)
 >  > [  0, -5,  7,  7 ]
 >  > [  3,  4, -1,  2 ]
 >  > [  1,  5,  6,  7 ]
 >  >shape= 3 4 ,rank= 2 ,size= 12
 >
 >  mask  is  (a matrix)
 >  > [ T,T,F,T ]
 >  > [ T,T,F,T ]
 >  > [ T,T,F,T ]
 >  >shape= 3 4 ,rank= 2 ,size= 12
 >
 >  so for == 7 and back=.false.
 >  so for == 7 the address of the element is  (a vector)
 >  > [  1 ]
 >  > [  4 ]
 >  >shape= 2 ,rank= 1 ,size= 2
 >
 >  so for == 7 and back=.true.
 >  so for == 7 the address of the element is  (a vector)
 >  > [  3 ]
 >  > [  4 ]
 >  >shape= 2 ,rank= 1 ,size= 2
 >
 >  This is independent of declared lower bounds for the array
 >   using dim=N
 >  array is  (a matrix)
 >  > [  1,  2, -9 ]
 >  > [  2,  2,  6 ]
 >  >shape= 2 3 ,rank= 2 ,size= 6
 >
 >    (a vector)
 >  > [  2 ]
 >  > [  1 ]
 >  > [  0 ]
 >  >shape= 3 ,rank= 1 ,size= 3
 >
 >    (a vector)
 >  > [  2 ]
 >  > [  1 ]
 >  >shape= 2 ,rank= 1 ,size= 2
 >

标准#

Fortran 95

另请参阅#

  • maxloc(3) - 数组中最大值的所在位置

  • minloc(3) - 数组中最小值的所在位置

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

transpose#

名称#

transpose(3) - [ARRAY:MANIPULATION] 转置秩为二的数组

概要#

    result = transpose(matrix)
     function transpose(matrix)

      type(TYPE(kind=KIND)            :: transpose(N,M)
      type(TYPE(kind=KIND),intent(in) :: matrix(M,N)

特性#

  • matrix 是任何类型且秩为二的数组。

  • 结果将与matrix具有相同的类型和种类,以及输入数组的反向形状

描述#

transpose(3) 转置秩为二的数组。

通过交换给定矩阵的行和列来转置数组。也就是说,结果的元素(i,j)对于所有(i,j)都具有输入的元素(j,i)的值。

选项#

  • matrix

    要转置的数组

结果#

输入数组的转置。结果与matrix具有相同的类型,如果matrix的形状为[ n, m ],则形状为[ m, n ]。

示例#

示例程序

program demo_transpose
implicit none
integer,save :: xx(3,5)= reshape([&
    1,  2,  3,  4,  5,    &
   10, 20, 30, 40, 50,    &
   11, 22, 33, 44, -1055  &
 ],shape(xx),order=[2,1])

call print_matrix_int('xx array:',xx)
call print_matrix_int('xx array transposed:',transpose(xx))

contains

subroutine print_matrix_int(title,arr)
! print small 2d integer arrays in row-column format
implicit none
character(len=*),intent(in)  :: title
integer,intent(in)           :: arr(:,:)
integer                      :: i
character(len=:),allocatable :: biggest
   write(*,*)trim(title)  ! print title
   biggest='           '  ! make buffer to write integer into
   ! find how many characters to use for integers
   write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
   ! use this format to write a row
   biggest='(" > [",*(i'//trim(biggest)//':,","))'
   ! print one row of array at a time
   do i=1,size(arr,dim=1)
      write(*,fmt=biggest,advance='no')arr(i,:)
      write(*,'(" ]")')
   enddo
end subroutine print_matrix_int

end program demo_transpose

结果

    xx array:
    > [     1,     2,     3,     4,     5 ]
    > [    10,    20,    30,    40,    50 ]
    > [    11,    22,    33,    44, -1055 ]
    xx array transposed:
    > [     1,    10,    11 ]
    > [     2,    20,    22 ]
    > [     3,    30,    33 ]
    > [     4,    40,    44 ]
    > [     5,    50, -1055 ]

标准#

Fortran 95

另请参阅#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

all#

名称#

all(3) - [ARRAY:REDUCTION] 确定所有值是否都为真

概要#

   result = all(mask [,dim])
     function all(mask ,dim)

      logical(kind=KIND),intent(in) :: mask(..)
      integer,intent(in),optional   :: dim
      logical(kind=KIND)            :: all(..)

特性#

  • masklogical数组

  • diminteger

  • 如果提供了dim,则结果为逻辑数组,否则为逻辑标量。它与mask具有相同的特性

描述#

all(3) 确定mask中沿维度dim的所有值是否都为真(如果指定了dim);否则,所有元素都将一起测试。

此测试类型称为沿维度dimmask元素的逻辑合取。

mask通常是logical表达式,允许比较数组和许多其他常见操作。

选项#

  • mask

    要测试所有元素是否为.true的逻辑数组。

  • dim

    dim 指示mask元素中用于对元素进行分组以进行测试的方向。

    dim 的值介于1和mask的秩之间。

    相应的实际参数不应为可选的虚拟参数。

    如果dim不存在,则测试所有元素并返回单个标量值。

结果#

  1. 如果dim不存在,则all(mask).true.,如果mask的所有元素都为.true.。如果mask的大小为零,它也为.true.;否则,它为.false.

  2. 如果mask的秩为一,则all(mask, dim)等效于all(mask)

  3. 如果**mask**的秩大于1且存在**dim**,则**all(mask,dim)**返回一个秩比**mask**少1的数组。数组的形状由**mask**的形状决定,其中**dim**维度被省略。对于沿着**dim**维度上的每一组元素,都会返回一个值。

示例#

示例程序

program demo_all
implicit none
logical,parameter :: T=.true., F=.false.
logical bool
  ! basic usage
   ! is everything true?
   bool = all([ T,T,T ])
   bool = all([ T,F,T ])
   print *, bool

  ! by a dimension
   ARRAYS: block
   integer :: a(2,3), b(2,3)
    ! set everything to one except one value in b
    a = 1
    b = 1
    b(2,2) = 2
    ! now compare those two arrays
    print *,'entire array :', all(a ==  b )
    print *,'compare columns:', all(a ==  b, dim=1)
    print *,'compare rows:', all(a ==  b, dim=2)
  end block ARRAYS

end program demo_all

结果

 >  T
 >  F
 >  entire array : F
 >  compare columns: T F T
 >  compare rows: T F

标准#

Fortran 95

另请参阅#

任何(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

any#

名称#

any(3) - [数组:归约] 确定逻辑数组中的任何值是否为.true.

概要#

    result = any(mask [,dim])
     function any(mask, dim)

      logical(kind=KIND),intent(in) :: mask(..)
      integer,intent(in),optional   :: dim
      logical(kind=KIND)            :: any(..)

特性#

  • masklogical数组

  • **dim**是一个标量整数

  • 如果提供了**dim**,则结果为逻辑数组,否则为逻辑标量。

描述#

any(3) 确定逻辑数组**mask**沿维度**dim**的任何值是否为.true.

选项#

  • mask

    要分组或全部测试以查找.true.值的逻辑表达式或值的数组。

  • dim

    一个位于1和**rank(mask)**之间的整数,指示返回沿指定维度的值数组而不是标量答案。

结果#

any(mask)返回一个类型为逻辑的标量值,其种类类型参数与**mask**的种类类型参数相同。如果存在**dim**,则**any(mask, dim)**返回一个秩比**mask**少1的数组。数组的形状由**mask**的形状决定,其中**dim**维度被省略。

  1. 如果**mask**的任何元素为.true.,则**any(mask)**为.true.;否则为.false.。如果**mask**的大小为零,则也为.false.

  2. 如果**mask**的秩为1,则**any(mask, dim)**等效于**any(mask)**。如果秩大于1,则**any(mask, dim)**通过将**any(mask)**应用于数组节来确定。

示例#

示例程序

program demo_any
implicit none
logical,parameter :: T=.true., F=.false.
integer           :: a(2,3), b(2,3)
logical           :: bool
  ! basic usage
   bool = any([F,F,T,F])
   print *,bool
   bool = any([F,F,F,F])
   print *,bool
  ! fill two integer arrays with values for testing
   a = 1
   b = 1
   b(:,2) = 2
   b(:,3) = 3
  ! using any(3) with logical expressions you can compare two arrays
  ! in a myriad of ways
   ! first, print where elements of b are bigger than in a
   call printl( 'first print b > a             ', b > a         )
   ! now use any() to test
   call printl( 'any true values?  any(b > a)  ', any(b > a )   )
   call printl( 'again by columns? any(b > a,1)', any(b > a, 1) )
   call printl( 'again by rows?    any(b > a,2)', any(b > a, 2) )
contains
! CONVENIENCE ROUTINE. this is not specific to ANY()
subroutine printl(title,a)
use, intrinsic :: iso_fortran_env, only : &
 & stderr=>ERROR_UNIT,&
 & stdin=>INPUT_UNIT,&
 & stdout=>OUTPUT_UNIT
implicit none

!@(#) print small 2d logical scalar, vector, or matrix

character(len=*),parameter   :: all='(*(g0,1x))'
character(len=*),parameter   :: row='(" > [ ",*(l1:,","))'
character(len=*),intent(in)  :: title
logical,intent(in)           :: a(..)
integer                      :: i
   write(*,*)
   write(*,all,advance='no')trim(title),&
    & ' : shape=',shape(a),',rank=',rank(a),',size=',size(a)
   ! get size and shape of input
   select rank(a)
   rank (0); write(*,'(a)')'(a scalar)'
      write(*,fmt=row,advance='no')a
      write(*,'(" ]")')
   rank (1); write(*,'(a)')'(a vector)'
      do i=1,size(a)
         write(*,fmt=row,advance='no')a(i)
         write(*,'(" ]")')
      enddo
   rank (2); write(*,'(a)')'(a matrix) '
      do i=1,size(a,dim=1)
         write(*,fmt=row,advance='no')a(i,:)
         write(*,'(" ]")')
      enddo
   rank default
      write(stderr,*)'*printl* did not expect rank=', rank(a), &
       & 'shape=', shape(a),'size=',size(a)
      stop '*printl* unexpected rank'
   end select

end subroutine printl

end program demo_any

结果

 >  T
 >  F
 >
 > first print b > a : shape=23,rank=2,size=6(a matrix)
 >  > [ F,T,T ]
 >  > [ F,T,T ]
 >
 > any true values?  any(b > a) : shape=,rank=0,size=1(a scalar)
 >  > [ T ]
 >
 > again by columns? any(b > a,1) : shape=3,rank=1,size=3(a vector)
 >  > [ F ]
 >  > [ T ]
 >  > [ T ]
 >
 > again by rows?    any(b > a,2) : shape=2,rank=1,size=2(a vector)
 >  > [ T ]
 >  > [ T ]

标准#

Fortran 95

另请参阅#

全部(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

count#

名称#

count(3) - [数组:归约] 统计数组中真值的数量

概要#

    result = count(mask [,dim] [,kind] )
     integer(kind=KIND) function count(mask, dim, KIND )

      logical(kind=**),intent(in) :: mask(..)
      integer(kind=**),intent(in),optional :: dim
      integer(kind=**),intent(in),optional :: KIND

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • **mask**是任何形状和种类的逻辑数组。

  • 如果存在**dim**,则结果为一个去掉了指定秩的数组。

  • **KIND**是一个作为整数种类的有效标量整数常量表达式

  • 除非指定了**kind**来声明结果的种类,否则返回值为默认的整数类型。

描述#

count(3) 统计逻辑**mask**中.true.元素的数量,或者,如果提供了**dim**参数,则统计数组在**dim**方向上每行的元素数量。如果数组大小为零或**mask**的所有元素都为假,则结果为0

选项#

  • mask

    要统计.true.值数量的数组

  • dim

    指定从结果中删除此维度并生成沿已删除维度统计.true.值数量的数组。如果不存在,则结果为**mask**中真元素的标量计数,该值必须在范围1 <= dim <= n内,其中n是**mask**的秩(维度数)。

    相应的实际参数不应是可选的虚拟参数、解除关联的指针或未分配的可分配对象。

  • kind

    一个 integer 初始化表达式,指示结果的种类参数。

结果#

如果不存在**dim**,则返回值为**mask**中.true.值的个数。

如果存在**dim**,则结果为一个秩比输入数组**mask**的秩小1的数组,并且大小对应于**array**的形状,其中**dim**维度被删除,其余元素包含沿已删除维度的.true.元素的数量。

示例#

示例程序

   program demo_count
   implicit none
   character(len=*),parameter :: ints='(*(i2,1x))'
   ! two arrays and a mask all with the same shape
   integer, dimension(2,3) :: a, b
   logical, dimension(2,3) :: mymask
   integer :: i
   integer :: c(2,3,4)

   print *,'the numeric arrays we will compare'
   a = reshape( [ 1, 2, 3, 4, 5, 6 ], [ 2, 3 ])
   b = reshape( [ 0, 7, 3, 4, 5, 8 ], [ 2, 3 ])
   c = reshape( [( i,i=1,24)], [ 2, 3 ,4])
   print '(3i3)', a(1,:)
   print '(3i3)', a(2,:)
   print *
   print '(3i3)', b(1,:)
   print '(3i3)', b(2,:)
   !
   ! basic calls
   print *, 'count a few basic things creating a mask from an expression'
   print *, 'count a>b',count(a>b)
   print *, 'count b<a',count(a<b)
   print *, 'count b==a',count(a==b)
   print *, 'check sum = ',count(a>b) + &
                         & count(a<b) + &
                         & count(a==b).eq.size(a)
   !
   ! The common usage is just getting a count, but if you want
   ! to specify the DIM argument and get back reduced arrays
   ! of counts this is easier to visualize if we look at a mask.
   print *, 'make a mask identifying unequal elements ...'
   mymask = a.ne.b
   print *, 'the mask generated from a.ne.b'
   print '(3l3)', mymask(1,:)
   print '(3l3)', mymask(2,:)
   !
   print *,'count total and along rows and columns ...'
   !
   print '(a)', 'number of elements not equal'
   print '(a)', '(ie. total true elements in the mask)'
   print '(3i3)', count(mymask)
   !
   print '(a)', 'count of elements not equal in each column'
   print '(a)', '(ie. total true elements in each column)'
   print '(3i3)', count(mymask, dim=1)
   !
   print '(a)', 'count of elements not equal in each row'
   print '(a)', '(ie. total true elements in each row)'
   print '(3i3)', count(mymask, dim=2)
   !
   ! working with rank=3 ...
   print *, 'lets try this with c(2,3,4)'
   print *,'  taking the result of the modulo   '
   print *,'   z=1      z=2      z=3      z=4   '
   print *,'  1 3 0 || 2 4 1 || 3 0 2 || 4 1 3 |'
   print *,'  2 4 1 || 3 0 2 || 4 1 3 || 0 2 4 |'
   print *,'                                    '
   print *,'  would result in the mask ..       '
   print *,'  F F T || F F F || F T F || F F F |'
   print *,'  F F F || F T F || F F F || T F F |'
   print *,'                                    '
   print *,' the total number of .true.values is'
   print ints, count(modulo(c,5).eq.0)
   call printi('counting up along a row and removing rows',&
   count(modulo(c,5).eq.0,dim=1))
   call printi('counting up along a column and removing columns',&
   count(modulo(c,5).eq.0,dim=2))
   call printi('counting up along a depth and removing depths',&
   count(modulo(c,5).eq.0,dim=3))
   !
   contains
   !
   ! CONVENIENCE ROUTINE FOR PRINTING SMALL INTEGER MATRICES
   subroutine printi(title,arr)
   implicit none
   !
   !@(#) print small 2d integer arrays in row-column format
   !
   character(len=*),parameter :: all='(*(g0,1x))' ! a handy format
   character(len=*),intent(in)  :: title
   integer,intent(in)           :: arr(:,:)
   integer                      :: i
   character(len=:),allocatable :: biggest
      !
      print all
      print all, trim(title),':(',shape(arr),')'  ! print title
      biggest='           '  ! make buffer to write integer into
      ! find how many characters to use for integers
      write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
      ! use this format to write a row
      biggest='(" > [",*(i'//trim(biggest)//':,","))'
      ! print one row of array at a time
      do i=1,size(arr,dim=1)
         write(*,fmt=biggest,advance='no')arr(i,:)
         write(*,'(" ]")')
      enddo
      !
   end subroutine printi
   end program demo_count

结果

 >   the numeric arrays we will compare
 >    1  3  5
 >    2  4  6
 >
 >    0  3  5
 >    7  4  8
 >   count a few basic things creating a mask from an expression
 >   count a>b           1
 >   count b<a           2
 >   count b==a           3
 >   check sum =  T
 >   make a mask identifying unequal elements ...
 >   the mask generated from a.ne.b
 >    T  F  F
 >    T  F  T
 >   count total and along rows and columns ...
 >  number of elements not equal
 >  (ie. total true elements in the mask)
 >    3
 >  count of elements not equal in each column
 >  (ie. total true elements in each column)
 >    2  0  1
 >  count of elements not equal in each row
 >  (ie. total true elements in each row)
 >    1  2
 >   lets try this with c(2,3,4)
 >     taking the result of the modulo
 >      z=1      z=2      z=3      z=4
 >     1 3 0 || 2 4 1 || 3 0 2 || 4 1 3 |
 >     2 4 1 || 3 0 2 || 4 1 3 || 0 2 4 |
 >
 >     would result in the mask ..
 >     F F T || F F F || F T F || F F F |
 >     F F F || F T F || F F F || T F F |
 >
 >    the total number of .true.values is
 >   4
 >
 >  counting up along a row and removing rows :( 3 4 )
 >   > [ 0, 0, 0, 1 ]
 >   > [ 0, 1, 1, 0 ]
 >   > [ 1, 0, 0, 0 ]
 >
 >  counting up along a column and removing columns :( 2 4 )
 >   > [ 1, 0, 1, 0 ]
 >   > [ 0, 1, 0, 1 ]
 >
 >  counting up along a depth and removing depths :( 2 3 )
 >   > [ 0, 1, 1 ]
 >   > [ 1, 1, 0 ]

标准#

Fortran 95,带 KIND 参数 - Fortran 2003

另请参阅#

any(3), all(3), sum(3),

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

maxval#

名称#

maxval(3) - [数组:归约] 确定数组或行中的最大值

概要#

    result = maxval(array [,mask]) | maxval(array [,dim] [,mask])
     NUMERIC function maxval(array ,dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • **NUMERIC**表示任何数值类型和种类。

描述#

maxval(3) 确定数组值中元素的最大值,或者,如果提供了**dim**参数,则确定数组在**dim**方向上每行的最大值。如果存在**mask**,则只考虑**mask**为.true.的元素。如果数组大小为零,或者**mask**的所有元素都为.false.,则结果为**array**的类型和种类的最小负数(如果**array**是数值类型),或者如果**array**是字符类型,则为一个空字符串。

选项#

  • array

    应为整数实数字符类型的数组。

  • dim

    (可选) 应为整数类型的标量,其值介于 1 和 array 的秩之间(包括 1 和秩)。它不能是可选的哑元参数。

  • mask

    (可选)应为类型为逻辑的数组,并且与**array**一致。

结果#

如果**dim**不存在,或者**array**的秩为1,则结果为标量。如果存在**dim**,则结果为一个秩比**array**的秩小1的数组,并且大小对应于**array**的大小,其中**dim**维度被删除。在所有情况下,结果与**array**的类型和种类相同。

示例#

示例程序

program demo_maxval
implicit none
integer,save :: ints(3,5)= reshape([&
   1,  2,  3,  4,  5, &
  10, 20, 30, 40, 50, &
  11, 22, 33, 44, 55  &
],shape(ints),order=[2,1])

   write(*,*) maxval(ints)
   write(*,*) maxval(ints,dim=1)
   write(*,*) maxval(ints,dim=2)
   ! find biggest number less than 30 with mask
   write(*,*) maxval(ints,mask=ints.lt.30)
end program demo_maxval

结果

 >  55
 >  11     22     33     44     55
 >   5     50     55
 >  22

标准#

Fortran 95

另请参阅#

maxloc(3), minloc(3), minval(3), max(3), min(3)

fortran-lang 内在描述

minval#

名称#

minval(3) - [数组:归约] 数组的最小值

概要#

    result = minval(array, [mask]) | minval(array [,dim] [,mask])
     NUMERIC function minval(array, dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • NUMERIC 是任何数值类型和种类。

描述#

minval(3) 确定数组值中元素的最小值,或者,如果提供了**dim**参数,则确定数组在**dim**方向上每行的最小值。

如果存在**mask**,则只考虑**mask**为.true.的元素。

如果数组大小为零,或者**mask**的所有元素都为.false.,则结果为huge(array)(如果**array**是数值类型),或者如果**array**是字符类型,则为一个长度为char(len=255)的字符字符串。

选项#

  • array

    应为整数实数字符类型的数组。

  • dim

    (可选)应为类型为整数的标量,其值在1到ARRAY的秩之间(包括1和秩)。它不能是可选的虚拟参数。

  • mask

    应为类型为logical的数组,且与array一致。

结果#

如果**dim**不存在,或者**array**的秩为1,则结果为标量。

如果存在**dim**,则结果为一个秩比**array**的秩小1的数组,并且大小对应于**array**的大小,其中**dim**维度被删除。在所有情况下,结果与**array**的类型和种类相同。

示例#

示例程序

program demo_minval
implicit none
integer :: i
character(len=*),parameter :: g='(3x,*(g0,1x))'

integer,save :: ints(3,5)= reshape([&
       1,  -2,   3,   4,   5,  &
      10,  20, -30,  40,  50,  &
      11,  22,  33, -44,  55  &
],shape(ints),order=[2,1])

integer,save :: box(3,5,2)

   box(:,:,1)=ints
   box(:,:,2)=-ints

   write(*,*)'Given the array'
   write(*,'(1x,*(g4.4,1x))') &
   & (ints(i,:),new_line('a'),i=1,size(ints,dim=1))

   write(*,*)'What is the smallest element in the array?'
   write(*,g) minval(ints),'at <',minloc(ints),'>'

   write(*,*)'What is the smallest element in each column?'
   write(*,g) minval(ints,dim=1)

   write(*,*)'What is the smallest element in each row?'
   write(*,g) minval(ints,dim=2)

   ! notice the shape of the output has less columns
   ! than the input in this case
   write(*,*)'What is the smallest element in each column,'
   write(*,*)'considering only those elements that are'
   write(*,*)'greater than zero?'
   write(*,g) minval(ints, dim=1, mask = ints > 0)

   write(*,*)&
   & 'if everything is false a zero-sized array is NOT returned'
   write(*,*) minval(ints, dim=1, mask = .false.)
   write(*,*)'even for a zero-sized input'
   write(*,g) minval([integer ::], dim=1, mask = .false.)

   write(*,*)'a scalar answer for everything false is huge()'
   write(*,g) minval(ints, mask = .false.)
   write(*,g) minval([integer ::], mask = .false.)

   write(*,*)'some calls with three dimensions'
   write(*,g) minval(box, mask = .true. )
   write(*,g) minval(box, dim=1, mask = .true. )

   write(*,g) minval(box, dim=2, mask = .true. )
   write(*,g) 'shape of answer is ', &
   & shape(minval(box, dim=2, mask = .true. ))

end program demo_minval

结果

 > Given the array
 >    1   -2    3    4    5
 >   10   20  -30   40   50
 >   11   22   33  -44   55
 >
 > What is the smallest element in the array?
 >   -44 at < 3 4 >
 > What is the smallest element in each column?
 >   1 -2 -30 -44 5
 > What is the smallest element in each row?
 >   -2 -30 -44
 > What is the smallest element in each column,
 > considering only those elements that are
 > greater than zero?
 >   1 20 3 4 5
 > if everything is false a zero-sized array is NOT returned
 >  2147483647  2147483647  2147483647  2147483647  2147483647
 > even for a zero-sized input
 >   2147483647
 > a scalar answer for everything false is huge()
 >   2147483647
 >   2147483647
 > some calls with three dimensions
 >   -55
 >   1 -2 -30 -44 5 -11 -22 -33 -40 -55
 >   -2 -30 -44 -5 -50 -55
 >   shape of answer is  3 2

标准#

Fortran 95

另请参阅#

min(3), minloc(3) maxloc(3), maxval(3), min(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

product#

名称#

product(3) - [数组:归约] 数组元素的乘积

概要#

    result = product(array [,dim] [,mask])
     NUMERIC function product(array, dim, mask)

      NUMERIC,intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • NUMERIC 是任何数值类型和种类。

描述#

product(3) 将**array**的所有选定元素相乘,或者如果**mask**中相应的元素为.true.,则沿维度**dim**相乘。

如果不存在**dim**,则返回一个包含**array**中所有元素乘积的标量。(注意,零大小的**array**返回1)。

当存在**dim**时,如果掩码数组的维度为1(即向量),则结果为标量。否则,返回一个秩为n-1的数组,其中n等于**array**的秩,并且形状类似于**array**,但去掉了维度**dim**。

选项#

  • array

    应为类型为整数实数复数的数组。

  • dim

    应为类型为整数的标量,其值在1到n范围内,其中n等于**array**的秩。

  • mask

    应为类型为逻辑,并且可以是标量或与**array**形状相同的数组。

结果#

结果与数组类型相同。

示例#

示例程序

program demo_product
implicit none
character(len=*),parameter :: all='(*(g0,1x))' ! a handy format
character(len=1),parameter :: nl=new_line('a')

NO_DIM: block
!    If DIM is not specified, the result is the product of all the
!    selected array elements.
integer :: i,n, p1, p2
integer,allocatable :: array(:)
   ! all elements are selected by default
   do n=1,10
      print all, 'factorial of ',n,' is ', product([(real(i),i=1,n)])
   enddo

   ! using a mask
   array=[10,12,13,15,20,25,30]
   p1=product(array, mask=mod(array, 2)==1) ! only odd elements
   p2=product(array, mask=mod(array, 2)/=1) ! only even elements
   print all, nl,'product of all elements',product(array) ! all elements
   print all, ' odd * even =',nl,p1,'*',p2,'=',p1*p2

   ! NOTE: If ARRAY is a zero-sized array, the result is equal to one
   print all
   print all, 'zero-sized array=>',product([integer :: ])
   ! NOTE: If nothing in the mask is true, this also results in a null
   !       array
   print all, 'all elements have a false mask=>', &
            & product(array,mask=.false.)

endblock NO_DIM

WITH_DIM: block
integer :: rect(2,3)
integer :: box(2,3,4)

!  lets fill a few arrays
   rect = reshape([ &
     1, 2, 3,       &
     4, 5, 6        &
   ],shape(rect),order=[2,1])
   call print_matrix_int('rect',rect)

!  Find the product of each column in RECT.
   print all, 'product of columns=',product(rect, dim = 1)

! Find the product of each row in RECT.
   print all, 'product of rows=',product(rect, dim = 2)

! now lets try a box
   box(:,:,1)=rect
   box(:,:,2)=rect*(+10)
   box(:,:,3)=rect*(-10)
   box(:,:,4)=rect*2
   ! lets look at the values
   call print_matrix_int('box 1',box(:,:,1))
   call print_matrix_int('box 2',box(:,:,2))
   call print_matrix_int('box 3',box(:,:,3))
   call print_matrix_int('box 4',box(:,:,4))

   ! remember without dim= even a box produces a scalar
   print all, 'no dim gives a scalar',product(real(box))

   ! only one plane has negative values, so note all the "1" values
   ! for vectors with no elements
   call print_matrix_int('negative values', &
   & product(box,mask=box < 0,dim=1))

!   If DIM is specified and ARRAY has rank greater than one, the
!   result is a new array in which dimension DIM has been eliminated.

   ! pick a dimension to multiply though
   call print_matrix_int('dim=1',product(box,dim=1))

   call print_matrix_int('dim=2',product(box,dim=2))

   call print_matrix_int('dim=3',product(box,dim=3))

endblock WITH_DIM

contains

   subroutine print_matrix_int(title,arr)
   implicit none

   !@(#) print small 2d integer arrays in row-column format

   character(len=*),intent(in)  :: title
   integer,intent(in)           :: arr(:,:)
   integer                      :: i
   character(len=:),allocatable :: biggest

      print all
      print all, trim(title),':(',shape(arr),')'  ! print title
      biggest='           '  ! make buffer to write integer into
      ! find how many characters to use for integers
      write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
      ! use this format to write a row
      biggest='(" > [",*(i'//trim(biggest)//':,","))'
      ! print one row of array at a time
      do i=1,size(arr,dim=1)
         write(*,fmt=biggest,advance='no')arr(i,:)
         write(*,'(" ]")')
      enddo

   end subroutine print_matrix_int

end program demo_product

结果

factorial of  1  is  1.000000
factorial of  2  is  2.000000
factorial of  3  is  6.000000
factorial of  4  is  24.00000
factorial of  5  is  120.0000
factorial of  6  is  720.0000
factorial of  7  is  5040.000
factorial of  8  is  40320.00
factorial of  9  is  362880.0
factorial of  10  is  3628800.

 product of all elements 351000000
 odd * even =
 4875 * 72000 = 351000000

zero-sized array=> 1
all elements have a false mask=> 1

rect :( 2 3 )
 > [  1,  2,  3 ]
 > [  4,  5,  6 ]
product of columns= 4 10 18
product of rows= 6 120

box 1 :( 2 3 )
 > [  1,  2,  3 ]
 > [  4,  5,  6 ]

box 2 :( 2 3 )
 > [  10,  20,  30 ]
 > [  40,  50,  60 ]

box 3 :( 2 3 )
 > [ -10, -20, -30 ]
 > [ -40, -50, -60 ]

box 4 :( 2 3 )
 > [   2,   4,   6 ]
 > [   8,  10,  12 ]
no dim gives a scalar .1719927E+26

negative values :( 3 4 )
 > [     1,     1,   400,     1 ]
 > [     1,     1,  1000,     1 ]
 > [     1,     1,  1800,     1 ]

dim=1 :( 3 4 )
 > [     4,   400,   400,    16 ]
 > [    10,  1000,  1000,    40 ]
 > [    18,  1800,  1800,    72 ]

dim=2 :( 2 4 )
 > [       6,    6000,   -6000,      48 ]
 > [     120,  120000, -120000,     960 ]

dim=3 :( 2 3 )
 > [    -200,   -3200,  -16200 ]
 > [  -51200, -125000, -259200 ]

标准#

Fortran 95

另请参阅#

sum(3),请注意,元素之间的乘法直接使用星号字符完成。

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

sum#

名称#

sum(3) - [ARRAY:REDUCTION] 对数组的元素求和

语法#

   result = sum(array [,dim[,mask]] | [mask] )
     TYPE(kind=KIND) function sum(array, dim, mask)

      TYPE(kind=KIND),intent(in) :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类。

  • array 可以是任何数值类型 - 整数实数复数

  • diminteger

  • mask逻辑类型,且与array 兼容。

  • 结果与array 的类型和种类相同。如果dim 不存在或array 是向量,则结果为标量;否则,结果为数组。

描述#

sum(3) 对array 的元素进行求和。

当仅指定array 时,会对所有元素求和,但可以通过dim 指定的维度返回求和的组,或者可以通过逻辑掩码选择要添加的元素。

没有指定求和的具体方法,因此是否补偿累积误差取决于处理器。

选项#

  • array

    包含要添加的元素的数组

  • dim

    一个介于 1 到 n 之间的值,其中 n 等于array 的秩(维度数)。dim 指定要创建求和的维度。如果不存在,则返回可选地由mask 选择的元素的标量和。

  • mask

    一个与array 形状相同的数组,用于指定要添加的元素。如果不存在,则所有元素都用于求和。

结果#

如果dim 不存在,则返回一个包含array 中所有选定元素之和的标量。否则,返回一个秩为 n-1 的数组,其中 n 等于array 的秩,并且形状类似于array,但去掉了维度dim。由于向量的秩为 1,因此结果为标量(如果 n==1,n-1 为零;秩为零表示标量)。

示例#

示例程序

program demo_sum
implicit none
integer :: vector(5) , matrix(3,4), box(5,6,7)

   vector = [ 1, 2, -3, 4, 5 ]

   matrix(1,:)=[  -1,   2,    -3,   4    ]
   matrix(2,:)=[  10,   -20,  30,   -40  ]
   matrix(3,:)=[  100,  200, -300,  400  ]

   box=11

  ! basics
   print *, 'sum all elements:',sum(vector)
   print *, 'real :',sum([11.0,-5.0,20.0])
   print *, 'complex :',sum([(1.1,-3.3),(4.0,5.0),(8.0,-6.0)])
  ! with MASK option
   print *, 'sum odd elements:',sum(vector, mask=mod(vector, 2)==1)
   print *, 'sum positive values:', sum(vector, mask=vector>0)

   call printi('the input array', matrix )
   call printi('sum of all elements in matrix', sum(matrix) )
   call printi('sum of positive elements', sum(matrix,matrix>=0) )
  ! along dimensions
   call printi('sum along rows', sum(matrix,dim=1) )
   call printi('sum along columns', sum(matrix,dim=2) )
   call printi('sum of a vector is always a scalar', sum(vector,dim=1) )
   call printi('sum of a volume by row', sum(box,dim=1) )
   call printi('sum of a volume by column', sum(box,dim=2) )
   call printi('sum of a volume by depth', sum(box,dim=3) )

contains
! CONVENIENCE ROUTINE; NOT DIRECTLY CONNECTED TO SPREAD(3)
subroutine printi(title,a)
use, intrinsic :: iso_fortran_env, only : stderr=>ERROR_UNIT,&
 & stdin=>INPUT_UNIT, stdout=>OUTPUT_UNIT
implicit none

!@(#) print small 2d integer scalar, vector, matrix in row-column format

character(len=*),intent(in)  :: title
integer,intent(in)           :: a(..)

character(len=*),parameter   :: all='(" ",*(g0,1x))'
character(len=20)            :: row
integer,allocatable          :: b(:,:)
integer                      :: i
   write(*,all,advance='no')trim(title)
   ! copy everything to a matrix to keep code simple
   select rank(a)
   rank (0); write(*,'(a)')' (a scalar)'; b=reshape([a],[1,1])
   rank (1); write(*,'(a)')' (a vector)'; b=reshape(a,[size(a),1])
   rank (2); write(*,'(a)')' (a matrix)'; b=a
   rank default; stop '*printi* unexpected rank'
   end select
   ! find how many characters to use for integers
   write(row,'(i0)')ceiling(log10(real(maxval(abs(b)))))+2
   ! use this format to write a row
   row='(" > [",*(i'//trim(row)//':,","))'
   do i=1,size(b,dim=1)
      write(*,fmt=row,advance='no')b(i,:)
      write(*,'(" ]")')
   enddo
   write(*,all) '>shape=',shape(a),',rank=',rank(a),',size=',size(a)
   write(*,*)
end subroutine printi
end program demo_sum

结果

    sum all elements:           9
    real :   26.00000
    complex : (13.10000,-4.300000)
    sum odd elements:           6
    sum positive values:          12
    the input array  (a matrix)
    > [   -1,    2,   -3,    4 ]
    > [   10,  -20,   30,  -40 ]
    > [  100,  200, -300,  400 ]
    >shape= 3 4 ,rank= 2 ,size= 12

    sum of all elements in matrix  (a scalar)
    > [  382 ]
    >shape= ,rank= 0 ,size= 1

    sum of positive elements  (a scalar)
    > [  746 ]
    >shape= ,rank= 0 ,size= 1

    sum along rows  (a vector)
    > [  109 ]
    > [  182 ]
    > [ -273 ]
    > [  364 ]
    >shape= 4 ,rank= 1 ,size= 4

    sum along columns  (a vector)
    > [    2 ]
    > [  -20 ]
    > [  400 ]
    >shape= 3 ,rank= 1 ,size= 3

    sum of a vector is always a scalar  (a scalar)
    > [  9 ]
    >shape= ,rank= 0 ,size= 1

    sum of a volume by row  (a matrix)
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    > [  55,  55,  55,  55,  55,  55,  55 ]
    >shape= 6 7 ,rank= 2 ,size= 42

    sum of a volume by column  (a matrix)
    > [  66,  66,  66,  66,  66,  66,  66 ]
    > [  66,  66,  66,  66,  66,  66,  66 ]
    > [  66,  66,  66,  66,  66,  66,  66 ]
    > [  66,  66,  66,  66,  66,  66,  66 ]
    > [  66,  66,  66,  66,  66,  66,  66 ]
    >shape= 5 7 ,rank= 2 ,size= 35

    sum of a volume by depth  (a matrix)
    > [  77,  77,  77,  77,  77,  77 ]
    > [  77,  77,  77,  77,  77,  77 ]
    > [  77,  77,  77,  77,  77,  77 ]
    > [  77,  77,  77,  77,  77,  77 ]
    > [  77,  77,  77,  77,  77,  77 ]
    >shape= 5 6 ,rank= 2 ,size= 30

标准#

Fortran 95

另请参阅#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

reshape#

名称#

reshape(3) - [ARRAY:RESHAPE] 用于重塑数组的函数

语法#

    result = reshape( source, shape [,pad] [,order] )
     type(TYPE(kind=KIND) function reshape

      type(TYPE(kind=KIND),intent(in)          :: source(..)
      integer(kind=**),intent(in)              :: shape(:)
      type(TYPE(kind=KIND),intent(in),optional :: pad(..)
      integer(kind=**),intent(in),optional     :: order(:)

特性#

  • source 是任何类型的数组

  • shape 定义了 Fortran 形状,因此是一个大小恒定的整数向量(秩为 1),最多包含 16 个非负值。

  • padsource 类型相同

  • ordershape 形状相同

  • 结果是形状为shape,类型与source 相同的数组。

  • 指定为 ** 的种类可以是该类型支持的任何种类。

描述#

reshape 使用来自source 以及可能来自pad 的元素构造一个任意形状的shape 数组。

如有必要,可以使用pad 中的元素填充新数组,或者根据order 定义的顺序进行排列。

在许多其他用途当中,reshape 可用于重新排序 Fortran 数组以匹配 C 数组排序,然后将数组从 Fortran 传递到 C 过程。

选项#

  • source

    包含要复制到结果中的元素的数组。如果省略pad 或其大小为零,则source 中必须有足够的元素来填充新形状。用 Fortran 表示为……

   if(.not.present(pad))then
      if(size(source) < product(shape))then
        stop 'not enough elements in the old array to fill the new one'
      endif
   endif
  • 形状

    这是正在生成的新的数组的形状。根据定义,形状的所有元素都是正整数或零,大小必须为 1 或更大,它最多可以有 16 个元素,但必须是恒定固定大小且秩为 1 的。

  • pad

    如果结果数组大于source,则用于填充额外的值。在将source 的所有元素都放入结果之后,它将被重复使用,直到结果的所有元素都被赋值。

    如果它不存在或是一个零大小的数组,则只能将source 转换为与source 大小相同或更小的另一个数组。

  • order

    用于以与正常 Fortran 数组元素顺序不同的顺序插入结果中的元素,在默认情况下,最左边的秩变化最快。

    根据秩的定义,这些值必须是 1 到 n 之间数字的排列,其中 n 是shape 的秩。

    source 和 pad 的元素按顺序放置到结果中;默认情况下,最左边的秩变化最快。若要更改元素在结果中放置的顺序,请使用order

结果#

结果是形状为shape,类型和类型参数与source 相同的数组。它首先填充source 元素的值,其余部分则重复填充pad 的副本,直到所有元素都被填充。新数组可能小于source

示例#

示例程序

program demo_reshape
implicit none
! notice the use of "shape(box)" on the RHS
integer :: box(3,4)=reshape([1,2,3,4,5,6,7,8,9,10,11,12],shape(box))
integer,allocatable :: v(:,:)
integer :: rc(2)
   ! basics0
    ! what is the current shape of the array?
    call printi('shape of box is ',box)
    ! change the shape
    call printi('reshaped ',reshape(box,[2,6]))
    call printi('reshaped ',reshape(box,[4,3]))

   ! fill in row column order using order
    v=reshape([1,2,3,4,10,20,30,40,100,200,300,400],[1,12])
    call printi('here is some data to shape',v)
    call printi('normally fills columns first ',reshape([v],[3,4]))
    call printi('fill rows first', reshape([v],[3,4],order=[2,1]))

    ! if we take the data and put in back in filling
    ! rows first instead of columns, and flipping the
    ! height and width of the box we not only fill in
    ! a vector using row-column order we actually
    ! transpose it.
    rc(2:1:-1)=shape(box)
    ! copy the data in changing column number fastest
    v=reshape(box,rc,order=[2,1])
    call printi('reshaped and reordered',v)
    ! of course we could have just done a transpose
    call printi('transposed',transpose(box))

   ! making the result bigger than source using pad
    v=reshape(box,rc*2,pad=[-1,-2,-3],order=[2,1])
    call printi('bigger and padded and reordered',v)
contains

subroutine printi(title,arr)
implicit none

!@(#) print small 2d integer arrays in row-column format

character(len=*),parameter :: all='(*(g0,1x))' ! a handy format
character(len=*),intent(in)  :: title
integer,intent(in)           :: arr(:,:)
integer                      :: i
character(len=:),allocatable :: biggest

   print all
   print all, trim(title),':(',shape(arr),')'  ! print title
   biggest='           '  ! make buffer to write integer into
   ! find how many characters to use for integers
   write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
   ! use this format to write a row
   biggest='(" > [",*(i'//trim(biggest)//':,","))'
   ! print one row of array at a time
   do i=1,size(arr,dim=1)
      write(*,fmt=biggest,advance='no')arr(i,:)
      write(*,'(" ]")')
   enddo

end subroutine printi

end program demo_reshape

结果

   shape of box is :( 3 4 )
    > [   1,   4,   7,  10 ]
    > [   2,   5,   8,  11 ]
    > [   3,   6,   9,  12 ]

   reshaped :( 2 6 )
    > [   1,   3,   5,   7,   9,  11 ]
    > [   2,   4,   6,   8,  10,  12 ]

   reshaped :( 4 3 )
    > [   1,   5,   9 ]
    > [   2,   6,  10 ]
    > [   3,   7,  11 ]
    > [   4,   8,  12 ]

   here is some data to shape :( 1 12 )
    > [   1,   2,   3,   4,  10,  20,  30,  40, 100, 200, 300, 400 ]

   normally fills columns first :( 3 4 )
    > [    1,    4,   30,  200 ]
    > [    2,   10,   40,  300 ]
    > [    3,   20,  100,  400 ]

   fill rows first :( 3 4 )
    > [    1,    2,    3,    4 ]
    > [   10,   20,   30,   40 ]
    > [  100,  200,  300,  400 ]

   reshaped and reordered :( 4 3 )
    > [   1,   2,   3 ]
    > [   4,   5,   6 ]
    > [   7,   8,   9 ]
    > [  10,  11,  12 ]

   transposed :( 4 3 )
    > [   1,   2,   3 ]
    > [   4,   5,   6 ]
    > [   7,   8,   9 ]
    > [  10,  11,  12 ]

   bigger and padded and reordered :( 8 6 )
    > [   1,   2,   3,   4,   5,   6 ]
    > [   7,   8,   9,  10,  11,  12 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]
    > [  -1,  -2,  -3,  -1,  -2,  -3 ]

标准#

Fortran 95

另请参阅#

shape(3)pack(3)transpose(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost