math

stdlib_math 模块

简介

stdlib_math 模块提供通用的数学函数。

提供的过程和方法

clip 函数

描述

返回一个位于给定区间 [xmin, xmax](区间包括 xminxmax)内的值,该值最接近输入值 x

语法

res = clip (x, xmin, xmax)

状态

实验性的

元素函数。

参数

x: integerreal 类型的标量。此参数为 intent(in)xmin: integerreal 类型的标量。此参数为 intent(in)xmax: integerreal 类型的标量,必须大于或等于 xmin。此参数为 intent(in)

注意:所有参数必须具有相同的 typekind

输出值或结果值

输出是 typekind 与参数相同的标量。

示例

示例 1

这里输入的类型为 integer,种类为 int32

program example_clip_integer
  use stdlib_math, only: clip
  use stdlib_kinds, only: int32
  implicit none
  integer(int32) :: x
  integer(int32) :: xmin
  integer(int32) :: xmax
  integer(int32) :: clipped_value

  xmin = -5_int32
  xmax = 5_int32
  x = 12_int32

  clipped_value = clip(x, xmin, xmax)
! clipped_value <- 5
end program example_clip_integer
示例 2

这里输入的类型为 real,种类为 sp

program example_clip_real
  use stdlib_math, only: clip
  use stdlib_kinds, only: sp
  implicit none
  real(sp) :: x
  real(sp) :: xmin
  real(sp) :: xmax
  real(sp) :: clipped_value

  xmin = -5.769_sp
  xmax = 3.025_sp
  x = 3.025_sp

  clipped_value = clip(x, xmin, xmax)
! clipped_value <- 3.02500010
end program example_clip_real

gcd 函数

描述

返回两个整数的最大公约数。

语法

res = gcd (a, b)

状态

实验性的

元素函数。

参数

a: 一个 intent(in) 的整数,用于获取其约数。b: 另一个 intent(in) 的整数,用于获取其约数。

注意:所有参数必须是相同 kind 的整数。

输出值或结果值

返回与参数具有相同 kind 的整数。

示例

示例 1
program example_gcd
  use stdlib_math, only: gcd
  implicit none
  integer :: a, b, c

  a = 48
  b = 18
  c = gcd(a, b) ! returns 6
end program example_gcd

linspace - 创建线性等间距的秩为一的数组

描述

返回从 [start, end] 的线性等间距的秩为 1 的数组。可选地,您可以通过传递 n 来指定返回数组的长度。

语法

res = linspace (start, end [, n])

状态

实验性的

纯函数。

参数

start: 应为任何数值类型或种类的标量。此参数为 intent(in)end: 应与 start 具有相同的 typekind。此参数为 intent(in)n: 应为指定输出长度的整数。此参数为 optionalintent(in)

输出值或结果值

输出是秩为 1 的数组,其长度为 100(默认值)或 n

如果 n == 1,则返回一个秩为 1 的数组,其唯一元素为 end。如果 n <= 0,则返回一个长度为 0 的秩为 1 的数组。

如果 start/endrealcomplex 类型,则 result 将与 start/end 具有相同的类型和种类。如果 start/endinteger 类型,则 result 将默认为 real(dp) 数组。

示例

示例 1

这里输入的类型为 complex,种类为 dp

program example_linspace_complex
  use stdlib_math, only: linspace
  use stdlib_kinds, only: dp
  implicit none

  complex(dp) :: start = cmplx(10.0_dp, 5.0_dp, kind=dp)
  complex(dp) :: end = cmplx(-10.0_dp, 15.0_dp, kind=dp)

  complex(dp) :: z(11)

  z = linspace(start, end, 11)
end program example_linspace_complex
示例 2

这里输入的类型为 integer,种类为 int16,结果默认为 real(dp)

program example_linspace_int16
  use stdlib_math, only: linspace
  use stdlib_kinds, only: int16, dp
  implicit none

  integer(int16) :: start = 10_int16
  integer(int16) :: end = 23_int16

  real(dp) :: r(15)

  r = linspace(start, end, 15)
end program example_linspace_int16

logspace - 创建对数等间距的秩为一的数组

描述

返回从 [base^start, base^end] 的对数等间距的秩为 1 的数组。数组的默认大小为 50。可选地,您可以通过传递 n 来指定返回数组的长度。您还可以指定用于计算范围的 base(默认值为 10)。

语法

res = logspace (start, end [, n [, base]])

状态

实验性的

纯函数。

参数

start: 应为任何数值类型的标量。所有种类都支持实数和复数参数。对于整数,目前只实现了默认种类。此参数为 intent(in)end: 应与 start 具有相同的 typekind。此参数为 intent(in)n: 应为指定输出长度的整数。此参数为 optionalintent(in)base : 应为任何数值类型的标量。所有种类都支持实数和复数参数。对于整数,目前只实现了默认种类。此参数为 optionalintent(in)

输出值或结果值

输出是秩为 1 的数组,其长度为 50(默认值)或 n

如果 n == 1,则返回一个秩为 1 的数组,其唯一元素为 base^end。如果 n <= 0,则返回一个长度为 0 的秩为 1 的数组

输出的 typekind 取决于传递的参数的 typekind

对于未指定 base 的函数调用:logspace(start, end)/logspace(start, end, n),输出的 typekind 遵循上述 linspace 的相同方案。

如果 start/endrealcomplex 类型,则 result 将与 start/end 具有相同的类型和种类。如果 start/end 为整数类型,则 result 将默认为 real(dp) 数组。

对于指定了 base 的函数调用,结果的 typekind 符合下表

start/end n base 输出
real(KIND) Integer real(KIND) real(KIND)
" " " " complex(KIND) complex(KIND)
" " " " Integer real(KIND)
complex(KIND) " " real(KIND) complex(KIND)
" " " " complex(KIND) complex(KIND)
" " " " Integer complex(KIND)
Integer " " real(KIND) real(KIND)
" " " " complex(KIND) complex(KIND)
" " " " Integer Integer

示例

示例 1

这里输入的类型为 complex,种类为 dpnbase 未指定,因此分别默认为 50 和 10。

program example_logspace_complex
  use stdlib_math, only: logspace
  use stdlib_kinds, only: dp
  implicit none

  complex(dp) :: start = (10.0_dp, 5.0_dp)
  complex(dp) :: end = (-10.0_dp, 15.0_dp)

  complex(dp) :: z(11) ! Complex values raised to complex powers results in complex values

  z = logspace(start, end, 11)
end program example_logspace_complex
示例 2

这里输入的类型为 integer 且为默认种类。base 未指定,因此默认为 10。

program example_logspace_int
  use stdlib_math, only: logspace
  use stdlib_kinds, only: dp
  implicit none

  integer, parameter :: start = 10
  integer, parameter :: end = 23
  integer, parameter :: n = 15

  real(dp) :: r(n) ! Integer values raised to real powers results in real values

  r = logspace(start, end, n)
end program example_logspace_int
示例 3

这里 start/end 的类型为 real 且为双精度。base 的类型为 complex 且也为双精度。

program example_logspace_rstart_cbase
  use stdlib_math, only: logspace
  use stdlib_kinds, only: dp
  implicit none

  real(dp) :: start = 0.0_dp
  real(dp) :: end = 3.0_dp
  integer, parameter :: n = 4
  complex(dp) :: base = (0.0_dp, 1.0_dp)

  complex(dp) :: z(n) ! complex values raised to real powers result in complex values

  z = logspace(start, end, n, base)

end program example_logspace_rstart_cbase

arange 函数

状态

实验性的

纯函数。

描述

创建具有给定间距的固定间距值的 integer/real 类型的秩为 1 的 array,位于给定区间内。

语法

result = arange (start [, end, step])

参数

所有参数应具有相同的类型和种类。

start: 应为 integer/real 标量。这是一个 intent(in) 参数。
默认 start 值为 1

end: 应为 integer/real 标量。这是一个 intent(in) 且为 optional 的参数。
默认 end 值为输入的 start 值。

step: 应为 integer/real 标量,且大于 0。这是一个 intent(in) 且为 optional 的参数。
默认 step 值为 1

警告

如果 step = 0,则 step 参数将被 arange 函数的内部过程更正为 1/1.0
如果 step < 0,则 step 参数将被 arange 函数的内部过程更正为 abs(step)

返回值

返回具有固定间距值的秩为 1 的 array

对于 integer 类型参数,结果向量的长度为 (end - start)/step + 1
对于 real 类型参数,结果向量的长度为 floor((end - start)/step) + 1

示例

program example_math_arange
  use stdlib_math, only: arange
  implicit none

  print *, arange(3)                 ! [1,2,3]
  print *, arange(-1)                ! [1,0,-1]
  print *, arange(0, 2)               ! [0,1,2]
  print *, arange(1, -1)              ! [1,0,-1]
  print *, arange(0, 2, 2)           ! [0,2]

  print *, arange(3.0)               ! [1.0,2.0,3.0]
  print *, arange(0.0, 5.0)           ! [0.0,1.0,2.0,3.0,4.0,5.0]
  print *, arange(0.0, 6.0, 2.5)       ! [0.0,2.5,5.0]

  print *, (1.0, 1.0)*arange(3)       ! [(1.0,1.0),(2.0,2.0),[3.0,3.0]]

  print *, arange(0.0, 2.0, -2.0)      ! [0.0,2.0].     Not recommended: `step` argument is negative!
  print *, arange(0.0, 2.0, 0.0)       ! [0.0,1.0,2.0]. Not recommended: `step` argument is zero!

end program example_math_arange

arg 函数

状态

实验性的

元素函数。

描述

arg 计算区间 (-π,π] 内 complex 标量的相位角(弧度版本)。θ 中的角度使得 z = abs(z)*exp((0.0, θ))

语法

result = arg (z)

参数

z: 应为 complex 标量/数组。这是一个 intent(in) 参数。

返回值

返回 complex 参数 zreal 类型相位角(弧度版本)。

注意:虽然复数 0 的角度是未定义的,但 arg((0,0)) 返回值 0

示例

program example_math_arg
  use stdlib_math, only: arg
  implicit none
  print *, arg((0.0, 0.0))                  ! 0.0
  print *, arg((3.0, 4.0))                  ! 0.927
  print *, arg(2.0*exp((0.0, 0.5)))         ! 0.5
  print *, arg([(0.0, 1.0), (1.0, 0.0), (0.0, -1.0), (-1.0, 0.0)])  ! [π/2, 0.0, -π/2, π]
end program example_math_arg

argd 函数

状态

实验性的

元素函数。

描述

argd 计算区间 (-180.0,180.0] 内 complex 标量的相位角(度版本)。θ 中的角度使得 z = abs(z)*exp((0.0, θ*π/180.0))

语法

result = argd (z)

参数

z: 应为 complex 标量/数组。这是一个 intent(in) 参数。

返回值

返回 complex 参数 zreal 类型相位角(度版本)。

注意:虽然复数 0 的角度是未定义的,但 argd((0,0)) 返回值 0

示例

program example_math_argd
  use stdlib_math, only: argd
  implicit none
  print *, argd((0.0, 0.0))                  ! 0.0°
  print *, argd((3.0, 4.0))                  ! 53.1°
  print *, argd(2.0*exp((0.0, 0.5)))         ! 28.64°
  print *, argd([(0.0, 1.0), (1.0, 0.0), (0.0, -1.0), (-1.0, 0.0)])  ! [90°, 0°, -90°, 180°]
end program example_math_argd

argpi 函数

状态

实验性的

元素函数。

描述

argpi 计算区间 (-1.0,1.0] 内 complex 标量的相位角(IEEE 圆形版本)。θ 中的角度使得 z = abs(z)*exp((0.0, θ*π))

语法

result = argpi (z)

参数

z: 应为 complex 标量/数组。这是一个 intent(in) 参数。

返回值

返回 complex 参数 zreal 类型相位角(圆形版本)。

注意:虽然复数 0 的角度是未定义的,但 argpi((0,0)) 返回值 0

示例

program example_math_argpi
  use stdlib_math, only: argpi
  implicit none
  print *, argpi((0.0, 0.0))                  ! 0.0
  print *, argpi((3.0, 4.0))                  ! 0.295
  print *, argpi(2.0*exp((0.0, 0.5)))         ! 0.159
  print *, argpi([(0.0, 1.0), (1.0, 0.0), (0.0, -1.0), (-1.0, 0.0)])  ! [0.5, 0.0, -0.5, 1.0]
end program example_math_argpi

deg2rad

状态

实验性的

元素函数。

描述

deg2rad 将相位角从度转换为弧度。

语法

result = deg2rad (theta)

参数

theta: 应为 real 标量/数组。

返回值

返回以弧度表示的 real 相位角。

示例

program example_math_deg2rad
    use stdlib_math, only: deg2rad
    implicit none
    print *, deg2rad(0.0)       ! 0.0
    print *, deg2rad(90.0)      ! 1.57508
    print *, deg2rad(-180.0)    ! -3.1416

end program example_math_deg2rad

rad2deg

状态

实验性的

元素函数。

描述

rad2deg 将相位角从弧度转换为度。

语法

result = rad2deg (theta)

参数

theta: 应为 real 标量/数组。

返回值

返回以度表示的 real 相位角。

示例

program example_math_rad2deg
    use stdlib_math, only: rad2deg
    use stdlib_constants, only: PI_sp
    implicit none
    print *, rad2deg(0.0)              ! 0.0
    print *, rad2deg(PI_sp / 2.0)      ! 90.0
    print *, rad2deg(-PI_sp)           ! -3.1416

end program example_math_rad2deg

is_close 函数

描述

返回一个布尔标量/数组,其中两个标量/数组在公差范围内逐元素相等。

!> For `real` type
is_close(a, b, rel_tol, abs_tol) = abs(a - b) <= max(rel_tol*(abs(a), abs(b)), abs_tol)

!> and for `complex` type
is_close(a, b, rel_tol, abs_tol) = is_close(a%re, b%re, rel_tol, abs_tol) .and. &
                                   is_close(a%im, b%im, rel_tol, abs_tol)

语法

bool = is_close (a, b [, rel_tol, abs_tol, equal_nan])

状态

实验性的。

元素函数。

参数

注意:所有 real/complex 参数必须具有相同的 kind
如果 rel_tol/abs_tol 的值为负数(不建议),则将被 is_close 的内部过程更正为 abs(rel_tol/abs_tol)

a: 应为 real/complex 标量/数组。此参数为 intent(in)

b: 应为 real/complex 标量/数组。此参数为 intent(in)

rel_tol: 应为 real 标量/数组。此参数为 intent(in)optional,默认值为 sqrt(epsilon(..))

abs_tol: 应为 real 标量/数组。此参数为 intent(in)optional,默认值为 0.0

equal_nan: 应为 logical 标量/数组。此参数为 intent(in)optional,默认值为 .false.。是否将 NaN 值视为相等。如果为 .true.,则 a 中的 NaN 值将被视为与 b 中的 NaN 值相等。

结果值

返回 logical 标量/数组。

示例

program example_math_is_close

  use stdlib_math, only: is_close
  implicit none
  real :: x(2) = [1, 2], y, NAN

  y = -3
  NAN = sqrt(y)

  print *, is_close(x, [real :: 1, 2.1])       ! [T, F]
  print *, is_close(2.0, 2.1, abs_tol=0.1)    ! T
  print *, NAN, is_close(2.0, NAN), is_close(2.0, NAN, equal_nan=.true.)   ! NAN, F, F
  print *, is_close(NAN, NAN), is_close(NAN, NAN, equal_nan=.true.)        ! F, T

end program example_math_is_close

all_close 函数

描述

返回一个布尔标量,其中两个数组在容差范围内逐元素相等。

语法

bool = all_close (a, b [, rel_tol, abs_tol, equal_nan])

状态

实验性的。

纯函数。

参数

注意:所有 real/complex 参数必须具有相同的 kind
如果 rel_tol/abs_tol 的值为负数(不推荐),则它将被 all_close 的内部过程修正为 abs(rel_tol/abs_tol)

a: 应为 real/complex 数组。此参数为 intent(in)

b: 应为 real/complex 数组。此参数为 intent(in)

rel_tol: 应为 real 标量。此参数为 intent(in)optional,默认值为 sqrt(epsilon(..))

abs_tol: 应为 real 标量。此参数为 intent(in)optional,默认值为 0.0

equal_nan: 应为 logical 标量。此参数为 intent(in)optional,默认值为 .false.。是否将 NaN 值视为相等。如果为 .true.,则 a 中的 NaN 值将被视为与 b 中的 NaN 值相等。

结果值

返回 logical 标量。

示例

program example_math_all_close

  use stdlib_math, only: all_close
  implicit none
  real    :: y, NAN
  complex :: z(4, 4)

  y = -3
  NAN = sqrt(y)
  z = (1.0, 1.0)

  print *, all_close(z + cmplx(1.0e-11, 1.0e-11), z)     ! T
  print *, NAN, all_close([NAN], [NAN]), all_close([NAN], [NAN], equal_nan=.true.)
! NAN, F, T

end program example_math_all_close

diff 函数

描述

计算数组相邻元素之间的差值。

语法

对于秩为 1 的数组
y = diff (x [, n, prepend, append])

对于秩为 2 的数组
y = diff (x [, n, dim, prepend, append])

状态

实验性的。

纯函数。

参数

x: 要进行差值的数组。应为 real/integerrank-1/rank-2 数组。此参数为 intent(in)

n: 迭代计算差值的次数。应为 integer 标量。此参数为 intent(in)optional,默认值为 1

dim: 要计算差值的输入数组的维度。其值必须在 1rank(x) 之间。应为 integer 标量。此参数为 intent(in)optional,默认值为 1

prepend, append: 要在执行差值之前沿轴追加到 a 的数组。维度和形状必须与 a 相匹配,除了轴。应为 real/integerrank-1/rank-2 数组。此参数为 intent(in)optional,默认值为无值。

注意

  • xprependappend 参数必须具有相同的 typekindrank
  • 如果 n 的值小于或等于 0(不推荐),则 diff 的返回值为 x
  • 如果 dim 的值不等于 12(不推荐),则 diff 的内部过程将使用 1

结果值

返回输入数组的有限差值。应为 real/integerrank-1/rank-2 数组。当 prependappend 均不存在时,结果 y 在维度 dim 方面比 x 少一个元素。

示例

program example_diff

  use stdlib_math, only: diff
  implicit none

  integer :: i(7) = [1, 1, 2, 3, 5, 8, 13]
  real    :: x(6) = [0, 5, 15, 30, 50, 75]
  integer :: A(3, 3) = reshape([1, 7, 17, 3, 11, 19, 5, 13, 23], [3, 3])
  integer :: Y(3, 2)

  print *, diff(i)        ! [0, 1, 1, 2, 3, 5]
  print *, diff(x, 2)     ! [5.0, 5.0, 5.0, 5.0]

  Y = diff(A, n=1, dim=2)
  print *, Y(1, :)        ! [2, 2]
  print *, Y(2, :)        ! [4, 2]
  print *, Y(3, :)        ! [2, 4]

  print *, diff(i, prepend=[0]) ! [1, 0, 1, 1, 2, 3, 5]
  print *, diff(i, append=[21]) ! [0, 1, 1, 2, 3, 5, 8]

end program example_diff

meshgrid 子例程

描述

从坐标向量计算坐标矩阵列表。

对于 $n \geq 1$ 个大小为 $(s_1, s_2, ..., s_n)$ 的坐标向量 $(x_1, x_2, ..., x_n)$,meshgrid 计算 $n$ 个具有相同形状的坐标矩阵 $(X_1, X_2, ..., X_n)$,对应于所选索引:- Cartesian 索引(默认行为):坐标矩阵的形状为 $(s_2, s_1, s_3, s_4, ... s_n)$。- 矩阵索引:坐标矩阵的形状为 $(s_1, s_2, s_3, s_4, ... s_n)$。

语法

对于 Cartesian 索引中的 2D 问题:call meshgrid (x, y, xm, ym)

对于 Cartesian 索引中的 3D 问题:call meshgrid (x, y, z, xm, ym, zm)

对于矩阵索引中的 3D 问题:call meshgrid (x, y, z, xm, ym, zm, indexing="ij")

只要 n 小于允许的最大数组秩,子例程就可以在 n 维情况下调用。

状态

实验性的。

子例程。

参数

对于 n 维问题,其中 n >= 1

x1, x2, ..., xn: 坐标向量。应为 real/integerrank-1 数组。这些参数为 intent(in)

xm1, xm2, ..., xmn: 坐标矩阵。应为类型为 realinteger 的数组,具有适当的形状:- 对于 Cartesian 索引,坐标矩阵的形状必须为 [size(x2), size(x1), size(x3), ..., size(xn)]。- 对于矩阵索引,坐标矩阵的形状必须为 [size(x1), size(x2), size(x3), ..., size(xn)]

这些参数为 intent(out)

indexing: 所选索引。应为 integer,对于 Cartesian 索引(默认值)等于 stdlib_meshgrid_xy,对于矩阵索引等于 stdlib_meshgrid_ijstdlib_meshgrid_xystdlib_meshgrid_ij 是在模块中定义的公共常量。此参数为 intent(in)optional,默认值为 stdlib_meshgrid_xy

示例

program example_meshgrid

    use stdlib_math, only: meshgrid, linspace, stdlib_meshgrid_ij
    use stdlib_kinds, only: sp

    implicit none

    integer, parameter :: nx = 3, ny = 2
    real(sp) :: x(nx), y(ny), &
            xm_cart(ny, nx), ym_cart(ny, nx), &
            xm_mat(nx, ny), ym_mat(nx, ny)

    x = linspace(0_sp, 1_sp, nx)
    y = linspace(0_sp, 1_sp, ny)

    call meshgrid(x, y, xm_cart, ym_cart)
    print *, "xm_cart = "
    call print_2d_array(xm_cart)
    print *, "ym_cart = "
    call print_2d_array(ym_cart)

    call meshgrid(x, y, xm_mat, ym_mat, indexing=stdlib_meshgrid_ij)
    print *, "xm_mat = "
    call print_2d_array(xm_mat)
    print *, "ym_mat = "
    call print_2d_array(ym_mat)

contains
    subroutine print_2d_array(array)
        real(sp), intent(in) :: array(:, :)
        integer :: i

        do i = 1, size(array, dim=1)
            print *, array(i, :)
        end do
    end subroutine
end program example_meshgrid