矩阵乘法、点积和数组移位#

cshift#

名称#

cshift(3) - [转换] 循环移位数组的元素

概要#

   result = cshift(array, shift [,dim])
    type(TYPE, kind=KIND) function cshift(array, shift, dim )

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

特征#

  • array 可以是任何类型和秩

  • shift 如果array的秩为一,则为整数标量。否则,它应为标量或秩为 n-1 且形状为 [d1, d2, …, dDIM-1, dDIM+1, …, dn],其中 [d1, d2, …, dn] 是array的形状。

  • dim 是一个整数标量,其值在范围 1 <= dim <= n 内,其中 n 是array的秩。如果dim不存在,则将其视为存在且值为 1。

  • 结果将自动与array具有相同的类型、种类和形状。

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

描述#

cshift(3) 沿dim维度对array的元素执行循环移位。如果省略dim,则将其视为1dim 是类型为整数的标量,其范围为1 <= dim <= n,其中“n”是array的秩。

如果array的秩为一,则array的所有元素都将移位shift个位置。如果秩大于一,则沿给定维度array的所有完整秩一节都将移位。从每个秩一节的一端移出的元素将移回另一端。

选项#

  • array

    要移位的任何类型的数组

  • shift

    循环移位的位数。负值产生右移,正值产生左移。

  • dim

    要移位多秩array的维度。默认为 1。

结果#

返回一个与array参数具有相同类型和秩的数组。

秩为二的数组的行可以全部移位相同的数量或不同的数量。

cshift#

示例#

示例程序

program demo_cshift
implicit none
integer, dimension(5)   :: i1,i2,i3
integer, dimension(3,4) :: a, b
   !basics
    i1=[10,20,30,40,50]
    print *,'start with:'
    print '(1x,5i3)', i1
    print *,'shift -2'
    print '(1x,5i3)', cshift(i1,-2)
    print *,'shift +2'
    print '(1x,5i3)', cshift(i1,+2)

    print *,'start with a matrix'
    a = reshape( [ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12 ], [ 3, 4 ])
    print '(4i3)', a(1,:)
    print '(4i3)', a(2,:)
    print '(4i3)', a(3,:)
    print *,'matrix shifted along rows, each by its own amount [-1,0,1]'
    b = cshift(a, SHIFT=[1, 0, -1], DIM=2)
    print *
    print '(4i3)', b(1,:)
    print '(4i3)', b(2,:)
    print '(4i3)', b(3,:)
end program demo_cshift

结果

 >  start with:
 >   10 20 30 40 50
 >  shift -2
 >   40 50 10 20 30
 >  shift +2
 >   30 40 50 10 20
 >  start with a matrix
 >   1  4  7 10
 >   2  5  8 11
 >   3  6  9 12
 >  matrix shifted along rows, each by its own amount
 >
 >   4  7 10  1
 >   2  5  8 11
 >  12  3  6  9

标准#

Fortran 95

另请参阅#

  • sum(3) - 对数组元素求和

  • product(3) - 数组元素的乘积

  • findloc(3) - 沿维度 DIM 标识的 ARRAY 的第一个元素的位置,该元素具有值

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

fortran-lang 内在函数描述

dot_product#

名称#

dot_product(3) - [转换] 两个向量的点积

概要#

    result = dot_product(vector_a, vector_b)
     TYPE(kind=KIND) function dot_product(vector_a, vector_b)

      TYPE(kind=KIND),intent(in) :: vector_a(:)
      TYPE(kind=KIND),intent(in) :: vector_b(:)

特征#

  • vector_avector_b 可以是任何数值或逻辑类型的秩为一的数组,大小相同

  • 这两个向量不必具有相同的种类,但在任何给定调用中都必须是逻辑的或数值的。

  • 结果与向量的类型和种类相同,该向量是另一个向量可选地提升到的更高类型(如果它们不同)。

这两个向量可以是数值的或逻辑的,并且必须是秩为一且大小相等的数组。

描述#

dot_product(3) 计算两个向量vector_avector_b的点积乘法。

选项#

  • vector_a

    秩为 1 的值向量

  • vector_b

    如果vector_a为数值类型,则类型应为数值;如果vectora 为类型 _logical,则类型应为逻辑vector_b应为与vector_a大小相同的秩一数组。

结果#

如果参数为数值,则返回值为数值类型的标量。如果参数为逻辑,则返回值为.true..false.

如果向量为整数实数,则结果为

     sum(vector_a*vector_b)

如果向量为复数,则结果为

     sum(conjg(vector_a)*vector_b)**

如果向量为逻辑,则结果为

     any(vector_a .and. vector_b)

示例#

示例程序

program demo_dot_prod
implicit none
    integer, dimension(3) :: a, b
    a = [ 1, 2, 3 ]
    b = [ 4, 5, 6 ]
    print '(3i3)', a
    print *
    print '(3i3)', b
    print *
    print *, dot_product(a,b)
end program demo_dot_prod

结果

  >  1  2  3
  >
  >  4  5  6
  >
  >           32

标准#

Fortran 95

另请参阅#

sum(3), conjg(3), any(3)

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

eoshift#

名称#

eoshift(3) - [转换] 数组元素的末端移位

概要#

  result = eoshift( array, shift [,boundary] [,dim] )
   type(TYPE(kind=KIND)) function eoshift(array,shift,boundary,dim)

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

特征#

  • array 任何类型的数组

  • shift 是任何种类的整数。它可以是标量。如果array的秩大于一,并且指定了dim,则它与array具有相同的形状,但去除了维度dim

  • boundary 可以是与array具有相同类型和种类的标量。当array的秩为一时,它必须是标量。否则,它可以是与array具有相同形状的数组,但去除了维度dim。对于某些类型,它可能仅不存在,如下所述。

  • dim 是任何种类的整数。默认为 1。

  • 结果与array具有相同的类型、类型参数和形状。

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

  • 结果是与array参数具有相同类型、种类和秩的数组。

描述#

eoshift(3) 沿dim维度对array的元素执行末端移位。

从每个秩一节的一端移出的元素将被丢弃。

如果存在boundary,则将boundary中的对应值复制回另一端,否则将使用默认值。

选项#

  • array

    任何类型的数组,其元素要移位。如果array的秩为一,则array的所有元素都将移位shift个位置。如果秩大于一,则沿给定维度array的所有完整秩一节都将移位。

  • shift

    要移位的元素数。负值向右移位,正值向左移位正在移位的向量。

  • boundary

    用于填充移位腾出的元素的值。如果boundary不存在,则根据array的类型复制以下内容。

    Array Type    | Boundary Value
    -----------------------------------------------------
    Numeric       | 0, 0.0, or (0.0, 0.0) of the type and kind of "array"
    Logical       | .false.
    Character(len)|  LEN blanks

这些是boundary可能不存在的唯一类型。对于这些类型,种类将根据需要转换为array的种类。

  • dim

    dim 的范围为

    1 <= DIM <= n

其中“n”array的秩。如果省略dim,则将其视为1

结果#

返回一个与输入具有相同特征的数组,其中指定数量的元素已沿指示的方向删除,并用boundary值指示的值填充腾出的元素。

示例#

示例程序

program demo_eoshift
implicit none
integer, dimension(3,3) :: a
integer :: i

    a = reshape( [ 1, 2, 3, 4, 5, 6, 7, 8, 9 ], [ 3, 3 ])
    print '(3i3)', (a(i,:),i=1,3)

    print *

    ! shift it
    a = eoshift(a, SHIFT=[1, 2, 1], BOUNDARY=-5, DIM=2)
    print '(3i3)', (a(i,:),i=1,3)

end program demo_eoshift

结果

  >  1  4  7
  >  2  5  8
  >  3  6  9
  >
  >  4  7 -5
  >  8 -5 -5
  >  6  9 -5

标准#

Fortran 95

另请参阅#

dshiftr(3), dshiftl(3)

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

matmul#

名称#

matmul(3) - [变换] 数值或逻辑矩阵乘法

概要#

    result = matmul(matrix_a,matrix_b)
     function matmul(matrix_a, matrix_b)

      type(TYPE1(kind=**)       :: matrix_a(..)
      type(TYPE2(kind=**)       :: matrix_b(..)
      type(TYPE(kind=PROMOTED)) :: matmul(..)

特征#

  • matrix_a 是一个秩为一或二的数值(整数实数复数)或逻辑数组。

  • matrix_b 是一个秩为一或二的数值(整数实数复数)或逻辑数组。

  • 至少一个参数必须是秩为二的。

  • matrix_b 的第一个维度的尺寸必须等于matrix_a 的最后一个维度的尺寸。

  • 结果的类型与每个参数的元素作为 RHS 表达式相乘时的类型相同(也就是说,如果参数的类型不同,则结果遵循与两个类型的简单标量乘法产生的相同的提升规则)。

  • 如果一个参数是逻辑类型的,则两者都必须是逻辑类型的。对于逻辑类型,结果类型与在数组的元素上使用.and.运算符时的类型相同。

  • 结果的形状取决于如下所述的参数的形状。

描述#

matmul(3) 对数值或逻辑参数执行矩阵乘法。

选项#

  • matrix_a

    秩为一或二的数值或逻辑数组。

  • matrix_b

    秩为一或二的数值或逻辑数组。matrix_a 的最后一个维度和matrix_b 的第一个维度必须相等。

    请注意,matrix_amatrix_b 可以是不同的数值类型。

结果#

数值参数#

如果matrix_amatrix_b 是数值类型,则结果是一个数组,包含matrix_amatrix_b 的常规矩阵乘积。

首先,对于数值表达式C=matmul(A,B)

  • 任何向量A(n)都被视为行向量A(1,n)

  • 任何向量B(n)都被视为列向量B(n,1)

形状和秩#

然后可以将结果的形状确定为第一个矩阵的行数和第二个矩阵的列数;但是,如果任何参数的秩为一(向量),则结果的秩也为一。相反,当两个参数的秩都为二时,结果的秩为二。也就是说……

  • 如果matrix_a 的形状为 [n,m] 且matrix_b 的形状为 [m,k],则结果的形状为 [n,k]。

  • 如果matrix_a 的形状为 [m] 且matrix_b 的形状为 [m,k],则结果的形状为 [k]。

  • 如果matrix_a 的形状为 [n,m] 且matrix_b 的形状为 [m],则结果的形状为 [n]。

#

然后,乘积的元素C(i,j)通过将A 的第 i 行和B 的第 j 列的项逐项相乘,并将这些乘积相加得到。换句话说,C(i,j)A 的第 i 行和B 的第 j 列的点积。

逻辑参数#

#

如果matrix_amatrix_b 的类型为逻辑类型,则结果的数组元素为

  Value_of_Element (i,j) = &
  ANY( (row_i_of_MATRIX_A) .AND. (column_j_of_MATRIX_B) )

示例#

示例程序

program demo_matmul
implicit none
integer :: a(2,3), b(3,2), c(2), d(3), e(2,2), f(3), g(2), v1(4),v2(4)
   a = reshape([1, 2, 3, 4, 5, 6], [2, 3])
   b = reshape([10, 20, 30, 40, 50, 60], [3, 2])
   c = [1, 2]
   d = [1, 2, 3]
   e = matmul(a, b)
   f = matmul(c,a)
   g = matmul(a,d)

   call print_matrix_int('A is ',a)
   call print_matrix_int('B is ',b)
   call print_vector_int('C is ',c)
   call print_vector_int('D is ',d)
   call print_matrix_int('E is matmul(A,B)',e)
   call print_vector_int('F is matmul(C,A)',f)
   call print_vector_int('G is matmul(A,D)',g)

   ! look at argument shapes when one is a vector
   write(*,'(" > shape")')
   ! at least one argument must be of rank two
   ! so for two vectors at least one must be reshaped
   v1=[11,22,33,44]
   v2=[10,20,30,40]

   ! these return a vector C(1:1)
   ! treat A(1:n) as A(1:1,1:n)
   call print_vector_int('Cd is a vector (not a scalar)',&
   & matmul(reshape(v1,[1,size(v1)]),v2))
   ! or treat B(1:m) as B(1:m,1:1)
   call print_vector_int('cD is a vector too',&
   & matmul(v1,reshape(v2,[size(v2),1])))

   ! or treat A(1:n) as A(1:1,1:n) and B(1:m) as B(1:m,1:1)
   ! but note this returns a matrix C(1:1,1:1) not a vector!
   call print_matrix_int('CD is a matrix',matmul(&
   & reshape(v1,[1,size(v1)]), &
   & reshape(v2,[size(v2),1])))

contains

! CONVENIENCE ROUTINES TO PRINT IN ROW-COLUMN ORDER
subroutine print_vector_int(title,arr)
character(len=*),intent(in)  :: title
integer,intent(in)           :: arr(:)
   call print_matrix_int(title,reshape(arr,[1,shape(arr)]))
end subroutine print_vector_int

subroutine print_matrix_int(title,arr)
!@(#) 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)
   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_matmul

结果

    >
    > A is
    > [  1,  3,  5 ]
    > [  2,  4,  6 ]
    >
    > B is
    > [  10,  40 ]
    > [  20,  50 ]
    > [  30,  60 ]
    >
    > C is
    > [  1,  2 ]
    >
    > D is
    > [  1,  2,  3 ]
    >
    > E is matmul(A,B)
    > [  220,  490 ]
    > [  280,  640 ]
    >
    > F is matmul(C,A)
    > [   5,  11,  17 ]
    >
    > G is matmul(A,D)
    > [  22,  28 ]
    > shape
    >
    > Cd is a vector (not a scalar)
    > [  3300 ]
    >
    > cD is a vector too
    > [  3300 ]
    >
    > CD is a matrix
    > [  3300 ]

标准#

Fortran 95

另请参见#

product(3)transpose(3)

资源#

  • 矩阵乘法:维基百科

  • Strassen 矩阵乘法算法的 Winograd 变体可能对优化非常大的矩阵的乘法感兴趣。请参见

    "GEMMW: A portable level 3 BLAS Winograd variant of Strassen's
    matrix-matrix multiply algorithm",

    Douglas, C. C., Heroux, M., Slishman, G., and Smith, R. M.,
    Journal of Computational Physics,
    Vol. 110, No. 1, January 1994, pages 1-10.

  The numerical instabilities of Strassen's method for matrix
  multiplication requires special processing.

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

parity#

名称#

parity(3) - [数组:归约] 通过 .NEQV. 运算进行数组归约

概要#

    result = parity( mask [,dim] )
     logical(kind=KIND) function parity(mask, dim)

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

特征#

  • mask 是一个逻辑数组

  • dim 是一个整数标量

  • 结果的类型为逻辑类型,与mask 的类型种类参数相同。如果dim 不出现,则结果为标量;否则,结果的秩和形状与mask 相同,但去掉了由dim 指定的维度。

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

描述#

parity(3) 计算mask 沿维度dim 的奇偶校验数组(即使用 .neqv. 进行归约),如果dim 存在且不为 1。否则,它将返回整个mask 数组的奇偶校验作为标量。

选项#

  • mask

    应为逻辑类型的数组。

  • dim

    (可选)应为整数类型的标量,其值在1 到 n 的范围内,其中n 等于mask 的秩。

结果#

结果与mask 的类型相同。

如果dim 缺失,则返回一个标量,其中包含mask 中所有元素的奇偶校验:如果奇数个元素为.true.,则为.true.,否则为.false.

如果 MASK 的秩为 1,则 PARITY (MASK, DIM) 等于 PARITY (MASK)。否则,结果是一个奇偶校验值数组,其中去掉了维度dim

示例#

示例程序

program demo_parity
implicit none
logical, parameter :: T=.true., F=.false.
logical :: x(3,4)
  ! basics
   print *, parity([T,F])
   print *, parity([T,F,F])
   print *, parity([T,F,F,T])
   print *, parity([T,F,F,T,T])
   x(1,:)=[T,T,T,T]
   x(2,:)=[T,T,T,T]
   x(3,:)=[T,T,T,T]
   print *, parity(x)
   print *, parity(x,dim=1)
   print *, parity(x,dim=2)
end program demo_parity

结果

 >  T
 >  T
 >  F
 >  T
 >  F
 >  T T T T
 >  F F F

标准#

Fortran 2008

另请参见#

  • all(3) - 确定所有值是否为真

  • any(3) - 确定逻辑数组中的任何值是否为.true.

  • count(3) - 统计数组中真值的数量

  • sum(3) - 对数组的元素求和

  • maxval(3) - 确定数组或行中的最大值

  • minval(3) - 数组的最小值

  • product(3) - 数组元素的乘积

  • reduce(3) - 通用数组归约

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

null#

名称#

null(3) - [变换] 返回一个分离指针的函数

概要#

    ptr => null( [mold] )
     function null(mold)

      type(TYPE(kind=**)),pointer,optional :: mold

特征#

  • mold 是任何关联状态和任何类型的指针。

  • 结果是一个分离指针或一个未分配的可分配实体。

描述#

null(3) 返回一个分离指针。

如果mold 存在,则返回相同类型的分离指针,否则类型由上下文确定。

Fortran 95 中,mold 是可选的。请注意,Fortran 2003 包括一些需要它的情况。

选项#

  • mold

    任何关联状态和任何类型的指针。

结果#

一个分离指针或一个未分配的可分配实体。

示例#

示例程序

!program demo_null
module showit
implicit none
private
character(len=*),parameter :: g='(*(g0,1x))'
public gen
! a generic interface that only differs in the
! type of the pointer the second argument is
interface gen
 module procedure s1
 module procedure s2
end interface

contains

subroutine s1 (j, pi)
 integer j
 integer, pointer :: pi
   if(associated(pi))then
      write(*,g)'Two integers in S1:,',j,'and',pi
   else
      write(*,g)'One integer in S1:,',j
   endif
end subroutine s1

subroutine s2 (k, pr)
 integer k
 real, pointer :: pr
   if(associated(pr))then
      write(*,g)'integer and real in S2:,',k,'and',pr
   else
      write(*,g)'One integer in S2:,',k
   endif
end subroutine s2

end module showit

program demo_null
use showit, only : gen

real,target :: x = 200.0
integer,target :: i = 100

real, pointer :: real_ptr
integer, pointer :: integer_ptr

! so how do we call S1() or S2() with a disassociated pointer?

! the answer is the null() function with a mold value

! since s1() and s2() both have a first integer
! argument the NULL() pointer must be associated
! to a real or integer type via the mold option
! so the following can distinguish whether s1(1)
! or s2() is called, even though the pointers are
! not associated or defined

call gen (1, null (real_ptr) )    ! invokes s2
call gen (2, null (integer_ptr) ) ! invokes s1
real_ptr => x
integer_ptr => i
call gen (3, real_ptr ) ! invokes s2
call gen (4, integer_ptr ) ! invokes s1

end program demo_null

结果

   One integer in S2:, 1
   One integer in S1:, 2
   integer and real in S2:, 3 and 200.000000
   Two integers in S1:, 4 and 100

标准#

Fortran 95

另请参见#

associated(3)

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

reduce#

名称#

reduce(3) - [变换] 数组的通用归约

概要#

此函数有两种形式

   result = reduce(array, operation [,mask]  [,identity]  [,ordered] )

   result = reduce (array, operation, dim  &
   & [,mask] [,identity] [,ordered] )
    type(TYPE(kind=KIND)) function reduce &
    & (array, operation, dim, mask, identity, ordered )

     type(TYPE(kind=KIND)),intent(in) :: array
     pure function                  :: operation
     integer,intent(in),optional    :: dim
     logical,optional               :: mask
     type(TYPE),intent(in),optional :: identity
     logical,intent(in),optional    :: ordered

特征#

  • array 是任何类型的数组

  • operation 是一个纯函数,正好有两个参数

    • 每个参数都是标量、非可分配的、非指针、非多态的和非可选的,与数组具有相同的类型和种类。

    • 如果一个参数具有异步、目标或值属性,则另一个也应具有该属性。

  • dim 是一个整数标量

  • mask 是一个与array 一致的逻辑类型

  • identity 是一个与array 具有相同类型和类型参数的标量

  • ordered 是一个逻辑标量

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

描述#

reduce(3) 通过迭代应用二元函数,将数组中一组条件选择的数值归约为单个值。

在函数式编程中很常见,reduce 函数累积地将二元运算符(一个具有两个参数的纯函数)应用于所有元素。

reduce 是一个“高阶”函数;即它是一个接收其他函数作为参数的函数。

reduce 函数接收一个二元运算符(一个具有两个参数的函数,就像基本的算术运算符一样)。它首先应用于列表中的两个未使用的值以生成一个累加器值,该值随后用作函数的第一个参数,因为该函数递归地应用于输入数组中所有剩余的选择值。

选项#

  • array

    任何类型和允许的秩的数组,从中选择值。

  • operation

    应为一个纯函数,正好有两个参数;每个参数应为一个标量、非可分配的、非指针、非多态的、非可选的虚拟数据对象,与array 具有相同的类型和类型参数。如果一个参数具有 ASYNCHRONOUS、TARGET 或 VALUE 属性,则另一个也应具有该属性。其结果应为非多态标量,并与array 具有相同的类型和类型参数。operation 应实现一个数学上的结合运算。它不需要是交换的。

    注意

    如果operation 在计算上不是结合的,则没有 ORDERED=.TRUE. 的 REDUCE 对于相同的参数值可能不会始终产生相同的结果,因为处理器可以将结合律应用于求值。

    例如,许多在数学上是结合的运算在应用于浮点数时并不是结合的。例如,您求和值的顺序可能会影响结果。

  • dim

    一个整数标量,其值在 1<= dim <= n 的范围内,其中 n 是array 的秩。

  • mask

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

    仅当**mask**对应的元素为真时,才会将**array**的这些元素传递给**operation**,就像使用**pack(3)**对**array**进行过滤一样。

  • 标识

    应为与**array**具有相同类型和类型参数的标量。如果初始序列为空,则如果存在**identify**,则结果值为**identify**,否则将启动错误终止。

  • 有序

    应为逻辑标量。如果存在**ordered**且其值为.true.,则对**operator**函数的调用将从**array**的前两个元素开始,并按行-列顺序继续,直到序列中只剩下一个元素,该元素为归约的值。否则,编译器可以自由地假设操作是可交换的,并可能以最优的方式评估归约。

**结果**#

结果与**array**具有相同的类型和类型参数。如果**dim**不存在,则它是标量。

如果存在**dim**,则它指示要执行归约的一个维度,并且结果数组的秩比输入数组的秩减少一个。

**示例**#

以下示例都使用函数MY_MULT,该函数返回其两个实数参数的乘积。

   program demo_reduce
   implicit none
   character(len=*),parameter :: f='("[",*(g0,",",1x),"]")'
   integer,allocatable :: arr(:), b(:,:)

   ! Basic usage:
      ! the product of the elements of an array
      arr=[1, 2, 3, 4 ]
      write(*,*) arr
      write(*,*) 'product=', reduce(arr, my_mult)
      write(*,*) 'sum=', reduce(arr, my_sum)

   ! Examples of masking:
      ! the product of only the positive elements of an array
      arr=[1, -1, 2, -2, 3, -3 ]
      write(*,*)'positive value product=',reduce(arr, my_mult, mask=arr>0)
   ! sum values ignoring negative values
      write(*,*)'sum positive values=',reduce(arr, my_sum, mask=arr>0)

   ! a single-valued array returns the single value as the
   ! calls to the operator stop when only one element remains
      arr=[ 1234 ]
      write(*,*)'single value sum',reduce(arr, my_sum )
      write(*,*)'single value product',reduce(arr, my_mult )

   ! Example of operations along a dimension:
   !  If B is the array   1 3 5
   !                      2 4 6
      b=reshape([1,2,3,4,5,6],[2,3])
      write(*,f) REDUCE(B, MY_MULT),'should be [720]'
      write(*,f) REDUCE(B, MY_MULT, DIM=1),'should be [2,12,30]'
      write(*,f) REDUCE(B, MY_MULT, DIM=2),'should be [15, 48]'

   contains

   pure function my_mult(a,b) result(c)
   integer,intent(in) :: a, b
   integer            :: c
      c=a*b
   end function my_mult

   pure function my_sum(a,b) result(c)
   integer,intent(in) :: a, b
   integer            :: c
      c=a+b
   end function my_sum

   end program demo_reduce

结果

     >  1 2 3 4
     >  product= 24
     >  sum=     10
     >  positive value sum= 6
     >  sum positive values= 6
     >  single value sum     1234
     >  single value product 1234
     > [720, should be [720],
     > [2, 12, 30, should be [2,12,30],
     > [15, 48, should be [15, 48],

**标准**#

Fortran 2018

**另请参见**#

**资源**#

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