控制和查询当前数值模型#
exponent#
名称#
exponent(3) - [MODEL_COMPONENTS] Exponent of floating-point number
Synopsis#
result = exponent(x)
elemental integer function exponent(x)
real(kind=**),intent(in) :: x
Characteristics#
x shall be of type real of any valid kind
the result is a default integer type
说明#
exponent(3) returns the value of the exponent part of x, provided the exponent is within the range of default integers.
选项#
- x
the value to query the exponent of
结果#
exponent(3) returns the value of the exponent part of x
If x is zero the value returned is zero.
If x is an IEEE infinity or NaN, the result has the value HUGE(0).
示例#
示例程序:
program demo_exponent
implicit none
real :: x = 1.0
integer :: i
i = exponent(x)
print *, i
print *, exponent(0.0)
print *, exponent([10.0,100.0,1000.0,-10000.0])
print *, 2**[10.0,100.0,1000.0,-10000.0]
print *, exponent(huge(0.0))
print *, exponent(tiny(0.0))
end program demo_exponent
结果:
> 4 7 10 14
> 128
> -125
标准#
Fortran 95
另见#
digits(3), epsilon(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions
fraction#
名称#
fraction(3) - [MODEL_COMPONENTS] 模型表示的小数部分
Synopsis#
result = fraction(x)
elemental real(kind=KIND) function fraction(x)
real(kind=KIND),intent(in) :: fraction
Characteristics#
x is of type real
The result has the same characteristics as the argument.
说明#
fraction(3) returns the fractional part of the model representation of x.
选项#
- x
The value to interrogate
结果#
The fractional part of the model representation of x is returned; it is x * radix(x)**(-exponent(x)).
If x has the value zero, the result is zero.
If x is an IEEE NaN, the result is that NaN.
If x is an IEEE infinity, the result is an IEEE NaN.
示例#
示例程序:
program demo_fraction
implicit none
real :: x
x = 178.1387e-4
print *, fraction(x), x * radix(x)**(-exponent(x))
end program demo_fraction
结果:
0.5700439 0.5700439
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions
nearest#
名称#
nearest(3) - [MODEL_COMPONENTS] 最近的可表示数字
Synopsis#
result = nearest(x, s)
elemental real(kind=KIND) function nearest(x,s)
real(kind=KIND),intent(in) :: x
real(kind=**),intent(in) :: s
Characteristics#
x may be a real value of any kind.
s may be a real value of any kind.
其返回与 x同种类型和种类.
a kind designated as ** may be any supported kind for the type
说明#
nearest(3) returns the processor-representable number nearest to x in the direction indicated by the sign of s.
选项#
- x
the value to find the nearest representable value of
- s
a non-zero value whose sign is used to determine the direction in which to search from x to the representable value.
If s is positive, nearest returns the processor-representable number greater than x and nearest to it.
If s is negative, nearest returns the processor-representable number smaller than x and nearest to it.
结果#
返回值与 x 的类型相同。如果 s 为正数,则 nearest 返回大于 x 且最接近它的处理器可表示数字。如果 s 为负数,则 nearest 返回小于 x 且最接近它的处理器可表示数字。
示例#
示例程序:
program demo_nearest
implicit none
real :: x, y
x = nearest(42.0, 1.0)
y = nearest(42.0, -1.0)
write (*,"(3(g20.15))") x, y, x - y
! write (*,"(3(g20.15))") &
! nearest(tiny(0.0),1.0), &
! nearest(tiny(0.0),-1.0), &
! nearest(tiny(0.0),1.0) -nearest(tiny(0.0),-1.0)
! write (*,"(3(g20.15))") &
! nearest(huge(0.0),1.0), &
! nearest(huge(0.0),-1.0), &
! nearest(huge(0.0),1.0)- nearest(huge(0.0),-1.0)
end program demo_nearest
结果:
42.0000038146973 41.9999961853027 .762939453125000E-05
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions
rrspacing#
名称#
rrspacing(3) - [MODEL_COMPONENTS] Reciprocal of the relative spacing of a numeric type
Synopsis#
result = rrspacing(x)
elemental real(kind=KIND) function rrspacing(x)
real(kind=KIND),intent(in) :: x
Characteristics#
x is type real an any kind
其返回与 x同种类型和种类.
说明#
rrspacing(3) returns the reciprocal of the relative spacing of model numbers near x.
选项#
- x
应为 real 类型。
结果#
返回值与 x 具有相同的类型和种类。返回的值等于 abs(fraction(x)) * float(radix(x))**digits(x)。
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions
scale#
名称#
scale(3) - [MODEL_COMPONENTS] 以基数的整数幂缩放实数值
Synopsis#
result = scale(x, i)
elemental real(kind=KIND) function scale(x, i)
real(kind=KIND),intent(in) :: x
integer(kind=**),intent(in) :: i
Characteristics#
x is type real of any kind
i is type an integer of any kind
the result is real of the same kind as x
说明#
scale(3) returns x * radix(x)**i.
It is almost certain the radix(base) of the platform is two, therefore scale(3) is generally the same as x*2**i
选项#
- x
the value to multiply by radix(x)**i. Its type and kind is used to determine the radix for values with its characteristics and determines the characteristics of the result, so care must be taken the returned value is within the range of the characteristics of x.
- i
The power to raise the radix of the machine to
结果#
The return value is x * radix(x)**i, assuming that value can be represented by a value of the type and kind of x.
示例#
示例程序:
program demo_scale
implicit none
real :: x = 178.1387e-4
integer :: i = 5
print *, scale(x,i), x*radix(x)**i
end program demo_scale
结果:
0.570043862 0.570043862
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
set_exponent#
名称#
set_exponent(3) - [MODEL_COMPONENTS] real value with specified exponent
Synopsis#
result = set_exponent(x, i)
elemental real(kind=KIND) function set_exponent(x,i)
real(kind=KIND),intent(in) :: x
integer(kind=**),intent(in) :: i
Characteristics#
x is type real
i is type integer
a kind designated as ** may be any supported kind for the type
其返回与 x同种类型和种类.
说明#
set_exponent(3) returns the real number whose fractional part is that of x and whose exponent part is i.
选项#
- x
应为 real 类型。
- i
应为 integer 类型。
结果#
The return value is of the same type and kind as x. The real number whose fractional part is that of x and whose exponent part if i is returned; it is fraction(x) * radix(x)**i.
If x has the value zero, the result has the same value as x.
If x is an IEEE infinity, the result is an IEEE NaN.
If x is an IEEE NaN, the result is the same NaN.
示例#
示例程序:
program demo_setexp
implicit none
real :: x = 178.1387e-4
integer :: i = 17
print *, set_exponent(x, i), fraction(x) * radix(x)**i
end program demo_setexp
结果:
74716.7891 74716.7891
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions
spacing#
名称#
spacing(3) - [MODEL_COMPONENTS] 给定类型的两个数字之间的最小距离
Synopsis#
result = spacing(x)
elemental real(kind=KIND) function spacing(x)
real(kind=KIND), intent(in) :: x
Characteristics#
x is type real of any valid kind
结果与输入参数 x 的类型相同。
说明#
spacing(3) determines the distance between the argument x and the nearest adjacent number of the same type.
选项#
- x
应为 real 类型。
结果#
If x does not have the value zero and is not an IEEE infinity or NaN, the result has the value nearest to x for values of the same type and kind assuming the value is representable.
Otherwise, the value is the same as tiny(x). + zero produces tiny(x) + IEEE Infinity produces an IEEE Nan + if an IEEE NaN, that NaN is returned
If there are two extended model values equally near to x, the value of greater absolute value is taken.
示例#
示例程序:
program demo_spacing
implicit none
integer, parameter :: sgl = selected_real_kind(p=6, r=37)
integer, parameter :: dbl = selected_real_kind(p=13, r=200)
write(*,*) spacing(1.0_sgl)
write(*,*) nearest(1.0_sgl,+1.0),nearest(1.0_sgl,+1.0)-1.0
write(*,*) spacing(1.0_dbl)
end program demo_spacing
结果:
Typical values …
1.1920929E-07
1.000000 1.1920929E-07
0.9999999 -5.9604645E-08
2.220446049250313E-016
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
digits#
名称#
digits(3) - [NUMERIC MODEL] Significant digits in the numeric model
Synopsis#
result = digits(x)
integer function digits(x)
TYPE(kind=KIND),intent(in) :: x(..)
Characteristics#
x an integer or real scalar or array
The return value is an integer of default kind.
说明#
digits(3) returns the number of significant digits of the internal model representation of x. For example, on a system using a 32-bit floating point representation, a default real number would likely return 24.
选项#
- x
a value of the type and kind to query
结果#
The number of significant digits in a variable of the type and kind of x.
示例#
示例程序:
program demo_digits
implicit none
integer :: i = 12345
real :: x = 3.143
doubleprecision :: y = 2.33d0
print *,'default integer:', digits(i)
print *,'default real: ', digits(x)
print *,'default doubleprecision:', digits(y)
end program demo_digits
结果:
> default integer: 31
> default real: 24
> default doubleprecision: 53
标准#
Fortran 95
另见#
epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
epsilon#
名称#
epsilon(3) - [NUMERIC MODEL] Epsilon 函数
Synopsis#
result = epsilon(x)
real(kind=kind(x)) function epsilon(x)
real(kind=kind(x),intent(in) :: x(..)
Characteristics#
x shall be of type real. It may be a scalar or an array.
the result is a scalar of the same type and kind type parameter as x.
说明#
epsilon(3) returns the floating point relative accuracy. It is the nearly negligible number relative to 1 such that 1+ little_number is not equal to 1; or more precisely
real( 1.0, kind(x)) + epsilon(x) /= real( 1.0, kind(x))
它可以被认为是从 1.0 到下一个最大浮点数的距离。
epsilon(3) 的一种用途是为搜索算法选择一个 delta 值,直到计算结果在估计值的 delta 范围内。
如果 delta 太小,算法可能永远不会停止,因为小于数据类型的十进制分辨率的计算求和值不会改变。
选项#
- x
其类型应该是 real.
结果#
返回值与参数的类型相同。
示例#
示例程序:
program demo_epsilon
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=sp) :: x = 3.143
real(kind=dp) :: y = 2.33d0
! so if x is of type real32, epsilon(x) has the value 2**-23
print *, epsilon(x)
! note just the type and kind of x matter, not the value
print *, epsilon(huge(x))
print *, epsilon(tiny(x))
! the value changes with the kind of the real value though
print *, epsilon(y)
! adding and subtracting epsilon(x) changes x
write(*,*)x == x + epsilon(x)
write(*,*)x == x - epsilon(x)
! these next two comparisons will be .true. !
write(*,*)x == x + epsilon(x) * 0.999999
write(*,*)x == x - epsilon(x) * 0.999999
! you can calculate epsilon(1.0d0)
write(*,*)my_dp_eps()
contains
function my_dp_eps()
! calculate the epsilon value of a machine the hard way
real(kind=dp) :: t
real(kind=dp) :: my_dp_eps
! starting with a value of 1, keep dividing the value
! by 2 until no change is detected. Note that with
! infinite precision this would be an infinite loop,
! but floating point values in Fortran have a defined
! and limited precision.
my_dp_eps = 1.0d0
SET_ST: do
my_dp_eps = my_dp_eps/2.0d0
t = 1.0d0 + my_dp_eps
if (t <= 1.0d0) exit
enddo SET_ST
my_dp_eps = 2.0d0*my_dp_eps
end function my_dp_eps
end program demo_epsilon
结果:
1.1920929E-07
1.1920929E-07
1.1920929E-07
2.220446049250313E-016
F
F
T
T
2.220446049250313E-016
标准#
Fortran 95
另见#
digits(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
huge#
名称#
huge(3) - [NUMERIC MODEL] 该类型种类的最大数
Synopsis#
result = huge(x)
TYPE(kind=KIND) function huge(x)
TYPE(kind=KIND),intent(in) :: x(..)
Characteristics#
x may be any real or integer scalar or array and any kind.
The result will be a scalar of the same type and kind as the input x
说明#
huge(3) returns the largest number that is not an overflow for the kind and type of x.
选项#
- x
x is an arbitrary value which is used merely to determine what kind and type of scalar is being queried. It need not be defined, as only its characteristics are used.
结果#
The result is the largest value supported by the specified type and kind.
Note the result is as the same kind as the input to ensure the returned value does not overflow. Any assignment of the result to a variable should take this into consideration.
示例#
示例程序:
program demo_huge
implicit none
character(len=*),parameter :: f='(i2,1x,2(i11,1x),f14.0:,1x,l1,1x,a)'
integer :: i,j,k,biggest
real :: v, w
! basic
print *, huge(0), huge(0.0), huge(0.0d0)
print *, tiny(0.0), tiny(0.0d0)
sum=0.0d0
! note subtracting one because counter is the end value+1 on exit
do i=0,huge(0)-1
sum=sum+i
enddo
write(*,*)'sum=',sum
! advanced
biggest=huge(0)
! be careful of overflow when using integers in computation
do i=1,14
j=6**i ! Danger, Danger
w=6**i ! Danger, Danger
v=6.0**i
k=v ! Danger, Danger
if(v.gt.biggest)then
write(*,f) i, j, k, v, v.eq.w, 'wrong j and k and w'
else
write(*,f) i, j, k, v, v.eq.w
endif
enddo
end program demo_huge
结果:
2147483647 3.4028235E+38 1.797693134862316E+308
1.1754944E-38 2.225073858507201E-308
1 6 6 6. T
2 36 36 36. T
3 216 216 216. T
4 1296 1296 1296. T
5 7776 7776 7776. T
6 46656 46656 46656. T
7 279936 279936 279936. T
8 1679616 1679616 1679616. T
9 10077696 10077696 10077696. T
10 60466176 60466176 60466176. T
11 362797056 362797056 362797056. T
12 -2118184960 -2147483648 2176782336. F wrong for j and k and w
13 175792128 -2147483648 13060694016. F wrong for j and k and w
14 1054752768 -2147483648 78364164096. F wrong for j and k and w
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
maxexponent#
名称#
maxexponent(3) - [NUMERIC MODEL] 实数的最大指数
Synopsis#
result = maxexponent(x)
elemental integer function maxexponent(x)
real(kind=**),intent(in) :: x
Characteristics#
x is a real scalar or array of any real kind
the result is a default integer scalar
说明#
maxexponent(3) returns the maximum exponent in the model of the type of x.
选项#
- x
A value used to select the kind of real to return a value for.
结果#
The value returned is the maximum exponent for the kind of the value queried
示例#
示例程序:
program demo_maxexponent
use, intrinsic :: iso_fortran_env, only : real32,real64,real128
implicit none
character(len=*),parameter :: g='(*(g0,1x))'
print g, minexponent(0.0_real32), maxexponent(0.0_real32)
print g, minexponent(0.0_real64), maxexponent(0.0_real64)
print g, minexponent(0.0_real128), maxexponent(0.0_real128)
end program demo_maxexponent
结果:
-125 128
-1021 1024
-16381 16384
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
minexponent#
名称#
minexponent(3) - [NUMERIC MODEL] 实数的最小指数
Synopsis#
result = minexponent(x)
elemental integer function minexponent(x)
real(kind=**),intent(in) :: x
Characteristics#
x is a real scalar or array of any real kind
the result is a default integer scalar
说明#
minexponent(3) returns the minimum exponent in the model of the type of x.
选项#
- x
A value used to select the kind of real to return a value for.
结果#
The value returned is the maximum exponent for the kind of the value queried
示例#
示例程序:
program demo_minexponent
use, intrinsic :: iso_fortran_env, only : &
&real_kinds, real32, real64, real128
implicit none
real(kind=real32) :: x
real(kind=real64) :: y
print *, minexponent(x), maxexponent(x)
print *, minexponent(y), maxexponent(y)
end program demo_minexponent
预期成果:
-125 128
-1021 1024
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
precision#
名称#
precision(3) - [NUMERIC MODEL] 实数小数精度
Synopsis#
result = precision(x)
integer function precision(x)
TYPE(kind=**),intent(in) :: x
Characteristics#
x shall be of type real or complex. It may be a scalar or an array.
the result is a default integer scalar.
说明#
precision(3) returns the decimal precision in the model of the type of x.
选项#
- x
the type and kind of the argument are used to determine which number model to query. The value of the argument is not unused; it may even be undefined.
结果#
The precision of values of the type and kind of x
示例#
示例程序:
program demo_precision
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=sp) :: x(2)
complex(kind=dp) :: y
print *, precision(x), range(x)
print *, precision(y), range(y)
end program demo_precision
结果:
> 6 37
> 15 307
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
radix#
名称#
radix(3) - [NUMERIC MODEL] Base of a numeric model
Synopsis#
result = radix(x)
integer function radix(x)
TYPE(kind=**),intent(in) :: x(..)
Characteristics#
x may be scalar or an array of any real or integer type.
the result is a default integer scalar.
说明#
radix(3) returns the base of the internal model representing the numeric entity x.
In a positional numeral system, the radix or base is the number of unique digits, including the digit zero, used to represent numbers.
This function helps to represent the internal computing model generically, but will be 2 (representing a binary machine) for any common platform for all the numeric types.
选项#
- x
used to identify the type of number to query.
结果#
The returned value indicates what base is internally used to represent the type of numeric value x represents.
示例#
示例程序:
program demo_radix
implicit none
print *, "The radix for the default integer kind is", radix(0)
print *, "The radix for the default real kind is", radix(0.0)
print *, "The radix for the doubleprecision real kind is", radix(0.0d0)
end program demo_radix
结果:
> The radix for the default integer kind is 2
> The radix for the default real kind is 2
> The radix for the doubleprecision real kind is 2
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
range#
名称#
range(3) - [NUMERIC MODEL] Decimal exponent range of a numeric kind
Synopsis#
result = range(x)
integer function range (x)
TYPE(kind=KIND),intent(in) :: x
Characteristics#
x may be of type integer, real, or complex. It may be a scalar or an array.
KIND is any kind supported by the type of x
the result is a default integer scalar
说明#
range(3) returns the decimal exponent range in the model of the type of x.
Since x is only used to determine the type and kind being interrogated, the value need not be defined.
选项#
- x
the value whose type and kind are used for the query
结果#
- 案例(i)
For an integer argument, the result has the value
int (log10 (huge(x)))
- 案例(ii)
For a real argument, the result has the value
int(min (log10 (huge(x)), -log10(tiny(x) )))
- 案例(iii)
For a complex argument, the result has the value
range(real(x))
示例#
示例程序:
program demo_range
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=sp) :: x(2)
complex(kind=dp) :: y
print *, precision(x), range(x)
print *, precision(y), range(y)
end program demo_range
结果:
> 6 37
> 15 307
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), rrspacing(3), scale(3), set_exponent(3), spacing(3), tiny(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
tiny#
名称#
tiny(3) - [NUMERIC MODEL] 实数的最小正数
Synopsis#
result = tiny(x)
real(kind=KIND) function tiny(x)
real(kind=KIND) :: x
Characteristics#
x may be any real scalar or array
the result has the same type and kind as x
说明#
tiny(3) returns the smallest positive (non zero) number of the type and kind of x.
For real x
result = 2.0**(minexponent(x)-1)
选项#
- x
The value whose kind is used to determine the model type to query
结果#
指定种类的 real 类型的最小正值。
示例#
示例程序:
program demo_tiny
implicit none
print *, 'default real is from', tiny(0.0), 'to',huge(0.0)
print *, 'doubleprecision is from ', tiny(0.0d0), 'to',huge(0.0d0)
end program demo_tiny
结果:
default real is from 1.17549435E-38 to 3.40282347E+38
doubleprecision is from 2.2250738585072014E-308 to
1.7976931348623157E+308
标准#
Fortran 95
另见#
digits(3), epsilon(3), exponent(3), fraction(3), huge(3), maxexponent(3), minexponent(3), nearest(3), precision(3), radix(3), range(3), rrspacing(3), scale(3), set_exponent(3), spacing(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost