数值值的处理和属性#

abs#

名称#

abs(3) - [数值] 绝对值

概要#

    result = abs(a)
     elemental TYPE(kind=KIND) function abs(a)

      TYPE(kind=KIND),intent(in) :: a

特性#

  • a 可以是任何实数整数复数值。

  • 如果a复数,则返回值将是与a具有相同种类的实数

    否则,返回的类型和种类与a相同。

描述#

abs(3) 计算数值参数a的绝对值。

在数学中,实数x的绝对值或模数,表示为|x|,是x的大小,不考虑其符号。

一个数的绝对值可以认为是它到零的距离。因此,对于复数值,绝对值是一个实数,其大小为sqrt(x%re**2,x%im**2),就像实部是 x 值,虚部是点 <x,y> 的 y 值一样。

选项#

  • a

    要计算其绝对值的数值。

结果#

如果a的类型为整数实数,则结果值为绝对值|a|,并且与输入参数具有相同的类型和种类。

如果a复数,其值为(x, y),则结果为一个实数,等于处理器对以下值的近似值:

        sqrt(x**2 + y**2)

计算时不会出现不必要的溢出或下溢(这意味着结果的计算可能会溢出返回的实数值的允许大小,并且如果在计算返回值时对非常小的值进行平方,则这些值可能会产生下溢,例如)。

也就是说,如果您将非复数值视为 x 轴上的复数值,并将复数值视为 x-y 点 <x%re,x%im>,则abs(3) 的结果是从原点到该值的(正)距离的大小。

示例#

示例程序

program demo_abs
implicit none
integer,parameter :: dp=kind(0.0d0)

integer           :: i = -1
real              :: x = -1.0
complex           :: z = (-3.0,-4.0)
doubleprecision   :: rr = -45.78_dp

character(len=*),parameter :: &
   ! some formats
   frmt  =  '(1x,a15,1x," In: ",g0,            T51," Out: ",g0)', &
   frmtc = '(1x,a15,1x," In: (",g0,",",g0,")",T51," Out: ",g0)',  &
   g     = '(*(g0,1x))'

  ! basic usage
    ! any integer, real, or complex type
    write(*, frmt)  'integer         ',  i, abs(i)
    write(*, frmt)  'real            ',  x, abs(x)
    write(*, frmt)  'doubleprecision ', rr, abs(rr)
    write(*, frmtc) 'complex         ',  z, abs(z)

  ! You can take the absolute value of any value whose positive value
  ! is representable with the same type and kind.
    write(*, *) 'abs range test : ', abs(huge(0)), abs(-huge(0))
    write(*, *) 'abs range test : ', abs(huge(0.0)), abs(-huge(0.0))
    write(*, *) 'abs range test : ', abs(tiny(0.0)), abs(-tiny(0.0))
    ! A dusty corner is that abs(-huge(0)-1) of an integer would be
    ! a representable negative value on most machines but result in a
    ! positive value out of range.

  ! elemental
    write(*, g) ' abs is elemental:', abs([20,  0,  -1,  -3,  100])

  ! COMPLEX input produces REAL output
    write(*, g)' complex input produces real output', &
    & abs(cmplx(30.0_dp,40.0_dp,kind=dp))
    ! dusty corner: "kind=dp" is required or the value returned by
    ! CMPLX() is a default real instead of double precision

  ! the returned value for complex input can be thought of as the
  ! distance from the origin <0,0>
    write(*, g) ' distance of (', z, ') from zero is', abs( z )
    write(*, g) ' so beware of overflow with complex values'
    !write(*, g) abs(cmplx( huge(0.0), huge(0.0) ))
    write(*, g) ' because the biggest default real is',huge(0.0)

end program demo_abs

结果

    integer          In: -1                     Out: 1
    real             In: -1.000000              Out: 1.000000
    doubleprecision  In: -45.78000000000000     Out: 45.78000000000000
    complex          In: (-3.000000,-4.000000)  Out: 5.000000
    abs range test :   2147483647  2147483647
    abs range test :   3.4028235E+38  3.4028235E+38
    abs range test :   1.1754944E-38  1.1754944E-38
    abs is elemental: 20 0 1 3 100
    complex input produces real output 50.00000000000000
    distance of ( -3.000000 -4.000000 ) from zero is 5.000000
    so beware of overflow with complex values
    Inf
    because the biggest default real is .3402823E+39

标准#

FORTRAN 77

另请参阅#

sign(3)

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

aint#

名称#

aint(3) - [数值] 向零截断为整数

概要#

    result = aint(x [,kind])
     elemental real(kind=KIND) function iaint(x,KIND)

      real(kind=**),intent(in)   :: x
      integer(kind=**),intent(in),optional :: KIND

特性#

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

  • 除非指定了kind,否则结果为默认种类的实数。

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

描述#

aint(3) 将其参数向零截断为整数。

选项#

  • x

    要截断的实数值。

  • kind

    指示结果的种类参数。

结果#

符号与x的符号相同,除非x的大小小于 1,在这种情况下返回零。

否则,aint(3) 返回不超过x大小且与输入符号相同的最大整数。

也就是说,它将值截断为零。

示例#

示例程序

program demo_aint
use, intrinsic :: iso_fortran_env, only : sp=>real32, dp=>real64
implicit none
real(kind=dp) :: x8
   print *,'basics:'
   print *,' just chops off the fractional part'
   print *,  aint(-2.999), aint(-2.1111)
   print *,' if |x| < 1 a positive zero is returned'
   print *,  aint(-0.999), aint( 0.9999)
   print *,' input may be of any real kind'
   x8 = 4.3210_dp
   print *, aint(-x8), aint(x8)
   print *,'elemental:'
   print *,aint([ &
    &  -2.7,  -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, &
    &  0.0,   &
    &  +0.5,  +1.0, +1.5, +2.0, +2.2, +2.5, +2.7  ])
end program demo_aint

结果

 basics:
  just chops off the fractional part
  -2.000000      -2.000000
  if |x| < 1 a positive zero is returned
  0.0000000E+00  0.0000000E+00
  input may be of any real kind
  -4.00000000000000        4.00000000000000
 elemental:
  -2.000000      -2.000000      -2.000000      -2.000000      -1.000000
  -1.000000      0.0000000E+00  0.0000000E+00  0.0000000E+00   1.000000
   1.000000       2.000000       2.000000       2.000000       2.000000

标准#

FORTRAN 77

另请参阅#

anint(3)int(3)nint(3)selected_int_kind(3)ceiling(3)floor(3)

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

anint#

名称#

anint(3) - [数值] 最近的实数整数

概要#

    result = anint(a [,kind])
     elemental real(kind=KIND) function anint(x,KIND)

      real(kind=**),intent(in)   :: x
      integer,intent(in),optional :: KIND

特性#

  • a 为任何种类的实数类型

  • KIND 是标量整数常量表达式。

  • 结果为实数类型。除非由kind指定,否则结果的种类与x相同。

描述#

anint(3) 将其参数舍入到最接近的整数。

与返回整数nint(3) 不同,可以返回完整的实数值范围(整数类型的数值范围通常小于实数类型)。

选项#

  • a

    要舍入的数值

  • kind

    指定结果的种类。默认为a的种类。

结果#

返回值是最接近a的实数整数。

如果a大于零,则anint(a)(3) 返回aint(a + 0.5)

如果a小于或等于零,则返回aint(a - 0.5),除非aint指定对于 |a| < 1,结果为零 (0)。

anint(a) 在 -0.5 < a <= -0.0 时是否返回负零取决于处理器。通常可以使用编译器开关启用或禁用对负零的支持。

示例#

示例程序

program demo_anint
use, intrinsic :: iso_fortran_env, only : real32, real64, real128
implicit none
real,allocatable :: arr(:)

  ! basics
   print *, 'ANINT (2.783) has the value 3.0 =>', anint(2.783)
   print *, 'ANINT (-2.783) has the value -3.0 =>', anint(-2.783)

   print *, 'by default the kind of the output is the kind of the input'
   print *, anint(1234567890.1234567890e0)
   print *, anint(1234567890.1234567890d0)

   print *, 'sometimes specifying the result kind is useful when passing'
   print *, 'results as an argument, for example.'
   print *, 'do you know why the results are different?'
   print *, anint(1234567890.1234567890,kind=real64)
   print *, anint(1234567890.1234567890d0,kind=real64)

  ! elemental
   print *, 'numbers on a cusp are always the most troublesome'
   print *, anint([ -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, 0.0 ])

   print *, 'negative zero is processor dependent'
   arr=[ 0.0, 0.1, 0.5, 1.0, 1.5, 2.0, 2.2, 2.5, 2.7 ]
   print *, anint(arr)
   arr=[ -0.0, -0.1, -0.5, -1.0, -1.5, -2.0, -2.2, -2.5, -2.7 ]
   print *, anint(arr)

end program demo_anint

结果

 >  ANINT (2.783) has the value 3.0 =>   3.000000
 >  ANINT (-2.783) has the value -3.0 =>  -3.000000
 >  by default the kind of the output is the kind of the input
 >   1.2345679E+09
 >    1234567890.00000
 >  sometimes specifying the result kind is useful when passing
 >  results as an argument, for example.
 >  do you know why the results are different?
 >    1234567936.00000
 >    1234567890.00000
 >  numbers on a cusp are always the most troublesome
 >   -3.000000      -3.000000      -2.000000      -2.000000      -2.000000
 >   -1.000000      -1.000000      0.0000000E+00
 >  negative zero is processor dependent
 >   0.0000000E+00  0.0000000E+00   1.000000       1.000000       2.000000
 >    2.000000       2.000000       3.000000       3.000000
 >   0.0000000E+00  0.0000000E+00  -1.000000      -1.000000      -2.000000
 >   -2.000000      -2.000000      -3.000000      -3.000000

标准#

FORTRAN 77

另请参阅#

aint(3)int(3)nint(3)selected_int_kind(3)ceiling(3)floor(3)

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

ceiling#

名称#

ceiling(3) - [数值] 整数上取整函数

概要#

    result = ceiling(a [,kind])
     elemental integer(KIND) function ceiling(a,KIND)

      real(kind=**),intent(in)  :: a
      integer,intent(in),optional :: KIND

特性#

  • ** a 为实数类型

  • KIND 应为标量整数常量表达式。如果存在,它指定结果的种类。

  • 结果为整数类型。如果未指定KIND,则为默认种类

描述#

ceiling(3) 返回大于或等于a的最小整数。

在数轴 -n <– 0 -> +n 上,返回值始终位于输入值的右侧或与之相同。

选项#

  • a

    要生成上取整的实数值。

  • kind

    指示结果的种类参数。

结果#

结果将等于a整数值,如果输入值不等于整数,则为大于a的最小整数。

如果a等于整数,则返回值为int(a)

如果结果无法在指定的整数类型中表示,则结果未定义。

示例#

示例程序

program demo_ceiling
implicit none
! just a convenient format for a list of integers
character(len=*),parameter :: ints='(*("   > ",5(i0:,",",1x),/))'
real :: x
real :: y
  ! basic usage
   x = 63.29
   y = -63.59
   print ints, ceiling(x)
   print ints, ceiling(y)
   ! note the result was the next integer larger to the right

  ! real values equal to whole numbers
   x = 63.0
   y = -63.0
   print ints, ceiling(x)
   print ints, ceiling(y)

  ! elemental (so an array argument is allowed)
   print ints , &
   & ceiling([ &
   &  -2.7,  -2.5, -2.2, -2.0, -1.5, &
   &  -1.0,  -0.5,  0.0, +0.5, +1.0, &
   &  +1.5,  +2.0, +2.2, +2.5, +2.7  ])

end program demo_ceiling

结果

   > 64
   > -63
   > 63
   > -63
   > -2, -2, -2, -2, -1,
   > -1, 0, 0, 1, 1,
   > 2, 2, 3, 3, 3

标准#

Fortran 95

另请参阅#

floor(3)nint(3)

aint(3)anint(3)int(3)selected_int_kind(3)

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

conjg#

名称#

conjg(3) - [数值] 复数的共轭

概要#

    result = conjg(z)
     elemental complex(kind=KIND) function conjg(z)

      complex(kind=**),intent(in) :: z

特征#

  • z 是任何有效类型的复数

  • 返回值与输入具有相同的复数类型。

描述#

conjg(3) 返回复数z 的共轭复数。

也就是说,如果 z复数(x, y),则结果为 (x, -y)

在数学中,复数的共轭复数是一个值,其实部和虚部的幅度相等,但y值的符号相反。

对于复数矩阵,conjg(array) 表示array的逐元素共轭;而不是array的共轭转置。

选项#

  • z

    要创建其共轭的值。

结果#

返回一个与输入值相等的值,除了虚部的符号与输入值的符号相反。

也就是说,如果 z 的值为 (x,y),则结果值为 (x, -y)

示例#

示例程序

program demo_conjg
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
complex :: z = (2.0, 3.0)
complex(kind=real64) :: dz = (   &
   &  1.2345678901234567_real64, -1.2345678901234567_real64)
complex :: arr(3,3)
integer :: i
   ! basics
    ! notice the sine of the imaginary component changes
    print *, z, conjg(z)

    ! any complex kind is supported. z is of default kind but
    ! dz is kind=real64.
    print *, dz
    dz = conjg(dz)
    print *, dz
    print *

    ! the function is elemental so it can take arrays
    arr(1,:)=[(-1.0, 2.0),( 3.0, 4.0),( 5.0,-6.0)]
    arr(2,:)=[( 7.0,-8.0),( 8.0, 9.0),( 9.0, 9.0)]
    arr(3,:)=[( 1.0, 9.0),( 2.0, 0.0),(-3.0,-7.0)]

    write(*,*)'original'
    write(*,'(3("(",g8.2,",",g8.2,")",1x))')(arr(i,:),i=1,3)
    arr = conjg(arr)
    write(*,*)'conjugate'
    write(*,'(3("(",g8.2,",",g8.2,")",1x))')(arr(i,:),i=1,3)

end program demo_conjg

结果

 >  (2.000000,3.000000) (2.000000,-3.000000)
 >
 >  (1.23456789012346,-1.23456789012346)
 >  (1.23456789012346,1.23456789012346)
 >
 >  original
 > (-1.0    , 2.0    ) ( 3.0    , 4.0    ) ( 5.0    ,-6.0    )
 > ( 7.0    ,-8.0    ) ( 8.0    , 9.0    ) ( 9.0    , 9.0    )
 > ( 1.0    , 9.0    ) ( 2.0    , 0.0    ) (-3.0    ,-7.0    )
 >
 >  conjugate
 > (-1.0    ,-2.0    ) ( 3.0    ,-4.0    ) ( 5.0    , 6.0    )
 > ( 7.0    , 8.0    ) ( 8.0    ,-9.0    ) ( 9.0    ,-9.0    )
 > ( 1.0    ,-9.0    ) ( 2.0    , 0.0    ) (-3.0    , 7.0    )

标准#

FORTRAN 77

另请参见#

Fortran 对复数值有强大的支持,包括许多接受或生成复数值的内建函数,以及代数和逻辑表达式。

abs(3)acosh(3)acos(3)asinh(3)asin(3)atan2(3)atanh(3)atan(3)cosh(3)cos(3)co_sum(3)dble(3)dot_product(3)exp(3)int(3)is_contiguous(3)kind(3)log(3)matmul(3)precision(3)product(3)range(3)rank(3)sinh(3)sin(3)sqrt(3)storage_size(3)sum(3)tanh(3)tan(3)unpack(3)

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

dim#

名称#

dim(3) - [数值] X - Y 的正差

概要#

    result = dim(x, y)
     elemental TYPE(kind=KIND) function dim(x, y )

      TYPE(kind=KIND),intent(in) :: x, y

特征#

  • xy 可以是任何实数整数,但类型和种类必须相同。

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

描述#

dim(3) 返回x - y 和零中的最大值。也就是说,如果结果为正,则返回差值x - y;否则返回零。它等价于

  max(0,x-y)

选项#

  • x

    被减数,即从该数中减去的数。

  • y

    减数;即被减去的数。

结果#

返回差值x - y 或零,取两者中的较大者。

示例#

示例程序

program demo_dim
use, intrinsic :: iso_fortran_env, only : real64
implicit none
integer           :: i
real(kind=real64) :: x

   ! basic usage
    i = dim(4, 15)
    x = dim(4.321_real64, 1.111_real64)
    print *, i
    print *, x

   ! elemental
    print *, dim([1,2,3],2)
    print *, dim([1,2,3],[3,2,1])
    print *, dim(-10,[0,-10,-20])

end program demo_dim

结果

 >            0
 >    3.21000000000000
 >            0           0           1
 >            0           0           2
 >            0           0          10

标准#

FORTRAN 77

另请参见#

****(3)

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

dprod#

名称#

dprod(3) - [数值] 双精度实数乘积

概要#

    result = dprod(x,y)
     elemental function dprod(x,y)

      real,intent(in) :: x
      real,intent(in) :: y
      doubleprecision :: dprod

特征#

  • x 是默认实数。

  • y 是默认实数。

  • 结果是双精度实数。

指定默认实数大小的编译器选项设置会影响此函数。

描述#

dprod(3) 生成默认实数xy双精度乘积。

也就是说,它应该在乘法之前将参数转换为双精度,而简单的表达式 x*y 不需要这样做。这在需要高精度的专门计算中可能很重要。

结果的值等于处理器对 xy 乘积的近似值。请注意,标准建议处理器以双精度计算乘积,而不是以单精度计算然后转换为双精度;但这只是一个建议。

选项#

  • x

    乘数

  • y

    被乘数

结果#

返回的乘积值应与 dble(x)*dble(y) 的值相同。

示例#

示例程序

program demo_dprod
implicit none
integer,parameter :: dp=kind(0.0d0)
real :: x = 5.2
real :: y = 2.3
doubleprecision :: xx
real(kind=dp)   :: dd

   print *,'algebraically 5.2 x 2.3 is exactly 11.96'
   print *,'as floating point values results may differ slightly:'
   ! basic usage
   dd = dprod(x,y)
   print *, 'compare dprod(xy)=',dd, &
   & 'to x*y=',x*y, &
   & 'to dble(x)*dble(y)=',dble(x)*dble(y)

   print *,'test if an expected result is produced'
   xx=-6.0d0
   write(*,*)DPROD(-3.0, 2.0),xx
   write(*,*)merge('PASSED','FAILED',DPROD(-3.0, 2.0) == xx)

   print *,'elemental'
   print *, dprod( [2.3,3.4,4.5], 10.0 )
   print *, dprod( [2.3,3.4,4.5], [9.8,7.6,5.4] )

end program demo_dprod

结果:(这在不同的编程环境中可能有所不同)

 >  algebraically 5.2 x 2.3 is exactly 11.96
 >  as floating point values results may differ slightly:
 >  compare dprod(xy)=   11.9599993133545      to x*y=   11.96000
 >  to dble(x)*dble(y)=   11.9599993133545
 >  test if an expected result is produced
 >   -6.00000000000000       -6.00000000000000
 >  PASSED
 >  elemental
 >    22.9999995231628     34.0000009536743     45.0000000000000
 >    22.5399999713898     25.8400004005432     24.3000004291534

标准#

FORTRAN 77

另请参见#

dble(3) real(3)

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

floor#

名称#

floor(3) - [数值] 返回不大于参数的最大整数值的函数

概要#

    result = floor(a [,kind])
     elemental integer(kind=KIND) function floor( a ,kind )

      real(kind=**),intent(in) :: a
      integer(kind=**),intent(in),optional :: KIND

特征#

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

  • a 是任何种类的实数

  • KIND整数类型的任何有效值。

  • 结果是指定或默认种类的整数

描述#

floor(3) 返回小于或等于a的最大整数。

换句话说,它选择数轴上该值所在位置或其左侧的整数。

这意味着必须注意实数a的大小不能超过输出值的范围,因为实数值支持的范围通常大于整数的范围。

选项#

  • a

    要进行运算的值。有效值受返回的整数种类的范围限制,范围为 -huge(int(a,kind=KIND))-1huge(int(a),kind=KIND)

  • kind

    一个标量整数常量初始化表达式,指示结果的种类参数。

结果#

如果存在kind,则返回值为integer(kind)类型,否则为默认种类的integer

如果无法在指定的整数类型中表示结果,则结果未定义。

如果在结果种类的范围内,则结果为数轴上输入值所在位置或其左侧的整数。

如果a为正,则结果为去除小数部分的值。

如果a为负,则为输入值所在位置或其左侧的整数。

示例#

示例程序

program demo_floor
implicit none
real :: x = 63.29
real :: y = -63.59
    print *, x, floor(x)
    print *, y, floor(y)
   ! elemental
   print *,floor([ &
   &  -2.7,  -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, &
   &  0.0,   &
   &  +0.5,  +1.0, +1.5, +2.0, +2.2, +2.5, +2.7  ])

   ! note even a small deviation from the whole number changes the result
   print *,      [2.0,2.0-epsilon(0.0),2.0-2*epsilon(0.0)]
   print *,floor([2.0,2.0-epsilon(0.0),2.0-2*epsilon(0.0)])

   ! A=Nan, Infinity or  <huge(0_KIND)-1 < A > huge(0_KIND) is undefined
end program demo_floor

结果

 >     63.29000             63
 >    -63.59000            -64
 >            -3         -3         -3         -2         -2         -1
 >            -1          0          0          1          1          2
 >             2          2          2
 >     2.000000      2.000000      2.000000
 >             2          1          1

标准#

Fortran 95

另请参见#

ceiling(3)nint(3)aint(3)anint(3)int(3)selected_int_kind(3)

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

max#

名称#

max(3) - [数值] 参数列表中的最大值

概要#

    result = max(a1, a2, a3, ...)
     elemental TYPE(kind=KIND) function max(a1, a2, a3, ... )

      TYPE(kind=KIND,intent(in),optional :: a1
      TYPE(kind=KIND,intent(in),optional :: a2
      TYPE(kind=KIND,intent(in),optional :: a3
                :
                :
                :

特征#

  • a3, a3, a4, … 必须与 a1 具有相同的类型和种类。

  • 参数可以(全部)是整数实数字符

  • 必须至少有两个参数。

  • 字符结果的长度是最长参数的长度。

  • 结果的类型和种类与参数相同。

描述#

max(3) 返回具有最大(最正)值的参数。

对于字符类型参数,结果如同参数已使用内在操作符依次进行比较,并考虑了字符类型的排序顺序。

如果选定的字符参数短于最长参数,则结果如同所有值在右侧用空格扩展到最长参数的长度。

Fortran 内在函数采用任意数量的选项的情况并不常见,此外,**max**(3) 是元素级的,这意味着任意数量的参数都可以是数组,只要它们具有相同的形状。示例中提供了一个扩展描述,用于阐明对于不熟悉用数组元素级调用“标量”函数的用户,其产生的行为。

要简单地获取数组的最大值,请参阅 maxval(3)。

**选项**#

  • a1

    第一个参数确定返回类型的类型和种类,以及任何剩余参数的类型和种类,并且是用于查找最大值(最正值)的一组值中的一个成员。

  • a2,a3,…

    要从中查找最大值的参数。

    **max**(3) 必须至少有两个参数。

**结果**#

返回值对应于与任何数组参数具有相同形状的数组,或者如果所有参数都是标量则为标量。

当任何参数为数组时,返回的值将是一个具有相同形状的数组,其中每个元素是在该位置发生的最大值,将所有标量值视为具有相同形状的数组,所有元素都设置为标量值。

**示例**#

示例程序

program demo_max
implicit none
real :: arr1(4)= [10.0,11.0,30.0,-100.0]
real :: arr2(5)= [20.0,21.0,32.0,-200.0,2200.0]
integer :: box(3,4)= reshape([-6,-5,-4,-3,-2,-1,1,2,3,4,5,6],shape(box))

  ! basic usage
   ! this is simple enough when all arguments are scalar

   ! the most positive value is returned, not the one with the
   ! largest magnitude
   write(*,*)'scalars:',max(10.0,11.0,30.0,-100.0)
   write(*,*)'scalars:',max(-22222.0,-0.0001)

   ! strings do not need to be of the same length
   write(*,*)'characters:',max('the','words','order')

   ! leading spaces are significant; everyone is padded on the right
   ! to the length of the longest argument
   write(*,*)'characters:',max('c','bb','a')
   write(*,*)'characters:',max(' c','b','a')

  ! elemental
   ! there must be at least two arguments, so even if A1 is an array
   ! max(A1) is not valid. See MAXVAL(3) and/or MAXLOC(3) instead.

   ! strings in a single array do need to be of the same length
   ! but the different objects can still be of different lengths.
   write(*,"(*('""',a,'""':,1x))")MAX(['A','Z'],['BB','Y '])
   ! note the result is now an array with the max of every element
   ! position, as can be illustrated numerically as well:
   write(*,'(a,*(i3,1x))')'box=   ',box
   write(*,'(a,*(i3,1x))')'box**2=',sign(1,box)*box**2
   write(*,'(a,*(i3,1x))')'max    ',max(box,sign(1,box)*box**2)

   ! Remember if any argument is an array by the definition of an
   ! elemental function all the array arguments must be the same shape.

   ! to find the single largest value of arrays you could use something
   ! like MAXVAL([arr1, arr2]) or probably better (no large temp array),
   ! max(maxval(arr1),maxval(arr2)) instead

   ! so this returns an array of the same shape as any input array
   ! where each result is the maximum that occurs at that position.
   write(*,*)max(arr1,arr2(1:4))
   ! this returns an array just like arr1 except all values less than
   ! zero are set to zero:
   write(*,*)max(box,0)
   ! When mixing arrays and scalars you can think of the scalars
   ! as being a copy of one of the arrays with all values set to
   ! the scalar value.

end program demo_max

结果

    scalars:   30.00000
    scalars: -9.9999997E-05
    characters:words
    characters:c
    characters:b
   "BB" "Z "
   box=    -6  -5  -4  -3  -2  -1   1   2   3   4   5   6
   box**2=-36 -25 -16  -9  -4  -1   1   4   9  16  25  36
   max     -6  -5  -4  -3  -2  -1   1   4   9  16  25  36
   20.00000  21.00000  32.00000  -100.0000
   0  0  0  0  0  0
   1  2  3  4  5  6

**标准**#

FORTRAN 77

**另请参阅**#

maxloc(3)minloc(3)maxval(3)minval(3)min(3)

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

min#

**名称**#

min(3) - [数值] 参数列表的最小值

**概要**#

    result = min(a1, a2, a3, ... )
     elemental TYPE(kind=KIND) function min(a1, a2, a3, ... )

      TYPE(kind=KIND,intent(in)   :: a1
      TYPE(kind=KIND,intent(in)   :: a2
      TYPE(kind=KIND,intent(in)   :: a3
                :
                :
                :

**特性**#

  • **TYPE** 可以是整数实数字符

**描述**#

min(3) 返回具有最小值(最负值)的参数。

有关 min(3) 和 max(3) 行为的扩展示例,请参阅 max(3)。

**选项**#

  • a1

    要确定最小值的一组值中的第一个元素。

  • a2, a3, …

    a1 类型和种类相同的表达式,用于完成查找最小值的一组值。

**结果**#

返回值对应于参数中的最小值,并且具有与第一个参数相同的类型和种类。

**示例**#

示例程序

program demo_min
implicit none
    write(*,*)min(10.0,11.0,30.0,-100.0)
end program demo_min

结果

      -100.0000000

**标准**#

FORTRAN 77

**另请参阅**#

maxloc(3)minloc(3)minval(3)max(3)

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

mod#

**名称**#

mod(3) - [数值] 余数函数

**概要**#

    result = mod(a, p)
     elemental type(TYPE(kind=KIND)) function mod(a,p)

      type(TYPE(kind=KIND),intent(in) :: a
      type(TYPE(kind=KIND),intent(in) :: p

**特性**#

  • 结果和参数都具有相同的类型和种类。

  • 类型可以是任何种类的实数整数

**描述**#

mod(3) 计算 a 除以 p 的余数。

在数学中,余数是在执行某些计算后“剩余”的数量。在算术中,余数是在将一个整数除以另一个整数以产生整数商(整数除法)后“剩余”的整数。在多项式的代数中,余数是在将一个多项式除以另一个多项式后“剩余”的多项式。模运算是在给定被除数和除数时产生此类余数的运算。

  • (余数)。(2022 年 10 月 10 日)。在维基百科中。https://en.wikipedia.org/wiki/Remainder

**选项**#

  • a

    被除数

  • p

    除数(不等于零)。

**结果**#

返回值是 a - (int(a/p) * p) 的结果。

从公式可以看出,p 的符号被抵消了。因此,返回值始终具有 a 的符号。

当然,结果的大小将小于 p 的大小,因为结果已减去了 p 的所有倍数。

**示例**#

示例程序

program demo_mod
implicit none

   ! basics
    print *, mod( -17,  3 ), modulo( -17,  3 )
    print *, mod(  17, -3 ), modulo(  17, -3 )
    print *, mod(  17,  3 ), modulo(  17,  3 )
    print *, mod( -17, -3 ), modulo( -17, -3 )

    print *, mod(-17.5, 5.2), modulo(-17.5, 5.2)
    print *, mod( 17.5,-5.2), modulo( 17.5,-5.2)
    print *, mod( 17.5, 5.2), modulo( 17.5, 5.2)
    print *, mod(-17.5,-5.2), modulo(-17.5,-5.2)

  ! with a divisor of 1 the fractional part is returned
    print *, mod(-17.5, 1.0), modulo(-17.5, 1.0)
    print *, mod( 17.5,-1.0), modulo( 17.5,-1.0)
    print *, mod( 17.5, 1.0), modulo( 17.5, 1.0)
    print *, mod(-17.5,-1.0), modulo(-17.5,-1.0)

end program demo_mod

结果

             -2           1
              2          -1
              2           2
             -2          -2
     -1.900001       3.299999
      1.900001      -3.299999
      1.900001       1.900001
     -1.900001      -1.900001
    -0.5000000      0.5000000
     0.5000000     -0.5000000
     0.5000000      0.5000000
    -0.5000000     -0.5000000

**标准**#

FORTRAN 77

**另请参阅**#

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

modulo#

**名称**#

modulo(3) - [数值] 模运算函数

**概要**#

    result = modulo(a, p)
     elemental TYPE(kind=KIND) function modulo(a,p)

      TYPE(kind=KIND),intent(in) :: a
      TYPE(kind=KIND),intent(in) :: p

**特性**#

  • a 可以是任何种类的实数整数

  • pa 具有相同的类型和种类

  • 结果和参数都具有相同的类型和种类。

**描述**#

modulo(3) 计算 ap

**选项**#

  • a

    要取模的值

  • p

    a 减少到的值,直到余数 <= p。它不能为零。

**结果**#

结果的类型和种类与参数相同。

  • 如果 ap 的类型为整数modulo(a,p) 的值为 a - floor (real(a) / real(p)) * p

  • 如果 ap 的类型为实数modulo(a,p) 的值为 a - floor (a / p) * p

返回值与 p 具有相同的符号,并且大小小于 p 的大小。

**示例**#

示例程序

program demo_modulo
implicit none
     print *, modulo(17,3)        ! yields 2
     print *, modulo(17.5,5.5)    ! yields 1.0

     print *, modulo(-17,3)       ! yields 1
     print *, modulo(-17.5,5.5)   ! yields 4.5

     print *, modulo(17,-3)       ! yields -1
     print *, modulo(17.5,-5.5)   ! yields -4.5
end program demo_modulo

结果

 >            2
 >    1.000000
 >            1
 >    4.500000
 >           -1
 >   -4.500000

**标准**#

Fortran 95

**另请参阅**#

mod(3)

fortran-lang 内在函数描述

sign#

**名称**#

sign(3) - [数值] 符号复制函数

**概要**#

    result = sign(a, b)
     elemental type(TYPE(kind=KIND))function sign(a, b)

      type(TYPE(kind=KIND)),intent(in) :: a, b

**特性**#

  • a 应为整数或实数类型。

  • b 应与 a 具有相同的类型。

  • 结果的特性与 a 相同。

**描述**#

sign(3) 返回一个值,该值具有a的大小,但具有b的符号。

对于区分正零和负零的处理器,sign() 可用于区分实数值 0.0 和 -0.0。当负零可区分时,SIGN (1.0, -0.0) 将返回 -1.0。

**选项**#

  • a

    将返回其大小的值。

  • b

    将返回其符号的值。

**结果**#

一个具有 a 的大小和 b 的符号的值。也就是说,

  • 如果b >= 0,则结果为abs(a)

  • 否则如果b < 0,则为-abs(a)

  • 如果b实数并且处理器区分-0.00.0,则结果为-abs(a)

**示例**#

示例程序

program demo_sign
implicit none
  ! basics
   print *,  sign( -12,  1 )
   print *,  sign( -12,  0 )
   print *,  sign( -12, -1 )
   print *,  sign(  12,  1 )
   print *,  sign(  12,  0 )
   print *,  sign(  12, -1 )

   if(sign(1.0,-0.0)== -1.0)then
      print *, 'this processor distinguishes +0 from -0'
   else
      print *, 'this processor does not distinguish +0 from -0'
   endif

   print *,  'elemental', sign( -12.0, [1.0, 0.0, -1.0] )

end program demo_sign

结果

             12
             12
            -12
             12
             12
            -12
    this processor does not distinguish +0 from -0
    elemental   12.00000       12.00000      -12.00000

**标准**#

FORTRAN 77

**另请参阅**#

abs(3)

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

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 的秩为 1,则为整数标量。否则,它应为标量或秩为 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 的秩为 1,则 array 的所有元素都将移位 shift 个位置。如果秩大于 1,则沿给定维度 array 的所有完整的秩为 1 的部分都将移位。从每个秩为 1 的部分的一端移出的元素将移回另一端。

**选项**#

  • array

    要移位的任何类型的数组

  • shift

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

  • dim

    沿其移动多秩**数组**的维度。默认为 1。

**结果**#

返回与**数组**参数类型和秩相同的数组。

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

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

**另请参阅**#

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_a**、**vector_b** 可以是任何相同大小的秩为一的数值或逻辑类型数组。

  • 这两个向量不必是相同类型的,但对于任何给定的调用,两者都必须是逻辑类型或数值类型。

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

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

**描述**#

**dot_product**(3) 计算两个向量**vector_a** 和 **vector_b** 的点积。

**选项**#

  • vector_a

    秩为 1 的值向量

  • vector_b

    如果**vector_a** 为数值类型,则类型应为数值类型;如果vector*a 为 _logical_ 类型,则类型应为 _logical_。vector_b 应为与**vector_a** 大小相同的秩为一的数组。

**结果**#

如果参数为数值类型,则返回值为数值类型的标量。如果参数为 _logical_ 类型,则返回值为 _ .true. _ 或 _ .false. _。

如果向量为 _integer_ 或 _real_ 类型,则结果为

     sum(vector_a*vector_b)

如果向量为 _complex_ 类型,则结果为

     sum(conjg(vector_a)*vector_b)**

如果向量为 _logical_ 类型,则结果为

     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** 的秩大于 1,并且指定了**dim**,则它与通过移除维度**dim** 而减少的**array** 形状相同。

  • **boundary** 可以是与**array** 类型和种类相同的标量。当**array** 的秩为 1 时,它必须是标量。否则,它可以是与通过维度**dim** 减少的**array** 形状相同的数组。对于某些类型,它可能仅不存在,如下所述。

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

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

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

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

**描述**#

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

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

如果存在**boundary**,则将从**boundary** 中复制相应的数值到另一端,否则将使用默认值。

**选项**#

  • array

    任何类型的数组,其元素将被移位。如果**array** 的秩为 1,则**array** 的所有元素都将移位**shift** 个位置。如果秩大于 1,则沿给定维度**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** 是秩为一或二的数值(_integer_、_real_ 或 _complex_)或 _logical_ 数组。

  • **matrix_b** 是秩为一或二的数值(_integer_、_real_ 或 _complex_)或 _logical_ 数组。

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

  • **matrix_b** 的第一维的大小必须等于**matrix_a** 的最后一维的大小。

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

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

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

**描述**#

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

**选项**#

  • matrix_a

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

  • matrix_b

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

    请注意,**matrix_a** 和**matrix_b** 可以是不同的数值类型。

**结果**#

**数值参数**#

如果**matrix_a** 和**matrix_b** 为数值类型,则结果为一个数组,其中包含**matrix_a** 和**matrix_b** 的常规矩阵乘积。

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

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

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

**形状和秩**#

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

  • 如果**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_a** 和**matrix_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指定的维度。

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

描述#

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

选项#

  • mask

    应为类型为逻辑的数组。

  • dim

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

结果#

结果与mask的类型相同。

如果dim不存在,则返回一个标量,表示mask中所有元素的奇偶校验:如果奇数个元素为.true.,则为.true.,否则为.false.

如果MASK的秩为一,则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

另请参见#

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