stdlib_intrinsics Module

Alternative implementations of some Fortran intrinsic functions offering either faster and/or more accurate evaluation. (Specification)



Interfaces

public interface kahan_kernel

  • private elemental subroutine kahan_kernel_sp(a, s, c)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a
    real(kind=sp), intent(inout) :: s
    real(kind=sp), intent(inout) :: c
  • private elemental subroutine kahan_kernel_m_sp(a, s, c, m)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a
    real(kind=sp), intent(inout) :: s
    real(kind=sp), intent(inout) :: c
    logical, intent(in) :: m
  • private elemental subroutine kahan_kernel_dp(a, s, c)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a
    real(kind=dp), intent(inout) :: s
    real(kind=dp), intent(inout) :: c
  • private elemental subroutine kahan_kernel_m_dp(a, s, c, m)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a
    real(kind=dp), intent(inout) :: s
    real(kind=dp), intent(inout) :: c
    logical, intent(in) :: m
  • private elemental subroutine kahan_kernel_csp(a, s, c)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a
    complex(kind=sp), intent(inout) :: s
    complex(kind=sp), intent(inout) :: c
  • private elemental subroutine kahan_kernel_m_csp(a, s, c, m)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a
    complex(kind=sp), intent(inout) :: s
    complex(kind=sp), intent(inout) :: c
    logical, intent(in) :: m
  • private elemental subroutine kahan_kernel_cdp(a, s, c)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a
    complex(kind=dp), intent(inout) :: s
    complex(kind=dp), intent(inout) :: c
  • private elemental subroutine kahan_kernel_m_cdp(a, s, c, m)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a
    complex(kind=dp), intent(inout) :: s
    complex(kind=dp), intent(inout) :: c
    logical, intent(in) :: m

public interface stdlib_dot_product

Summary

dot_product of rank 1 arrays. (Specification)

Description

compute the dot_product of rank 1 arrays. The 1-D base implementation follows a chunked approach for optimizing performance and increasing accuracy. Supported data types include real, complex and integer.

  • private pure module function stdlib_dot_product_cdp(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a(:)
    complex(kind=dp), intent(in) :: b(:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_dot_product_csp(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a(:)
    complex(kind=sp), intent(in) :: b(:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_dot_product_dp(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a(:)
    real(kind=dp), intent(in) :: b(:)

    Return Value real(kind=dp)

  • private pure module function stdlib_dot_product_int16(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: a(:)
    integer(kind=int16), intent(in) :: b(:)

    Return Value integer(kind=int16)

  • private pure module function stdlib_dot_product_int32(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: a(:)
    integer(kind=int32), intent(in) :: b(:)

    Return Value integer(kind=int32)

  • private pure module function stdlib_dot_product_int64(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: a(:)
    integer(kind=int64), intent(in) :: b(:)

    Return Value integer(kind=int64)

  • private pure module function stdlib_dot_product_int8(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: a(:)
    integer(kind=int8), intent(in) :: b(:)

    Return Value integer(kind=int8)

  • private pure module function stdlib_dot_product_sp(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a(:)
    real(kind=sp), intent(in) :: b(:)

    Return Value real(kind=sp)

public interface stdlib_dot_product_kahan

Summary

dot_product of rank 1 arrays. (Specification)

Description

compute the dot_product of rank 1 arrays. The implementation follows a chunked approach combined with a kahan kernel for optimizing performance and increasing accuracy. Supported data types include real and complex.

  • private pure module function stdlib_dot_product_kahan_cdp(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a(:)
    complex(kind=dp), intent(in) :: b(:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_dot_product_kahan_csp(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a(:)
    complex(kind=sp), intent(in) :: b(:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_dot_product_kahan_dp(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a(:)
    real(kind=dp), intent(in) :: b(:)

    Return Value real(kind=dp)

  • private pure module function stdlib_dot_product_kahan_sp(a, b) result(p)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a(:)
    real(kind=sp), intent(in) :: b(:)

    Return Value real(kind=sp)

public interface stdlib_sum

Summary

Sum elements of rank N arrays. (Specification)

Description

This interface provides standard conforming call for sum of elements of any rank. The 1-D base implementation follows a chunked approach for optimizing performance and increasing accuracy. The N-D interfaces calls upon the (N-1)-D implementation. Supported data types include real, complex and integer.

  • private pure module function stdlib_sum_1d_cdp(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a(:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_sum_1d_cdp_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_sum_1d_csp(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a(:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_sum_1d_csp_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_sum_1d_dp(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a(:)

    Return Value real(kind=dp)

  • private pure module function stdlib_sum_1d_dp_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value real(kind=dp)

  • private pure module function stdlib_sum_1d_int16(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: a(:)

    Return Value integer(kind=int16)

  • private pure module function stdlib_sum_1d_int16_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value integer(kind=int16)

  • private pure module function stdlib_sum_1d_int32(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: a(:)

    Return Value integer(kind=int32)

  • private pure module function stdlib_sum_1d_int32_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value integer(kind=int32)

  • private pure module function stdlib_sum_1d_int64(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: a(:)

    Return Value integer(kind=int64)

  • private pure module function stdlib_sum_1d_int64_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value integer(kind=int64)

  • private pure module function stdlib_sum_1d_int8(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: a(:)

    Return Value integer(kind=int8)

  • private pure module function stdlib_sum_1d_int8_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value integer(kind=int8)

  • private pure module function stdlib_sum_1d_sp(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a(:)

    Return Value real(kind=sp)

  • private pure module function stdlib_sum_1d_sp_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value real(kind=sp)

  • private pure module function stdlib_sum_2d_cdp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_sum_2d_csp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_sum_2d_dim_cdp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value complex(kind=dp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_2d_dim_csp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value complex(kind=sp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_2d_dim_dp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value real(kind=dp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_2d_dim_int16(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value integer(kind=int16), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_2d_dim_int32(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value integer(kind=int32), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_2d_dim_int64(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value integer(kind=int64), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_2d_dim_int8(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value integer(kind=int8), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_2d_dim_sp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value real(kind=sp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_2d_dp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value real(kind=dp)

  • private pure module function stdlib_sum_2d_int16(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value integer(kind=int16)

  • private pure module function stdlib_sum_2d_int32(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value integer(kind=int32)

  • private pure module function stdlib_sum_2d_int64(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value integer(kind=int64)

  • private pure module function stdlib_sum_2d_int8(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value integer(kind=int8)

  • private pure module function stdlib_sum_2d_sp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value real(kind=sp)

  • private pure module function stdlib_sum_3d_cdp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_sum_3d_csp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_sum_3d_dim_cdp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value complex(kind=dp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_3d_dim_csp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value complex(kind=sp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_3d_dim_dp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value real(kind=dp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_3d_dim_int16(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value integer(kind=int16), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_3d_dim_int32(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value integer(kind=int32), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_3d_dim_int64(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value integer(kind=int64), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_3d_dim_int8(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value integer(kind=int8), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_3d_dim_sp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value real(kind=sp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_3d_dp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value real(kind=dp)

  • private pure module function stdlib_sum_3d_int16(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value integer(kind=int16)

  • private pure module function stdlib_sum_3d_int32(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value integer(kind=int32)

  • private pure module function stdlib_sum_3d_int64(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value integer(kind=int64)

  • private pure module function stdlib_sum_3d_int8(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value integer(kind=int8)

  • private pure module function stdlib_sum_3d_sp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value real(kind=sp)

public interface stdlib_sum_kahan

Summary

Sum elements of rank N arrays. (Specification)

Description

This interface provides standard conforming call for sum of elements of any rank. The 1-D base implementation follows a chunked approach combined with a kahan kernel for optimizing performance and increasing accuracy. The N-D interfaces calls upon the (N-1)-D implementation. Supported data types include real and complex.

  • private pure module function stdlib_sum_kahan_1d_cdp(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a(:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_sum_kahan_1d_cdp_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_sum_kahan_1d_csp(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a(:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_sum_kahan_1d_csp_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_sum_kahan_1d_dp(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a(:)

    Return Value real(kind=dp)

  • private pure module function stdlib_sum_kahan_1d_dp_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value real(kind=dp)

  • private pure module function stdlib_sum_kahan_1d_sp(a) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a(:)

    Return Value real(kind=sp)

  • private pure module function stdlib_sum_kahan_1d_sp_mask(a, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a(:)
    logical, intent(in) :: mask(:)

    Return Value real(kind=sp)

  • private pure module function stdlib_sum_kahan_2d_cdp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_sum_kahan_2d_csp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_sum_kahan_2d_dim_cdp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value complex(kind=dp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_kahan_2d_dim_csp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value complex(kind=sp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_kahan_2d_dim_dp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value real(kind=dp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_kahan_2d_dim_sp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:)

    Return Value real(kind=sp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_kahan_2d_dp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value real(kind=dp)

  • private pure module function stdlib_sum_kahan_2d_sp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:,:)
    logical, intent(in), optional :: mask(:,:)

    Return Value real(kind=sp)

  • private pure module function stdlib_sum_kahan_3d_cdp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value complex(kind=dp)

  • private pure module function stdlib_sum_kahan_3d_csp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value complex(kind=sp)

  • private pure module function stdlib_sum_kahan_3d_dim_cdp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value complex(kind=dp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_kahan_3d_dim_csp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value complex(kind=sp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_kahan_3d_dim_dp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value real(kind=dp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_kahan_3d_dim_sp(x, dim, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:,:,:)
    integer, intent(in) :: dim
    logical, intent(in), optional :: mask(:,:,:)

    Return Value real(kind=sp), (merge(size(x,1),size(x,2),mask=1

  • private pure module function stdlib_sum_kahan_3d_dp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value real(kind=dp)

  • private pure module function stdlib_sum_kahan_3d_sp(x, mask) result(s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:,:,:)
    logical, intent(in), optional :: mask(:,:,:)

    Return Value real(kind=sp)



Fortran-lang/stdlib was developed by fortran-lang/stdlib contributors
© 2025 Creative Commons License
def840da

Documentation generated by FORD on 2025-04-03 06:18