Controlling and querying the current numeric model#

exponent#

Name#

exponent(3) - [MODEL_COMPONENTS] Exponent function

Syntax#

result = exponent(x)

Description#

exponent(x) returns the value of the exponent part of x. If x is zero the value returned is zero.

Arguments#

  • x

    The type shall be real.

Returns#

The return value is of type default integer.

Examples#

Sample program:

program demo_exponent
implicit none
real :: x = 1.0
integer :: i
   i = exponent(x)
   print *, i
   print *, exponent(0.0)
end program demo_exponent

Results:

              1
              0

Standard#

Fortran 95 and later

See Also#

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#

Name#

fraction(3) - [MODEL_COMPONENTS] Fractional part of the model representation

Syntax#

y = fraction(x)

Description#

fraction(x) returns the fractional part of the model representation of x.

Arguments#

  • x

    The type of the argument shall be a real.

Returns#

The return value is of the same type and kind as the argument. The fractional part of the model representation of x is returned; it is x * radix(x)**(-exponent(x)).

Examples#

Sample program:

program demo_fraction
implicit none
real :: x
   x = 178.1387e-4
   print *, fraction(x), x * radix(x)**(-exponent(x))
end program demo_fraction

Results:

     0.570043862      0.570043862    

Standard#

Fortran 95 and later

See Also#

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#

Name#

nearest(3) - [MODEL_COMPONENTS] Nearest representable number

Syntax#

result = nearest(x, s)

Description#

nearest(x, s) returns the processor-representable number nearest to x in the direction indicated by the sign of s.

Arguments#

  • x

    Shall be of type real.

  • s

    Shall be of type real and not equal to zero.

Returns#

The return value is of the same type as x. 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.

Examples#

Sample program:

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

Results:

   42.0000038146973    41.9999961853027    .762939453125000E-05

Standard#

Fortran 95 and later

See Also#

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#

Name#

rrspacing(3) - [MODEL_COMPONENTS] Reciprocal of the relative spacing

Syntax#

result = rrspacing(x)

Description#

rrspacing(x) returns the reciprocal of the relative spacing of model numbers near x.

Arguments#

  • x

    Shall be of type real.

Returns#

The return value is of the same type and kind as x. The value returned is equal to abs(fraction(x)) * float(radix(x))**digits(x).

Standard#

Fortran 95 and later

See Also#

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#

Name#

scale(3) - [MODEL_COMPONENTS] Scale a real value by a whole power of the radix

Syntax#

result = scale(x, i)

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

Description#

scale(x,i) returns x * radix(x)**i.

Arguments#

  • x

    The type of the argument shall be a real.

  • i

    The type of the argument shall be a integer.

Returns#

The return value is of the same type and kind as x. Its value is x * radix(x)**i.

Examples#

Sample program:

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

Results:

    0.570043862      0.570043862

Standard#

Fortran 95 and later

See Also#

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

set_exponent#

Name#

set_exponent(3) - [MODEL_COMPONENTS] Set the exponent of the model

Syntax#

result = set_exponent(x, i)

Description#

set_exponent(x, i) returns the real number whose fractional part is that of x and whose exponent part is i.

Arguments#

  • x

    Shall be of type real.

  • i

    Shall be of type integer.

Returns#

The return value is of the same type and kind as x. The real number whose fractional part is that that of x and whose exponent part if i is returned; it is fraction(x) * radix(x)**i.

Examples#

Sample program:

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

Results:

      74716.7891       74716.7891    

Standard#

Fortran 95 and later

See Also#

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#

Name#

spacing(3) - [MODEL_COMPONENTS] Smallest distance between two numbers of a given type

Syntax#

result = spacing(x)

Description#

Determines the distance between the argument x and the nearest adjacent number of the same type.

Arguments#

  • x

    Shall be of type real.

Returns#

The result is of the same type as the input argument x.

Examples#

Sample program:

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)      ! "1.1920929e-07"          on i686
   write(*,*) spacing(1.0_dbl)      ! "2.220446049250313e-016" on i686
end program demo_spacing

Results:

      1.19209290E-07
      2.2204460492503131E-016

Standard#

Fortran 95 and later

See Also#

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

digits#

Name#

digits(3) - [NUMERIC MODEL] Significant digits function

Syntax#

result = digits(x)
    function digits(x)
    type(integer(kind=kind(0)))      :: digits
    type(TYPE(kind=KIND)),intent(in) :: x(..)

where TYPE may be integer or real and KIND is any kind supported by TYPE.

Description#

digits(x) 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.

Arguments#

  • x

    The type may be a scalar or array of type integer or real.

Returns#

The return value is of type integer of default kind.

Examples#

Sample program:

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

Typical Results:

    default integer:                  31
    default real:                     24
    default doubleprecision:          53

Standard#

Fortran 95 and later

See Also#

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#

Name#

epsilon(3) - [NUMERIC MODEL] Epsilon function

Syntax#

result = epsilon(x)

Description#

epsilon(x) 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))

It may be thought of as the distance from 1.0 to the next largest floating point number.

One use of epsilon(3) is to select a delta value for algorithms that search until the calculation is within delta of an estimate.

If delta is too small the algorithm might never halt, as a computation summing values smaller than the decimal resolution of the data type does not change.

Arguments#

  • x

    The type shall be real.

Returns#

The return value is of the same type as the argument.

Examples#

Sample program:

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

Results:

  1.1920929E-07
  1.1920929E-07
  1.1920929E-07
  2.220446049250313E-016
 F
 F
 T
 T
  2.220446049250313E-016

Standard#

Fortran 95 and later

See Also#

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#

Name#

huge(3) - [NUMERIC MODEL] Largest number of a type and kind

Syntax#

result = huge(x)

   function huge(x) result(answer)
   TYPE(kind=KIND),intent(in) :: x
   TYPE(kind=KIND) :: answer

where TYPE may be real or integer and KIND is any supported associated kind.

Description#

huge(x) returns the largest number that is not an infinity for the kind and type of x.

Arguments#

  • x

    Shall be an arbitrary value of type real or integer. The value is used merely to determine what kind and type of scalar is being queried.

Returns#

The return value is of the same type and kind as x and is the largest value supported by the specified model.

Examples#

Sample program:

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)

   ! 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

Results:

  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

Standard#

Fortran 95 and later

See Also#

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#

Name#

maxexponent(3) - [NUMERIC MODEL] Maximum exponent of a real kind

Syntax#

result = maxexponent(x)

Description#

maxexponent(x) returns the maximum exponent in the model of the type of x.

Arguments#

  • x

    Shall be of type real.

Returns#

The return value is of type integer and of the default integer kind.

Examples#

Sample program:

program demo_maxexponent
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=sp) :: x
real(kind=dp) :: y

   print *, minexponent(x), maxexponent(x)
   print *, minexponent(y), maxexponent(y)
end program demo_maxexponent

Results:

           -125         128
          -1021        1024

Standard#

Fortran 95 and later

See Also#

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

minexponent#

Name#

minexponent(3) - [NUMERIC MODEL] Minimum exponent of a real kind

Syntax#

result = minexponent(x)

Description#

minexponent(x) returns the minimum exponent in the model of the type of x.

Arguments#

  • x

    Shall be of type real.

Returns#

The return value is of type integer and of the default integer kind.

Examples#

Sample program:

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

Expected Results:

        -125         128
       -1021        1024

Standard#

Fortran 95 and later

See Also#

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

precision#

Name#

precision(3) - [NUMERIC MODEL] Decimal precision of a real kind

Syntax#

result = precision(x)

Description#

precision(x) returns the decimal precision in the model of the type of x.

Arguments#

  • x

    Shall be of type real or complex.

Returns#

The return value is of type integer and of the default integer kind.

Examples#

Sample program:

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

Results:

              6          37
             15         307

Standard#

Fortran 95 and later

See Also#

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

radix#

Name#

radix(3) - [NUMERIC MODEL] Base of a model number

Syntax#

result = radix(x)

Description#

radix(x) returns the base of the model representing the entity x.

Arguments#

  • x

    Shall be of type integer or real

Returns#

The return value is a scalar of type integer and of the default integer kind.

Examples#

Sample program:

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 doubleprecsion real kind is", radix(0.0d0)
end program demo_radix

Results:

    The radix for the default integer kind is           2
    The radix for the default real kind is           2
    The radix for the doubleprecsion real kind is           2

Standard#

Fortran 95 and later

See Also#

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

range#

Name#

range(3) - [NUMERIC MODEL] Decimal exponent range of a real kind

Syntax#

result = range(x)

      function range (x)
      integer :: range
      type(TYPE,kind=KIND),intent(in) :: x

where TYPE is real or complex and KIND is any kind supported by TYPE.

Description#

range(x) returns the decimal exponent range in the model of the type of x.

Arguments#

  • x

    Shall be of type real or complex.

Returns#

The return value is of type integer and of the default integer kind.

Examples#

Sample program:

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

Results:

              6          37
             15         307

Standard#

Fortran 95 and later

See Also#

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

tiny#

Name#

tiny(3) - [NUMERIC MODEL] Smallest positive number of a real kind

Syntax#

result = tiny(x)
   real(kind=KIND) function(x)
   real(kind=KIND) :: x

where KIND may be any kind supported by type real

Description#

tiny(x) returns the smallest positive (non zero) number of the type and kind of x.

Arguments#

  • x

    Shall be of type real.

Returns#

The smallest positive value for the real type of the specified kind.

The return value is of the same type and kind as x.

Examples#

Sample program:

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

Results:

 default real is from 1.17549435E-38 to 3.40282347E+38
 doubleprecision is from 2.2250738585072014E-308 to 1.7976931348623157E+308

Standard#

Fortran 95 and later

See Also#

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