stdlib_math Module



Contents


Variables

TypeVisibilityAttributesNameInitial
integer, public, parameter:: DEFAULT_LINSPACE_LENGTH =100
integer, public, parameter:: DEFAULT_LOGSPACE_BASE =10
integer, public, parameter:: DEFAULT_LOGSPACE_LENGTH =50
real(kind=dp), public, parameter:: EULERS_NUMBER_DP =exp(1.0_dp)
real(kind=sp), public, parameter:: EULERS_NUMBER_SP =exp(1.0_sp)

Interfaces

public interface all_close

Returns a boolean scalar where two arrays are element-wise equal within a tolerance. (Specification)

  • private pure module function all_close_1_cdp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: a(:)
    complex(kind=dp), intent(in) :: b(:)
    real(kind=dp), intent(in), optional :: rel_tol
    real(kind=dp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_1_csp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: a(:)
    complex(kind=sp), intent(in) :: b(:)
    real(kind=sp), intent(in), optional :: rel_tol
    real(kind=sp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_1_rdp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: a(:)
    real(kind=dp), intent(in) :: b(:)
    real(kind=dp), intent(in), optional :: rel_tol
    real(kind=dp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_1_rsp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: a(:)
    real(kind=sp), intent(in) :: b(:)
    real(kind=sp), intent(in), optional :: rel_tol
    real(kind=sp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_2_cdp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: a(:,:)
    complex(kind=dp), intent(in) :: b(:,:)
    real(kind=dp), intent(in), optional :: rel_tol
    real(kind=dp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_2_csp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: a(:,:)
    complex(kind=sp), intent(in) :: b(:,:)
    real(kind=sp), intent(in), optional :: rel_tol
    real(kind=sp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_2_rdp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: a(:,:)
    real(kind=dp), intent(in) :: b(:,:)
    real(kind=dp), intent(in), optional :: rel_tol
    real(kind=dp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_2_rsp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: a(:,:)
    real(kind=sp), intent(in) :: b(:,:)
    real(kind=sp), intent(in), optional :: rel_tol
    real(kind=sp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_3_cdp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: a(:,:,:)
    complex(kind=dp), intent(in) :: b(:,:,:)
    real(kind=dp), intent(in), optional :: rel_tol
    real(kind=dp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_3_csp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: a(:,:,:)
    complex(kind=sp), intent(in) :: b(:,:,:)
    real(kind=sp), intent(in), optional :: rel_tol
    real(kind=sp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_3_rdp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: a(:,:,:)
    real(kind=dp), intent(in) :: b(:,:,:)
    real(kind=dp), intent(in), optional :: rel_tol
    real(kind=dp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private pure module function all_close_3_rsp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: a(:,:,:)
    real(kind=sp), intent(in) :: b(:,:,:)
    real(kind=sp), intent(in), optional :: rel_tol
    real(kind=sp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

public interface arange

arange creates a one-dimensional array of the integer/real type with fixed-spaced values of given spacing, within a given interval. (Specification)

  • private pure module function arange_i_int16(start, end, step) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int16), intent(in) :: start
    integer(kind=int16), intent(in), optional :: end
    integer(kind=int16), intent(in), optional :: step

    Return Value integer(kind=int16),allocatable, (:)

  • private pure module function arange_i_int32(start, end, step) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int32), intent(in) :: start
    integer(kind=int32), intent(in), optional :: end
    integer(kind=int32), intent(in), optional :: step

    Return Value integer(kind=int32),allocatable, (:)

  • private pure module function arange_i_int64(start, end, step) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int64), intent(in) :: start
    integer(kind=int64), intent(in), optional :: end
    integer(kind=int64), intent(in), optional :: step

    Return Value integer(kind=int64),allocatable, (:)

  • private pure module function arange_i_int8(start, end, step) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int8), intent(in) :: start
    integer(kind=int8), intent(in), optional :: end
    integer(kind=int8), intent(in), optional :: step

    Return Value integer(kind=int8),allocatable, (:)

  • private pure module function arange_r_dp(start, end, step) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: start
    real(kind=dp), intent(in), optional :: end
    real(kind=dp), intent(in), optional :: step

    Return Value real(kind=dp),allocatable, (:)

  • private pure module function arange_r_sp(start, end, step) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: start
    real(kind=sp), intent(in), optional :: end
    real(kind=sp), intent(in), optional :: step

    Return Value real(kind=sp),allocatable, (:)

public interface arg

arg computes the phase angle in the interval (-π,π]. (Specification)

  • private elemental function arg_sp(z) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: z

    Return Value real(kind=sp)

  • private elemental function arg_dp(z) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: z

    Return Value real(kind=dp)

public interface argd

argd computes the phase angle of degree version in the interval (-180.0,180.0]. (Specification)

  • private elemental function argd_sp(z) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: z

    Return Value real(kind=sp)

  • private elemental function argd_dp(z) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: z

    Return Value real(kind=dp)

public interface argpi

argpi computes the phase angle of circular version in the interval (-1.0,1.0]. (Specification)

  • private elemental function argpi_sp(z) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: z

    Return Value real(kind=sp)

  • private elemental function argpi_dp(z) result(result)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: z

    Return Value real(kind=dp)

public interface clip

  • private elemental function clip_int8(x, xmin, xmax) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int8), intent(in) :: x
    integer(kind=int8), intent(in) :: xmin
    integer(kind=int8), intent(in) :: xmax

    Return Value integer(kind=int8)

  • private elemental function clip_int16(x, xmin, xmax) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int16), intent(in) :: x
    integer(kind=int16), intent(in) :: xmin
    integer(kind=int16), intent(in) :: xmax

    Return Value integer(kind=int16)

  • private elemental function clip_int32(x, xmin, xmax) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int32), intent(in) :: x
    integer(kind=int32), intent(in) :: xmin
    integer(kind=int32), intent(in) :: xmax

    Return Value integer(kind=int32)

  • private elemental function clip_int64(x, xmin, xmax) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int64), intent(in) :: x
    integer(kind=int64), intent(in) :: xmin
    integer(kind=int64), intent(in) :: xmax

    Return Value integer(kind=int64)

  • private elemental function clip_sp(x, xmin, xmax) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: x
    real(kind=sp), intent(in) :: xmin
    real(kind=sp), intent(in) :: xmax

    Return Value real(kind=sp)

  • private elemental function clip_dp(x, xmin, xmax) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: x
    real(kind=dp), intent(in) :: xmin
    real(kind=dp), intent(in) :: xmax

    Return Value real(kind=dp)

public interface diff

Computes differences between adjacent elements of an array. (Specification)

  • private pure module function diff_1_dp(x, n, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: x(:)
    integer, intent(in), optional :: n
    real(kind=dp), intent(in), optional :: prepend(:)
    real(kind=dp), intent(in), optional :: append(:)

    Return Value real(kind=dp),allocatable, (:)

  • private pure module function diff_1_int16(x, n, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int16), intent(in) :: x(:)
    integer, intent(in), optional :: n
    integer(kind=int16), intent(in), optional :: prepend(:)
    integer(kind=int16), intent(in), optional :: append(:)

    Return Value integer(kind=int16),allocatable, (:)

  • private pure module function diff_1_int32(x, n, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int32), intent(in) :: x(:)
    integer, intent(in), optional :: n
    integer(kind=int32), intent(in), optional :: prepend(:)
    integer(kind=int32), intent(in), optional :: append(:)

    Return Value integer(kind=int32),allocatable, (:)

  • private pure module function diff_1_int64(x, n, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int64), intent(in) :: x(:)
    integer, intent(in), optional :: n
    integer(kind=int64), intent(in), optional :: prepend(:)
    integer(kind=int64), intent(in), optional :: append(:)

    Return Value integer(kind=int64),allocatable, (:)

  • private pure module function diff_1_int8(x, n, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int8), intent(in) :: x(:)
    integer, intent(in), optional :: n
    integer(kind=int8), intent(in), optional :: prepend(:)
    integer(kind=int8), intent(in), optional :: append(:)

    Return Value integer(kind=int8),allocatable, (:)

  • private pure module function diff_1_sp(x, n, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: x(:)
    integer, intent(in), optional :: n
    real(kind=sp), intent(in), optional :: prepend(:)
    real(kind=sp), intent(in), optional :: append(:)

    Return Value real(kind=sp),allocatable, (:)

  • private pure module function diff_2_dp(x, n, dim, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: x(:,:)
    integer, intent(in), optional :: n
    integer, intent(in), optional :: dim
    real(kind=dp), intent(in), optional :: prepend(:,:)
    real(kind=dp), intent(in), optional :: append(:,:)

    Return Value real(kind=dp),allocatable, (:,:)

  • private pure module function diff_2_int16(x, n, dim, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int16), intent(in) :: x(:,:)
    integer, intent(in), optional :: n
    integer, intent(in), optional :: dim
    integer(kind=int16), intent(in), optional :: prepend(:,:)
    integer(kind=int16), intent(in), optional :: append(:,:)

    Return Value integer(kind=int16),allocatable, (:,:)

  • private pure module function diff_2_int32(x, n, dim, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int32), intent(in) :: x(:,:)
    integer, intent(in), optional :: n
    integer, intent(in), optional :: dim
    integer(kind=int32), intent(in), optional :: prepend(:,:)
    integer(kind=int32), intent(in), optional :: append(:,:)

    Return Value integer(kind=int32),allocatable, (:,:)

  • private pure module function diff_2_int64(x, n, dim, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int64), intent(in) :: x(:,:)
    integer, intent(in), optional :: n
    integer, intent(in), optional :: dim
    integer(kind=int64), intent(in), optional :: prepend(:,:)
    integer(kind=int64), intent(in), optional :: append(:,:)

    Return Value integer(kind=int64),allocatable, (:,:)

  • private pure module function diff_2_int8(x, n, dim, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int8), intent(in) :: x(:,:)
    integer, intent(in), optional :: n
    integer, intent(in), optional :: dim
    integer(kind=int8), intent(in), optional :: prepend(:,:)
    integer(kind=int8), intent(in), optional :: append(:,:)

    Return Value integer(kind=int8),allocatable, (:,:)

  • private pure module function diff_2_sp(x, n, dim, prepend, append) result(y)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: x(:,:)
    integer, intent(in), optional :: n
    integer, intent(in), optional :: dim
    real(kind=sp), intent(in), optional :: prepend(:,:)
    real(kind=sp), intent(in), optional :: append(:,:)

    Return Value real(kind=sp),allocatable, (:,:)

public interface gcd

Returns the greatest common divisor of two integers (Specification)

Read more…
  • private elemental function gcd_int8(a, b) result(res)

    Returns the greatest common divisor of two integers of kind int8 using the Euclidean algorithm.

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int8), intent(in) :: a
    integer(kind=int8), intent(in) :: b

    Return Value integer(kind=int8)

  • private elemental function gcd_int16(a, b) result(res)

    Returns the greatest common divisor of two integers of kind int16 using the Euclidean algorithm.

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int16), intent(in) :: a
    integer(kind=int16), intent(in) :: b

    Return Value integer(kind=int16)

  • private elemental function gcd_int32(a, b) result(res)

    Returns the greatest common divisor of two integers of kind int32 using the Euclidean algorithm.

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int32), intent(in) :: a
    integer(kind=int32), intent(in) :: b

    Return Value integer(kind=int32)

  • private elemental function gcd_int64(a, b) result(res)

    Returns the greatest common divisor of two integers of kind int64 using the Euclidean algorithm.

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int64), intent(in) :: a
    integer(kind=int64), intent(in) :: b

    Return Value integer(kind=int64)

public interface is_close

Returns a boolean scalar/array where two scalar/arrays are element-wise equal within a tolerance. (Specification)

  • private elemental module function is_close_cdp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: a
    complex(kind=dp), intent(in) :: b
    real(kind=dp), intent(in), optional :: rel_tol
    real(kind=dp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private elemental module function is_close_csp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: a
    complex(kind=sp), intent(in) :: b
    real(kind=sp), intent(in), optional :: rel_tol
    real(kind=sp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private elemental module function is_close_rdp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: a
    real(kind=dp), intent(in) :: b
    real(kind=dp), intent(in), optional :: rel_tol
    real(kind=dp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

  • private elemental module function is_close_rsp(a, b, rel_tol, abs_tol, equal_nan) result(close)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: a
    real(kind=sp), intent(in) :: b
    real(kind=sp), intent(in), optional :: rel_tol
    real(kind=sp), intent(in), optional :: abs_tol
    logical, intent(in), optional :: equal_nan

    Return Value logical

public interface linspace

Create rank 1 array of linearly spaced elements If the number of elements is not specified, create an array with size 100. If n is a negative value, return an array with size 0. If n = 1, return an array whose only element is end (Specification)

Read more…
  • private pure module function linspace_default_1_cdp_cdp(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: start
    complex(kind=dp), intent(in) :: end

    Return Value complex(kind=dp)(DEFAULT_LINSPACE_LENGTH)

  • private pure module function linspace_default_1_csp_csp(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: start
    complex(kind=sp), intent(in) :: end

    Return Value complex(kind=sp)(DEFAULT_LINSPACE_LENGTH)

  • private pure module function linspace_default_1_iint16_iint16(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int16), intent(in) :: start
    integer(kind=int16), intent(in) :: end

    Return Value real(kind=dp)(DEFAULT_LINSPACE_LENGTH)

  • private pure module function linspace_default_1_iint32_iint32(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int32), intent(in) :: start
    integer(kind=int32), intent(in) :: end

    Return Value real(kind=dp)(DEFAULT_LINSPACE_LENGTH)

  • private pure module function linspace_default_1_iint64_iint64(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int64), intent(in) :: start
    integer(kind=int64), intent(in) :: end

    Return Value real(kind=dp)(DEFAULT_LINSPACE_LENGTH)

  • private pure module function linspace_default_1_iint8_iint8(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int8), intent(in) :: start
    integer(kind=int8), intent(in) :: end

    Return Value real(kind=dp)(DEFAULT_LINSPACE_LENGTH)

  • private pure module function linspace_default_1_rdp_rdp(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: start
    real(kind=dp), intent(in) :: end

    Return Value real(kind=dp)(DEFAULT_LINSPACE_LENGTH)

  • private pure module function linspace_default_1_rsp_rsp(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: start
    real(kind=sp), intent(in) :: end

    Return Value real(kind=sp)(DEFAULT_LINSPACE_LENGTH)

  • private pure module function linspace_n_1_cdp_cdp(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: start
    complex(kind=dp), intent(in) :: end
    integer, intent(in) :: n

    Return Value complex(kind=dp)(max(n,0))

  • private pure module function linspace_n_1_csp_csp(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: start
    complex(kind=sp), intent(in) :: end
    integer, intent(in) :: n

    Return Value complex(kind=sp)(max(n,0))

  • private pure module function linspace_n_1_iint16_iint16(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int16), intent(in) :: start
    integer(kind=int16), intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=dp)(max(n,0))

  • private pure module function linspace_n_1_iint32_iint32(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int32), intent(in) :: start
    integer(kind=int32), intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=dp)(max(n,0))

  • private pure module function linspace_n_1_iint64_iint64(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int64), intent(in) :: start
    integer(kind=int64), intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=dp)(max(n,0))

  • private pure module function linspace_n_1_iint8_iint8(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=int8), intent(in) :: start
    integer(kind=int8), intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=dp)(max(n,0))

  • private pure module function linspace_n_1_rdp_rdp(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: start
    real(kind=dp), intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=dp)(max(n,0))

  • private pure module function linspace_n_1_rsp_rsp(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: start
    real(kind=sp), intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=sp)(max(n,0))

public interface logspace

Create rank 1 array of logarithmically spaced elements from basestart to baseend. If the number of elements is not specified, create an array with size 50. If n is a negative value, return an array with size 0. If n = 1, return an array whose only element is base**end. If no base is specified, logspace will default to using a base of 10

Read more…
  • private pure module function logspace_1_cdp_default(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: start
    complex(kind=dp), intent(in) :: end

    Return Value complex(kind=dp)(DEFAULT_LOGSPACE_LENGTH)

  • private pure module function logspace_1_cdp_n(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: start
    complex(kind=dp), intent(in) :: end
    integer, intent(in) :: n

    Return Value complex(kind=dp)(max(n,0))

  • private pure module function logspace_1_cdp_n_cbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: start
    complex(kind=dp), intent(in) :: end
    integer, intent(in) :: n
    complex(kind=dp), intent(in) :: base

    Return Value complex(kind=dp)(max(n,0))

  • private pure module function logspace_1_cdp_n_ibase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: start
    complex(kind=dp), intent(in) :: end
    integer, intent(in) :: n
    integer, intent(in) :: base

    Return Value complex(kind=dp)(max(n,0))

  • private pure module function logspace_1_cdp_n_rbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=dp), intent(in) :: start
    complex(kind=dp), intent(in) :: end
    integer, intent(in) :: n
    real(kind=dp), intent(in) :: base

    Return Value complex(kind=dp)(max(n,0))

  • private pure module function logspace_1_csp_default(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: start
    complex(kind=sp), intent(in) :: end

    Return Value complex(kind=sp)(DEFAULT_LOGSPACE_LENGTH)

  • private pure module function logspace_1_csp_n(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: start
    complex(kind=sp), intent(in) :: end
    integer, intent(in) :: n

    Return Value complex(kind=sp)(max(n,0))

  • private pure module function logspace_1_csp_n_cbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: start
    complex(kind=sp), intent(in) :: end
    integer, intent(in) :: n
    complex(kind=sp), intent(in) :: base

    Return Value complex(kind=sp)(max(n,0))

  • private pure module function logspace_1_csp_n_ibase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: start
    complex(kind=sp), intent(in) :: end
    integer, intent(in) :: n
    integer, intent(in) :: base

    Return Value complex(kind=sp)(max(n,0))

  • private pure module function logspace_1_csp_n_rbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    complex(kind=sp), intent(in) :: start
    complex(kind=sp), intent(in) :: end
    integer, intent(in) :: n
    real(kind=sp), intent(in) :: base

    Return Value complex(kind=sp)(max(n,0))

  • private pure module function logspace_1_iint32_default(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer, intent(in) :: start
    integer, intent(in) :: end

    Return Value real(kind=dp)(DEFAULT_LOGSPACE_LENGTH)

  • private pure module function logspace_1_iint32_n(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer, intent(in) :: start
    integer, intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=dp)(n)

  • private pure module function logspace_1_iint32_n_cdpbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer, intent(in) :: start
    integer, intent(in) :: end
    integer, intent(in) :: n
    complex(kind=dp), intent(in) :: base

    Return Value complex(kind=dp)(max(n,0))

  • private pure module function logspace_1_iint32_n_cspbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer, intent(in) :: start
    integer, intent(in) :: end
    integer, intent(in) :: n
    complex(kind=sp), intent(in) :: base

    Return Value complex(kind=sp)(max(n,0))

  • private pure module function logspace_1_iint32_n_ibase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer, intent(in) :: start
    integer, intent(in) :: end
    integer, intent(in) :: n
    integer, intent(in) :: base

    Return Value integer(max(n,0))

  • private pure module function logspace_1_iint32_n_rdpbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer, intent(in) :: start
    integer, intent(in) :: end
    integer, intent(in) :: n
    real(kind=dp), intent(in) :: base

    Return Value real(kind=dp)(max(n,0))

  • private pure module function logspace_1_iint32_n_rspbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    integer, intent(in) :: start
    integer, intent(in) :: end
    integer, intent(in) :: n
    real(kind=sp), intent(in) :: base

    Return Value real(kind=sp)(max(n,0))

  • private pure module function logspace_1_rdp_default(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: start
    real(kind=dp), intent(in) :: end

    Return Value real(kind=dp)(DEFAULT_LOGSPACE_LENGTH)

  • private pure module function logspace_1_rdp_n(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: start
    real(kind=dp), intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=dp)(max(n,0))

  • private pure module function logspace_1_rdp_n_cbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: start
    real(kind=dp), intent(in) :: end
    integer, intent(in) :: n
    complex(kind=dp), intent(in) :: base

    Return Value real(kind=dp)(max(n,0))

  • private pure module function logspace_1_rdp_n_ibase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: start
    real(kind=dp), intent(in) :: end
    integer, intent(in) :: n
    integer, intent(in) :: base

    Return Value real(kind=dp)(max(n,0))

  • private pure module function logspace_1_rdp_n_rbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=dp), intent(in) :: start
    real(kind=dp), intent(in) :: end
    integer, intent(in) :: n
    real(kind=dp), intent(in) :: base

    Return Value real(kind=dp)(max(n,0))

  • private pure module function logspace_1_rsp_default(start, end) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: start
    real(kind=sp), intent(in) :: end

    Return Value real(kind=sp)(DEFAULT_LOGSPACE_LENGTH)

  • private pure module function logspace_1_rsp_n(start, end, n) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: start
    real(kind=sp), intent(in) :: end
    integer, intent(in) :: n

    Return Value real(kind=sp)(max(n,0))

  • private pure module function logspace_1_rsp_n_cbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: start
    real(kind=sp), intent(in) :: end
    integer, intent(in) :: n
    complex(kind=sp), intent(in) :: base

    Return Value real(kind=sp)(max(n,0))

  • private pure module function logspace_1_rsp_n_ibase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: start
    real(kind=sp), intent(in) :: end
    integer, intent(in) :: n
    integer, intent(in) :: base

    Return Value real(kind=sp)(max(n,0))

  • private pure module function logspace_1_rsp_n_rbase(start, end, n, base) result(res)

    Arguments

    TypeIntentOptionalAttributesName
    real(kind=sp), intent(in) :: start
    real(kind=sp), intent(in) :: end
    integer, intent(in) :: n
    real(kind=sp), intent(in) :: base

    Return Value real(kind=sp)(max(n,0))