Procedure | Location | Procedure Type | Description |
---|---|---|---|
adjustl | stdlib_string_type | Interface | Left-adjust the character sequence represented by the string. The length of the character sequence remains unchanged. |
adjustr | stdlib_string_type | Interface | Right-adjust the character sequence represented by the string. The length of the character sequence remains unchanged. |
all_close | stdlib_math | Interface | Returns a boolean scalar where two arrays are element-wise equal within a tolerance. (Specification) |
and | stdlib_bitsets | Interface | Sets the bits in |
and_not | stdlib_bitsets | Interface | Sets the bits in |
arange | stdlib_math | Interface |
|
arg | stdlib_math | Interface |
|
arg_select | stdlib_selection | Interface | |
argd | stdlib_math | Interface |
|
argpi | stdlib_math | Interface |
|
assignment(=) | stdlib_string_type | Interface | Assign a character sequence to a string. |
assignment(=) | stdlib_bitsets | Interface | Used to define assignment for |
asum | stdlib_linalg_blas | Interface | ASUM takes the sum of the absolute values. |
axpy | stdlib_linalg_blas | Interface | AXPY constant times a vector plus a vector. |
bidx | stdlib_stringlist_type | Interface | Returns an instance of type 'stringlist_index_type' representing backward index Specifications |
bits | stdlib_bitsets | Function | Returns the number of bit positions in |
cdf_exp | stdlib_stats_distribution_exponential | Interface | Version experimental |
cdf_normal | stdlib_stats_distribution_normal | Interface | Normal Distribution Cumulative Distribution Function (Specification) |
cdf_uniform | stdlib_stats_distribution_uniform | Interface | Get uniform distribution cumulative distribution function (cdf) for integer, real and complex variables. (Specification) |
char | stdlib_string_type | Interface | Return the character sequence represented by the string. |
check | stdlib_error | Subroutine | Checks the value of a logical condition (Specification) |
chol | stdlib_linalg | Interface | Computes the Cholesky factorization , or . (Specification) |
cholesky | stdlib_linalg | Interface | Computes the Cholesky factorization , or . (Specification) |
chomp | stdlib_strings | Interface | Remove trailing characters in set from string. If no character set is provided trailing whitespace is removed. |
clip | stdlib_math | Interface | |
coo2csc | stdlib_sparse_conversion | Interface | |
coo2csr | stdlib_sparse_conversion | Interface | |
coo2dense | stdlib_sparse_conversion | Interface | |
coo2ordered | stdlib_sparse_conversion | Subroutine | |
copy | stdlib_linalg_blas | Interface | COPY copies a vector x to a vector y. |
copy_key | stdlib_hashmap_wrappers | Subroutine | Copies the contents of the key, old_key, to the key, new_key (Specifications) |
copy_other | stdlib_hashmap_wrappers | Subroutine | Copies the other data, other_in, to the variable, other_out (Specifications) |
corr | stdlib_stats | Interface | Pearson correlation of array elements (Specification) |
count | stdlib_strings | Interface | Returns the number of times substring 'pattern' has appeared in the input string 'string' Specifications |
cov | stdlib_stats | Interface | Covariance of array elements (Specification) |
cross_product | stdlib_linalg | Interface | Computes the cross product of two vectors, returning a rank-1 and size-3 array (Specification) |
csc2coo | stdlib_sparse_conversion | Interface | |
csr2coo | stdlib_sparse_conversion | Interface | |
csr2dense | stdlib_sparse_conversion | Interface | |
csr2ell | stdlib_sparse_conversion | Interface | |
csr2sellc | stdlib_sparse_conversion | Interface | |
deg2rad | stdlib_math | Interface |
|
dense2coo | stdlib_sparse_conversion | Interface | |
det | stdlib_linalg | Interface | Computes the determinant of a square matrix (Specification) |
diag | stdlib_linalg | Interface | Creates a diagonal array or extract the diagonal elements of an array (Specification) |
diag | stdlib_sparse_conversion | Interface | |
diff | stdlib_math | Interface | Computes differences between adjacent elements of an array. (Specification) |
dist_rand | stdlib_random | Interface | Version experimental |
dlegendre | stdlib_specialfunctions | Interface | First derivative Legendre polynomial |
dot | stdlib_linalg_blas | Interface | DOT forms the dot product of two vectors. uses unrolled loops for increments equal to one. |
dotc | stdlib_linalg_blas | Interface | DOTC forms the dot product of two complex vectors DOTC = X^H * Y |
dotu | stdlib_linalg_blas | Interface | DOTU forms the dot product of two complex vectors DOTU = X^T * Y |
eig | stdlib_linalg | Interface | Solves the eigendecomposition for square matrix . (Specification) |
eigh | stdlib_linalg | Interface | Solves the eigendecomposition for a real symmetric or complex Hermitian square matrix. (Specification) |
eigvals | stdlib_linalg | Interface | Returns the eigenvalues , , for square matrix . (Specification) |
eigvalsh | stdlib_linalg | Interface | Returns the eigenvalues , , for a real symmetric or complex Hermitian square matrix. (Specification) |
ends_with | stdlib_strings | Interface | Check whether a string ends with substring or not |
error_handler | stdlib_bitsets | Subroutine | |
error_stop | stdlib_error | Interface | |
extract | stdlib_bitsets | Interface | Creates a new bitset, |
eye | stdlib_linalg | Function | Constructs the identity matrix. (Specification) |
falseloc | stdlib_array | Function | Return the positions of the false elements in array. Specification |
fibonacci_hash | stdlib_hash_64bit | Function | Maps the 64 bit integer |
fibonacci_hash | stdlib_hash_32bit | Function | Maps the 32 bit integer |
fidx | stdlib_stringlist_type | Interface | Returns an instance of type 'stringlist_index_type' representing forward index Specifications |
find | stdlib_strings | Interface | Finds the starting index of substring 'pattern' in the input 'string' Specifications |
fnv_1_hash | stdlib_hash_64bit | Interface | FNV_1 interfaces (Specification) |
fnv_1_hash | stdlib_hash_32bit | Interface | FNV_1 interfaces (Specification) |
fnv_1_hasher | stdlib_hashmap_wrappers | Function | Hashes a key with the FNV_1 algorithm Arguments: key - the key to be hashed |
fnv_1a_hash | stdlib_hash_64bit | Interface | FNV_1A interfaces (Specification) |
fnv_1a_hash | stdlib_hash_32bit | Interface | FNV_1A interfaces (Specification) |
fnv_1a_hasher | stdlib_hashmap_wrappers | Function | Hashes a key with the FNV_1a algorithm (Specifications) |
free_key | stdlib_hashmap_wrappers | Subroutine | Frees the memory in a key (Specifications) |
free_other | stdlib_hashmap_wrappers | Subroutine | Frees the memory in the other data (Specifications) |
from_ijv | stdlib_sparse_conversion | Interface | |
gamma | stdlib_specialfunctions_gamma | Interface | Gamma function for integer and complex numbers |
gauss_legendre | stdlib_quadrature | Interface | Computes Gauss-Legendre quadrature nodes and weights. |
gauss_legendre_lobatto | stdlib_quadrature | Interface | Computes Gauss-Legendre-Lobatto quadrature nodes and weights. |
gbmv | stdlib_linalg_blas | Interface | GBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals. |
gcd | stdlib_math | Interface | Returns the greatest common divisor of two integers (Specification) |
gemm | stdlib_linalg_blas | Interface | GEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = XT or op( X ) = X*H, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix. |
gemv | stdlib_linalg_blas | Interface | GEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix. |
ger | stdlib_linalg_blas | Interface | GER performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
gerc | stdlib_linalg_blas | Interface | GERC performs the rank 1 operation A := alphaxy**H + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
geru | stdlib_linalg_blas | Interface | GERU performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
get | stdlib_hashmap_wrappers | Interface | |
get_norm | stdlib_linalg | Interface | Vector norm: subroutine interface version: experimental |
get_stdlib_version | stdlib_version | Subroutine | Getter function to retrieve standard library version |
getline | stdlib_io | Interface | Read a whole line from a formatted unit into a string variable |
hbmv | stdlib_linalg_blas | Interface | HBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian band matrix, with k super-diagonals. |
hemm | stdlib_linalg_blas | Interface | HEMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is an hermitian matrix and B and C are m by n matrices. |
hemv | stdlib_linalg_blas | Interface | HEMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix. |
her | stdlib_linalg_blas | Interface | HER performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix. |
her2 | stdlib_linalg_blas | Interface | HER2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix. |
her2k | stdlib_linalg_blas | Interface | HER2K performs one of the hermitian rank 2k operations C := alphaABH + conjg( alpha )BAH + betaC, or C := alphaAHB + conjg( alpha )BHA + betaC, where alpha and beta are scalars with beta real, C is an n by n hermitian matrix and A and B are n by k matrices in the first case and k by n matrices in the second case. |
herk | stdlib_linalg_blas | Interface | HERK performs one of the hermitian rank k operations C := alphaAAH + betaC, or C := alphaAHA + betaC, where alpha and beta are real scalars, C is an n by n hermitian matrix and A is an n by k matrix in the first case and a k by n matrix in the second case. |
hpmv | stdlib_linalg_blas | Interface | HPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form. |
hpr | stdlib_linalg_blas | Interface | HPR performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix, supplied in packed form. |
hpr2 | stdlib_linalg_blas | Interface | HPR2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form. |
iachar | stdlib_string_type | Interface | Code in ASCII collating sequence. |
ichar | stdlib_string_type | Interface | Character-to-integer conversion function. |
index | stdlib_string_type | Interface | Position of a substring within a string. |
inv | stdlib_linalg | Interface | Inverse of a square matrix (Specification) |
invert | stdlib_linalg | Interface | Inversion of a square matrix (Specification) |
is_alpha | stdlib_ascii | Function | Checks whether |
is_alphanum | stdlib_ascii | Function | Checks whether |
is_ascii | stdlib_ascii | Function | Checks whether or not |
is_blank | stdlib_ascii | Function | Checks whether or not |
is_close | stdlib_math | Interface | Returns a boolean scalar/array where two scalar/arrays are element-wise equal within a tolerance. (Specification) |
is_control | stdlib_ascii | Function | Checks whether |
is_diagonal | stdlib_linalg | Interface | Checks if a matrix (rank-2 array) is diagonal (Specification) |
is_digit | stdlib_ascii | Function | Checks whether |
is_graphical | stdlib_ascii | Function | Checks whether or not |
is_hermitian | stdlib_linalg | Interface | Checks if a matrix (rank-2 array) is Hermitian (Specification) |
is_hessenberg | stdlib_linalg | Interface | Checks if a matrix (rank-2 array) is Hessenberg (Specification) |
is_hex_digit | stdlib_ascii | Function | Checks whether |
is_lower | stdlib_ascii | Function | Checks whether |
is_octal_digit | stdlib_ascii | Function | Checks whether |
is_printable | stdlib_ascii | Function | Checks whether or not |
is_punctuation | stdlib_ascii | Function | Checks whether or not |
is_skew_symmetric | stdlib_linalg | Interface | Checks if a matrix (rank-2 array) is skew-symmetric (Specification) |
is_square | stdlib_linalg | Interface | Checks if a matrix (rank-2 array) is square (Specification) |
is_symmetric | stdlib_linalg | Interface | Checks if a matrix (rank-2 array) is symmetric (Specification) |
is_triangular | stdlib_linalg | Interface | Checks if a matrix (rank-2 array) is triangular (Specification) |
is_upper | stdlib_ascii | Function | Checks whether |
is_white | stdlib_ascii | Function | Checks whether or not |
kronecker_product | stdlib_linalg | Interface | Computes the Kronecker product of two arrays of size M1xN1, and of M2xN2, returning an (M1M2)x(N1N2) array (Specification) |
legendre | stdlib_specialfunctions | Interface | Legendre polynomial |
len | stdlib_string_type | Interface | Returns the length of the character sequence represented by the string. |
len_trim | stdlib_string_type | Interface | Returns the length of the character sequence without trailing spaces represented by the string. |
lge | stdlib_string_type | Interface | Lexically compare the order of two character sequences being greater equal, The left-hand side, the right-hand side or both character sequences can be represented by a string. |
lgt | stdlib_string_type | Interface | Lexically compare the order of two character sequences being greater, The left-hand side, the right-hand side or both character sequences can be represented by a string. |
linalg_error_handling | stdlib_linalg_state | Subroutine | Flow control: on output flag present, return it; otherwise, halt on error |
linalg_state_type | stdlib_linalg_state | Interface | |
linspace | stdlib_math | Interface | 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) |
lle | stdlib_string_type | Interface | Lexically compare the order of two character sequences being less equal, The left-hand side, the right-hand side or both character sequences can be represented by a string. |
llt | stdlib_string_type | Interface | Lexically compare the order of two character sequences being less, The left-hand side, the right-hand side or both character sequences can be represented by a string. |
load_npy | stdlib_io_npy | Interface | Load multidimensional array in npy format (Specification) |
loadtxt | stdlib_io | Interface | Loads a 2D array from a text file (Specification) |
log_factorial | stdlib_specialfunctions_gamma | Interface | Logarithm of factorial n!, integer variable |
log_gamma | stdlib_specialfunctions_gamma | Interface | Logarithm of gamma function |
log_lower_incomplete_gamma | stdlib_specialfunctions_gamma | Interface | Logarithm of lower incomplete gamma function |
log_upper_incomplete_gamma | stdlib_specialfunctions_gamma | Interface | Logarithm of upper incomplete gamma function |
logspace | stdlib_math | Interface | 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 |
lower_incomplete_gamma | stdlib_specialfunctions_gamma | Interface | Lower incomplete gamma function |
lstsq | stdlib_linalg | Interface | Computes the squares solution to system . (Specification) |
lstsq_space | stdlib_linalg | Interface | Computes the integer, real [, complex] working space required by the least-squares solver (Specification) |
mean | stdlib_stats | Interface | Mean of array elements (Specification) |
median | stdlib_stats | Interface | Median of array elements (Specification) |
meshgrid | stdlib_math | Interface | Computes a list of coordinate matrices from coordinate vectors. (Specification) |
moment | stdlib_stats | Interface | Central moment of array elements (Specification) |
move | stdlib_string_type | Interface | Moves the allocated character scalar from 'from' to 'to' Specifications |
new_nmhash32_seed | stdlib_hash_32bit | Interface | |
new_nmhash32x_seed | stdlib_hash_32bit | Interface | |
new_pengy_hash_seed | stdlib_hash_64bit | Interface | |
new_spooky_hash_seed | stdlib_hash_64bit | Interface | |
new_water_hash_seed | stdlib_hash_32bit | Interface | |
nmhash32 | stdlib_hash_32bit | Interface | NMHASH32 interfaces (Specification) |
nmhash32x | stdlib_hash_32bit | Interface | NMHASH32X interfaces (Specification) |
norm | stdlib_linalg | Interface | Computes the vector norm of a generic-rank array . (Specification) |
nrm2 | stdlib_linalg_blas | Interface | NRM2 returns the euclidean norm of a vector via the function name, so that NRM2 := sqrt( x'*x ) |
odd_random_integer | stdlib_hash_64bit | Subroutine | Returns a 64 bit pseudo random integer, |
odd_random_integer | stdlib_hash_32bit | Subroutine | Returns a 32 bit pseudo random integer, |
open | stdlib_io | Function | Opens a file (Specification) |
operator(+) | stdlib_ansi | Interface | |
operator(.det.) | stdlib_linalg | Interface | Determinant operator of a square matrix (Specification) |
operator(.inv.) | stdlib_linalg | Interface | Inverse operator of a square matrix (Specification) |
operator(//) | stdlib_ansi | Interface | |
operator(//) | stdlib_string_type | Interface | Concatenate two character sequences, the left-hand side, the right-hand side or both character sequences can be represented by a string. |
operator(//) | stdlib_stringlist_type | Interface | Concatenates stringlist with the input entity Returns a new stringlist Specifications |
operator(/=) | stdlib_string_type | Interface | Compare two character sequences for inequality, the left-hand side, the right-hand side or both character sequences can be represented by a string. |
operator(/=) | stdlib_stringlist_type | Interface | Compares stringlist for inequality with the input entity Returns a logical Specifications |
operator(/=) | stdlib_linalg_state | Interface | |
operator(/=) | stdlib_bitsets | Interface | Returns |
operator(<) | stdlib_string_type | Interface | Compare two character sequences for being less, the left-hand side, the right-hand side or both character sequences can be represented by a string. |
operator(<) | stdlib_linalg_state | Interface | |
operator(<) | stdlib_bitsets | Interface | Returns |
operator(<=) | stdlib_string_type | Interface | Compare two character sequences for being less than, the left-hand side, the right-hand side or both character sequences can be represented by a string. |
operator(<=) | stdlib_linalg_state | Interface | |
operator(<=) | stdlib_bitsets | Interface | Returns |
operator(==) | stdlib_hashmap_wrappers | Interface | |
operator(==) | stdlib_string_type | Interface | Compare two character sequences for equality, the left-hand side, the right-hand side or both character sequences can be represented by a string. |
operator(==) | stdlib_stringlist_type | Interface | Compares stringlist for equality with the input entity Returns a logical Specifications |
operator(==) | stdlib_linalg_state | Interface | Comparison operators |
operator(==) | stdlib_bitsets | Interface | Returns |
operator(>) | stdlib_string_type | Interface | Compare two character sequences for being greater, the left-hand side, the right-hand side or both character sequences can be represented by a string. |
operator(>) | stdlib_linalg_state | Interface | |
operator(>) | stdlib_bitsets | Interface | Returns |
operator(>=) | stdlib_string_type | Interface | Compare two character sequences for being greater than, the left-hand side, the right-hand side or both character sequences can be represented by a string. |
operator(>=) | stdlib_linalg_state | Interface | |
operator(>=) | stdlib_bitsets | Interface | Returns |
optval | stdlib_optval | Interface | Fallback value for optional arguments (Specification) |
or | stdlib_bitsets | Interface | Sets the bits in |
ord_sort | stdlib_sorting | Interface | The generic subroutine interface implementing the |
outer_product | stdlib_linalg | Interface | Computes the outer product of two vectors, returning a rank-2 array (Specification) |
padl | stdlib_strings | Interface | Left pad the input string Specifications |
padr | stdlib_strings | Interface | Right pad the input string Specifications |
parse_mode | stdlib_io | Function | |
pdf_exp | stdlib_stats_distribution_exponential | Interface | Version experimental |
pdf_normal | stdlib_stats_distribution_normal | Interface | Normal Distribution Probability Density Function (Specification) |
pdf_uniform | stdlib_stats_distribution_uniform | Interface | Get uniform distribution probability density (pdf) for integer, real and complex variables. (Specification) |
pengy_hash | stdlib_hash_64bit | Interface | PENGY_HASH interfaces (Specification) |
qr | stdlib_linalg | Interface | Computes the QR factorization of matrix . (Specification) |
qr_space | stdlib_linalg | Interface | Computes the working array space required by the QR factorization solver (Specification) |
rad2deg | stdlib_math | Interface |
|
radix_sort | stdlib_sorting | Interface | The generic subroutine interface implementing the LSD radix sort algorithm, see https://en.wikipedia.org/wiki/Radix_sort for more details. It is always O(N) in sorting random data, but need a O(N) buffer. (Specification) |
random_seed | stdlib_random | Interface | Version experimental |
read(formatted) | stdlib_string_type | Interface | Read a character sequence from a connected unformatted unit into the string. |
read(unformatted) | stdlib_string_type | Interface | Read a character sequence from a connected unformatted unit into the string. |
regularized_gamma_p | stdlib_specialfunctions_gamma | Interface | Regularized (normalized) lower incomplete gamma function, P |
regularized_gamma_q | stdlib_specialfunctions_gamma | Interface | Regularized (normalized) upper incomplete gamma function, Q |
repeat | stdlib_string_type | Interface | Repeats the character sequence hold by the string by the number of specified copies. |
replace_all | stdlib_strings | Interface | Replaces all the occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Version: experimental |
reverse | stdlib_string_type | Interface | Reverses the character sequence hold by the input string |
reverse | stdlib_ascii | Function | Reverse the character order in the input character variable (Specification) |
rot | stdlib_linalg_blas | Interface | ROT applies a plane rotation. |
rotg | stdlib_linalg_blas | Interface | The computation uses the formulas |x| = sqrt( Re(x)2 + Im(x)2 ) sgn(x) = x / |x| if x /= 0 = 1 if x = 0 c = |a| / sqrt(|a|2 + |b|2) s = sgn(a) * conjg(b) / sqrt(|a|2 + |b|2) When a and b are real and r /= 0, the formulas simplify to r = sgn(a)sqrt(|a|2 + |b|*2) c = a / r s = b / r the same as in SROTG when |a| > |b|. When |b| >= |a|, the sign of c and s will be different from those computed by SROTG if the signs of a and b are not the same. |
rotm | stdlib_linalg_blas | Interface | ROTM applies the modified Givens transformation, , to the 2-by-N matrix
where indicates transpose. The elements of are in
DX(LX+IINCX), I = 0:N-1, where LX = 1 if INCX >= 0, else LX = (-INCX)N,
and similarly for DY using LY and INCY.
With DPARAM(1)=DFLAG, has one of the following forms:
|
rotmg | stdlib_linalg_blas | Interface | ROTMG Constructs the modified Givens transformation matrix which zeros the
second component of the 2-vector
With DPARAM(1)=DFLAG, has one of the following forms: |
rvs_exp | stdlib_stats_distribution_exponential | Interface | Version experimental |
rvs_normal | stdlib_stats_distribution_normal | Interface | Normal Distribution Random Variates (Specification) |
rvs_uniform | stdlib_stats_distribution_uniform | Interface | Get uniformly distributed random variate for integer, real and complex variables. (Specification) |
save_npy | stdlib_io_npy | Interface | Save multidimensional array in npy format (Specification) |
savetxt | stdlib_io | Interface | Saves a 2D array into a text file (Specification) |
sbmv | stdlib_linalg_blas | Interface | SBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric band matrix, with k super-diagonals. |
scal | stdlib_linalg_blas | Interface | SCAL scales a vector by a constant. |
scan | stdlib_string_type | Interface | Scan a string for the presence of a set of characters. Scans a string for any of the characters in a set of characters. |
sdot | stdlib_linalg_blas | Interface | Compute the inner product of two vectors with extended precision accumulation and result. Returns D.P. dot product accumulated in D.P., for S.P. SX and SY SDOT = sum for I = 0 to N-1 of SX(LX+IINCX) * SY(LY+IINCY), where LX = 1 if INCX >= 0, else LX = 1+(1-N)*INCX, and LY is defined in a similar way using INCY. |
seeded_nmhash32_hasher | stdlib_hashmap_wrappers | Function | Hashes a key with the NMHASH32 hash algorithm (Specifications) |
seeded_nmhash32x_hasher | stdlib_hashmap_wrappers | Function | Hashes a key with the NMHASH32X hash algorithm (Specifications) Arguments: key - the key to be hashed seed - the seed (unused) for the hashing algorithm |
seeded_water_hasher | stdlib_hashmap_wrappers | Function | Hashes a key with the waterhash algorithm (Specifications) |
select | stdlib_selection | Interface | |
set | stdlib_hashmap_wrappers | Interface | |
shuffle | stdlib_stats_distribution_uniform | Interface | Fisher-Yates shuffle algorithm for a rank one array of integer, real and complex variables. (Specification) |
simps | stdlib_quadrature | Interface | Integrates sampled values using Simpson's rule (Specification) |
simps_weights | stdlib_quadrature | Interface | Integrates sampled values using trapezoidal rule weights for given abscissas (Specification) |
slice | stdlib_strings | Interface | Extracts characters from the input string to return a new string |
solve | stdlib_linalg | Interface | Solves the linear system for the unknown vector from a square matrix . (Specification) |
solve_lstsq | stdlib_linalg | Interface | Computes the squares solution to system . (Specification) |
solve_lu | stdlib_linalg | Interface | Solves the linear system for the unknown vector from a square matrix . (Specification) |
sort | stdlib_sorting | Interface | The generic subroutine interface implementing the |
sort_index | stdlib_sorting | Interface | The generic subroutine interface implementing the |
spmv | stdlib_linalg_blas | Interface | SPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form. |
spmv | stdlib_sparse_spmv | Interface | |
spooky_hash | stdlib_hash_64bit | Interface | SPOOKY_HASH interfaces (Specification) |
spookyHash_128 | stdlib_hash_64bit | Interface | |
spr | stdlib_linalg_blas | Interface | SPR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix, supplied in packed form. |
spr2 | stdlib_linalg_blas | Interface | SPR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form. |
srot | stdlib_linalg_blas | Interface | SROT applies a plane rotation, where the cos and sin (c and s) are real and the vectors cx and cy are complex. jack dongarra, linpack, 3/11/78. |
sscal | stdlib_linalg_blas | Interface | SSCAL scales a complex vector by a real constant. |
starts_with | stdlib_strings | Interface | Check whether a string starts with substring or not |
stdlib_cabs1 | stdlib_linalg_blas_aux | Interface | |
stdlib_caxpy | stdlib_linalg_blas_c | Subroutine | CAXPY constant times a vector plus a vector. |
stdlib_ccopy | stdlib_linalg_blas_c | Subroutine | CCOPY copies a vector x to a vector y. |
stdlib_cdotc | stdlib_linalg_blas_c | Function | CDOTC forms the dot product of two complex vectors CDOTC = X^H * Y |
stdlib_cdotu | stdlib_linalg_blas_c | Function | CDOTU forms the dot product of two complex vectors CDOTU = X^T * Y |
stdlib_cgbmv | stdlib_linalg_blas_c | Subroutine | CGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals. |
stdlib_cgemm | stdlib_linalg_blas_c | Subroutine | CGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = XT or op( X ) = X*H, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix. |
stdlib_cgemv | stdlib_linalg_blas_c | Subroutine | CGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix. |
stdlib_cgerc | stdlib_linalg_blas_c | Subroutine | CGERC performs the rank 1 operation A := alphaxy**H + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
stdlib_cgeru | stdlib_linalg_blas_c | Subroutine | CGERU performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
stdlib_chbmv | stdlib_linalg_blas_c | Subroutine | CHBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian band matrix, with k super-diagonals. |
stdlib_chemm | stdlib_linalg_blas_c | Subroutine | CHEMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is an hermitian matrix and B and C are m by n matrices. |
stdlib_chemv | stdlib_linalg_blas_c | Subroutine | CHEMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix. |
stdlib_cher | stdlib_linalg_blas_c | Subroutine | CHER performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix. |
stdlib_cher2 | stdlib_linalg_blas_c | Subroutine | CHER2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix. |
stdlib_cher2k | stdlib_linalg_blas_c | Subroutine | CHER2K performs one of the hermitian rank 2k operations C := alphaABH + conjg( alpha )BAH + betaC, or C := alphaAHB + conjg( alpha )BHA + betaC, where alpha and beta are scalars with beta real, C is an n by n hermitian matrix and A and B are n by k matrices in the first case and k by n matrices in the second case. |
stdlib_cherk | stdlib_linalg_blas_c | Subroutine | CHERK performs one of the hermitian rank k operations C := alphaAAH + betaC, or C := alphaAHA + betaC, where alpha and beta are real scalars, C is an n by n hermitian matrix and A is an n by k matrix in the first case and a k by n matrix in the second case. |
stdlib_chpmv | stdlib_linalg_blas_c | Subroutine | CHPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form. |
stdlib_chpr | stdlib_linalg_blas_c | Subroutine | CHPR performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix, supplied in packed form. |
stdlib_chpr2 | stdlib_linalg_blas_c | Subroutine | CHPR2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form. |
stdlib_crotg | stdlib_linalg_blas_c | Subroutine | The computation uses the formulas |x| = sqrt( Re(x)2 + Im(x)2 ) sgn(x) = x / |x| if x /= 0 = 1 if x = 0 c = |a| / sqrt(|a|2 + |b|2) s = sgn(a) * conjg(b) / sqrt(|a|2 + |b|2) When a and b are real and r /= 0, the formulas simplify to r = sgn(a)sqrt(|a|2 + |b|*2) c = a / r s = b / r the same as in SROTG when |a| > |b|. When |b| >= |a|, the sign of c and s will be different from those computed by SROTG if the signs of a and b are not the same. |
stdlib_cscal | stdlib_linalg_blas_c | Subroutine | CSCAL scales a vector by a constant. |
stdlib_csrot | stdlib_linalg_blas_c | Subroutine | CSROT applies a plane rotation, where the cos and sin (c and s) are real and the vectors cx and cy are complex. jack dongarra, linpack, 3/11/78. |
stdlib_csscal | stdlib_linalg_blas_c | Subroutine | CSSCAL scales a complex vector by a real constant. |
stdlib_cswap | stdlib_linalg_blas_c | Subroutine | CSWAP interchanges two vectors. |
stdlib_csymm | stdlib_linalg_blas_c | Subroutine | CSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices. |
stdlib_csyr2k | stdlib_linalg_blas_c | Subroutine | CSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case. |
stdlib_csyrk | stdlib_linalg_blas_c | Subroutine | CSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case. |
stdlib_ctbmv | stdlib_linalg_blas_c | Subroutine | CTBMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. |
stdlib_ctbsv | stdlib_linalg_blas_c | Subroutine | CTBSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_ctpmv | stdlib_linalg_blas_c | Subroutine | CTPMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. |
stdlib_ctpsv | stdlib_linalg_blas_c | Subroutine | CTPSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_ctrmm | stdlib_linalg_blas_c | Subroutine | CTRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ) where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. |
stdlib_ctrmv | stdlib_linalg_blas_c | Subroutine | CTRMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix. |
stdlib_ctrsm | stdlib_linalg_blas_c | Subroutine | CTRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. The matrix X is overwritten on B. |
stdlib_ctrsv | stdlib_linalg_blas_c | Subroutine | CTRSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_dasum | stdlib_linalg_blas_d | Function | DASUM takes the sum of the absolute values. |
stdlib_daxpy | stdlib_linalg_blas_d | Subroutine | DAXPY constant times a vector plus a vector. uses unrolled loops for increments equal to one. |
stdlib_dcopy | stdlib_linalg_blas_d | Subroutine | DCOPY copies a vector, x, to a vector, y. uses unrolled loops for increments equal to 1. |
stdlib_ddot | stdlib_linalg_blas_d | Function | DDOT forms the dot product of two vectors. uses unrolled loops for increments equal to one. |
stdlib_dgbmv | stdlib_linalg_blas_d | Subroutine | DGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals. |
stdlib_dgemm | stdlib_linalg_blas_d | Subroutine | DGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = X*T, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix. |
stdlib_dgemv | stdlib_linalg_blas_d | Subroutine | DGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix. |
stdlib_dger | stdlib_linalg_blas_d | Subroutine | DGER performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
stdlib_dnrm2 | stdlib_linalg_blas_d | Function | DNRM2 returns the euclidean norm of a vector via the function name, so that DNRM2 := sqrt( x'*x ) |
stdlib_drot | stdlib_linalg_blas_d | Subroutine | DROT applies a plane rotation. |
stdlib_drotg | stdlib_linalg_blas_d | Subroutine | The computation uses the formulas sigma = sgn(a) if |a| > |b| = sgn(b) if |b| >= |a| r = sigmasqrt( a2 + b2 ) c = 1; s = 0 if r = 0 c = a/r; s = b/r if r != 0 The subroutine also computes z = s if |a| > |b|, = 1/c if |b| >= |a| and c != 0 = 1 if c = 0 This allows c and s to be reconstructed from z as follows: If z = 1, set c = 0, s = 1. If |z| < 1, set c = sqrt(1 - z2) and s = z. If |z| > 1, set c = 1/z and s = sqrt( 1 - c*2). |
stdlib_drotm | stdlib_linalg_blas_d | Subroutine | DROTM applies the modified Givens transformation, , to the 2-by-N matrix
where indicates transpose. The elements of are in
DX(LX+IINCX), I = 0:N-1, where LX = 1 if INCX >= 0, else LX = (-INCX)N,
and similarly for DY using LY and INCY.
With DPARAM(1)=DFLAG, has one of the following forms:
|
stdlib_drotmg | stdlib_linalg_blas_d | Subroutine | DROTMG Constructs the modified Givens transformation matrix which zeros the
second component of the 2-vector
With DPARAM(1)=DFLAG, has one of the following forms: |
stdlib_dsbmv | stdlib_linalg_blas_d | Subroutine | DSBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric band matrix, with k super-diagonals. |
stdlib_dscal | stdlib_linalg_blas_d | Subroutine | DSCAL scales a vector by a constant. uses unrolled loops for increment equal to 1. |
stdlib_dsdot | stdlib_linalg_blas_d | Function | Compute the inner product of two vectors with extended precision accumulation and result. Returns D.P. dot product accumulated in D.P., for S.P. SX and SY DSDOT = sum for I = 0 to N-1 of SX(LX+IINCX) * SY(LY+IINCY), where LX = 1 if INCX >= 0, else LX = 1+(1-N)*INCX, and LY is defined in a similar way using INCY. |
stdlib_dspmv | stdlib_linalg_blas_d | Subroutine | DSPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form. |
stdlib_dspr | stdlib_linalg_blas_d | Subroutine | DSPR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix, supplied in packed form. |
stdlib_dspr2 | stdlib_linalg_blas_d | Subroutine | DSPR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form. |
stdlib_dswap | stdlib_linalg_blas_d | Subroutine | DSWAP interchanges two vectors. uses unrolled loops for increments equal to 1. |
stdlib_dsymm | stdlib_linalg_blas_d | Subroutine | DSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices. |
stdlib_dsymv | stdlib_linalg_blas_d | Subroutine | DSYMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix. |
stdlib_dsyr | stdlib_linalg_blas_d | Subroutine | DSYR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix. |
stdlib_dsyr2 | stdlib_linalg_blas_d | Subroutine | DSYR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix. |
stdlib_dsyr2k | stdlib_linalg_blas_d | Subroutine | DSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case. |
stdlib_dsyrk | stdlib_linalg_blas_d | Subroutine | DSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case. |
stdlib_dtbmv | stdlib_linalg_blas_d | Subroutine | DTBMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. |
stdlib_dtbsv | stdlib_linalg_blas_d | Subroutine | DTBSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_dtpmv | stdlib_linalg_blas_d | Subroutine | DTPMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. |
stdlib_dtpsv | stdlib_linalg_blas_d | Subroutine | DTPSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_dtrmm | stdlib_linalg_blas_d | Subroutine | DTRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ), where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = A**T. |
stdlib_dtrmv | stdlib_linalg_blas_d | Subroutine | DTRMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix. |
stdlib_dtrsm | stdlib_linalg_blas_d | Subroutine | DTRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = A**T. The matrix X is overwritten on B. |
stdlib_dtrsv | stdlib_linalg_blas_d | Subroutine | DTRSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_dzasum | stdlib_linalg_blas_d | Function | DZASUM takes the sum of the (|Re(.)| + |Im(.)|)'s of a complex vector and returns a double precision result. |
stdlib_dznrm2 | stdlib_linalg_blas_d | Function | DZNRM2 returns the euclidean norm of a vector via the function name, so that DZNRM2 := sqrt( x*Hx ) |
stdlib_icamax | stdlib_linalg_blas_aux | Function | |
stdlib_idamax | stdlib_linalg_blas_aux | Function | |
stdlib_isamax | stdlib_linalg_blas_aux | Function | |
stdlib_izamax | stdlib_linalg_blas_aux | Function | |
stdlib_lsame | stdlib_linalg_blas_aux | Function | LSAME returns .TRUE. if CA is the same letter as CB regardless of case. |
stdlib_sasum | stdlib_linalg_blas_s | Function | SASUM takes the sum of the absolute values. uses unrolled loops for increment equal to one. |
stdlib_saxpy | stdlib_linalg_blas_s | Subroutine | SAXPY constant times a vector plus a vector. uses unrolled loops for increments equal to one. |
stdlib_scasum | stdlib_linalg_blas_s | Function | SCASUM takes the sum of the (|Re(.)| + |Im(.)|)'s of a complex vector and returns a single precision result. |
stdlib_scnrm2 | stdlib_linalg_blas_s | Function | SCNRM2 returns the euclidean norm of a vector via the function name, so that SCNRM2 := sqrt( x*Hx ) |
stdlib_scopy | stdlib_linalg_blas_s | Subroutine | SCOPY copies a vector, x, to a vector, y. uses unrolled loops for increments equal to 1. |
stdlib_sdot | stdlib_linalg_blas_s | Function | SDOT forms the dot product of two vectors. uses unrolled loops for increments equal to one. |
stdlib_sdsdot | stdlib_linalg_blas_s | Function | Compute the inner product of two vectors with extended precision accumulation. Returns S.P. result with dot product accumulated in D.P. SDSDOT = SB + sum for I = 0 to N-1 of SX(LX+IINCX)SY(LY+IINCY), where LX = 1 if INCX >= 0, else LX = 1+(1-N)INCX, and LY is defined in a similar way using INCY. |
stdlib_sgbmv | stdlib_linalg_blas_s | Subroutine | SGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals. |
stdlib_sgemm | stdlib_linalg_blas_s | Subroutine | SGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = X*T, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix. |
stdlib_sgemv | stdlib_linalg_blas_s | Subroutine | SGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix. |
stdlib_sger | stdlib_linalg_blas_s | Subroutine | SGER performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
stdlib_snrm2 | stdlib_linalg_blas_s | Function | SNRM2 returns the euclidean norm of a vector via the function name, so that SNRM2 := sqrt( x'*x ). |
stdlib_srot | stdlib_linalg_blas_s | Subroutine | applies a plane rotation. |
stdlib_srotg | stdlib_linalg_blas_s | Subroutine | The computation uses the formulas sigma = sgn(a) if |a| > |b| = sgn(b) if |b| >= |a| r = sigmasqrt( a2 + b2 ) c = 1; s = 0 if r = 0 c = a/r; s = b/r if r != 0 The subroutine also computes z = s if |a| > |b|, = 1/c if |b| >= |a| and c != 0 = 1 if c = 0 This allows c and s to be reconstructed from z as follows: If z = 1, set c = 0, s = 1. If |z| < 1, set c = sqrt(1 - z2) and s = z. If |z| > 1, set c = 1/z and s = sqrt( 1 - c*2). |
stdlib_srotm | stdlib_linalg_blas_s | Subroutine | SROTM applies the modified Givens transformation, , to the 2-by-N matrix
where indicates transpose. The elements of are in
SX(LX+IINCX), I = 0:N-1, where LX = 1 if INCX >= 0, else LX = (-INCX)N,
and similarly for SY using LY and INCY.
With SPARAM(1)=SFLAG, has one of the following forms:
|
stdlib_srotmg | stdlib_linalg_blas_s | Subroutine | SROTMG Constructs the modified Givens transformation matrix which zeros the
second component of the 2-vector
With SPARAM(1)=SFLAG, has one of the following forms: |
stdlib_ssbmv | stdlib_linalg_blas_s | Subroutine | SSBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric band matrix, with k super-diagonals. |
stdlib_sscal | stdlib_linalg_blas_s | Subroutine | SSCAL scales a vector by a constant. uses unrolled loops for increment equal to 1. |
stdlib_sspmv | stdlib_linalg_blas_s | Subroutine | SSPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form. |
stdlib_sspr | stdlib_linalg_blas_s | Subroutine | SSPR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix, supplied in packed form. |
stdlib_sspr2 | stdlib_linalg_blas_s | Subroutine | SSPR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form. |
stdlib_sswap | stdlib_linalg_blas_s | Subroutine | SSWAP interchanges two vectors. uses unrolled loops for increments equal to 1. |
stdlib_ssymm | stdlib_linalg_blas_s | Subroutine | SSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices. |
stdlib_ssymv | stdlib_linalg_blas_s | Subroutine | SSYMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix. |
stdlib_ssyr | stdlib_linalg_blas_s | Subroutine | SSYR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix. |
stdlib_ssyr2 | stdlib_linalg_blas_s | Subroutine | SSYR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix. |
stdlib_ssyr2k | stdlib_linalg_blas_s | Subroutine | SSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case. |
stdlib_ssyrk | stdlib_linalg_blas_s | Subroutine | SSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case. |
stdlib_stbmv | stdlib_linalg_blas_s | Subroutine | STBMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. |
stdlib_stbsv | stdlib_linalg_blas_s | Subroutine | STBSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_stpmv | stdlib_linalg_blas_s | Subroutine | STPMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. |
stdlib_stpsv | stdlib_linalg_blas_s | Subroutine | STPSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_strmm | stdlib_linalg_blas_s | Subroutine | STRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ), where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = A**T. |
stdlib_strmv | stdlib_linalg_blas_s | Subroutine | STRMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix. |
stdlib_strsm | stdlib_linalg_blas_s | Subroutine | STRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = A**T. The matrix X is overwritten on B. |
stdlib_strsv | stdlib_linalg_blas_s | Subroutine | STRSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_xerbla | stdlib_linalg_blas_aux | Subroutine | XERBLA is an error handler for the LAPACK routines. It is called by an LAPACK routine if an input parameter has an invalid value. A message is printed and execution stops. Installers may consider modifying the STOP statement in order to call system-specific exception-handling facilities. |
stdlib_xerbla_array | stdlib_linalg_blas_aux | Subroutine | XERBLA_ARRAY assists other languages in calling XERBLA, the LAPACK and BLAS error handler. Rather than taking a Fortran string argument as the function's name, XERBLA_ARRAY takes an array of single characters along with the array's length. XERBLA_ARRAY then copies up to 32 characters of that array into a Fortran string and passes that to XERBLA. If called with a non-positive SRNAME_LEN, XERBLA_ARRAY will call XERBLA with a string of all blank characters. Say some macro or other device makes XERBLA_ARRAY available to C99 by a name lapack_xerbla and with a common Fortran calling convention. Then a C99 program could invoke XERBLA via: { int flen = strlen(func); lapack_xerbla(func, } Providing XERBLA_ARRAY is not necessary for intercepting LAPACK errors. XERBLA_ARRAY calls XERBLA. |
stdlib_zaxpy | stdlib_linalg_blas_z | Subroutine | ZAXPY constant times a vector plus a vector. |
stdlib_zcopy | stdlib_linalg_blas_z | Subroutine | ZCOPY copies a vector, x, to a vector, y. |
stdlib_zdotc | stdlib_linalg_blas_z | Function | ZDOTC forms the dot product of two complex vectors ZDOTC = X^H * Y |
stdlib_zdotu | stdlib_linalg_blas_z | Function | ZDOTU forms the dot product of two complex vectors ZDOTU = X^T * Y |
stdlib_zdrot | stdlib_linalg_blas_z | Subroutine | Applies a plane rotation, where the cos and sin (c and s) are real and the vectors cx and cy are complex. jack dongarra, linpack, 3/11/78. |
stdlib_zdscal | stdlib_linalg_blas_z | Subroutine | ZDSCAL scales a vector by a constant. |
stdlib_zgbmv | stdlib_linalg_blas_z | Subroutine | ZGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals. |
stdlib_zgemm | stdlib_linalg_blas_z | Subroutine | ZGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = XT or op( X ) = X*H, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix. |
stdlib_zgemv | stdlib_linalg_blas_z | Subroutine | ZGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix. |
stdlib_zgerc | stdlib_linalg_blas_z | Subroutine | ZGERC performs the rank 1 operation A := alphaxy**H + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
stdlib_zgeru | stdlib_linalg_blas_z | Subroutine | ZGERU performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix. |
stdlib_zhbmv | stdlib_linalg_blas_z | Subroutine | ZHBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian band matrix, with k super-diagonals. |
stdlib_zhemm | stdlib_linalg_blas_z | Subroutine | ZHEMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is an hermitian matrix and B and C are m by n matrices. |
stdlib_zhemv | stdlib_linalg_blas_z | Subroutine | ZHEMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix. |
stdlib_zher | stdlib_linalg_blas_z | Subroutine | ZHER performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix. |
stdlib_zher2 | stdlib_linalg_blas_z | Subroutine | ZHER2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix. |
stdlib_zher2k | stdlib_linalg_blas_z | Subroutine | ZHER2K performs one of the hermitian rank 2k operations C := alphaABH + conjg( alpha )BAH + betaC, or C := alphaAHB + conjg( alpha )BHA + betaC, where alpha and beta are scalars with beta real, C is an n by n hermitian matrix and A and B are n by k matrices in the first case and k by n matrices in the second case. |
stdlib_zherk | stdlib_linalg_blas_z | Subroutine | ZHERK performs one of the hermitian rank k operations C := alphaAAH + betaC, or C := alphaAHA + betaC, where alpha and beta are real scalars, C is an n by n hermitian matrix and A is an n by k matrix in the first case and a k by n matrix in the second case. |
stdlib_zhpmv | stdlib_linalg_blas_z | Subroutine | ZHPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form. |
stdlib_zhpr | stdlib_linalg_blas_z | Subroutine | ZHPR performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix, supplied in packed form. |
stdlib_zhpr2 | stdlib_linalg_blas_z | Subroutine | ZHPR2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form. |
stdlib_zrotg | stdlib_linalg_blas_z | Subroutine | The computation uses the formulas |x| = sqrt( Re(x)2 + Im(x)2 ) sgn(x) = x / |x| if x /= 0 = 1 if x = 0 c = |a| / sqrt(|a|2 + |b|2) s = sgn(a) * conjg(b) / sqrt(|a|2 + |b|2) When a and b are real and r /= 0, the formulas simplify to r = sgn(a)sqrt(|a|2 + |b|*2) c = a / r s = b / r the same as in DROTG when |a| > |b|. When |b| >= |a|, the sign of c and s will be different from those computed by DROTG if the signs of a and b are not the same. |
stdlib_zscal | stdlib_linalg_blas_z | Subroutine | ZSCAL scales a vector by a constant. |
stdlib_zswap | stdlib_linalg_blas_z | Subroutine | ZSWAP interchanges two vectors. |
stdlib_zsymm | stdlib_linalg_blas_z | Subroutine | ZSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices. |
stdlib_zsyr2k | stdlib_linalg_blas_z | Subroutine | ZSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case. |
stdlib_zsyrk | stdlib_linalg_blas_z | Subroutine | ZSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case. |
stdlib_ztbmv | stdlib_linalg_blas_z | Subroutine | ZTBMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. |
stdlib_ztbsv | stdlib_linalg_blas_z | Subroutine | ZTBSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_ztpmv | stdlib_linalg_blas_z | Subroutine | ZTPMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. |
stdlib_ztpsv | stdlib_linalg_blas_z | Subroutine | ZTPSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
stdlib_ztrmm | stdlib_linalg_blas_z | Subroutine | ZTRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ) where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. |
stdlib_ztrmv | stdlib_linalg_blas_z | Subroutine | ZTRMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix. |
stdlib_ztrsm | stdlib_linalg_blas_z | Subroutine | ZTRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. The matrix X is overwritten on B. |
stdlib_ztrsv | stdlib_linalg_blas_z | Subroutine | ZTRSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
string_type | stdlib_string_type | Interface | Constructor for new string instances |
stringlist_type | stdlib_stringlist_type | Interface | Constructor for stringlist Returns an instance of type stringlist_type Specifications |
strip | stdlib_strings | Interface | Remove leading and trailing whitespace characters. |
svd | stdlib_linalg | Interface | Computes the singular value decomposition of a |
svdvals | stdlib_linalg | Interface | Computes the singular values of a |
swap | stdlib_math | Interface | Swap the values of the lhs and rhs arguments (Specification) |
swap | stdlib_linalg_blas | Interface | SWAP interchanges two vectors. |
symm | stdlib_linalg_blas | Interface | SYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices. |
symv | stdlib_linalg_blas | Interface | SYMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix. |
syr | stdlib_linalg_blas | Interface | SYR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix. |
syr2 | stdlib_linalg_blas | Interface | SYR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix. |
syr2k | stdlib_linalg_blas | Interface | SYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case. |
syrk | stdlib_linalg_blas | Interface | SYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case. |
tbmv | stdlib_linalg_blas | Interface | TBMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. |
tbsv | stdlib_linalg_blas | Interface | TBSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
to_lower | stdlib_string_type | Interface | Returns the lowercase version of the character sequence hold by the input string |
to_lower | stdlib_ascii | Function | Convert character variable to lower case (Specification) |
to_num | stdlib_str2num | Interface | Conversion of strings to numbers (Specification) |
to_num_from_stream | stdlib_str2num | Interface | Conversion of a stream of values in a string to numbers (Specification) |
to_real | stdlib_codata_type | Interface | Get the constant value or uncertainty. |
to_sentence | stdlib_string_type | Interface | Returns the sentencecase version of the character sequence hold by the input string |
to_sentence | stdlib_ascii | Function | Converts character sequence to sentence case (Specification) |
to_string | stdlib_ansi | Interface | |
to_string | stdlib_strings | Interface | Format or transfer other types as a string. (Specification) |
to_title | stdlib_string_type | Interface | Returns the titlecase version of the character sequence hold by the input string |
to_title | stdlib_ascii | Function | Converts character sequence to title case (Specification) |
to_upper | stdlib_string_type | Interface | Returns the uppercase version of the character sequence hold by the input string |
to_upper | stdlib_ascii | Function | Convert character variable to upper case (Specification) |
tpmv | stdlib_linalg_blas | Interface | TPMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. |
tpsv | stdlib_linalg_blas | Interface | TPSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
trace | stdlib_linalg | Interface | Computes the trace of a matrix (Specification) |
trapz | stdlib_quadrature | Interface | Integrates sampled values using trapezoidal rule (Specification) |
trapz_weights | stdlib_quadrature | Interface | Integrates sampled values using trapezoidal rule weights for given abscissas (Specification) |
trim | stdlib_string_type | Interface | Returns the character sequence hold by the string without trailing spaces. |
trmm | stdlib_linalg_blas | Interface | TRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ) where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. |
trmv | stdlib_linalg_blas | Interface | TRMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix. |
trsm | stdlib_linalg_blas | Interface | TRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. The matrix X is overwritten on B. |
trsv | stdlib_linalg_blas | Interface | TRSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine. |
trueloc | stdlib_array | Function | Return the positions of the true elements in array. Specification |
universal_mult_hash | stdlib_hash_64bit | Function | Uses the "random" odd 64 bit integer |
universal_mult_hash | stdlib_hash_32bit | Function | Uses the "random" odd 32 bit integer |
upper_incomplete_gamma | stdlib_specialfunctions_gamma | Interface | Upper incomplete gamma function |
var | stdlib_stats | Interface | Variance of array elements (Specification) |
verify | stdlib_string_type | Interface | Scan a string for the absence of a set of characters. Verifies that all the characters in string belong to the set of characters in set. |
water_hash | stdlib_hash_32bit | Interface | WATER_HASH interfaces (Specification) |
write(formatted) | stdlib_string_type | Interface | Write the character sequence hold by the string to a connected formatted unit. |
write(unformatted) | stdlib_string_type | Interface | Write the character sequence hold by the string to a connected unformatted unit. |
xor | stdlib_bitsets | Interface | Sets the bits in |
zfill | stdlib_strings | Interface | Left pad the input string with zeros. Specifications |