通用数学函数#
acos#
名称#
acos(3) - [数学:三角函数] 反余弦函数
概要#
result = acos(x)
elemental TYPE(kind=KIND) function acos(x)
TYPE(kind=KIND),intent(in) :: x
特征#
TYPE 可以是实数或复数
KIND 可以是相关类型支持的任何种类。
返回值将与参数具有相同的类型和种类。
描述#
acos(3) 计算x的反余弦(cos(x) 的反函数)。
选项#
- x
要计算其反正切的值。
如果类型为实数,则该值必须满足 |x| <= 1。
结果#
返回值与x的类型和种类相同。结果的实部以弧度表示,范围在0 <= acos(x%re) <= PI 之间。
示例#
示例程序
program demo_acos
use, intrinsic :: iso_fortran_env, only : real_kinds,real32,real64,real128
implicit none
character(len=*),parameter :: all='(*(g0,1x))'
real(kind=real64) :: x , d2r
! basics
x = 0.866_real64
print all,'acos(',x,') is ', acos(x)
! acos(-1) should be PI
print all,'for reference &
&PI ~= 3.14159265358979323846264338327950288419716939937510'
write(*,*) acos(-1.0_real64)
d2r=acos(-1.0_real64)/180.0_real64
print all,'90 degrees is ', d2r*90.0_real64, ' radians'
! elemental
print all,'elemental',acos([-1.0,-0.5,0.0,0.50,1.0])
! complex
print *,'complex',acos( (-1.0, 0.0) )
print *,'complex',acos( (-1.0, -1.0) )
print *,'complex',acos( ( 0.0, -0.0) )
print *,'complex',acos( ( 1.0, 0.0) )
end program demo_acos
结果
acos( 0.86599999999999999 ) is 0.52364958093182890
for reference PI ~= 3.14159265358979323846264338327950288419716939937510
3.1415926535897931
90 degrees is 1.5707963267948966 radians
elemental 3.14159274 2.09439516 1.57079637 1.04719758 0.00000000
complex (3.14159274,-0.00000000)
complex (2.23703575,1.06127501)
complex (1.57079637,0.00000000)
complex (0.00000000,-0.00000000)
标准#
FORTRAN 77;对于复数参数 - Fortran 2008
另请参阅#
反函数:cos(3)
资源#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
acosh#
名称#
acosh(3) - [数学:三角函数] 反双曲余弦函数
概要#
result = acosh(x)
elemental TYPE(kind=KIND) function acosh(x)
TYPE(kind=KIND),intent(in) :: x
特征#
TYPE 可以是实数或复数
KIND 可以是相关类型支持的任何种类。
返回值将与参数具有相同的类型和种类。
描述#
acosh(3) 以弧度计算x的反双曲余弦。
选项#
- x
要计算其双曲余弦的值
结果#
结果的值等于 X 的反双曲余弦函数的处理器相关近似值。
如果x为复数,则结果的虚部以弧度表示,介于
0 <= aimag(acosh(x)) <= PI
示例#
示例程序
program demo_acosh
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=dp), dimension(3) :: x = [ 1.0d0, 2.0d0, 3.0d0 ]
write (*,*) acosh(x)
end program demo_acosh
结果
0.000000000000000E+000 1.31695789692482 1.76274717403909
标准#
Fortran 2008
另请参阅#
反函数:cosh(3)
资源#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
asin#
名称#
asin(3) - [数学:三角函数] 反正弦函数
概要#
result = asin(x)
elemental TYPE(kind=KIND) function asin(x)
TYPE(kind=KIND) :: x
特征#
TYPE 可以是实数或复数
KIND 可以是相关类型支持的任何种类。
返回值将与参数具有相同的类型和种类。
描述#
asin(3) 计算其参数x的反正弦。
反正弦是正弦函数的反函数。当试图在已知直角三角形的斜边和对边的长度时找到角度时,它通常用于三角学。
选项#
- x
要计算其反正弦的值
类型应为实数且大小小于或等于 1;或为复数。
结果#
result 结果的值等于 arcsin(x) 的处理器相关近似值。
如果x为实数,则结果为实数,并以弧度表示,范围在
PI/2 <= ASIN (X) <= PI/2.
如果参数(以及结果)是虚数,则结果的实部以弧度表示,范围在
-PI/2 <= real(asin(x)) <= PI/2
示例#
当您知道对边与斜边的比率时,反正弦可以帮助您找到直角的度数。
因此,如果您知道一条铁路在 50 英里的轨道上垂直上升 1.25 英里,则可以使用反正弦确定轨道的平均倾斜角。鉴于
sin(theta) = 1.25 miles/50 miles (opposite/hypotenuse)
示例程序
program demo_asin
use, intrinsic :: iso_fortran_env, only : dp=>real64
implicit none
! value to convert degrees to radians
real(kind=dp),parameter :: D2R=acos(-1.0_dp)/180.0_dp
real(kind=dp) :: angle, rise, run
character(len=*),parameter :: all='(*(g0,1x))'
! given sine(theta) = 1.25 miles/50 miles (opposite/hypotenuse)
! then taking the arcsine of both sides of the equality yields
! theta = arcsine(1.25 miles/50 miles) ie. arcsine(opposite/hypotenuse)
rise=1.250_dp
run=50.00_dp
angle = asin(rise/run)
print all, 'angle of incline(radians) = ', angle
angle = angle/D2R
print all, 'angle of incline(degrees) = ', angle
print all, 'percent grade=',rise/run*100.0_dp
end program demo_asin
结果
angle of incline(radians) = 2.5002604899361139E-002
angle of incline(degrees) = 1.4325437375665075
percent grade= 2.5000000000000000
坡度百分比是指坡度,以百分比表示。要计算坡度,您需要将上升高度除以水平距离。在本例中,上升高度为 1.25 英里,水平距离为 50 英里,因此坡度为 1.25/50 = 0.025。以百分比表示,为 2.5%。
对于美国,2.5% 通常被认为是上限。这意味着前进 100 英尺时上升 2.5 英尺。在美国,这是第一条主要的美国铁路(巴尔的摩和俄亥俄铁路)的最大坡度。请注意,弯道会增加火车上的摩擦阻力,从而降低允许的坡度。
标准#
FORTRAN 77,对于复数参数 Fortran 2008
另请参阅#
反函数:sin(3)
资源#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
asinh#
名称#
asinh(3) - [数学:三角函数] 反双曲正弦函数
概要#
result = asinh(x)
elemental TYPE(kind=KIND) function asinh(x)
TYPE(kind=KIND) :: x
特征#
x 可以是任何实数或复数类型
KIND 可以是相关类型支持的任何种类
返回值将与参数x具有相同的类型和种类
描述#
asinh(3) 计算x的反双曲正弦。
选项#
- x
要计算其反双曲正弦的值
结果#
结果的值等于x的反双曲正弦函数的处理器相关近似值。
如果x为复数,则结果的虚部以弧度表示,介于-PI/2 <= aimag(asinh(x)) <= PI/2之间。
示例#
示例程序
program demo_asinh
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=dp), dimension(3) :: x = [ -1.0d0, 0.0d0, 1.0d0 ]
! elemental
write (*,*) asinh(x)
end program demo_asinh
结果
-0.88137358701954305 0.0000000000000000 0.88137358701954305
标准#
Fortran 2008
另请参阅#
反函数:sinh(3)
资源#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
atan#
名称#
atan(3) - [数学:三角函数] 反正切函数
概要#
result = atan([x) | atan(y, x)
elemental TYPE(kind=KIND) function atan(y,x)
TYPE(kind=KIND),intent(in) :: x
TYPE(kind=**),intent(in),optional :: y
特征#
如果存在y,则x和y都必须为实数。否则,x可以是复数。
KIND 可以是相关类型支持的任何种类。
返回值与x的类型和种类相同。
描述#
atan(3) 计算x的反正切。
选项#
- x
要计算其反正切的值。如果存在y,则x应为实数。
- y
与**x**具有相同类型和种类。如果**x**为零,则**y**不能为零。
**结果**#
返回值与**x**具有相同类型和种类。如果存在**y**,则结果与**atan2(y,x)**相同。否则,它是**x**的反正切,其中结果的实部以弧度表示,且位于范围**-PI/2 <= atan(x) <= PI/2**内。
**示例**#
示例程序
program demo_atan
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
character(len=*),parameter :: all='(*(g0,1x))'
real(kind=real64),parameter :: &
Deg_Per_Rad = 57.2957795130823208767981548_real64
real(kind=real64) :: x
x=2.866_real64
print all, atan(x)
print all, atan( 2.0d0, 2.0d0),atan( 2.0d0, 2.0d0)*Deg_Per_Rad
print all, atan( 2.0d0,-2.0d0),atan( 2.0d0,-2.0d0)*Deg_Per_Rad
print all, atan(-2.0d0, 2.0d0),atan(-2.0d0, 2.0d0)*Deg_Per_Rad
print all, atan(-2.0d0,-2.0d0),atan(-2.0d0,-2.0d0)*Deg_Per_Rad
end program demo_atan
结果
1.235085437457879
.7853981633974483 45.00000000000000
2.356194490192345 135.0000000000000
-.7853981633974483 -45.00000000000000
-2.356194490192345 -135.0000000000000
**标准**#
对于复数参数,使用FORTRAN 77;对于两个参数,使用Fortran 2008。
**另请参阅**#
**资源**#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
atan2#
**名称**#
atan2(3) - [数学:三角函数]反正切函数
**概要**#
result = atan2(y, x)
elemental real(kind=KIND) function atan2(y, x)
real,kind=KIND) :: atan2
real,kind=KIND),intent(in) :: y, x
**特征**#
**x**和**y**必须是相同种类的实数。
返回值与**y**和**x**具有相同的类型和种类。
**描述**#
atan2(3)以弧度计算复数(**x**,**y**)的反正切的处理器相关近似值,或者等效地计算值**y/x**的反正切的主值(它确定一个唯一的角度)。
如果**y**的值为零,则**x**的值不能为零。
结果相位位于范围-PI <= ATAN2 (Y,X) <= PI内,并且等于arctan(Y/X)值的处理器相关近似值。
**选项**#
- y
复数值**(x,y)**的虚部或点**<x,y>**的**y**分量。
- x
复数值**(x,y)**的实部或点**<x,y>**的**x**分量。
**结果**#
根据定义,返回值是复数**(x, y)**的主值,或者换句话说,是phasor x+i*y的相位。
主值只是当我们将弧度值调整到介于**-PI**和**PI**(含)之间时得到的值。
反正切的经典定义是在笛卡尔坐标系中从原点**<0,0>**到点**<x,y>**的直线形成的角度。
将其描绘成向量,很容易看出,如果**x**和**y**都为零,则角度是不确定的,因为它直接位于原点之上,因此**atan(0.0,0.0)**将产生错误。
按象限划分的返回值范围
> +PI/2
> |
> |
> PI/2 < z < PI | 0 > z < PI/2
> |
> +-PI -------------+---------------- +-0
> |
> PI/2 < -z < PI | 0 < -z < PI/2
> |
> |
> -PI/2
>
NOTES:
If the processor distinguishes -0 and +0 then the sign of the
returned value is that of Y when Y is zero, else when Y is zero
the returned value is always positive.
**示例**#
示例程序
program demo_atan2
real :: z
complex :: c
!
! basic usage
! ATAN2 (1.5574077, 1.0) has the value 1.0 (approximately).
z=atan2(1.5574077, 1.0)
write(*,*) 'radians=',z,'degrees=',r2d(z)
!
! elemental arrays
write(*,*)'elemental',atan2( [10.0, 20.0], [30.0,40.0] )
!
! elemental arrays and scalars
write(*,*)'elemental',atan2( [10.0, 20.0], 50.0 )
!
! break complex values into real and imaginary components
! (note TAN2() can take a complex type value )
c=(0.0,1.0)
write(*,*)'complex',c,atan2( x=c%re, y=c%im )
!
! extended sample converting cartesian coordinates to polar
COMPLEX_VALS: block
real :: ang, radius
complex,allocatable :: vals(:)
!
vals=[ &
( 1.0, 0.0 ), & ! 0
( 1.0, 1.0 ), & ! 45
( 0.0, 1.0 ), & ! 90
(-1.0, 1.0 ), & ! 135
(-1.0, 0.0 ), & ! 180
(-1.0,-1.0 ), & ! 225
( 0.0,-1.0 )] ! 270
do i=1,size(vals)
call cartesian_to_polar(vals(i)%re, vals(i)%im, radius,ang)
write(*,101)vals(i),ang,r2d(ang),radius
enddo
101 format( &
& 'X= ',f5.2, &
& ' Y= ',f5.2, &
& ' ANGLE= ',g0, &
& T38,'DEGREES= ',g0.4, &
& T54,'DISTANCE=',g0)
endblock COMPLEX_VALS
!
contains
!
elemental real function r2d(radians)
! input radians to convert to degrees
doubleprecision,parameter :: DEGREE=0.017453292519943d0 ! radians
real,intent(in) :: radians
r2d=radians / DEGREE ! do the conversion
end function r2d
!
subroutine cartesian_to_polar(x,y,radius,inclination)
! return angle in radians in range 0 to 2*PI
implicit none
real,intent(in) :: x,y
real,intent(out) :: radius,inclination
radius=sqrt(x**2+y**2)
if(radius.eq.0)then
inclination=0.0
else
inclination=atan2(y,x)
if(inclination < 0.0)inclination=inclination+2*atan2(0.0d0,-1.0d0)
endif
end subroutine cartesian_to_polar
!
end program demo_atan2
结果
> radians= 1.000000 degrees= 57.29578
> elemental 0.3217506 0.4636476
> elemental 0.1973956 0.3805064
> complex (0.0000000E+00,1.000000) 1.570796
> X= 1.00 Y= 0.00 ANGLE= .000000 DEGREES= .000 DISTANCE=1.000000
> X= 1.00 Y= 1.00 ANGLE= .7853982 DEGREES= 45.00 DISTANCE=1.414214
> X= 0.00 Y= 1.00 ANGLE= 1.570796 DEGREES= 90.00 DISTANCE=1.000000
> X= -1.00 Y= 1.00 ANGLE= 2.356194 DEGREES= 135.0 DISTANCE=1.414214
> X= -1.00 Y= 0.00 ANGLE= 3.141593 DEGREES= 180.0 DISTANCE=1.000000
> X= -1.00 Y= -1.00 ANGLE= 3.926991 DEGREES= 225.0 DISTANCE=1.414214
> X= 0.00 Y= -1.00 ANGLE= 4.712389 DEGREES= 270.0 DISTANCE=1.000000
**标准**#
FORTRAN 77
**另请参阅**#
**资源**#
arctan:wikipedia fortran-lang 内在描述 (许可证:MIT) @urbanjost
atanh#
**名称**#
atanh(3) - [数学:三角函数]反双曲正切函数
**概要**#
result = atanh(x)
elemental TYPE(kind=KIND) function atanh(x)
TYPE(kind=KIND),intent(in) :: x
**特征**#
**x**可以是任何关联类型的实数或复数
返回值将与参数具有相同的类型和种类。
**描述**#
atanh(3)计算**x**的反双曲正切。
**选项**#
- x
类型应为实数或复数。
**结果**#
返回值与**x**具有相同的类型和种类。如果**x**为复数,则结果的虚部以弧度表示,且位于
**-PI/2 <= aimag(atanh(x)) <= PI/2**
**示例**#
示例程序
program demo_atanh
implicit none
real, dimension(3) :: x = [ -1.0, 0.0, 1.0 ]
write (*,*) atanh(x)
end program demo_atanh
结果
> -Infinity 0.0000000E+00 Infinity
**标准**#
Fortran 2008
**另请参阅**#
反函数:tanh(3)
**资源**#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
cos#
**名称**#
cos(3) - [数学:三角函数]余弦函数
**概要**#
result = cos(x)
elemental TYPE(kind=KIND) function cos(x)
TYPE(kind=KIND),intent(in) :: x
**特征**#
**x**的类型为任何有效种类的实数或复数。
**KIND**可以是**x**的关联类型支持的任何种类。
返回值将与参数**x**具有相同的类型和种类。
**描述**#
cos(3)计算以弧度表示的角度**x**的余弦。
实数值的余弦是直角三角形中邻边与斜边之比。
**选项**#
- x
要计算其余弦的角度(以弧度表示)。
**结果**#
返回值是**x**的正切。
如果**x**的类型为实数,则返回值以弧度表示,且位于范围**-1 <= cos(x) <= 1**内。
如果**x**的类型为复数,则其实部被视为弧度值,通常称为相位。
**示例**#
示例程序
program demo_cos
implicit none
character(len=*),parameter :: g2='(a,t20,g0)'
doubleprecision,parameter :: PI=atan(1.0d0)*4.0d0
write(*,g2)'COS(0.0)=',cos(0.0)
write(*,g2)'COS(PI)=',cos(PI)
write(*,g2)'COS(PI/2.0d0)=',cos(PI/2.0d0),'EPSILON=',epsilon(PI)
write(*,g2)'COS(2*PI)=',cos(2*PI)
write(*,g2)'COS(-2*PI)=',cos(-2*PI)
write(*,g2)'COS(-2000*PI)=',cos(-2000*PI)
write(*,g2)'COS(3000*PI)=',cos(3000*PI)
end program demo_cos
结果
> COS(0.0)= 1.000000
> COS(PI)= -1.000000000000000
> COS(PI/2.0d0)= .6123233995736766E-16
> EPSILON= .2220446049250313E-15
> COS(2*PI)= 1.000000000000000
> COS(-2*PI)= 1.000000000000000
> COS(-2000*PI)= 1.000000000000000
> COS(3000*PI)= 1.000000000000000
**标准**#
FORTRAN 77
**另请参阅**#
**资源**#
fortran-lang 内在描述
cosh#
**名称**#
cosh(3) - [数学:三角函数]双曲余弦函数
**概要**#
result = cosh(x)
elemental TYPE(kind=KIND) function cosh(x)
TYPE(kind=KIND),intent(in) :: x
**特征**#
**TYPE**可以是任何种类的实数或复数。
返回值将与参数具有相同的类型和种类。
**描述**#
cosh(3)计算**x**的双曲余弦。
如果**x**的类型为复数,则其虚部被视为弧度值。
**选项**#
- x
要计算其双曲余弦的值
**结果**#
如果**x**为复数,则结果的虚部以弧度表示。
如果**x**为实数,则返回值的下限为1,**cosh(x) >= 1**。
**示例**#
示例程序
program demo_cosh
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
write(*,*)'X=',x,'COSH(X=)',cosh(x)
end program demo_cosh
结果
> X= 1.00000000000000 COSH(X=) 1.54308063481524
**标准**#
FORTRAN 77,对于复数参数 - Fortran 2008
**另请参阅**#
反函数:acosh(3)
**资源**#
fortran-lang 内在描述
sin#
**名称**#
sin(3) - [数学:三角函数]正弦函数
**概要**#
result = sin(x)
elemental TYPE(kind=KIND) function sin(x)
TYPE(kind=KIND) :: x
**特征**#
x 可以是任何实数或复数类型
**KIND**可以是**x**的关联类型支持的任何种类。
返回值将与参数**x**具有相同的类型和种类。
**描述**#
sin(3)计算给定角度大小(以弧度表示)的正弦。
直角三角形中一个角的正弦是该角对边长度与斜边长度之比。
**选项**#
- x
要计算其正弦的角度(以弧度表示)。
**结果**#
result返回值包含**x**的正弦的处理器相关近似值
如果X的类型为实数,则将其视为弧度值。
如果X的类型为复数,则其实部被视为弧度值。
**示例**#
示例程序
program sample_sin
implicit none
real :: x = 0.0
x = sin(x)
write(*,*)'X=',x
end program sample_sin
结果
> X= 0.0000000E+00
扩展示例#
海弗森公式#
摘自维基百科中的“海弗森公式”文章
The haversine formula is an equation important in navigation,
giving great-circle distances between two points on a sphere from
their longitudes and latitudes.
因此,要显示美国田纳西州纳什维尔国际机场 (BNA) 与美国加利福尼亚州洛杉矶国际机场 (LAX) 之间的弧线距离,您需要先获取它们的纬度和经度,通常表示为
BNA: N 36 degrees 7.2', W 86 degrees 40.2'
LAX: N 33 degrees 56.4', W 118 degrees 24.0'
转换为浮点值(以度为单位)为
Latitude Longitude
- BNA
36.12, -86.67
- LAX
33.94, -118.40
然后使用海弗森公式粗略计算这两个位置之间地球表面的距离
示例程序
program demo_sin
implicit none
real :: d
d = haversine(36.12,-86.67, 33.94,-118.40) ! BNA to LAX
print '(A,F9.4,A)', 'distance: ',d,' km'
contains
function haversine(latA,lonA,latB,lonB) result (dist)
!
! calculate great circle distance in kilometers
! given latitude and longitude in degrees
!
real,intent(in) :: latA,lonA,latB,lonB
real :: a,c,dist,delta_lat,delta_lon,lat1,lat2
real,parameter :: radius = 6371 ! mean earth radius in kilometers,
! recommended by the International Union of Geodesy and Geophysics
! generate constant pi/180
real, parameter :: deg_to_rad = atan(1.0)/45.0
delta_lat = deg_to_rad*(latB-latA)
delta_lon = deg_to_rad*(lonB-lonA)
lat1 = deg_to_rad*(latA)
lat2 = deg_to_rad*(latB)
a = (sin(delta_lat/2))**2 + &
& cos(lat1)*cos(lat2)*(sin(delta_lon/2))**2
c = 2*asin(sqrt(a))
dist = radius*c
end function haversine
end program demo_sin
结果
> distance: 2886.4446 km
**标准**#
FORTRAN 77
**另请参阅**#
asin(3),cos(3),tan(3),acosh(3),acos(3),asinh(3),atan2(3),atanh(3),acosh(3),asinh(3),atanh(3)
资源#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
sinh#
名称#
sinh(3) - [数学:三角函数] 双曲正弦函数
概要#
result = sinh(x)
elemental TYPE(kind=KIND) function sinh(x)
TYPE(kind=KIND) :: x
特征#
TYPE 可以是实数或复数
KIND 可以是相关类型支持的任何种类。
返回值将与参数具有相同的类型和种类。
描述#
sinh(3) 计算x的双曲正弦。
x 的双曲正弦在数学上定义为
sinh(x) = (exp(x) - exp(-x)) / 2.0
选项#
- x
要计算其双曲正弦的值
结果#
结果的值等于 sinh(X) 的处理器相关的近似值。如果 X 的类型为复数,则其虚部被视为以弧度为单位的值。
示例#
示例程序
program demo_sinh
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real64) :: x = - 1.0_real64
real(kind=real64) :: nan, inf
character(len=20) :: line
! basics
print *, sinh(x)
print *, (exp(x)-exp(-x))/2.0
! sinh(3) is elemental and can handle an array
print *, sinh([x,2.0*x,x/3.0])
! a NaN input returns NaN
line='NAN'
read(line,*) nan
print *, sinh(nan)
! a Inf input returns Inf
line='Infinity'
read(line,*) inf
print *, sinh(inf)
! an overflow returns Inf
x=huge(0.0d0)
print *, sinh(x)
end program demo_sinh
结果
-1.1752011936438014
-1.1752011936438014
-1.1752011936438014 -3.6268604078470190 -0.33954055725615012
NaN
Infinity
Infinity
标准#
Fortran 95,对于复数参数 Fortran 2008
另请参见#
资源#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
tan#
名称#
tan(3) - [数学:三角函数] 正切函数
概要#
result = tan(x)
elemental TYPE(kind=KIND) function tan(x)
TYPE(kind=KIND),intent(in) :: x
特征#
x的类型可以是任何受支持种类的实数或复数
返回值将与参数**x**具有相同的类型和种类。
描述#
tan(3) 计算x的正切。
选项#
- x
对于实数输入,以弧度为单位计算正切的角度。如果x的类型为复数,则其实部被视为以弧度为单位的值。
结果#
返回值是值x的正切。
示例#
示例程序
program demo_tan
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 0.165_real64
write(*,*)x, tan(x)
end program demo_tan
结果
0.16500000000000001 0.16651386310913616
标准#
FORTRAN 77。对于复数参数,Fortran 2008。
另请参见#
atan(3),atan2(3),cos(3),sin(3)
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
tanh#
名称#
tanh(3) - [数学:三角函数] 双曲正切函数
概要#
result = tanh(x)
elemental TYPE(kind=KIND) function tanh(x)
TYPE(kind=KIND),intent(in) :: x
特征#
x可以是实数或复数,以及处理器支持的任何关联种类。
返回值将与参数具有相同的类型和种类。
描述#
tanh(3) 计算x的双曲正切。
选项#
- x
要计算其双曲正切的值。
结果#
返回x的双曲正切。
如果x为复数,则结果的虚部被视为弧度值。
如果x为实数,则返回值位于范围
-1 <= tanh(x) <= 1.
示例#
示例程序
program demo_tanh
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real64) :: x = 2.1_real64
write(*,*)x, tanh(x)
end program demo_tanh
结果
2.1000000000000001 0.97045193661345386
标准#
FORTRAN 77,对于复数参数 Fortran 2008
另请参见#
资源#
fortran-lang 内在描述
random_number#
名称#
random_number(3) - [数学:随机] 伪随机数
概要#
call random_number(harvest)
subroutine random_number(harvest)
real,intent(out) :: harvest(..)
特征#
harvest和结果是默认的实数变量
描述#
random_number(3) 从范围 0 <= x < 1 内的均匀分布中返回单个伪随机数或伪随机数数组。
选项#
- harvest
应为类型为实数的标量或数组。
示例#
示例程序
program demo_random_number
use, intrinsic :: iso_fortran_env, only : dp=>real64
implicit none
integer, allocatable :: seed(:)
integer :: n
integer :: first,last
integer :: i
integer :: rand_int
integer,allocatable :: count(:)
real(kind=dp) :: rand_val
call random_seed(size = n)
allocate(seed(n))
call random_seed(get=seed)
first=1
last=10
allocate(count(last-first+1))
! To have a discrete uniform distribution on the integers
! [first, first+1, ..., last-1, last] carve the continuous
! distribution up into last+1-first equal sized chunks,
! mapping each chunk to an integer.
!
! One way is:
! call random_number(rand_val)
! choose one from last-first+1 integers
! rand_int = first + FLOOR((last+1-first)*rand_val)
count=0
! generate a lot of random integers from 1 to 10 and count them.
! with a large number of values you should get about the same
! number of each value
do i=1,100000000
call random_number(rand_val)
rand_int=first+floor((last+1-first)*rand_val)
if(rand_int.ge.first.and.rand_int.le.last)then
count(rand_int)=count(rand_int)+1
else
write(*,*)rand_int,' is out of range'
endif
enddo
write(*,'(i0,1x,i0)')(i,count(i),i=1,size(count))
end program demo_random_number
结果
1 10003588
2 10000104
3 10000169
4 9997996
5 9995349
6 10001304
7 10001909
8 9999133
9 10000252
10 10000196
标准#
Fortran 95
另请参见#
fortran-lang 内在描述
random_seed#
名称#
random_seed(3) - [数学:随机] 初始化伪随机数序列
概要#
call random_seed( [size] [,put] [,get] )
subroutine random_seed( size, put, get )
integer,intent(out),optional :: size
integer,intent(in),optional :: put(*)
integer,intent(out),optional :: get(*)
特征#
size一个标量默认整数
put一个秩为一的默认整数数组
get一个秩为一的默认整数数组
结果
描述#
random_seed(3) 重新启动或查询 random_number 使用的伪随机数生成器的状态。
如果在没有参数的情况下调用 random_seed,则它将使用从操作系统检索到的随机数据进行播种。
选项#
- size
指定与put和get参数一起使用的数组的最小大小。
- put
数组的大小必须大于或等于size参数返回的数字。
- get
它是intent(out),并且数组的大小必须大于或等于size参数返回的数字。
示例#
示例程序
program demo_random_seed
implicit none
integer, allocatable :: seed(:)
integer :: n
call random_seed(size = n)
allocate(seed(n))
call random_seed(get=seed)
write (*, *) seed
end program demo_random_seed
结果
-674862499 -1750483360 -183136071 -317862567 682500039
349459 344020729 -1725483289
标准#
Fortran 95
另请参见#
fortran-lang 内在描述
exp#
名称#
exp(3) - [数学] 以e为底的指数函数
概要#
result = exp(x)
elemental TYPE(kind=KIND) function exp(x)
TYPE(kind=KIND),intent(in) :: x
特征#
x可以是任何种类的实数或复数。
返回值与x具有相同的类型和种类。
描述#
exp(3) 返回e(自然对数的底数)的x次幂的值。
“e”也称为欧拉常数。
如果x的类型为复数,则其虚部被视为以弧度为单位的值,使得如果(见欧拉公式)
cx=(re,im)
那么
exp(cx) = exp(re) * cmplx(cos(im),sin(im),kind=kind(cx))
由于exp(3) 是log(3) 的反函数,因此x的实数分量的最大有效幅度为log(huge(x))。
选项#
- x
类型应为实数或复数。
结果#
结果的值为e**x,其中e是欧拉常数。
如果x的类型为复数,则其虚部被视为以弧度为单位的值。
示例#
示例程序
program demo_exp
implicit none
real :: x, re, im
complex :: cx
x = 1.0
write(*,*)"Euler's constant is approximately",exp(x)
!! complex values
! given
re=3.0
im=4.0
cx=cmplx(re,im)
! complex results from complex arguments are Related to Euler's formula
write(*,*)'given the complex value ',cx
write(*,*)'exp(x) is',exp(cx)
write(*,*)'is the same as',exp(re)*cmplx(cos(im),sin(im),kind=kind(cx))
! exp(3) is the inverse function of log(3) so
! the real component of the input must be less than or equal to
write(*,*)'maximum real component',log(huge(0.0))
! or for double precision
write(*,*)'maximum doubleprecision component',log(huge(0.0d0))
! but since the imaginary component is passed to the cos(3) and sin(3)
! functions the imaginary component can be any real value
end program demo_exp
结果
Euler's constant is approximately 2.718282
given the complex value (3.000000,4.000000)
exp(x) is (-13.12878,-15.20078)
is the same as (-13.12878,-15.20078)
maximum real component 88.72284
maximum doubleprecision component 709.782712893384
标准#
FORTRAN 77
另请参见#
资源#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
log#
名称#
log(3) - [数学] 自然对数
概要#
result = log(x)
elemental TYPE(kind=KIND) function log(x)
TYPE(kind=KIND),intent(in) :: x
特征#
x可以是任何实数或复数种类。
结果与x具有相同的类型和特征。
描述#
log(3) 计算x的自然对数,即以“e”为底的对数。
选项#
- x
要计算其自然对数的值。如果x为实数,则其值应大于零。如果x为复数,则其值不应为零。
结果#
x的自然对数。如果x是复数值(r,i),则虚部“i”位于范围
-PI < i <= PI
如果x的实部小于零且x的虚部为零,则结果的虚部近似为PI,如果PI的虚部为正实数零或处理器不区分正实数零和负实数零,并且近似为-PI,如果x的虚部为负实数零。
示例#
示例程序
program demo_log
implicit none
real(kind(0.0d0)) :: x = 2.71828182845904518d0
complex :: z = (1.0, 2.0)
write(*,*)x, log(x) ! will yield (approximately) 1
write(*,*)z, log(z)
end program demo_log
结果
2.7182818284590451 1.0000000000000000
(1.00000000,2.00000000) (0.804718971,1.10714877)
标准#
FORTRAN 77
另请参见#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
log10#
名称#
log10(3) - [数学] 以10为底的对数或常用对数
概要#
result = log10(x)
elemental real(kind=KIND) function log10(x)
real(kind=KIND),intent(in) :: x
特征#
x可以是任何种类的实数值
结果与x具有相同的类型和特征。
描述#
log10(3) 计算x以10为底的对数。这通常称为“常用对数”。
选项#
- x
一个实数值 > 0,用于取对数。
结果#
x 的以 10 为底的对数
示例#
示例程序
program demo_log10
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 10.0_real64
x = log10(x)
write(*,'(*(g0))')'log10(',x,') is ',log10(x)
! elemental
write(*, *)log10([1.0, 10.0, 100.0, 1000.0, 10000.0, &
& 100000.0, 1000000.0, 10000000.0])
end program demo_log10
结果
> log10(1.000000000000000) is .000000000000000
> 0.0000000E+00 1.000000 2.000000 3.000000 4.000000
> 5.000000 6.000000 7.000000
标准#
FORTRAN 77
另请参见#
fortran-lang 内在描述
sqrt#
名称#
sqrt(3) - [数学] 平方根函数
概要#
result = sqrt(x)
elemental TYPE(kind=KIND) function sqrt(x)
TYPE(kind=KIND),intent(in) :: x
特征#
TYPE 可以是实数或复数。
KIND 可以是声明类型有效的任何种类。
结果具有与x相同的特征。
描述#
sqrt(3) 计算x的主平方根。
正在考虑求平方根的数称为被开方数。
在数学中,被开方数x的平方根是一个数y,使得y*y = x。
每个非负被开方数x都有两个大小相同的平方根,一个正数,一个负数。非负平方根称为主平方根。
例如,9 的主平方根是 3,即使 (-3)*(-3) 也等于 9。
负数的平方根是复数的一种特殊情况,其中当complex输入时,被开方数的组成部分不需要为正才能具有有效的平方根。
选项#
- x
要查找其主平方根的被开方数。如果x为实数,则其值必须大于或等于零。
结果#
返回x的主平方根。
对于复数结果,实部大于或等于零。
当结果的实部为零时,虚部的符号与x的虚部相同。
示例#
示例程序
program demo_sqrt
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x, x2
complex :: z, z2
! basics
x = 2.0_real64
! complex
z = (1.0, 2.0)
write(*,*)'input values ',x,z
x2 = sqrt(x)
z2 = sqrt(z)
write(*,*)'output values ',x2,z2
! elemental
write(*,*)'elemental',sqrt([64.0,121.0,30.0])
! alternatives
x2 = x**0.5
z2 = z**0.5
write(*,*)'alternatively',x2,z2
end program demo_sqrt
结果
input values 2.00000000000000 (1.000000,2.000000)
output values 1.41421356237310 (1.272020,0.7861513)
elemental 8.000000 11.00000 5.477226
alternatively 1.41421356237310 (1.272020,0.7861513)
标准#
FORTRAN 77
另请参见#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
hypot#
名称#
hypot(3) - [数学] 返回欧几里得距离 - 点到原点的距离。
概要#
result = hypot(x, y)
elemental real(kind=KIND) function hypot(x,y)
real(kind=KIND),intent(in) :: x
real(kind=KIND),intent(in) :: y
特征#
x,y和结果都应为实数且具有相同的kind。
描述#
hypot(3) 被称为欧几里得距离函数。它等于
sqrt(x**2+y**2)
不会出现不必要的下溢或上溢。
在数学中,欧几里得空间中两点之间的欧几里得距离是这两点之间线段的长度。
hypot(x,y) 返回点<x,y>与原点之间的距离。
选项#
- x
类型应为实数。
- y
类型和kind类型参数应与x相同。
结果#
返回值具有与x相同的类型和kind类型参数。
结果是点<x,y>到原点<0.0,0.0>的距离的正值。
示例#
示例程序
program demo_hypot
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real32) :: x, y
real(kind=real32),allocatable :: xs(:), ys(:)
integer :: i
character(len=*),parameter :: f='(a,/,SP,*(3x,g0,1x,g0:,/))'
x = 1.e0_real32
y = 0.5e0_real32
write(*,*)
write(*,'(*(g0))')'point <',x,',',y,'> is ',hypot(x,y)
write(*,'(*(g0))')'units away from the origin'
write(*,*)
! elemental
xs=[ x, x**2, x*10.0, x*15.0, -x**2 ]
ys=[ y, y**2, -y*20.0, y**2, -y**2 ]
write(*,f)"the points",(xs(i),ys(i),i=1,size(xs))
write(*,f)"have distances from the origin of ",hypot(xs,ys)
write(*,f)"the closest is",minval(hypot(xs,ys))
end program demo_hypot
结果
point <1.00000000,0.500000000> is 1.11803401
units away from the origin
the points
+1.00000000 +0.500000000
+1.00000000 +0.250000000
+10.0000000 -10.0000000
+15.0000000 +0.250000000
-1.00000000 -0.250000000
have distances from the origin of
+1.11803401 +1.03077638
+14.1421356 +15.0020828
+1.03077638
the closest is
+1.03077638
标准#
Fortran 2008
另请参见#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
bessel_j0#
名称#
bessel_j0(3) - [数学] 零阶第一类贝塞尔函数
概要#
result = bessel_j0(x)
elemental real(kind=KIND) function bessel_j0(x)
real(kind=KIND),intent(in) :: x
特征#
KIND 可以是实数类型支持的任何KIND。
结果与x具有相同的类型和kind。
描述#
bessel_j0(3) 计算x的零阶第一类贝塞尔函数。
选项#
- x
要操作的值。
结果#
x的零阶第一类贝塞尔函数。结果位于范围-0.4027 <= bessel(0,x) <= 1内。
示例#
示例程序
program demo_bessel_j0
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x
x = 0.0_real64
x = bessel_j0(x)
write(*,*)x
end program demo_bessel_j0
结果
1.0000000000000000
标准#
Fortran 2008
另请参见#
bessel_j1(3),bessel_jn(3),bessel_y0(3),bessel_y1(3),bessel_yn(3)
fortran-lang 内在描述
bessel_j1#
名称#
bessel_j1(3) - [数学] 一阶第一类贝塞尔函数
概要#
result = bessel_j1(x)
elemental real(kind=KIND) function bessel_j1(x)
real(kind=KIND),intent(in) :: x
特征#
KIND 可以是任何支持的实数KIND。
结果与x具有相同的类型和kind
描述#
bessel_j1(3) 计算x的一阶第一类贝塞尔函数。
选项#
- x
类型应为实数。
结果#
返回值的类型为实数,位于范围-0.5818 <= bessel(0,x) <= 0.5818内。它与x具有相同的kind。
示例#
示例程序
program demo_bessel_j1
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
x = bessel_j1(x)
write(*,*)x
end program demo_bessel_j1
结果
0.44005058574493350
标准#
Fortran 2008
另请参见#
bessel_j0(3),bessel_jn(3),bessel_y0(3),bessel_y1(3),bessel_yn(3)
fortran-lang 内在描述
bessel_jn#
名称#
bessel_jn(3) - [数学] 第一类贝塞尔函数
概要#
result = bessel_jn(n, x)
elemental real(kind=KIND) function bessel_jn(n,x)
integer(kind=**),intent(in) :: n
real(kind=KIND),intent(in) :: x
KIND 可以是实数类型的任何有效值
x为实数
返回值与x具有相同的类型和种类。
result = bessel_jn(n1, n2, x)
real(kind=KIND) function bessel_jn(n1, n2, ,x)
integer(kind=**),intent(in) :: n1
integer(kind=**),intent(in) :: n2
real(kind=KIND),intent(in) :: x
n1为整数
n2为整数
x为实数
返回值与x具有相同的类型和种类。
描述#
bessel_jn( n, x )计算x的n阶第一类贝塞尔函数。
bessel_jn(n1, n2, x)返回一个数组,其中包含从n1到n2阶的第一类贝塞尔函数/贝塞尔函数。
选项#
- n
一个非负标量整数。
- n1
一个非负标量整数。
- n2
一个非负标量整数。
- x
对于bessel_jn(n,x)应为标量,或对于bessel_jn(n1, n2, x)为数组。
结果#
BESSEL_JN (N, X) 的结果值是 X 的 N 阶第一类贝塞尔函数的处理器相关近似值。
BESSEL_JN (N1, N2, X) 的结果是一个秩为一的数组,其范围为 MAX (N2-N1+1, 0)。BESSEL_JN (N1, N2, X) 的结果值的第 i 个元素是 X 的 N1+i-1 阶第一类贝塞尔函数的处理器相关近似值。
示例#
示例程序
program demo_bessel_jn
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
x = bessel_jn(5,x)
write(*,*)x
end program demo_bessel_jn
结果
2.4975773021123450E-004
标准#
Fortran 2008
另请参见#
bessel_j0(3),bessel_j1(3),bessel_y0(3),bessel_y1(3),bessel_yn(3)
fortran-lang 内在描述
bessel_y0#
名称#
bessel_y0(3) - [数学] 零阶第二类贝塞尔函数
概要#
result = bessel_y0(x)
elemental real(kind=KIND) function bessel_y0(x)
real(kind=KIND),intent(in) :: x
特征#
KIND 可以是任何支持的实数KIND。
结果的特征(类型、kind)与x相同
描述#
bessel_y0(3) 计算x的零阶第二类贝塞尔函数。
选项#
- x
类型应为实数。其值应大于零。
结果#
返回值的类型为实数。它与x具有相同的kind。
示例#
示例程序
program demo_bessel_y0
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 0.0_real64
x = bessel_y0(x)
write(*,*)x
end program demo_bessel_y0
结果
-Infinity
标准#
Fortran 2008
另请参见#
bessel_j0(3),bessel_j1(3),bessel_jn(3),bessel_y1(3),bessel_yn(3)
fortran-lang 内在描述
bessel_y1#
名称#
bessel_y1(3) - [数学] 一阶第二类贝塞尔函数
概要#
result = bessel_y1(x)
elemental real(kind=KIND) function bessel_y1(x)
real(kind=KIND),intent(in) :: x
特征#
KIND 可以是任何支持的实数KIND。
结果的特征(类型、kind)与x相同
描述#
bessel_y1(3) 计算x的一阶第二类贝塞尔函数。
选项#
- x
类型应为实数。其值应大于零。
结果#
返回值为实数。它与x的类型相同。
示例#
示例程序
program demo_bessel_y1
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
write(*,*)x, bessel_y1(x)
end program demo_bessel_y1
结果
> 1.00000000000000 -0.781212821300289
标准#
Fortran 2008
另请参阅#
bessel_j0(3),bessel_j1(3),bessel_jn(3),bessel_y0(3),bessel_yn(3)
fortran-lang 内在描述
bessel_yn#
名称#
bessel_yn(3) - [数学] 第二类贝塞尔函数
概要#
result = bessel_yn(n, x)
elemental real(kind=KIND) function bessel_yn(n,x)
integer(kind=**),intent(in) :: n
real(kind=KIND),intent(in) :: x
特征#
n 为整数
x为实数
返回值与x具有相同的类型和种类。
result = bessel_yn(n1, n2, x)
real(kind=KIND) function bessel_yn(n1, n2, ,x)
integer(kind=**),intent(in) :: n1
integer(kind=**),intent(in) :: n2
real(kind=KIND),intent(in) :: x
n1为整数
n2为整数
x为实数
返回值与x具有相同的类型和种类。
描述#
bessel_yn(n, x) 计算x的n阶第二类贝塞尔函数。
bessel_yn(n1, n2, x) 返回一个数组,其中包含从n1到n2阶的第一类贝塞尔函数。
选项#
- n
应为整数类型且非负的标量或数组。
- n1
应为整数类型且非负的非负标量。
- n2
应为整数类型且非负的非负标量。
- x
实数非负值。注意bessel_yn(n1, n2, x) 不是元素级的,在这种情况下它必须是标量。
结果#
BESSEL_YN (N, X) 的结果值是 X 的 N 阶第二类贝塞尔函数的处理器相关的近似值。
BESSEL_YN (N1, N2, X) 的结果是一个秩为一的数组,其范围为MAX (N2-N1+1, 0)。BESSEL_YN (N1, N2, X) 的结果值的第 i 个元素是 X 的 N1+i-1 阶第二类贝塞尔函数的处理器相关的近似值。
示例#
示例程序
program demo_bessel_yn
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
write(*,*) x,bessel_yn(5,x)
end program demo_bessel_yn
结果
1.0000000000000000 -260.40586662581222
标准#
Fortran 2008
另请参阅#
bessel_j0(3),bessel_j1(3),bessel_jn(3),bessel_y0(3),bessel_y1(3)
fortran-lang 内在描述
erf#
名称#
erf(3) - [数学] 误差函数
概要#
result = erf(x)
elemental real(kind=KIND) function erf(x)
real(kind=KIND),intent(in) :: x
特征#
x 的类型为实数
结果与x的类型和种类相同。
描述#
erf(3) 计算x的误差函数,定义为
选项#
- x
类型应为实数。
结果#
返回值的类型为实数,与x的种类相同,并且位于范围-1 <= erf(x) <= 1 内。
示例#
示例程序
program demo_erf
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 0.17_real64
write(*,*)x, erf(x)
end program demo_erf
结果
0.17000000000000001 0.18999246120180879
标准#
Fortran 2008
另请参阅#
资源#
fortran-lang 内在描述
erfc#
名称#
erfc(3) - [数学] 余误差函数
概要#
result = erfc(x)
elemental real(kind=KIND) function erfc(x)
real(kind=KIND),intent(in) :: x
特征#
x 的类型为实数,并且任何有效的种类
KIND 是实数类型中任何有效的值
结果与x的特征相同
描述#
erfc(3) 计算x的余误差函数。简单来说,这等价于1 - erf(x),但是提供erfc是因为如果对于较大的x调用erf(x)并从1中减去结果,则会极大地损失相对精度。
erfc(x) 定义为
选项#
- x
类型应为实数。
结果#
返回值的类型为实数,与x的种类相同。它位于范围
0 \<= **erfc**(x) \<= 2.
内,并且是x的余误差函数(**1-erf(x))**的处理器相关的近似值。
示例#
示例程序
program demo_erfc
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real64) :: x = 0.17_real64
write(*,'(*(g0))')'X=',x, ' ERFC(X)=',erfc(x)
write(*,'(*(g0))')'equivalently 1-ERF(X)=',1-erf(x)
end program demo_erfc
结果
> X=.1700000000000000 ERFC(X)=.8100075387981912
> equivalently 1-ERF(X)=.8100075387981912
标准#
Fortran 2008
另请参阅#
资源#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
erfc_scaled#
名称#
erfc_scaled(3) - [数学] 缩放的余误差函数
概要#
result = erfc_scaled(x)
elemental real(kind=KIND) function erfc_scaled(x)
real(kind=KIND),intent(in) :: x
特征#
x 的类型为任何有效种类的实数
KIND 是实数类型中任何有效的种类
结果与x的特征相同
描述#
erfc_scaled(3) 计算x的指数缩放的余误差函数
erfc_scaled(x)=exp(x*x)erfc(x)
注释1#
余误差函数渐近于 exp(-X2)/(X/PI)。因此,当使用 ISO/IEC/IEEE 60559:2011 单精度算术时,它在大约 X >= 9 时下溢。指数缩放的余误差函数渐近于 1/(X PI)。因此,它直到 X > HUGE (X)/PI 时才会下溢。
选项#
x 要应用erfc函数的值
结果#
x的指数缩放的余误差函数的近似值
示例#
示例程序
program demo_erfc_scaled
implicit none
real(kind(0.0d0)) :: x = 0.17d0
x = erfc_scaled(x)
print *, x
end program demo_erfc_scaled
结果
> 0.833758302149981
标准#
Fortran 2008
另请参阅#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost
gamma#
名称#
gamma(3) - [数学] Gamma 函数,它对正整数产生阶乘
概要#
result = gamma(x)
elemental real(kind=KIND) function gamma( x)
type(real,kind=KIND),intent(in) :: x
特征#
x 是一个实数值
返回一个与x种类相同的实数值。
描述#
gamma(x) 计算x的 Gamma 值。对于n的正整数,Gamma 函数可用于计算阶乘,因为(n-1)! == gamma(real(n))。也就是说
n! == gamma(real(n+1))
选项#
- x
应为实数类型,且既不为零也不为负整数。
结果#
返回值的类型为实数,与x的种类相同。结果的值等于x的 Gamma 函数的处理器相关的近似值。
示例#
示例程序
program demo_gamma
use, intrinsic :: iso_fortran_env, only : wp=>real64
implicit none
real :: x, xa(4)
integer :: i
x = gamma(1.0)
write(*,*)'gamma(1.0)=',x
! elemental
xa=gamma([1.0,2.0,3.0,4.0])
write(*,*)xa
write(*,*)
! gamma(3) is related to the factorial function
do i=1,20
! check value is not too big for default integer type
if(factorial(i).gt.huge(0))then
write(*,*)i,factorial(i)
else
write(*,*)i,factorial(i),int(factorial(i))
endif
enddo
! more factorials
FAC: block
integer,parameter :: n(*)=[0,1,5,11,170]
integer :: j
do j=1,size(n)
write(*,'(*(g0,1x))')'factorial of', n(j),' is ', &
& product([(real(i,kind=wp),i=1,n(j))]), &
& gamma(real(n(j)+1,kind=wp))
enddo
endblock FAC
contains
function factorial(i) result(f)
integer,parameter :: dp=kind(0d0)
integer,intent(in) :: i
real :: f
if(i.le.0)then
write(*,'(*(g0))')'<ERROR> gamma(3) function value ',i,' <= 0'
stop '<STOP> bad value in gamma function'
endif
f=gamma(real(i+1))
end function factorial
end program demo_gamma
结果
gamma(1.0)= 1.000000
1.000000 1.000000 2.000000 6.000000
1 1.000000 1
2 2.000000 2
3 6.000000 6
4 24.00000 24
5 120.0000 120
6 720.0000 720
7 5040.000 5040
8 40320.00 40320
9 362880.0 362880
10 3628800. 3628800
11 3.9916800E+07 39916800
12 4.7900160E+08 479001600
13 6.2270208E+09
14 8.7178289E+10
15 1.3076744E+12
16 2.0922791E+13
17 3.5568741E+14
18 6.4023735E+15
19 1.2164510E+17
20 2.4329020E+18
factorial of 0 is 1.000000000000000 1.000000000000000
factorial of 1 is 1.000000000000000 1.000000000000000
factorial of 5 is 120.0000000000000 120.0000000000000
factorial of 11 is 39916800.00000000 39916800.00000000
factorial of 170 is .7257415615307994E+307 .7257415615307999E+307
标准#
Fortran 2008
另请参阅#
Gamma 函数的对数:log_gamma(3)
资源#
fortran-lang 内在描述
log_gamma#
名称#
log_gamma(3) - [数学] Gamma 函数绝对值的自然对数
概要#
result = log_gamma(x)
elemental real(kind=KIND) function log_gamma(x)
real(kind=KIND),intent(in) :: x
特征#
x 可以是任何实数类型
返回值与x的类型和种类相同。
描述#
log_gamma(3) 计算 Gamma 函数绝对值的自然对数。
选项#
- x
既不为负也不为零的值,以呈现结果。
结果#
结果的值等于x的 Gamma 函数绝对值的自然对数的处理器相关的近似值。
示例#
示例程序
program demo_log_gamma
implicit none
real :: x = 1.0
write(*,*)x,log_gamma(x) ! returns 0.0
write(*,*)x,log_gamma(3.0) ! returns 0.693 (approximately)
end program demo_log_gamma
结果
> 1.000000 0.0000000E+00
> 1.000000 0.6931472
标准#
Fortran 2008
另请参阅#
Gamma 函数:gamma(3)
fortran-lang 内在描述
log_gamma#
名称#
log_gamma(3) - [数学] Gamma 函数绝对值的自然对数
概要#
result = log_gamma(x)
elemental real(kind=KIND) function log_gamma(x)
real(kind=KIND),intent(in) :: x
特征#
x 可以是任何实数类型
返回值与x的类型和种类相同。
描述#
log_gamma(3) 计算 Gamma 函数绝对值的自然对数。
选项#
- x
既不为负也不为零的值,以呈现结果。
结果#
结果的值等于x的 Gamma 函数绝对值的自然对数的处理器相关的近似值。
示例#
示例程序
program demo_log_gamma
implicit none
real :: x = 1.0
write(*,*)x,log_gamma(x) ! returns 0.0
write(*,*)x,log_gamma(3.0) ! returns 0.693 (approximately)
end program demo_log_gamma
结果
> 1.000000 0.0000000E+00
> 1.000000 0.6931472
标准#
Fortran 2008
另请参阅#
Gamma 函数:gamma(3)
fortran-lang 内在描述
norm2#
名称#
norm2(3) - [数学] 欧几里得向量范数
概要#
result = norm2(array, [dim])
real(kind=KIND) function norm2(array, dim)
real(kind=KIND),intent(in) :: array(..)
integer(kind=**),intent(in),optional :: dim
特征#
array 应为 实数 类型的数组。
dim 应为 整数 类型的标量
结果与 array 的类型相同。
描述#
norm2(3) 计算 array 沿维度 dim 的欧几里得向量范数(L_2 范数或广义 L 范数)。
选项#
- array
用于 L_2 范数计算的输入值数组
- dim
一个介于 1 到 rank(array) 之间的数值。
结果#
如果 dim 缺失,则返回一个标量,该标量为 array 元素平方和的平方根。
否则,返回一个秩为 n-1 的数组,其中 n 等于 array 的秩,并且形状类似于 array,但去掉了维度 DIM。
Case (i): The result of NORM2 (X) has a value equal to a
processor-dependent approximation to the generalized
L norm of X, which is the square root of the sum of
the squares of the elements of X. If X has size zero,
the result has the value zero.
Case (ii): The result of NORM2 (X, DIM=DIM) has a value equal
to that of NORM2 (X) if X has rank one. Otherwise,
the resulting array is reduced in rank with dimension
**dim** removed, and each remaining elment is the
result of NORM2(X) for the values along dimension
**dim**.
建议处理器在计算结果时避免不必要的溢出或下溢。
示例#
示例程序
program demo_norm2
implicit none
integer :: i
real :: x(2,3) = reshape([ &
1, 2, 3, &
4, 5, 6 &
],shape(x),order=[2,1])
write(*,*) 'input in row-column order'
write(*,*) 'x='
write(*,'(4x,3f4.0)')transpose(x)
write(*,*)
write(*,*) 'norm2(x)=',norm2(x)
write(*,*) 'which is equivalent to'
write(*,*) 'sqrt(sum(x**2))=',sqrt(sum(x**2))
write(*,*)
write(*,*) 'for reference the array squared is'
write(*,*) 'x**2='
write(*,'(4x,3f4.0)')transpose(x**2)
write(*,*)
write(*,*) 'norm2(x,dim=1)=',norm2(x,dim=1)
write(*,*) 'norm2(x,dim=2)=',norm2(x,dim=2)
write(*,*) '(sqrt(sum(x(:,i)**2)),i=1,3)=',(sqrt(sum(x(:,i)**2)),i=1,3)
write(*,*) '(sqrt(sum(x(i,:)**2)),i=1,2)=',(sqrt(sum(x(i,:)**2)),i=1,2)
end program demo_norm2
结果
> input in row-column order
> x=
> 1. 2. 3.
> 4. 5. 6.
>
> norm2(x)= 9.539392
> which is equivalent to
> sqrt(sum(x**2))= 9.539392
>
> for reference the array squared is
> x**2=
> 1. 4. 9.
> 16. 25. 36.
>
> norm2(x,dim=1)= 4.123106 5.385165 6.708204
> norm2(x,dim=2)= 3.741657 8.774964
> (sqrt(sum(x(:,i)**2)),i=1,3)= 4.123106 5.385165 6.708204
> (sqrt(sum(x(i,:)**2)),i=1,2)= 3.741657 8.774964
标准#
Fortran 2008
另请参阅#
fortran-lang 内在函数描述(许可证:MIT)@urbanjost