Procedures

ProcedureLocationProcedure TypeDescription
adjustl stdlib_string_type Interface

Left-adjust the character sequence represented by the string. The length of the character sequence remains unchanged.

Read more…
adjustr stdlib_string_type Interface

Right-adjust the character sequence represented by the string. The length of the character sequence remains unchanged.

Read more…
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 set1 to the bitwise and of the original bits in set1 and set2. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
and_not stdlib_bitsets Interface

Sets the bits in set1 to the bitwise and of the original bits in set1 with the bitwise negation of set2. The sets must have the same number of bits otherwise the result is undefined.

Read more…
arange stdlib_math Interface

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

arg stdlib_math Interface

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

arg_select stdlib_selection Interface

(Specification)

argd stdlib_math Interface

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

argpi stdlib_math Interface

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

assignment(=) stdlib_string_type Interface

Assign a character sequence to a string.

assignment(=) stdlib_bitsets Interface

Used to define assignment for bitset_large. (Specification)

Read more…
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 self.

cdf_exp stdlib_stats_distribution_exponential Interface

Version experimental

Read more…
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.

Read more…
check stdlib_error Subroutine

Checks the value of a logical condition (Specification)

Read more…
chol stdlib_linalg Interface

Computes the Cholesky factorization , or . (Specification)

Read more…
cholesky stdlib_linalg Interface

Computes the Cholesky factorization , or . (Specification)

Read more…
chomp stdlib_strings Interface

Remove trailing characters in set from string. If no character set is provided trailing whitespace is removed.

Read more…
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)

Read more…
copy_other stdlib_hashmap_wrappers Subroutine

Copies the other data, other_in, to the variable, other_out (Specifications)

Read more…
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

deg2rad converts phase angles from degrees to radians. (Specification)

dense2coo stdlib_sparse_conversion Interface
det stdlib_linalg Interface

Computes the determinant of a square matrix (Specification)

Read more…
diag stdlib_sparse_conversion Interface
diag stdlib_linalg Interface

Creates a diagonal array or extract the diagonal elements of an array (Specification)

diff stdlib_math Interface

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

dist_rand stdlib_random Interface

Version experimental

Read more…
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)

Read more…
eigh stdlib_linalg Interface

Solves the eigendecomposition for a real symmetric or complex Hermitian square matrix. (Specification)

Read more…
eigvals stdlib_linalg Interface

Returns the eigenvalues , , for square matrix . (Specification)

Read more…
eigvalsh stdlib_linalg Interface

Returns the eigenvalues , , for a real symmetric or complex Hermitian square matrix. (Specification)

Read more…
ends_with stdlib_strings Interface

Check whether a string ends with substring or not

Read more…
error_handler stdlib_bitsets Subroutine
error_stop stdlib_error Interface
extract stdlib_bitsets Interface

Creates a new bitset, new, from a range, start_pos to stop_pos, in bitset old. If start_pos is greater than stop_pos the new bitset is empty. If start_pos is less than zero or stop_pos is greater than bits(old)-1 then if status is present it has the value index_invalid_error and new is undefined, otherwise processing stops with an informative message. (Specification)

Read more…
eye stdlib_linalg Interface

Constructs the identity matrix (Specification)

falseloc stdlib_array Function

Return the positions of the false elements in array. Specification

fibonacci_hash stdlib_hash_32bit Function

Maps the 32 bit integer key to an unsigned integer value with only nbits bits where nbits is less than 32 (Specification)

fibonacci_hash stdlib_hash_64bit Function

Maps the 64 bit integer key to an unsigned integer value with only nbits bits where nbits is less than 64 (Specification)

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

Read more…
fnv_1_hash stdlib_hash_32bit Interface

FNV_1 interfaces (Specification)

fnv_1_hash stdlib_hash_64bit 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_32bit Interface

FNV_1A interfaces (Specification)

fnv_1a_hash stdlib_hash_64bit Interface

FNV_1A interfaces (Specification)

fnv_1a_hasher stdlib_hashmap_wrappers Function

Hashes a key with the FNV_1a algorithm (Specifications)

Read more…
free_key stdlib_hashmap_wrappers Subroutine

Frees the memory in a key (Specifications)

Read more…
free_other stdlib_hashmap_wrappers Subroutine

Frees the memory in the other data (Specifications)

Read more…
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)

Read more…
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

Read more…
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.

hermitian stdlib_linalg Interface

Computes the Hermitian version of a rank-2 matrix. For complex matrices, this returns conjg(transpose(a)). For real or integer matrices, this returns transpose(a).

Read more…
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.

Read more…
ichar stdlib_string_type Interface

Character-to-integer conversion function.

Read more…
index stdlib_string_type Interface

Position of a substring within a string.

Read more…
inv stdlib_linalg Interface

Inverse of a square matrix (Specification)

Read more…
invert stdlib_linalg Interface

Inversion of a square matrix (Specification)

Read more…
is_alpha stdlib_ascii Function

Checks whether c is an ASCII letter (A .. Z, a .. z).

is_alphanum stdlib_ascii Function

Checks whether c is a letter or a number (0 .. 9, a .. z, A .. Z).

is_ascii stdlib_ascii Function

Checks whether or not c is in the ASCII character set - i.e. in the range 0 .. 0x7F.

is_blank stdlib_ascii Function

Checks whether or not c is a blank character. That includes the only the space and tab characters

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 c is a control character.

is_diagonal stdlib_linalg Interface

Checks if a matrix (rank-2 array) is diagonal (Specification)

is_digit stdlib_ascii Function

Checks whether c is a digit (0 .. 9).

is_graphical stdlib_ascii Function

Checks whether or not c is a printable character other than the space character.

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 c is a digit in base 16 (0 .. 9, A .. F, a .. f).

is_lower stdlib_ascii Function

Checks whether c is a lowercase ASCII letter (a .. z).

is_octal_digit stdlib_ascii Function

Checks whether c is a digit in base 8 (0 .. 7).

is_printable stdlib_ascii Function

Checks whether or not c is a printable character - including the space character.

is_punctuation stdlib_ascii Function

Checks whether or not c is a punctuation character. That includes all ASCII characters which are not control characters, letters, digits, or whitespace.

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 c is an uppercase ASCII letter (A .. Z).

is_white stdlib_ascii Function

Checks whether or not c is a whitespace character. That includes the space, tab, vertical tab, form feed, carriage return, and linefeed characters.

join stdlib_strings Interface

Joins an array of strings into a single string. The chunks are separated with a space, or an optional user-defined separator. Specifications

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.

Read more…
len_trim stdlib_string_type Interface

Returns the length of the character sequence without trailing spaces represented by the string.

Read more…
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.

Read more…
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.

Read more…
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)

Read more…
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.

Read more…
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.

Read more…
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

Read more…
lower_incomplete_gamma stdlib_specialfunctions_gamma Interface

Lower incomplete gamma function

lstsq stdlib_linalg Interface

Computes the squares solution to system . (Specification)

Read more…
lstsq_space stdlib_linalg Interface

Computes the integer, real [, complex] working space required by the least-squares solver (Specification)

Read more…
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)

mnorm stdlib_linalg Interface

Matrix norms: function interface version: experimental

Read more…
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

(Specification

new_nmhash32x_seed stdlib_hash_32bit Interface

(Specification)

new_pengy_hash_seed stdlib_hash_64bit Interface
new_spooky_hash_seed stdlib_hash_64bit Interface
new_water_hash_seed stdlib_hash_32bit Interface

(Specification)

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)

Read more…
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_32bit Subroutine

Returns a 32 bit pseudo random integer, harvest, distributed uniformly over the odd integers of the int32 kind. (Specification)

odd_random_integer stdlib_hash_64bit Subroutine

Returns a 64 bit pseudo random integer, harvest, distributed uniformly over the odd integers of the 64 bit kind. (Specification)

open stdlib_io Function

Opens a file (Specification)

Read more…
operator(+) stdlib_ansi Interface
operator(.det.) stdlib_linalg Interface

Determinant operator of a square matrix (Specification)

Read more…
operator(.inv.) stdlib_linalg Interface

Inverse operator of a square matrix (Specification)

Read more…
operator(.pinv.) stdlib_linalg Interface

Pseudo-inverse operator of a matrix (Specification)

Read more…
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.

Read more…
operator(//) stdlib_ansi Interface
operator(//) stdlib_stringlist_type Interface

Concatenates stringlist with the input entity Returns a new stringlist Specifications

operator(/=) stdlib_linalg_state Interface
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.

Read more…
operator(/=) stdlib_bitsets Interface

Returns .true. if not all bits in set1 and set2 have the same value, .false. otherwise. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
operator(/=) stdlib_stringlist_type Interface

Compares stringlist for inequality with the input entity Returns a logical Specifications

operator(<) stdlib_linalg_state Interface
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.

Read more…
operator(<) stdlib_bitsets Interface

Returns .true. if the bits in set1 and set2 differ and the highest order different bit is set to 0 in set1 and to 1 in set2, .false. otherwise. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
operator(<=) stdlib_linalg_state Interface
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.

Read more…
operator(<=) stdlib_bitsets Interface

Returns .true. if the bits in set1 and set2 are the same or the highest order different bit is set to 0 in set1 and to 1 in set2, .false. otherwise. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
operator(==) stdlib_linalg_state Interface

Comparison operators

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.

Read more…
operator(==) stdlib_bitsets Interface

Returns .true. if all bits in set1 and set2 have the same value, .false. otherwise. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
operator(==) stdlib_hashmap_wrappers Interface
operator(==) stdlib_stringlist_type Interface

Compares stringlist for equality with the input entity Returns a logical Specifications

operator(>) stdlib_linalg_state Interface
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.

Read more…
operator(>) stdlib_bitsets Interface

Returns .true. if the bits in set1 and set2 differ and the highest order different bit is set to 1 in set1 and to 0 in set2, .false. otherwise. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
operator(>=) stdlib_linalg_state Interface
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.

Read more…
operator(>=) stdlib_bitsets Interface

Returns .true. if the bits in set1 and set2 are the same or the highest order different bit is set to 1 in set1 and to 0 in set2, .false. otherwise. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
optval stdlib_optval Interface

Fallback value for optional arguments (Specification)

or stdlib_bitsets Interface

Sets the bits in set1 to the bitwise or of the original bits in set1 and set2. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
ord_sort stdlib_sorting Interface

The generic subroutine interface implementing the ORD_SORT algorithm, a translation to Fortran 2008, of the "Rust" sort algorithm found in slice.rs https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs#L2159 ORD_SORT is a hybrid stable comparison algorithm combining merge sort, and insertion sort. (Specification)

Read more…
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

Read more…
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)

pinv stdlib_linalg Interface

Pseudo-inverse of a matrix (Specification)

Read more…
pseudoinvert stdlib_linalg Interface

Computation of the Moore-Penrose pseudo-inverse (Specification)

Read more…
qr stdlib_linalg Interface

Computes the QR factorization of matrix . (Specification)

Read more…
qr_space stdlib_linalg Interface

Computes the working array space required by the QR factorization solver (Specification)

Read more…
rad2deg stdlib_math Interface

rad2deg converts phase angles from radians to degrees. (Specification)

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 more…
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.

Read more…
replace_all stdlib_strings Interface

Replaces all the occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Version: experimental

reverse stdlib_ascii Function

Reverse the character order in the input character variable (Specification)

Read more…
reverse stdlib_string_type Interface

Reverses the character sequence hold by the input string

Read more…
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: See ROTMG for a description of data storage in DPARAM.

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: Locations 2-4 of DPARAM contain DH11, DH21, DH12 and DH22 respectively. (Values of 1.0, -1.0, or 0.0 implied by the value of DPARAM(1) are not stored in DPARAM.) The values of parameters GAMSQ and RGAMSQ may be inexact. This is OK as they are only used for testing the size of DD1 and DD2. All actual scaling of data is done using GAM.

rvs_exp stdlib_stats_distribution_exponential Interface

Version experimental

Read more…
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.

Read more…
schur stdlib_linalg Interface

Computes the Schur decomposition of matrix . (Specification)

Read more…
schur_space stdlib_linalg Interface

Computes the working array space required by the Schur decomposition solver (Specification)

Read more…
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)

Read more…
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)

Read more…
select stdlib_selection Interface

(Specification)

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

Read more…
solve stdlib_linalg Interface

Solves the linear system for the unknown vector from a square matrix . (Specification)

Read more…
solve_lstsq stdlib_linalg Interface

Computes the squares solution to system . (Specification)

Read more…
solve_lu stdlib_linalg Interface

Solves the linear system for the unknown vector from a square matrix . (Specification)

Read more…
sort stdlib_sorting Interface

The generic subroutine interface implementing the SORT algorithm, based on the introsort of David Musser. (Specification)

sort_index stdlib_sorting Interface

The generic subroutine interface implementing the SORT_INDEX algorithm, based on the "Rust" sort algorithm found in slice.rs https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs#L2159 but modified to return an array of indices that would provide a stable sort of the rank one ARRAY input. (Specification)

Read more…
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

Read more…
stdlib_cabs1 stdlib_linalg_blas_aux Interface
stdlib_caxpy stdlib_blas Interface
stdlib_cbbcsd stdlib_lapack_eig_svd_lsq Interface
stdlib_cbdsqr stdlib_lapack_eig_svd_lsq Interface
stdlib_ccopy stdlib_blas Interface
stdlib_cdotc stdlib_blas Interface
stdlib_cdotu stdlib_blas Interface
stdlib_cgbbrd stdlib_lapack_eig_svd_lsq Interface
stdlib_cgbcon stdlib_lapack_solve Interface
stdlib_cgbequ stdlib_lapack_solve Interface
stdlib_cgbequb stdlib_lapack_solve Interface
stdlib_cgbmv stdlib_blas Interface
stdlib_cgbrfs stdlib_lapack_solve Interface
stdlib_cgbsv stdlib_lapack_solve Interface
stdlib_cgbsvx stdlib_lapack_solve Interface
stdlib_cgbtf2 stdlib_lapack_solve Interface
stdlib_cgbtrf stdlib_lapack_solve Interface
stdlib_cgbtrs stdlib_lapack_solve Interface
stdlib_cgebak stdlib_lapack_eig_svd_lsq Interface
stdlib_cgebal stdlib_lapack_eig_svd_lsq Interface
stdlib_cgebd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_cgebrd stdlib_lapack_eig_svd_lsq Interface
stdlib_cgecon stdlib_lapack_solve Interface
stdlib_cgeequ stdlib_lapack_solve Interface
stdlib_cgeequb stdlib_lapack_solve Interface
stdlib_cgees stdlib_lapack_eig_svd_lsq Interface
stdlib_cgeesx stdlib_lapack_eig_svd_lsq Interface
stdlib_cgeev stdlib_lapack_eig_svd_lsq Interface
stdlib_cgeevx stdlib_lapack_eig_svd_lsq Interface
stdlib_cgehd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_cgehrd stdlib_lapack_eig_svd_lsq Interface
stdlib_cgejsv stdlib_lapack_eig_svd_lsq Interface
stdlib_cgelq stdlib_lapack_orthogonal_factors Interface
stdlib_cgelq2 stdlib_lapack_orthogonal_factors Interface
stdlib_cgelqf stdlib_lapack_orthogonal_factors Interface
stdlib_cgelqt stdlib_lapack_orthogonal_factors Interface
stdlib_cgelqt3 stdlib_lapack_orthogonal_factors Interface
stdlib_cgels stdlib_lapack_eig_svd_lsq Interface
stdlib_cgelsd stdlib_lapack_eig_svd_lsq Interface
stdlib_cgelss stdlib_lapack_eig_svd_lsq Interface
stdlib_cgelsy stdlib_lapack_eig_svd_lsq Interface
stdlib_cgemlq stdlib_lapack_orthogonal_factors Interface
stdlib_cgemlqt stdlib_lapack_orthogonal_factors Interface
stdlib_cgemm stdlib_blas Interface
stdlib_cgemqr stdlib_lapack_orthogonal_factors Interface
stdlib_cgemqrt stdlib_lapack_orthogonal_factors Interface
stdlib_cgemv stdlib_blas Interface
stdlib_cgeql2 stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqlf stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqp3 stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqr stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqr2 stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqr2p stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqrf stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqrfp stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqrt stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqrt2 stdlib_lapack_orthogonal_factors Interface
stdlib_cgeqrt3 stdlib_lapack_orthogonal_factors Interface
stdlib_cgerc stdlib_blas Interface
stdlib_cgerfs stdlib_lapack_solve Interface
stdlib_cgerq2 stdlib_lapack_orthogonal_factors Interface
stdlib_cgerqf stdlib_lapack_orthogonal_factors Interface
stdlib_cgeru stdlib_blas Interface
stdlib_cgesc2 stdlib_lapack_solve Interface
stdlib_cgesdd stdlib_lapack_eig_svd_lsq Interface
stdlib_cgesv stdlib_lapack_solve Interface
stdlib_cgesvd stdlib_lapack_eig_svd_lsq Interface
stdlib_cgesvdq stdlib_lapack_eig_svd_lsq Interface
stdlib_cgesvj stdlib_lapack_eig_svd_lsq Interface
stdlib_cgesvx stdlib_lapack_solve Interface
stdlib_cgetc2 stdlib_lapack_solve Interface
stdlib_cgetf2 stdlib_lapack_solve Interface
stdlib_cgetrf stdlib_lapack_solve Interface
stdlib_cgetrf2 stdlib_lapack_solve Interface
stdlib_cgetri stdlib_lapack_solve Interface
stdlib_cgetrs stdlib_lapack_solve Interface
stdlib_cgetsls stdlib_lapack_eig_svd_lsq Interface
stdlib_cgetsqrhrt stdlib_lapack_orthogonal_factors Interface
stdlib_cggbak stdlib_lapack_eig_svd_lsq Interface
stdlib_cggbal stdlib_lapack_eig_svd_lsq Interface
stdlib_cgges stdlib_lapack_eig_svd_lsq Interface
stdlib_cgges3 stdlib_lapack_eig_svd_lsq Interface
stdlib_cggesx stdlib_lapack_eig_svd_lsq Interface
stdlib_cggev stdlib_lapack_eig_svd_lsq Interface
stdlib_cggev3 stdlib_lapack_eig_svd_lsq Interface
stdlib_cggevx stdlib_lapack_eig_svd_lsq Interface
stdlib_cggglm stdlib_lapack_eig_svd_lsq Interface
stdlib_cgghd3 stdlib_lapack_eig_svd_lsq Interface
stdlib_cgghrd stdlib_lapack_eig_svd_lsq Interface
stdlib_cgglse stdlib_lapack_eig_svd_lsq Interface
stdlib_cggqrf stdlib_lapack_orthogonal_factors Interface
stdlib_cggrqf stdlib_lapack_orthogonal_factors Interface
stdlib_cgsvj0 stdlib_lapack_eig_svd_lsq Interface
stdlib_cgsvj1 stdlib_lapack_eig_svd_lsq Interface
stdlib_cgtcon stdlib_lapack_solve Interface
stdlib_cgtrfs stdlib_lapack_solve Interface
stdlib_cgtsv stdlib_lapack_solve Interface
stdlib_cgtsvx stdlib_lapack_solve Interface
stdlib_cgttrf stdlib_lapack_solve Interface
stdlib_cgttrs stdlib_lapack_solve Interface
stdlib_cgtts2 stdlib_lapack_solve Interface
stdlib_chb2st_kernels stdlib_lapack_eig_svd_lsq Interface
stdlib_chbev stdlib_lapack_eig_svd_lsq Interface
stdlib_chbevd stdlib_lapack_eig_svd_lsq Interface
stdlib_chbevx stdlib_lapack_eig_svd_lsq Interface
stdlib_chbgst stdlib_lapack_eig_svd_lsq Interface
stdlib_chbgv stdlib_lapack_eig_svd_lsq Interface
stdlib_chbgvd stdlib_lapack_eig_svd_lsq Interface
stdlib_chbgvx stdlib_lapack_eig_svd_lsq Interface
stdlib_chbmv stdlib_blas Interface
stdlib_chbtrd stdlib_lapack_eig_svd_lsq Interface
stdlib_checon stdlib_lapack_solve Interface
stdlib_checon_rook stdlib_lapack_solve Interface
stdlib_cheequb stdlib_lapack_solve Interface
stdlib_cheev stdlib_lapack_eig_svd_lsq Interface
stdlib_cheevd stdlib_lapack_eig_svd_lsq Interface
stdlib_cheevr stdlib_lapack_eig_svd_lsq Interface
stdlib_cheevx stdlib_lapack_eig_svd_lsq Interface
stdlib_chegs2 stdlib_lapack_eig_svd_lsq Interface
stdlib_chegst stdlib_lapack_eig_svd_lsq Interface
stdlib_chegv stdlib_lapack_eig_svd_lsq Interface
stdlib_chegvd stdlib_lapack_eig_svd_lsq Interface
stdlib_chegvx stdlib_lapack_eig_svd_lsq Interface
stdlib_chemm stdlib_blas Interface
stdlib_chemv stdlib_blas Interface
stdlib_cher stdlib_blas Interface
stdlib_cher2 stdlib_blas Interface
stdlib_cher2k stdlib_blas Interface
stdlib_cherfs stdlib_lapack_solve Interface
stdlib_cherk stdlib_blas Interface
stdlib_chesv stdlib_lapack_solve Interface
stdlib_chesv_aa stdlib_lapack_solve Interface
stdlib_chesv_rk stdlib_lapack_solve Interface
stdlib_chesv_rook stdlib_lapack_solve Interface
stdlib_chesvx stdlib_lapack_solve Interface
stdlib_cheswapr stdlib_lapack_solve Interface
stdlib_chetd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_chetf2 stdlib_lapack_solve Interface
stdlib_chetf2_rk stdlib_lapack_solve Interface
stdlib_chetf2_rook stdlib_lapack_solve Interface
stdlib_chetrd stdlib_lapack_eig_svd_lsq Interface
stdlib_chetrd_hb2st stdlib_lapack_eig_svd_lsq Interface
stdlib_chetrd_he2hb stdlib_lapack_eig_svd_lsq Interface
stdlib_chetrf stdlib_lapack_solve Interface
stdlib_chetrf_aa stdlib_lapack_solve Interface
stdlib_chetrf_rk stdlib_lapack_solve Interface
stdlib_chetrf_rook stdlib_lapack_solve Interface
stdlib_chetri stdlib_lapack_solve Interface
stdlib_chetri_rook stdlib_lapack_solve Interface
stdlib_chetrs stdlib_lapack_solve Interface
stdlib_chetrs2 stdlib_lapack_solve Interface
stdlib_chetrs_3 stdlib_lapack_solve Interface
stdlib_chetrs_aa stdlib_lapack_solve Interface
stdlib_chetrs_rook stdlib_lapack_solve Interface
stdlib_chfrk stdlib_lapack_base Interface
stdlib_chgeqz stdlib_lapack_eig_svd_lsq Interface
stdlib_chla_transtype stdlib_linalg_lapack_aux Function

This subroutine translates from a BLAST-specified integer constant to the character string specifying a transposition operation. CHLA_TRANSTYPE returns an CHARACTER*1. If CHLA_TRANSTYPE: is 'X', then input is not an integer indicating a transposition operator. Otherwise CHLA_TRANSTYPE returns the constant value corresponding to TRANS.

stdlib_chpcon stdlib_lapack_solve Interface
stdlib_chpev stdlib_lapack_eig_svd_lsq Interface
stdlib_chpevd stdlib_lapack_eig_svd_lsq Interface
stdlib_chpevx stdlib_lapack_eig_svd_lsq Interface
stdlib_chpgst stdlib_lapack_eig_svd_lsq Interface
stdlib_chpgv stdlib_lapack_eig_svd_lsq Interface
stdlib_chpgvd stdlib_lapack_eig_svd_lsq Interface
stdlib_chpgvx stdlib_lapack_eig_svd_lsq Interface
stdlib_chpmv stdlib_blas Interface
stdlib_chpr stdlib_blas Interface
stdlib_chpr2 stdlib_blas Interface
stdlib_chprfs stdlib_lapack_solve Interface
stdlib_chpsv stdlib_lapack_solve Interface
stdlib_chpsvx stdlib_lapack_solve Interface
stdlib_chptrd stdlib_lapack_eig_svd_lsq Interface
stdlib_chptrf stdlib_lapack_solve Interface
stdlib_chptri stdlib_lapack_solve Interface
stdlib_chptrs stdlib_lapack_solve Interface
stdlib_chsein stdlib_lapack_eig_svd_lsq Interface
stdlib_chseqr stdlib_lapack_eig_svd_lsq Interface
stdlib_cla_gbamv stdlib_lapack_base Interface
stdlib_cla_gbrcond_c stdlib_lapack_others Interface
stdlib_cla_gbrpvgrw stdlib_lapack_solve Interface
stdlib_cla_geamv stdlib_lapack_base Interface
stdlib_cla_gercond_c stdlib_lapack_others Interface
stdlib_cla_gerpvgrw stdlib_lapack_others Interface
stdlib_cla_heamv stdlib_lapack_base Interface
stdlib_cla_hercond_c stdlib_lapack_others Interface
stdlib_cla_herpvgrw stdlib_lapack_solve Interface
stdlib_cla_lin_berr stdlib_lapack_solve Interface
stdlib_cla_porcond_c stdlib_lapack_others Interface
stdlib_cla_porpvgrw stdlib_lapack_solve Interface
stdlib_cla_syamv stdlib_lapack_others Interface
stdlib_cla_syrcond_c stdlib_lapack_others Interface
stdlib_cla_syrpvgrw stdlib_lapack_others Interface
stdlib_cla_wwaddw stdlib_lapack_base Interface
stdlib_clabrd stdlib_lapack_eig_svd_lsq Interface
stdlib_clacgv stdlib_lapack_base Interface
stdlib_clacn2 stdlib_lapack_solve Interface
stdlib_clacon stdlib_lapack_solve Interface
stdlib_clacp2 stdlib_lapack_base Interface
stdlib_clacpy stdlib_lapack_base Interface
stdlib_clacrm stdlib_lapack_base Interface
stdlib_clacrt stdlib_lapack_base Interface
stdlib_cladiv stdlib_lapack_base Interface
stdlib_claed0 stdlib_lapack_eig_svd_lsq Interface
stdlib_claed7 stdlib_lapack_eig_svd_lsq Interface
stdlib_claed8 stdlib_lapack_eig_svd_lsq Interface
stdlib_claein stdlib_lapack_eig_svd_lsq Interface
stdlib_claesy stdlib_lapack_eig_svd_lsq Interface
stdlib_claev2 stdlib_lapack_eig_svd_lsq Interface
stdlib_clags2 stdlib_lapack_eig_svd_lsq Interface
stdlib_clagtm stdlib_lapack_base Interface
stdlib_clahef stdlib_lapack_solve Interface
stdlib_clahef_aa stdlib_lapack_solve Interface
stdlib_clahef_rk stdlib_lapack_solve Interface
stdlib_clahef_rook stdlib_lapack_solve Interface
stdlib_clahqr stdlib_lapack_eig_svd_lsq Interface
stdlib_clahr2 stdlib_lapack_eig_svd_lsq Interface
stdlib_claic1 stdlib_lapack_eig_svd_lsq Interface
stdlib_clals0 stdlib_lapack_eig_svd_lsq Interface
stdlib_clalsa stdlib_lapack_eig_svd_lsq Interface
stdlib_clalsd stdlib_lapack_eig_svd_lsq Interface
stdlib_clamswlq stdlib_lapack_orthogonal_factors Interface
stdlib_clamtsqr stdlib_lapack_orthogonal_factors Interface
stdlib_clangb stdlib_lapack_base Interface
stdlib_clange stdlib_lapack_base Interface
stdlib_clangt stdlib_lapack_base Interface
stdlib_clanhb stdlib_lapack_base Interface
stdlib_clanhe stdlib_lapack_base Interface
stdlib_clanhf stdlib_lapack_base Interface
stdlib_clanhp stdlib_lapack_base Interface
stdlib_clanhs stdlib_lapack_base Interface
stdlib_clanht stdlib_lapack_base Interface
stdlib_clansb stdlib_lapack_base Interface
stdlib_clansp stdlib_lapack_base Interface
stdlib_clansy stdlib_lapack_base Interface
stdlib_clantb stdlib_lapack_base Interface
stdlib_clantp stdlib_lapack_base Interface
stdlib_clantr stdlib_lapack_base Interface
stdlib_clapll stdlib_lapack_eig_svd_lsq Interface
stdlib_clapmr stdlib_lapack_eig_svd_lsq Interface
stdlib_clapmt stdlib_lapack_eig_svd_lsq Interface
stdlib_claqgb stdlib_lapack_solve Interface
stdlib_claqge stdlib_lapack_solve Interface
stdlib_claqhb stdlib_lapack_solve Interface
stdlib_claqhe stdlib_lapack_solve Interface
stdlib_claqhp stdlib_lapack_solve Interface
stdlib_claqp2 stdlib_lapack_orthogonal_factors Interface
stdlib_claqps stdlib_lapack_orthogonal_factors Interface
stdlib_claqr0 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqr1 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqr2 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqr3 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqr4 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqr5 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqsb stdlib_lapack_base Interface
stdlib_claqsp stdlib_lapack_solve Interface
stdlib_claqsy stdlib_lapack_solve Interface
stdlib_claqz0 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqz1 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqz2 stdlib_lapack_eig_svd_lsq Interface
stdlib_claqz3 stdlib_lapack_eig_svd_lsq Interface
stdlib_clar1v stdlib_lapack_eig_svd_lsq Interface
stdlib_clar2v stdlib_lapack_base Interface
stdlib_clarcm stdlib_lapack_base Interface
stdlib_clarf stdlib_lapack_base Interface
stdlib_clarfb stdlib_lapack_base Interface
stdlib_clarfb_gett stdlib_lapack_orthogonal_factors Interface
stdlib_clarfg stdlib_lapack_base Interface
stdlib_clarfgp stdlib_lapack_base Interface
stdlib_clarft stdlib_lapack_base Interface
stdlib_clarfx stdlib_lapack_base Interface
stdlib_clarfy stdlib_lapack_base Interface
stdlib_clargv stdlib_lapack_base Interface
stdlib_clarnv stdlib_lapack_base Interface
stdlib_clarrv stdlib_lapack_eig_svd_lsq Interface
stdlib_clartg stdlib_lapack_base Interface
stdlib_clartv stdlib_lapack_base Interface
stdlib_clarz stdlib_lapack_orthogonal_factors Interface
stdlib_clarzb stdlib_lapack_orthogonal_factors Interface
stdlib_clarzt stdlib_lapack_orthogonal_factors Interface
stdlib_clascl stdlib_lapack_base Interface
stdlib_claset stdlib_lapack_base Interface
stdlib_clasr stdlib_lapack_base Interface
stdlib_classq stdlib_lapack_base Interface
stdlib_claswlq stdlib_lapack_orthogonal_factors Interface
stdlib_claswp stdlib_lapack_solve Interface
stdlib_clasyf stdlib_lapack_solve Interface
stdlib_clasyf_aa stdlib_lapack_solve Interface
stdlib_clasyf_rk stdlib_lapack_solve Interface
stdlib_clasyf_rook stdlib_lapack_solve Interface
stdlib_clatbs stdlib_lapack_solve Interface
stdlib_clatdf stdlib_lapack_solve Interface
stdlib_clatps stdlib_lapack_solve Interface
stdlib_clatrd stdlib_lapack_eig_svd_lsq Interface
stdlib_clatrs stdlib_lapack_solve Interface
stdlib_clatrz stdlib_lapack_orthogonal_factors Interface
stdlib_clatsqr stdlib_lapack_orthogonal_factors Interface
stdlib_claunhr_col_getrfnp stdlib_lapack_orthogonal_factors Interface
stdlib_claunhr_col_getrfnp2 stdlib_lapack_orthogonal_factors Interface
stdlib_clauu2 stdlib_lapack_solve Interface
stdlib_clauum stdlib_lapack_solve Interface
stdlib_cpbcon stdlib_lapack_solve Interface
stdlib_cpbequ stdlib_lapack_solve Interface
stdlib_cpbrfs stdlib_lapack_solve Interface
stdlib_cpbstf stdlib_lapack_eig_svd_lsq Interface
stdlib_cpbsv stdlib_lapack_solve Interface
stdlib_cpbsvx stdlib_lapack_solve Interface
stdlib_cpbtf2 stdlib_lapack_solve Interface
stdlib_cpbtrf stdlib_lapack_solve Interface
stdlib_cpbtrs stdlib_lapack_solve Interface
stdlib_cpftrf stdlib_lapack_solve Interface
stdlib_cpftri stdlib_lapack_solve Interface
stdlib_cpftrs stdlib_lapack_solve Interface
stdlib_cpocon stdlib_lapack_solve Interface
stdlib_cpoequ stdlib_lapack_solve Interface
stdlib_cpoequb stdlib_lapack_solve Interface
stdlib_cporfs stdlib_lapack_solve Interface
stdlib_cposv stdlib_lapack_solve Interface
stdlib_cposvx stdlib_lapack_solve Interface
stdlib_cpotf2 stdlib_lapack_solve Interface
stdlib_cpotrf stdlib_lapack_solve Interface
stdlib_cpotrf2 stdlib_lapack_solve Interface
stdlib_cpotri stdlib_lapack_solve Interface
stdlib_cpotrs stdlib_lapack_solve Interface
stdlib_cppcon stdlib_lapack_solve Interface
stdlib_cppequ stdlib_lapack_solve Interface
stdlib_cpprfs stdlib_lapack_solve Interface
stdlib_cppsv stdlib_lapack_solve Interface
stdlib_cppsvx stdlib_lapack_solve Interface
stdlib_cpptrf stdlib_lapack_solve Interface
stdlib_cpptri stdlib_lapack_solve Interface
stdlib_cpptrs stdlib_lapack_solve Interface
stdlib_cpstf2 stdlib_lapack_solve Interface
stdlib_cpstrf stdlib_lapack_solve Interface
stdlib_cptcon stdlib_lapack_solve Interface
stdlib_cpteqr stdlib_lapack_eig_svd_lsq Interface
stdlib_cptrfs stdlib_lapack_solve Interface
stdlib_cptsv stdlib_lapack_solve Interface
stdlib_cptsvx stdlib_lapack_solve Interface
stdlib_cpttrf stdlib_lapack_solve Interface
stdlib_cpttrs stdlib_lapack_solve Interface
stdlib_cptts2 stdlib_lapack_solve Interface
stdlib_crot stdlib_lapack_base Interface
stdlib_crotg stdlib_blas Interface
stdlib_cscal stdlib_blas Interface
stdlib_cspcon stdlib_lapack_solve Interface
stdlib_cspmv stdlib_lapack_base Interface
stdlib_cspr stdlib_lapack_base Interface
stdlib_csprfs stdlib_lapack_solve Interface
stdlib_cspsv stdlib_lapack_solve Interface
stdlib_cspsvx stdlib_lapack_solve Interface
stdlib_csptrf stdlib_lapack_solve Interface
stdlib_csptri stdlib_lapack_solve Interface
stdlib_csptrs stdlib_lapack_solve Interface
stdlib_csrot stdlib_blas Interface
stdlib_csrscl stdlib_lapack_base Interface
stdlib_csscal stdlib_blas Interface
stdlib_cstedc stdlib_lapack_eig_svd_lsq Interface
stdlib_cstegr stdlib_lapack_eig_svd_lsq Interface
stdlib_cstein stdlib_lapack_eig_svd_lsq Interface
stdlib_cstemr stdlib_lapack_eig_svd_lsq Interface
stdlib_csteqr stdlib_lapack_eig_svd_lsq Interface
stdlib_cswap stdlib_blas Interface
stdlib_csycon stdlib_lapack_solve Interface
stdlib_csycon_rook stdlib_lapack_solve Interface
stdlib_csyconv stdlib_lapack_solve Interface
stdlib_csyconvf stdlib_lapack_solve Interface
stdlib_csyconvf_rook stdlib_lapack_solve Interface
stdlib_csyequb stdlib_lapack_solve Interface
stdlib_csymm stdlib_blas Interface
stdlib_csymv stdlib_lapack_base Interface
stdlib_csyr stdlib_lapack_base Interface
stdlib_csyr2k stdlib_blas Interface
stdlib_csyrfs stdlib_lapack_solve Interface
stdlib_csyrk stdlib_blas Interface
stdlib_csysv stdlib_lapack_solve Interface
stdlib_csysv_aa stdlib_lapack_solve Interface
stdlib_csysv_rk stdlib_lapack_solve Interface
stdlib_csysv_rook stdlib_lapack_solve Interface
stdlib_csysvx stdlib_lapack_solve Interface
stdlib_csyswapr stdlib_lapack_solve Interface
stdlib_csytf2 stdlib_lapack_solve Interface
stdlib_csytf2_rk stdlib_lapack_solve Interface
stdlib_csytf2_rook stdlib_lapack_solve Interface
stdlib_csytrf stdlib_lapack_solve Interface
stdlib_csytrf_aa stdlib_lapack_solve Interface
stdlib_csytrf_rk stdlib_lapack_solve Interface
stdlib_csytrf_rook stdlib_lapack_solve Interface
stdlib_csytri stdlib_lapack_solve Interface
stdlib_csytri_rook stdlib_lapack_solve Interface
stdlib_csytrs stdlib_lapack_solve Interface
stdlib_csytrs2 stdlib_lapack_solve Interface
stdlib_csytrs_3 stdlib_lapack_solve Interface
stdlib_csytrs_aa stdlib_lapack_solve Interface
stdlib_csytrs_rook stdlib_lapack_solve Interface
stdlib_ctbcon stdlib_lapack_solve Interface
stdlib_ctbmv stdlib_blas Interface
stdlib_ctbrfs stdlib_lapack_solve Interface
stdlib_ctbsv stdlib_blas Interface
stdlib_ctbtrs stdlib_lapack_solve Interface
stdlib_ctfsm stdlib_lapack_base Interface
stdlib_ctftri stdlib_lapack_solve Interface
stdlib_ctfttp stdlib_lapack_base Interface
stdlib_ctfttr stdlib_lapack_base Interface
stdlib_ctgevc stdlib_lapack_eig_svd_lsq Interface
stdlib_ctgex2 stdlib_lapack_eig_svd_lsq Interface
stdlib_ctgexc stdlib_lapack_eig_svd_lsq Interface
stdlib_ctgsen stdlib_lapack_eig_svd_lsq Interface
stdlib_ctgsja stdlib_lapack_eig_svd_lsq Interface
stdlib_ctgsna stdlib_lapack_eig_svd_lsq Interface
stdlib_ctgsy2 stdlib_lapack_eig_svd_lsq Interface
stdlib_ctgsyl stdlib_lapack_eig_svd_lsq Interface
stdlib_ctpcon stdlib_lapack_solve Interface
stdlib_ctplqt stdlib_lapack_orthogonal_factors Interface
stdlib_ctplqt2 stdlib_lapack_orthogonal_factors Interface
stdlib_ctpmlqt stdlib_lapack_orthogonal_factors Interface
stdlib_ctpmqrt stdlib_lapack_orthogonal_factors Interface
stdlib_ctpmv stdlib_blas Interface
stdlib_ctpqrt stdlib_lapack_orthogonal_factors Interface
stdlib_ctpqrt2 stdlib_lapack_orthogonal_factors Interface
stdlib_ctprfb stdlib_lapack_orthogonal_factors Interface
stdlib_ctprfs stdlib_lapack_solve Interface
stdlib_ctpsv stdlib_blas Interface
stdlib_ctptri stdlib_lapack_solve Interface
stdlib_ctptrs stdlib_lapack_solve Interface
stdlib_ctpttf stdlib_lapack_base Interface
stdlib_ctpttr stdlib_lapack_base Interface
stdlib_ctrcon stdlib_lapack_solve Interface
stdlib_ctrevc stdlib_lapack_eig_svd_lsq Interface
stdlib_ctrevc3 stdlib_lapack_eig_svd_lsq Interface
stdlib_ctrexc stdlib_lapack_eig_svd_lsq Interface
stdlib_ctrmm stdlib_blas Interface
stdlib_ctrmv stdlib_blas Interface
stdlib_ctrrfs stdlib_lapack_solve Interface
stdlib_ctrsen stdlib_lapack_eig_svd_lsq Interface
stdlib_ctrsm stdlib_blas Interface
stdlib_ctrsna stdlib_lapack_eig_svd_lsq Interface
stdlib_ctrsv stdlib_blas Interface
stdlib_ctrsyl stdlib_lapack_eig_svd_lsq Interface
stdlib_ctrti2 stdlib_lapack_solve Interface
stdlib_ctrtri stdlib_lapack_solve Interface
stdlib_ctrtrs stdlib_lapack_solve Interface
stdlib_ctrttf stdlib_lapack_base Interface
stdlib_ctrttp stdlib_lapack_base Interface
stdlib_ctzrzf stdlib_lapack_orthogonal_factors Interface
stdlib_cunbdb stdlib_lapack_eig_svd_lsq Interface
stdlib_cunbdb1 stdlib_lapack_eig_svd_lsq Interface
stdlib_cunbdb2 stdlib_lapack_eig_svd_lsq Interface
stdlib_cunbdb3 stdlib_lapack_eig_svd_lsq Interface
stdlib_cunbdb4 stdlib_lapack_eig_svd_lsq Interface
stdlib_cunbdb5 stdlib_lapack_eig_svd_lsq Interface
stdlib_cunbdb6 stdlib_lapack_eig_svd_lsq Interface
stdlib_cuncsd stdlib_lapack_eig_svd_lsq Interface
stdlib_cuncsd2by1 stdlib_lapack_eig_svd_lsq Interface
stdlib_cung2l stdlib_lapack_orthogonal_factors Interface
stdlib_cung2r stdlib_lapack_orthogonal_factors Interface
stdlib_cungbr stdlib_lapack_eig_svd_lsq Interface
stdlib_cunghr stdlib_lapack_eig_svd_lsq Interface
stdlib_cungl2 stdlib_lapack_orthogonal_factors Interface
stdlib_cunglq stdlib_lapack_orthogonal_factors Interface
stdlib_cungql stdlib_lapack_orthogonal_factors Interface
stdlib_cungqr stdlib_lapack_orthogonal_factors Interface
stdlib_cungr2 stdlib_lapack_orthogonal_factors Interface
stdlib_cungrq stdlib_lapack_orthogonal_factors Interface
stdlib_cungtr stdlib_lapack_eig_svd_lsq Interface
stdlib_cungtsqr stdlib_lapack_orthogonal_factors Interface
stdlib_cungtsqr_row stdlib_lapack_orthogonal_factors Interface
stdlib_cunhr_col stdlib_lapack_orthogonal_factors Interface
stdlib_cunm22 stdlib_lapack_orthogonal_factors Interface
stdlib_cunm2l stdlib_lapack_orthogonal_factors Interface
stdlib_cunm2r stdlib_lapack_orthogonal_factors Interface
stdlib_cunmbr stdlib_lapack_eig_svd_lsq Interface
stdlib_cunmhr stdlib_lapack_eig_svd_lsq Interface
stdlib_cunml2 stdlib_lapack_orthogonal_factors Interface
stdlib_cunmlq stdlib_lapack_orthogonal_factors Interface
stdlib_cunmql stdlib_lapack_orthogonal_factors Interface
stdlib_cunmqr stdlib_lapack_orthogonal_factors Interface
stdlib_cunmr2 stdlib_lapack_orthogonal_factors Interface
stdlib_cunmr3 stdlib_lapack_orthogonal_factors Interface
stdlib_cunmrq stdlib_lapack_orthogonal_factors Interface
stdlib_cunmrz stdlib_lapack_orthogonal_factors Interface
stdlib_cunmtr stdlib_lapack_eig_svd_lsq Interface
stdlib_cupgtr stdlib_lapack_eig_svd_lsq Interface
stdlib_cupmtr stdlib_lapack_eig_svd_lsq Interface
stdlib_dasum stdlib_blas Interface
stdlib_daxpy stdlib_blas Interface
stdlib_dbbcsd stdlib_lapack_eig_svd_lsq Interface
stdlib_dbdsdc stdlib_lapack_eig_svd_lsq Interface
stdlib_dbdsqr stdlib_lapack_eig_svd_lsq Interface
stdlib_dcopy stdlib_blas Interface
stdlib_ddisna stdlib_lapack_eig_svd_lsq Interface
stdlib_ddot stdlib_blas Interface
stdlib_dgbbrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dgbcon stdlib_lapack_solve Interface
stdlib_dgbequ stdlib_lapack_solve Interface
stdlib_dgbequb stdlib_lapack_solve Interface
stdlib_dgbmv stdlib_blas Interface
stdlib_dgbrfs stdlib_lapack_solve Interface
stdlib_dgbsv stdlib_lapack_solve Interface
stdlib_dgbsvx stdlib_lapack_solve Interface
stdlib_dgbtf2 stdlib_lapack_solve Interface
stdlib_dgbtrf stdlib_lapack_solve Interface
stdlib_dgbtrs stdlib_lapack_solve Interface
stdlib_dgebak stdlib_lapack_eig_svd_lsq Interface
stdlib_dgebal stdlib_lapack_eig_svd_lsq Interface
stdlib_dgebd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dgebrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dgecon stdlib_lapack_solve Interface
stdlib_dgeequ stdlib_lapack_solve Interface
stdlib_dgeequb stdlib_lapack_solve Interface
stdlib_dgees stdlib_lapack_eig_svd_lsq Interface
stdlib_dgeesx stdlib_lapack_eig_svd_lsq Interface
stdlib_dgeev stdlib_lapack_eig_svd_lsq Interface
stdlib_dgeevx stdlib_lapack_eig_svd_lsq Interface
stdlib_dgehd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dgehrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dgejsv stdlib_lapack_eig_svd_lsq Interface
stdlib_dgelq stdlib_lapack_orthogonal_factors Interface
stdlib_dgelq2 stdlib_lapack_orthogonal_factors Interface
stdlib_dgelqf stdlib_lapack_orthogonal_factors Interface
stdlib_dgelqt stdlib_lapack_orthogonal_factors Interface
stdlib_dgelqt3 stdlib_lapack_orthogonal_factors Interface
stdlib_dgels stdlib_lapack_eig_svd_lsq Interface
stdlib_dgelsd stdlib_lapack_eig_svd_lsq Interface
stdlib_dgelss stdlib_lapack_eig_svd_lsq Interface
stdlib_dgelsy stdlib_lapack_eig_svd_lsq Interface
stdlib_dgemlq stdlib_lapack_orthogonal_factors Interface
stdlib_dgemlqt stdlib_lapack_orthogonal_factors Interface
stdlib_dgemm stdlib_blas Interface
stdlib_dgemqr stdlib_lapack_orthogonal_factors Interface
stdlib_dgemqrt stdlib_lapack_orthogonal_factors Interface
stdlib_dgemv stdlib_blas Interface
stdlib_dgeql2 stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqlf stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqp3 stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqr stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqr2 stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqr2p stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqrf stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqrfp stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqrt stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqrt2 stdlib_lapack_orthogonal_factors Interface
stdlib_dgeqrt3 stdlib_lapack_orthogonal_factors Interface
stdlib_dger stdlib_blas Interface
stdlib_dgerfs stdlib_lapack_solve Interface
stdlib_dgerq2 stdlib_lapack_orthogonal_factors Interface
stdlib_dgerqf stdlib_lapack_orthogonal_factors Interface
stdlib_dgesc2 stdlib_lapack_solve Interface
stdlib_dgesdd stdlib_lapack_eig_svd_lsq Interface
stdlib_dgesv stdlib_lapack_solve Interface
stdlib_dgesvd stdlib_lapack_eig_svd_lsq Interface
stdlib_dgesvdq stdlib_lapack_eig_svd_lsq Interface
stdlib_dgesvj stdlib_lapack_eig_svd_lsq Interface
stdlib_dgesvx stdlib_lapack_solve Interface
stdlib_dgetc2 stdlib_lapack_solve Interface
stdlib_dgetf2 stdlib_lapack_solve Interface
stdlib_dgetrf stdlib_lapack_solve Interface
stdlib_dgetrf2 stdlib_lapack_solve Interface
stdlib_dgetri stdlib_lapack_solve Interface
stdlib_dgetrs stdlib_lapack_solve Interface
stdlib_dgetsls stdlib_lapack_eig_svd_lsq Interface
stdlib_dgetsqrhrt stdlib_lapack_orthogonal_factors Interface
stdlib_dggbak stdlib_lapack_eig_svd_lsq Interface
stdlib_dggbal stdlib_lapack_eig_svd_lsq Interface
stdlib_dgges stdlib_lapack_eig_svd_lsq Interface
stdlib_dgges3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dggesx stdlib_lapack_eig_svd_lsq Interface
stdlib_dggev stdlib_lapack_eig_svd_lsq Interface
stdlib_dggev3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dggevx stdlib_lapack_eig_svd_lsq Interface
stdlib_dggglm stdlib_lapack_eig_svd_lsq Interface
stdlib_dgghd3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dgghrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dgglse stdlib_lapack_eig_svd_lsq Interface
stdlib_dggqrf stdlib_lapack_orthogonal_factors Interface
stdlib_dggrqf stdlib_lapack_orthogonal_factors Interface
stdlib_dgsvj0 stdlib_lapack_eig_svd_lsq Interface
stdlib_dgsvj1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dgtcon stdlib_lapack_solve Interface
stdlib_dgtrfs stdlib_lapack_solve Interface
stdlib_dgtsv stdlib_lapack_solve Interface
stdlib_dgtsvx stdlib_lapack_solve Interface
stdlib_dgttrf stdlib_lapack_solve Interface
stdlib_dgttrs stdlib_lapack_solve Interface
stdlib_dgtts2 stdlib_lapack_solve Interface
stdlib_dhgeqz stdlib_lapack_eig_svd_lsq Interface
stdlib_dhsein stdlib_lapack_eig_svd_lsq Interface
stdlib_dhseqr stdlib_lapack_eig_svd_lsq Interface
stdlib_disnan stdlib_lapack_base Interface
stdlib_dla_gbamv stdlib_lapack_base Interface
stdlib_dla_gbrcond stdlib_lapack_solve Interface
stdlib_dla_gbrpvgrw stdlib_lapack_solve Interface
stdlib_dla_geamv stdlib_lapack_base Interface
stdlib_dla_gercond stdlib_lapack_solve Interface
stdlib_dla_gerpvgrw stdlib_lapack_others Interface
stdlib_dla_lin_berr stdlib_lapack_solve Interface
stdlib_dla_porcond stdlib_lapack_solve Interface
stdlib_dla_porpvgrw stdlib_lapack_solve Interface
stdlib_dla_syamv stdlib_lapack_others Interface
stdlib_dla_syrcond stdlib_lapack_others Interface
stdlib_dla_syrpvgrw stdlib_lapack_others Interface
stdlib_dla_wwaddw stdlib_lapack_base Interface
stdlib_dlabad stdlib_lapack_base Interface
stdlib_dlabrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dlacn2 stdlib_lapack_solve Interface
stdlib_dlacon stdlib_lapack_solve Interface
stdlib_dlacpy stdlib_lapack_base Interface
stdlib_dladiv stdlib_lapack_base Interface
stdlib_dladiv1 stdlib_lapack_base Interface
stdlib_dladiv2 stdlib_lapack_base Interface
stdlib_dlae2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaebz stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed0 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed4 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed5 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed6 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed7 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed8 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaed9 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaeda stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaein stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaev2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaexc stdlib_lapack_eig_svd_lsq Interface
stdlib_dlag2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlag2s stdlib_lapack_base Interface
stdlib_dlags2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlagtf stdlib_lapack_eig_svd_lsq Interface
stdlib_dlagtm stdlib_lapack_base Interface
stdlib_dlagts stdlib_lapack_eig_svd_lsq Interface
stdlib_dlagv2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlahqr stdlib_lapack_eig_svd_lsq Interface
stdlib_dlahr2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaic1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaisnan stdlib_lapack_base Interface
stdlib_dlaln2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlals0 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlalsa stdlib_lapack_eig_svd_lsq Interface
stdlib_dlalsd stdlib_lapack_eig_svd_lsq Interface
stdlib_dlamc3 stdlib_lapack_base Interface
stdlib_dlamch stdlib_lapack_base Interface
stdlib_dlamrg stdlib_lapack_eig_svd_lsq Interface
stdlib_dlamswlq stdlib_lapack_orthogonal_factors Interface
stdlib_dlamtsqr stdlib_lapack_orthogonal_factors Interface
stdlib_dlaneg stdlib_lapack_eig_svd_lsq Interface
stdlib_dlangb stdlib_lapack_base Interface
stdlib_dlange stdlib_lapack_base Interface
stdlib_dlangt stdlib_lapack_base Interface
stdlib_dlanhs stdlib_lapack_base Interface
stdlib_dlansb stdlib_lapack_base Interface
stdlib_dlansf stdlib_lapack_base Interface
stdlib_dlansp stdlib_lapack_base Interface
stdlib_dlanst stdlib_lapack_base Interface
stdlib_dlansy stdlib_lapack_base Interface
stdlib_dlantb stdlib_lapack_base Interface
stdlib_dlantp stdlib_lapack_base Interface
stdlib_dlantr stdlib_lapack_base Interface
stdlib_dlanv2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaorhr_col_getrfnp stdlib_lapack_orthogonal_factors Interface
stdlib_dlaorhr_col_getrfnp2 stdlib_lapack_orthogonal_factors Interface
stdlib_dlapll stdlib_lapack_eig_svd_lsq Interface
stdlib_dlapmr stdlib_lapack_eig_svd_lsq Interface
stdlib_dlapmt stdlib_lapack_eig_svd_lsq Interface
stdlib_dlapy2 stdlib_lapack_base Interface
stdlib_dlapy3 stdlib_lapack_base Interface
stdlib_dlaqgb stdlib_lapack_solve Interface
stdlib_dlaqge stdlib_lapack_solve Interface
stdlib_dlaqp2 stdlib_lapack_orthogonal_factors Interface
stdlib_dlaqps stdlib_lapack_orthogonal_factors Interface
stdlib_dlaqr0 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqr1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqr2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqr3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqr4 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqr5 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqsb stdlib_lapack_base Interface
stdlib_dlaqsp stdlib_lapack_solve Interface
stdlib_dlaqsy stdlib_lapack_solve Interface
stdlib_dlaqtr stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqz0 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqz1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqz2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqz3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaqz4 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlar1v stdlib_lapack_eig_svd_lsq Interface
stdlib_dlar2v stdlib_lapack_base Interface
stdlib_dlarf stdlib_lapack_base Interface
stdlib_dlarfb stdlib_lapack_base Interface
stdlib_dlarfb_gett stdlib_lapack_orthogonal_factors Interface
stdlib_dlarfg stdlib_lapack_base Interface
stdlib_dlarfgp stdlib_lapack_base Interface
stdlib_dlarft stdlib_lapack_base Interface
stdlib_dlarfx stdlib_lapack_base Interface
stdlib_dlarfy stdlib_lapack_base Interface
stdlib_dlargv stdlib_lapack_base Interface
stdlib_dlarnv stdlib_lapack_base Interface
stdlib_dlarra stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarrb stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarrc stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarre stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarrf stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarrj stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarrk stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarrr stdlib_lapack_eig_svd_lsq Interface
stdlib_dlarrv stdlib_lapack_eig_svd_lsq Interface
stdlib_dlartg stdlib_lapack_base Interface
stdlib_dlartgp stdlib_lapack_base Interface
stdlib_dlartgs stdlib_lapack_eig_svd_lsq Interface
stdlib_dlartv stdlib_lapack_base Interface
stdlib_dlaruv stdlib_lapack_base Interface
stdlib_dlarz stdlib_lapack_orthogonal_factors Interface
stdlib_dlarzb stdlib_lapack_orthogonal_factors Interface
stdlib_dlarzt stdlib_lapack_orthogonal_factors Interface
stdlib_dlas2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlascl stdlib_lapack_base Interface
stdlib_dlasd0 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasd1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasd3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasd4 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasd5 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasd6 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasd7 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasd8 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasda stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasdq stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasdt stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaset stdlib_lapack_base Interface
stdlib_dlasq1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasq2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasq3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasq4 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasq5 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasq6 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasr stdlib_lapack_base Interface
stdlib_dlasrt stdlib_lapack_base Interface
stdlib_dlassq stdlib_lapack_base Interface
stdlib_dlasv2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlaswlq stdlib_lapack_orthogonal_factors Interface
stdlib_dlaswp stdlib_lapack_solve Interface
stdlib_dlasy2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dlasyf stdlib_lapack_solve Interface
stdlib_dlasyf_aa stdlib_lapack_solve Interface
stdlib_dlasyf_rk stdlib_lapack_solve Interface
stdlib_dlasyf_rook stdlib_lapack_solve Interface
stdlib_dlat2s stdlib_lapack_base Interface
stdlib_dlatbs stdlib_lapack_solve Interface
stdlib_dlatdf stdlib_lapack_solve Interface
stdlib_dlatps stdlib_lapack_solve Interface
stdlib_dlatrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dlatrs stdlib_lapack_solve Interface
stdlib_dlatrz stdlib_lapack_orthogonal_factors Interface
stdlib_dlatsqr stdlib_lapack_orthogonal_factors Interface
stdlib_dlauu2 stdlib_lapack_solve Interface
stdlib_dlauum stdlib_lapack_solve Interface
stdlib_dnrm2 stdlib_blas Interface
stdlib_dopgtr stdlib_lapack_eig_svd_lsq Interface
stdlib_dopmtr stdlib_lapack_eig_svd_lsq Interface
stdlib_dorbdb stdlib_lapack_eig_svd_lsq Interface
stdlib_dorbdb1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dorbdb2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dorbdb3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dorbdb4 stdlib_lapack_eig_svd_lsq Interface
stdlib_dorbdb5 stdlib_lapack_eig_svd_lsq Interface
stdlib_dorbdb6 stdlib_lapack_eig_svd_lsq Interface
stdlib_dorcsd stdlib_lapack_eig_svd_lsq Interface
stdlib_dorcsd2by1 stdlib_lapack_eig_svd_lsq Interface
stdlib_dorg2l stdlib_lapack_orthogonal_factors Interface
stdlib_dorg2r stdlib_lapack_orthogonal_factors Interface
stdlib_dorgbr stdlib_lapack_eig_svd_lsq Interface
stdlib_dorghr stdlib_lapack_eig_svd_lsq Interface
stdlib_dorgl2 stdlib_lapack_orthogonal_factors Interface
stdlib_dorglq stdlib_lapack_orthogonal_factors Interface
stdlib_dorgql stdlib_lapack_orthogonal_factors Interface
stdlib_dorgqr stdlib_lapack_orthogonal_factors Interface
stdlib_dorgr2 stdlib_lapack_orthogonal_factors Interface
stdlib_dorgrq stdlib_lapack_orthogonal_factors Interface
stdlib_dorgtr stdlib_lapack_eig_svd_lsq Interface
stdlib_dorgtsqr stdlib_lapack_orthogonal_factors Interface
stdlib_dorgtsqr_row stdlib_lapack_orthogonal_factors Interface
stdlib_dorhr_col stdlib_lapack_orthogonal_factors Interface
stdlib_dorm22 stdlib_lapack_eig_svd_lsq Interface
stdlib_dorm2l stdlib_lapack_orthogonal_factors Interface
stdlib_dorm2r stdlib_lapack_orthogonal_factors Interface
stdlib_dormbr stdlib_lapack_eig_svd_lsq Interface
stdlib_dormhr stdlib_lapack_eig_svd_lsq Interface
stdlib_dorml2 stdlib_lapack_orthogonal_factors Interface
stdlib_dormlq stdlib_lapack_orthogonal_factors Interface
stdlib_dormql stdlib_lapack_orthogonal_factors Interface
stdlib_dormqr stdlib_lapack_orthogonal_factors Interface
stdlib_dormr2 stdlib_lapack_orthogonal_factors Interface
stdlib_dormr3 stdlib_lapack_orthogonal_factors Interface
stdlib_dormrq stdlib_lapack_orthogonal_factors Interface
stdlib_dormrz stdlib_lapack_orthogonal_factors Interface
stdlib_dormtr stdlib_lapack_eig_svd_lsq Interface
stdlib_dpbcon stdlib_lapack_solve Interface
stdlib_dpbequ stdlib_lapack_solve Interface
stdlib_dpbrfs stdlib_lapack_solve Interface
stdlib_dpbstf stdlib_lapack_eig_svd_lsq Interface
stdlib_dpbsv stdlib_lapack_solve Interface
stdlib_dpbsvx stdlib_lapack_solve Interface
stdlib_dpbtf2 stdlib_lapack_solve Interface
stdlib_dpbtrf stdlib_lapack_solve Interface
stdlib_dpbtrs stdlib_lapack_solve Interface
stdlib_dpftrf stdlib_lapack_solve Interface
stdlib_dpftri stdlib_lapack_solve Interface
stdlib_dpftrs stdlib_lapack_solve Interface
stdlib_dpocon stdlib_lapack_solve Interface
stdlib_dpoequ stdlib_lapack_solve Interface
stdlib_dpoequb stdlib_lapack_solve Interface
stdlib_dporfs stdlib_lapack_solve Interface
stdlib_dposv stdlib_lapack_solve Interface
stdlib_dposvx stdlib_lapack_solve Interface
stdlib_dpotf2 stdlib_lapack_solve Interface
stdlib_dpotrf stdlib_lapack_solve Interface
stdlib_dpotrf2 stdlib_lapack_solve Interface
stdlib_dpotri stdlib_lapack_solve Interface
stdlib_dpotrs stdlib_lapack_solve Interface
stdlib_dppcon stdlib_lapack_solve Interface
stdlib_dppequ stdlib_lapack_solve Interface
stdlib_dpprfs stdlib_lapack_solve Interface
stdlib_dppsv stdlib_lapack_solve Interface
stdlib_dppsvx stdlib_lapack_solve Interface
stdlib_dpptrf stdlib_lapack_solve Interface
stdlib_dpptri stdlib_lapack_solve Interface
stdlib_dpptrs stdlib_lapack_solve Interface
stdlib_dpstf2 stdlib_lapack_solve Interface
stdlib_dpstrf stdlib_lapack_solve Interface
stdlib_dptcon stdlib_lapack_solve Interface
stdlib_dpteqr stdlib_lapack_eig_svd_lsq Interface
stdlib_dptrfs stdlib_lapack_solve Interface
stdlib_dptsv stdlib_lapack_solve Interface
stdlib_dptsvx stdlib_lapack_solve Interface
stdlib_dpttrf stdlib_lapack_solve Interface
stdlib_dpttrs stdlib_lapack_solve Interface
stdlib_dptts2 stdlib_lapack_solve Interface
stdlib_drot stdlib_blas Interface
stdlib_drotg stdlib_blas Interface
stdlib_drotm stdlib_blas Interface
stdlib_drotmg stdlib_blas Interface
stdlib_droundup_lwork stdlib_linalg_lapack_aux Function

ROUNDUP_LWORK >= LWORK. ROUNDUP_LWORK is guaranteed to have zero decimal part.

stdlib_drscl stdlib_lapack_base Interface
stdlib_dsb2st_kernels stdlib_lapack_eig_svd_lsq Interface
stdlib_dsbev stdlib_lapack_eig_svd_lsq Interface
stdlib_dsbevd stdlib_lapack_eig_svd_lsq Interface
stdlib_dsbevx stdlib_lapack_eig_svd_lsq Interface
stdlib_dsbgst stdlib_lapack_eig_svd_lsq Interface
stdlib_dsbgv stdlib_lapack_eig_svd_lsq Interface
stdlib_dsbgvd stdlib_lapack_eig_svd_lsq Interface
stdlib_dsbgvx stdlib_lapack_eig_svd_lsq Interface
stdlib_dsbmv stdlib_blas Interface
stdlib_dsbtrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dscal stdlib_blas Interface
stdlib_dsdot stdlib_blas Interface
stdlib_dsfrk stdlib_lapack_base Interface
stdlib_dspcon stdlib_lapack_solve Interface
stdlib_dspev stdlib_lapack_eig_svd_lsq Interface
stdlib_dspevd stdlib_lapack_eig_svd_lsq Interface
stdlib_dspevx stdlib_lapack_eig_svd_lsq Interface
stdlib_dspgst stdlib_lapack_eig_svd_lsq Interface
stdlib_dspgv stdlib_lapack_eig_svd_lsq Interface
stdlib_dspgvd stdlib_lapack_eig_svd_lsq Interface
stdlib_dspgvx stdlib_lapack_eig_svd_lsq Interface
stdlib_dspmv stdlib_blas Interface
stdlib_dspr stdlib_blas Interface
stdlib_dspr2 stdlib_blas Interface
stdlib_dsprfs stdlib_lapack_solve Interface
stdlib_dspsv stdlib_lapack_solve Interface
stdlib_dspsvx stdlib_lapack_solve Interface
stdlib_dsptrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dsptrf stdlib_lapack_solve Interface
stdlib_dsptri stdlib_lapack_solve Interface
stdlib_dsptrs stdlib_lapack_solve Interface
stdlib_dstebz stdlib_lapack_eig_svd_lsq Interface
stdlib_dstedc stdlib_lapack_eig_svd_lsq Interface
stdlib_dstegr stdlib_lapack_eig_svd_lsq Interface
stdlib_dstein stdlib_lapack_eig_svd_lsq Interface
stdlib_dstemr stdlib_lapack_eig_svd_lsq Interface
stdlib_dsteqr stdlib_lapack_eig_svd_lsq Interface
stdlib_dsterf stdlib_lapack_eig_svd_lsq Interface
stdlib_dstev stdlib_lapack_eig_svd_lsq Interface
stdlib_dstevd stdlib_lapack_eig_svd_lsq Interface
stdlib_dstevr stdlib_lapack_eig_svd_lsq Interface
stdlib_dstevx stdlib_lapack_eig_svd_lsq Interface
stdlib_dswap stdlib_blas Interface
stdlib_dsycon stdlib_lapack_solve Interface
stdlib_dsycon_rook stdlib_lapack_solve Interface
stdlib_dsyconv stdlib_lapack_solve Interface
stdlib_dsyconvf stdlib_lapack_solve Interface
stdlib_dsyconvf_rook stdlib_lapack_solve Interface
stdlib_dsyequb stdlib_lapack_solve Interface
stdlib_dsyev stdlib_lapack_eig_svd_lsq Interface
stdlib_dsyevd stdlib_lapack_eig_svd_lsq Interface
stdlib_dsyevr stdlib_lapack_eig_svd_lsq Interface
stdlib_dsyevx stdlib_lapack_eig_svd_lsq Interface
stdlib_dsygs2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dsygst stdlib_lapack_eig_svd_lsq Interface
stdlib_dsygv stdlib_lapack_eig_svd_lsq Interface
stdlib_dsygvd stdlib_lapack_eig_svd_lsq Interface
stdlib_dsygvx stdlib_lapack_eig_svd_lsq Interface
stdlib_dsymm stdlib_blas Interface
stdlib_dsymv stdlib_blas Interface
stdlib_dsyr stdlib_blas Interface
stdlib_dsyr2 stdlib_blas Interface
stdlib_dsyr2k stdlib_blas Interface
stdlib_dsyrfs stdlib_lapack_solve Interface
stdlib_dsyrk stdlib_blas Interface
stdlib_dsysv stdlib_lapack_solve Interface
stdlib_dsysv_aa stdlib_lapack_solve Interface
stdlib_dsysv_rk stdlib_lapack_solve Interface
stdlib_dsysv_rook stdlib_lapack_solve Interface
stdlib_dsysvx stdlib_lapack_solve Interface
stdlib_dsyswapr stdlib_lapack_solve Interface
stdlib_dsytd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dsytf2 stdlib_lapack_solve Interface
stdlib_dsytf2_rk stdlib_lapack_solve Interface
stdlib_dsytf2_rook stdlib_lapack_solve Interface
stdlib_dsytrd stdlib_lapack_eig_svd_lsq Interface
stdlib_dsytrd_sb2st stdlib_lapack_eig_svd_lsq Interface
stdlib_dsytrd_sy2sb stdlib_lapack_eig_svd_lsq Interface
stdlib_dsytrf stdlib_lapack_solve Interface
stdlib_dsytrf_aa stdlib_lapack_solve Interface
stdlib_dsytrf_rk stdlib_lapack_solve Interface
stdlib_dsytrf_rook stdlib_lapack_solve Interface
stdlib_dsytri stdlib_lapack_solve Interface
stdlib_dsytri_rook stdlib_lapack_solve Interface
stdlib_dsytrs stdlib_lapack_solve Interface
stdlib_dsytrs2 stdlib_lapack_solve Interface
stdlib_dsytrs_3 stdlib_lapack_solve Interface
stdlib_dsytrs_aa stdlib_lapack_solve Interface
stdlib_dsytrs_rook stdlib_lapack_solve Interface
stdlib_dtbcon stdlib_lapack_solve Interface
stdlib_dtbmv stdlib_blas Interface
stdlib_dtbrfs stdlib_lapack_solve Interface
stdlib_dtbsv stdlib_blas Interface
stdlib_dtbtrs stdlib_lapack_solve Interface
stdlib_dtfsm stdlib_lapack_base Interface
stdlib_dtftri stdlib_lapack_solve Interface
stdlib_dtfttp stdlib_lapack_base Interface
stdlib_dtfttr stdlib_lapack_base Interface
stdlib_dtgevc stdlib_lapack_eig_svd_lsq Interface
stdlib_dtgex2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dtgexc stdlib_lapack_eig_svd_lsq Interface
stdlib_dtgsen stdlib_lapack_eig_svd_lsq Interface
stdlib_dtgsja stdlib_lapack_eig_svd_lsq Interface
stdlib_dtgsna stdlib_lapack_eig_svd_lsq Interface
stdlib_dtgsy2 stdlib_lapack_eig_svd_lsq Interface
stdlib_dtgsyl stdlib_lapack_eig_svd_lsq Interface
stdlib_dtpcon stdlib_lapack_solve Interface
stdlib_dtplqt stdlib_lapack_orthogonal_factors Interface
stdlib_dtplqt2 stdlib_lapack_orthogonal_factors Interface
stdlib_dtpmlqt stdlib_lapack_orthogonal_factors Interface
stdlib_dtpmqrt stdlib_lapack_orthogonal_factors Interface
stdlib_dtpmv stdlib_blas Interface
stdlib_dtpqrt stdlib_lapack_orthogonal_factors Interface
stdlib_dtpqrt2 stdlib_lapack_orthogonal_factors Interface
stdlib_dtprfb stdlib_lapack_orthogonal_factors Interface
stdlib_dtprfs stdlib_lapack_solve Interface
stdlib_dtpsv stdlib_blas Interface
stdlib_dtptri stdlib_lapack_solve Interface
stdlib_dtptrs stdlib_lapack_solve Interface
stdlib_dtpttf stdlib_lapack_base Interface
stdlib_dtpttr stdlib_lapack_base Interface
stdlib_dtrcon stdlib_lapack_solve Interface
stdlib_dtrevc stdlib_lapack_eig_svd_lsq Interface
stdlib_dtrevc3 stdlib_lapack_eig_svd_lsq Interface
stdlib_dtrexc stdlib_lapack_eig_svd_lsq Interface
stdlib_dtrmm stdlib_blas Interface
stdlib_dtrmv stdlib_blas Interface
stdlib_dtrrfs stdlib_lapack_solve Interface
stdlib_dtrsen stdlib_lapack_eig_svd_lsq Interface
stdlib_dtrsm stdlib_blas Interface
stdlib_dtrsna stdlib_lapack_eig_svd_lsq Interface
stdlib_dtrsv stdlib_blas Interface
stdlib_dtrsyl stdlib_lapack_eig_svd_lsq Interface
stdlib_dtrti2 stdlib_lapack_solve Interface
stdlib_dtrtri stdlib_lapack_solve Interface
stdlib_dtrtrs stdlib_lapack_solve Interface
stdlib_dtrttf stdlib_lapack_base Interface
stdlib_dtrttp stdlib_lapack_base Interface
stdlib_dtzrzf stdlib_lapack_orthogonal_factors Interface
stdlib_dzasum stdlib_blas Interface
stdlib_dznrm2 stdlib_blas Interface
stdlib_dzsum1 stdlib_lapack_base Interface
stdlib_icamax stdlib_linalg_blas_aux Function
stdlib_icmax1 stdlib_linalg_lapack_aux Function

IMAX1: finds the index of the first vector element of maximum absolute value. Based on IAMAX from Level 1 BLAS. The change is to use the 'genuine' absolute value.

stdlib_idamax stdlib_linalg_blas_aux Function
stdlib_ieeeck stdlib_linalg_lapack_aux Function

IEEECK is called from the ILAENV to verify that Infinity and possibly NaN arithmetic is safe (i.e. will not trap).

stdlib_ilaclc stdlib_linalg_lapack_aux Function
stdlib_ilaclr stdlib_linalg_lapack_aux Function
stdlib_iladiag stdlib_linalg_lapack_aux Function

This subroutine translated from a character string specifying if a matrix has unit diagonal or not to the relevant BLAST-specified integer constant. ILADIAG returns an INTEGER. If ILADIAG: < 0, then the input is not a character indicating a unit or non-unit diagonal. Otherwise ILADIAG returns the constant value corresponding to DIAG.

stdlib_iladlc stdlib_linalg_lapack_aux Function
stdlib_iladlr stdlib_linalg_lapack_aux Function
stdlib_ilaenv stdlib_linalg_lapack_aux Function

ILAENV is called from the LAPACK routines to choose problem-dependent parameters for the local environment. See ISPEC for a description of the parameters. ILAENV returns an INTEGER if ILAENV >= 0: ILAENV returns the value of the parameter specified by ISPEC if ILAENV < 0: if ILAENV = -k, the k-th argument had an illegal value. This version provides a set of parameters which should give good, but not optimal, performance on many of the currently available computers. Users are encouraged to modify this subroutine to set the tuning parameters for their particular machine using the option and problem size information in the arguments. This routine will not function correctly if it is converted to all lower case. Converting it to all upper case is allowed.

stdlib_ilaenv2stage stdlib_linalg_lapack_aux Function

ILAENV2STAGE is called from the LAPACK routines to choose problem-dependent parameters for the local environment. See ISPEC for a description of the parameters. It sets problem and machine dependent parameters useful for *_2STAGE and related subroutines. ILAENV2STAGE returns an INTEGER if ILAENV2STAGE >= 0: ILAENV2STAGE returns the value of the parameter specified by ISPEC if ILAENV2STAGE < 0: if ILAENV2STAGE = -k, the k-th argument had an illegal value. This version provides a set of parameters which should give good, but not optimal, performance on many of the currently available computers for the 2-stage solvers. Users are encouraged to modify this subroutine to set the tuning parameters for their particular machine using the option and problem size information in the arguments. This routine will not function correctly if it is converted to all lower case. Converting it to all upper case is allowed.

stdlib_ilaprec stdlib_linalg_lapack_aux Function

This subroutine translated from a character string specifying an intermediate precision to the relevant BLAST-specified integer constant. ILAPREC returns an INTEGER. If ILAPREC: < 0, then the input is not a character indicating a supported intermediate precision. Otherwise ILAPREC returns the constant value corresponding to PREC.

stdlib_ilaslc stdlib_linalg_lapack_aux Function
stdlib_ilaslr stdlib_linalg_lapack_aux Function
stdlib_ilatrans stdlib_linalg_lapack_aux Function

This subroutine translates from a character string specifying a transposition operation to the relevant BLAST-specified integer constant. ILATRANS returns an INTEGER. If ILATRANS: < 0, then the input is not a character indicating a transposition operator. Otherwise ILATRANS returns the constant value corresponding to TRANS.

stdlib_ilauplo stdlib_linalg_lapack_aux Function

This subroutine translated from a character string specifying a upper- or lower-triangular matrix to the relevant BLAST-specified integer constant. ILAUPLO returns an INTEGER. If ILAUPLO: < 0, then the input is not a character indicating an upper- or lower-triangular matrix. Otherwise ILAUPLO returns the constant value corresponding to UPLO.

stdlib_ilazlc stdlib_linalg_lapack_aux Function
stdlib_ilazlr stdlib_linalg_lapack_aux Function
stdlib_iparam2stage stdlib_linalg_lapack_aux Function

This program sets problem and machine dependent parameters useful for xHETRD_2STAGE, xHETRD_HE2HB, xHETRD_HB2ST, xGEBRD_2STAGE, xGEBRD_GE2GB, xGEBRD_GB2BD and related subroutines for eigenvalue problems. It is called whenever ILAENV is called with 17 <= ISPEC <= 21. It is called whenever ILAENV2STAGE is called with 1 <= ISPEC <= 5 with a direct conversion ISPEC + 16.

stdlib_iparmq stdlib_linalg_lapack_aux Function

This program sets problem and machine dependent parameters useful for xHSEQR and related subroutines for eigenvalue problems. It is called whenever IPARMQ is called with 12 <= ISPEC <= 16

stdlib_isamax stdlib_linalg_blas_aux Function
stdlib_izamax stdlib_linalg_blas_aux Function
stdlib_izmax1 stdlib_linalg_lapack_aux Function

IMAX1: finds the index of the first vector element of maximum absolute value. Based on IAMAX from Level 1 BLAS. The change is to use the 'genuine' absolute value.

stdlib_lsame stdlib_linalg_blas_aux Function

LSAME returns .TRUE. if CA is the same letter as CB regardless of case.

stdlib_lsamen stdlib_linalg_lapack_aux Function

LSAMEN tests if the first N letters of CA are the same as the first N letters of CB, regardless of case. LSAMEN returns .TRUE. if CA and CB are equivalent except for case and .FALSE. otherwise. LSAMEN also returns .FALSE. if LEN( CA ) or LEN( CB ) is less than N.

stdlib_sasum stdlib_blas Interface
stdlib_saxpy stdlib_blas Interface
stdlib_sbbcsd stdlib_lapack_eig_svd_lsq Interface
stdlib_sbdsdc stdlib_lapack_eig_svd_lsq Interface
stdlib_sbdsqr stdlib_lapack_eig_svd_lsq Interface
stdlib_scasum stdlib_blas Interface
stdlib_scnrm2 stdlib_blas Interface
stdlib_scopy stdlib_blas Interface
stdlib_scsum1 stdlib_lapack_base Interface
stdlib_sdisna stdlib_lapack_eig_svd_lsq Interface
stdlib_sdot stdlib_blas Interface
stdlib_sgbbrd stdlib_lapack_eig_svd_lsq Interface
stdlib_sgbcon stdlib_lapack_solve Interface
stdlib_sgbequ stdlib_lapack_solve Interface
stdlib_sgbequb stdlib_lapack_solve Interface
stdlib_sgbmv stdlib_blas Interface
stdlib_sgbrfs stdlib_lapack_solve Interface
stdlib_sgbsv stdlib_lapack_solve Interface
stdlib_sgbsvx stdlib_lapack_solve Interface
stdlib_sgbtf2 stdlib_lapack_solve Interface
stdlib_sgbtrf stdlib_lapack_solve Interface
stdlib_sgbtrs stdlib_lapack_solve Interface
stdlib_sgebak stdlib_lapack_eig_svd_lsq Interface
stdlib_sgebal stdlib_lapack_eig_svd_lsq Interface
stdlib_sgebd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_sgebrd stdlib_lapack_eig_svd_lsq Interface
stdlib_sgecon stdlib_lapack_solve Interface
stdlib_sgeequ stdlib_lapack_solve Interface
stdlib_sgeequb stdlib_lapack_solve Interface
stdlib_sgees stdlib_lapack_eig_svd_lsq Interface
stdlib_sgeesx stdlib_lapack_eig_svd_lsq Interface
stdlib_sgeev stdlib_lapack_eig_svd_lsq Interface
stdlib_sgeevx stdlib_lapack_eig_svd_lsq Interface
stdlib_sgehd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_sgehrd stdlib_lapack_eig_svd_lsq Interface
stdlib_sgejsv stdlib_lapack_eig_svd_lsq Interface
stdlib_sgelq stdlib_lapack_orthogonal_factors Interface
stdlib_sgelq2 stdlib_lapack_orthogonal_factors Interface
stdlib_sgelqf stdlib_lapack_orthogonal_factors Interface
stdlib_sgelqt stdlib_lapack_orthogonal_factors Interface
stdlib_sgelqt3 stdlib_lapack_orthogonal_factors Interface
stdlib_sgels stdlib_lapack_eig_svd_lsq Interface
stdlib_sgelsd stdlib_lapack_eig_svd_lsq Interface
stdlib_sgelss stdlib_lapack_eig_svd_lsq Interface
stdlib_sgelsy stdlib_lapack_eig_svd_lsq Interface
stdlib_sgemlq stdlib_lapack_orthogonal_factors Interface
stdlib_sgemlqt stdlib_lapack_orthogonal_factors Interface
stdlib_sgemm stdlib_blas Interface
stdlib_sgemqr stdlib_lapack_orthogonal_factors Interface
stdlib_sgemqrt stdlib_lapack_orthogonal_factors Interface
stdlib_sgemv stdlib_blas Interface
stdlib_sgeql2 stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqlf stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqp3 stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqr stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqr2 stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqr2p stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqrf stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqrfp stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqrt stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqrt2 stdlib_lapack_orthogonal_factors Interface
stdlib_sgeqrt3 stdlib_lapack_orthogonal_factors Interface
stdlib_sger stdlib_blas Interface
stdlib_sgerfs stdlib_lapack_solve Interface
stdlib_sgerq2 stdlib_lapack_orthogonal_factors Interface
stdlib_sgerqf stdlib_lapack_orthogonal_factors Interface
stdlib_sgesc2 stdlib_lapack_solve Interface
stdlib_sgesdd stdlib_lapack_eig_svd_lsq Interface
stdlib_sgesv stdlib_lapack_solve Interface
stdlib_sgesvd stdlib_lapack_eig_svd_lsq Interface
stdlib_sgesvdq stdlib_lapack_eig_svd_lsq Interface
stdlib_sgesvj stdlib_lapack_eig_svd_lsq Interface
stdlib_sgesvx stdlib_lapack_solve Interface
stdlib_sgetc2 stdlib_lapack_solve Interface
stdlib_sgetf2 stdlib_lapack_solve Interface
stdlib_sgetrf stdlib_lapack_solve Interface
stdlib_sgetrf2 stdlib_lapack_solve Interface
stdlib_sgetri stdlib_lapack_solve Interface
stdlib_sgetrs stdlib_lapack_solve Interface
stdlib_sgetsls stdlib_lapack_eig_svd_lsq Interface
stdlib_sgetsqrhrt stdlib_lapack_orthogonal_factors Interface
stdlib_sggbak stdlib_lapack_eig_svd_lsq Interface
stdlib_sggbal stdlib_lapack_eig_svd_lsq Interface
stdlib_sgges stdlib_lapack_eig_svd_lsq Interface
stdlib_sgges3 stdlib_lapack_eig_svd_lsq Interface
stdlib_sggesx stdlib_lapack_eig_svd_lsq Interface
stdlib_sggev stdlib_lapack_eig_svd_lsq Interface
stdlib_sggev3 stdlib_lapack_eig_svd_lsq Interface
stdlib_sggevx stdlib_lapack_eig_svd_lsq Interface
stdlib_sggglm stdlib_lapack_eig_svd_lsq Interface
stdlib_sgghd3 stdlib_lapack_eig_svd_lsq Interface
stdlib_sgghrd stdlib_lapack_eig_svd_lsq Interface
stdlib_sgglse stdlib_lapack_eig_svd_lsq Interface
stdlib_sggqrf stdlib_lapack_orthogonal_factors Interface
stdlib_sggrqf stdlib_lapack_orthogonal_factors Interface
stdlib_sgsvj0 stdlib_lapack_eig_svd_lsq Interface
stdlib_sgsvj1 stdlib_lapack_eig_svd_lsq Interface
stdlib_sgtcon stdlib_lapack_solve Interface
stdlib_sgtrfs stdlib_lapack_solve Interface
stdlib_sgtsv stdlib_lapack_solve Interface
stdlib_sgtsvx stdlib_lapack_solve Interface
stdlib_sgttrf stdlib_lapack_solve Interface
stdlib_sgttrs stdlib_lapack_solve Interface
stdlib_sgtts2 stdlib_lapack_solve Interface
stdlib_shgeqz stdlib_lapack_eig_svd_lsq Interface
stdlib_shsein stdlib_lapack_eig_svd_lsq Interface
stdlib_shseqr stdlib_lapack_eig_svd_lsq Interface
stdlib_sisnan stdlib_lapack_base Interface
stdlib_sla_gbamv stdlib_lapack_base Interface
stdlib_sla_gbrcond stdlib_lapack_solve Interface
stdlib_sla_gbrpvgrw stdlib_lapack_solve Interface
stdlib_sla_geamv stdlib_lapack_base Interface
stdlib_sla_gercond stdlib_lapack_solve Interface
stdlib_sla_gerpvgrw stdlib_lapack_others Interface
stdlib_sla_lin_berr stdlib_lapack_solve Interface
stdlib_sla_porcond stdlib_lapack_solve Interface
stdlib_sla_porpvgrw stdlib_lapack_solve Interface
stdlib_sla_syamv stdlib_lapack_others Interface
stdlib_sla_syrcond stdlib_lapack_others Interface
stdlib_sla_syrpvgrw stdlib_lapack_others Interface
stdlib_sla_wwaddw stdlib_lapack_base Interface
stdlib_slabad stdlib_lapack_base Interface
stdlib_slabrd stdlib_lapack_eig_svd_lsq Interface
stdlib_slacn2 stdlib_lapack_solve Interface
stdlib_slacon stdlib_lapack_solve Interface
stdlib_slacpy stdlib_lapack_base Interface
stdlib_sladiv stdlib_lapack_base Interface
stdlib_sladiv1 stdlib_lapack_base Interface
stdlib_sladiv2 stdlib_lapack_base Interface
stdlib_slae2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaebz stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed0 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed1 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed3 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed4 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed5 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed6 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed7 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed8 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaed9 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaeda stdlib_lapack_eig_svd_lsq Interface
stdlib_slaein stdlib_lapack_eig_svd_lsq Interface
stdlib_slaev2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaexc stdlib_lapack_eig_svd_lsq Interface
stdlib_slag2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slag2d stdlib_lapack_base Interface
stdlib_slags2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slagtf stdlib_lapack_eig_svd_lsq Interface
stdlib_slagtm stdlib_lapack_base Interface
stdlib_slagts stdlib_lapack_eig_svd_lsq Interface
stdlib_slagv2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slahqr stdlib_lapack_eig_svd_lsq Interface
stdlib_slahr2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaic1 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaisnan stdlib_lapack_base Interface
stdlib_slaln2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slals0 stdlib_lapack_eig_svd_lsq Interface
stdlib_slalsa stdlib_lapack_eig_svd_lsq Interface
stdlib_slalsd stdlib_lapack_eig_svd_lsq Interface
stdlib_slamc3 stdlib_lapack_base Interface
stdlib_slamch stdlib_lapack_base Interface
stdlib_slamrg stdlib_lapack_eig_svd_lsq Interface
stdlib_slamswlq stdlib_lapack_orthogonal_factors Interface
stdlib_slamtsqr stdlib_lapack_orthogonal_factors Interface
stdlib_slaneg stdlib_lapack_eig_svd_lsq Interface
stdlib_slangb stdlib_lapack_base Interface
stdlib_slange stdlib_lapack_base Interface
stdlib_slangt stdlib_lapack_base Interface
stdlib_slanhs stdlib_lapack_base Interface
stdlib_slansb stdlib_lapack_base Interface
stdlib_slansf stdlib_lapack_base Interface
stdlib_slansp stdlib_lapack_base Interface
stdlib_slanst stdlib_lapack_base Interface
stdlib_slansy stdlib_lapack_base Interface
stdlib_slantb stdlib_lapack_base Interface
stdlib_slantp stdlib_lapack_base Interface
stdlib_slantr stdlib_lapack_base Interface
stdlib_slanv2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaorhr_col_getrfnp stdlib_lapack_orthogonal_factors Interface
stdlib_slaorhr_col_getrfnp2 stdlib_lapack_orthogonal_factors Interface
stdlib_slapll stdlib_lapack_eig_svd_lsq Interface
stdlib_slapmr stdlib_lapack_eig_svd_lsq Interface
stdlib_slapmt stdlib_lapack_eig_svd_lsq Interface
stdlib_slapy2 stdlib_lapack_base Interface
stdlib_slapy3 stdlib_lapack_base Interface
stdlib_slaqgb stdlib_lapack_solve Interface
stdlib_slaqge stdlib_lapack_solve Interface
stdlib_slaqp2 stdlib_lapack_orthogonal_factors Interface
stdlib_slaqps stdlib_lapack_orthogonal_factors Interface
stdlib_slaqr0 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqr1 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqr2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqr3 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqr4 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqr5 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqsb stdlib_lapack_base Interface
stdlib_slaqsp stdlib_lapack_solve Interface
stdlib_slaqsy stdlib_lapack_solve Interface
stdlib_slaqtr stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqz0 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqz1 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqz2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqz3 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaqz4 stdlib_lapack_eig_svd_lsq Interface
stdlib_slar1v stdlib_lapack_eig_svd_lsq Interface
stdlib_slar2v stdlib_lapack_base Interface
stdlib_slarf stdlib_lapack_base Interface
stdlib_slarfb stdlib_lapack_base Interface
stdlib_slarfb_gett stdlib_lapack_orthogonal_factors Interface
stdlib_slarfg stdlib_lapack_base Interface
stdlib_slarfgp stdlib_lapack_base Interface
stdlib_slarft stdlib_lapack_base Interface
stdlib_slarfx stdlib_lapack_base Interface
stdlib_slarfy stdlib_lapack_base Interface
stdlib_slargv stdlib_lapack_base Interface
stdlib_slarnv stdlib_lapack_base Interface
stdlib_slarra stdlib_lapack_eig_svd_lsq Interface
stdlib_slarrb stdlib_lapack_eig_svd_lsq Interface
stdlib_slarrc stdlib_lapack_eig_svd_lsq Interface
stdlib_slarrd stdlib_lapack_eig_svd_lsq Interface
stdlib_slarre stdlib_lapack_eig_svd_lsq Interface
stdlib_slarrf stdlib_lapack_eig_svd_lsq Interface
stdlib_slarrj stdlib_lapack_eig_svd_lsq Interface
stdlib_slarrk stdlib_lapack_eig_svd_lsq Interface
stdlib_slarrr stdlib_lapack_eig_svd_lsq Interface
stdlib_slarrv stdlib_lapack_eig_svd_lsq Interface
stdlib_slartg stdlib_lapack_base Interface
stdlib_slartgp stdlib_lapack_base Interface
stdlib_slartgs stdlib_lapack_eig_svd_lsq Interface
stdlib_slartv stdlib_lapack_base Interface
stdlib_slaruv stdlib_lapack_base Interface
stdlib_slarz stdlib_lapack_orthogonal_factors Interface
stdlib_slarzb stdlib_lapack_orthogonal_factors Interface
stdlib_slarzt stdlib_lapack_orthogonal_factors Interface
stdlib_slas2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slascl stdlib_lapack_base Interface
stdlib_slasd0 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasd1 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasd3 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasd4 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasd5 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasd6 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasd7 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasd8 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasda stdlib_lapack_eig_svd_lsq Interface
stdlib_slasdq stdlib_lapack_eig_svd_lsq Interface
stdlib_slasdt stdlib_lapack_eig_svd_lsq Interface
stdlib_slaset stdlib_lapack_base Interface
stdlib_slasq1 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasq2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasq3 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasq4 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasq5 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasq6 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasr stdlib_lapack_base Interface
stdlib_slasrt stdlib_lapack_base Interface
stdlib_slassq stdlib_lapack_base Interface
stdlib_slasv2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slaswlq stdlib_lapack_orthogonal_factors Interface
stdlib_slaswp stdlib_lapack_solve Interface
stdlib_slasy2 stdlib_lapack_eig_svd_lsq Interface
stdlib_slasyf stdlib_lapack_solve Interface
stdlib_slasyf_aa stdlib_lapack_solve Interface
stdlib_slasyf_rk stdlib_lapack_solve Interface
stdlib_slasyf_rook stdlib_lapack_solve Interface
stdlib_slatbs stdlib_lapack_solve Interface
stdlib_slatdf stdlib_lapack_solve Interface
stdlib_slatps stdlib_lapack_solve Interface
stdlib_slatrd stdlib_lapack_eig_svd_lsq Interface
stdlib_slatrs stdlib_lapack_solve Interface
stdlib_slatrz stdlib_lapack_orthogonal_factors Interface
stdlib_slatsqr stdlib_lapack_orthogonal_factors Interface
stdlib_slauu2 stdlib_lapack_solve Interface
stdlib_slauum stdlib_lapack_solve Interface
stdlib_snrm2 stdlib_blas Interface
stdlib_sopgtr stdlib_lapack_eig_svd_lsq Interface
stdlib_sopmtr stdlib_lapack_eig_svd_lsq Interface
stdlib_sorbdb stdlib_lapack_eig_svd_lsq Interface
stdlib_sorbdb1 stdlib_lapack_eig_svd_lsq Interface
stdlib_sorbdb2 stdlib_lapack_eig_svd_lsq Interface
stdlib_sorbdb3 stdlib_lapack_eig_svd_lsq Interface
stdlib_sorbdb4 stdlib_lapack_eig_svd_lsq Interface
stdlib_sorbdb5 stdlib_lapack_eig_svd_lsq Interface
stdlib_sorbdb6 stdlib_lapack_eig_svd_lsq Interface
stdlib_sorcsd stdlib_lapack_eig_svd_lsq Interface
stdlib_sorcsd2by1 stdlib_lapack_eig_svd_lsq Interface
stdlib_sorg2l stdlib_lapack_orthogonal_factors Interface
stdlib_sorg2r stdlib_lapack_orthogonal_factors Interface
stdlib_sorgbr stdlib_lapack_eig_svd_lsq Interface
stdlib_sorghr stdlib_lapack_eig_svd_lsq Interface
stdlib_sorgl2 stdlib_lapack_orthogonal_factors Interface
stdlib_sorglq stdlib_lapack_orthogonal_factors Interface
stdlib_sorgql stdlib_lapack_orthogonal_factors Interface
stdlib_sorgqr stdlib_lapack_orthogonal_factors Interface
stdlib_sorgr2 stdlib_lapack_orthogonal_factors Interface
stdlib_sorgrq stdlib_lapack_orthogonal_factors Interface
stdlib_sorgtr stdlib_lapack_eig_svd_lsq Interface
stdlib_sorgtsqr stdlib_lapack_orthogonal_factors Interface
stdlib_sorgtsqr_row stdlib_lapack_orthogonal_factors Interface
stdlib_sorhr_col stdlib_lapack_orthogonal_factors Interface
stdlib_sorm22 stdlib_lapack_eig_svd_lsq Interface
stdlib_sorm2l stdlib_lapack_orthogonal_factors Interface
stdlib_sorm2r stdlib_lapack_orthogonal_factors Interface
stdlib_sormbr stdlib_lapack_eig_svd_lsq Interface
stdlib_sormhr stdlib_lapack_eig_svd_lsq Interface
stdlib_sorml2 stdlib_lapack_orthogonal_factors Interface
stdlib_sormlq stdlib_lapack_orthogonal_factors Interface
stdlib_sormql stdlib_lapack_orthogonal_factors Interface
stdlib_sormqr stdlib_lapack_orthogonal_factors Interface
stdlib_sormr2 stdlib_lapack_orthogonal_factors Interface
stdlib_sormr3 stdlib_lapack_orthogonal_factors Interface
stdlib_sormrq stdlib_lapack_orthogonal_factors Interface
stdlib_sormrz stdlib_lapack_orthogonal_factors Interface
stdlib_sormtr stdlib_lapack_eig_svd_lsq Interface
stdlib_spbcon stdlib_lapack_solve Interface
stdlib_spbequ stdlib_lapack_solve Interface
stdlib_spbrfs stdlib_lapack_solve Interface
stdlib_spbstf stdlib_lapack_eig_svd_lsq Interface
stdlib_spbsv stdlib_lapack_solve Interface
stdlib_spbsvx stdlib_lapack_solve Interface
stdlib_spbtf2 stdlib_lapack_solve Interface
stdlib_spbtrf stdlib_lapack_solve Interface
stdlib_spbtrs stdlib_lapack_solve Interface
stdlib_spftrf stdlib_lapack_solve Interface
stdlib_spftri stdlib_lapack_solve Interface
stdlib_spftrs stdlib_lapack_solve Interface
stdlib_spocon stdlib_lapack_solve Interface
stdlib_spoequ stdlib_lapack_solve Interface
stdlib_spoequb stdlib_lapack_solve Interface
stdlib_sporfs stdlib_lapack_solve Interface
stdlib_sposv stdlib_lapack_solve Interface
stdlib_sposvx stdlib_lapack_solve Interface
stdlib_spotf2 stdlib_lapack_solve Interface
stdlib_spotrf stdlib_lapack_solve Interface
stdlib_spotrf2 stdlib_lapack_solve Interface
stdlib_spotri stdlib_lapack_solve Interface
stdlib_spotrs stdlib_lapack_solve Interface
stdlib_sppcon stdlib_lapack_solve Interface
stdlib_sppequ stdlib_lapack_solve Interface
stdlib_spprfs stdlib_lapack_solve Interface
stdlib_sppsv stdlib_lapack_solve Interface
stdlib_sppsvx stdlib_lapack_solve Interface
stdlib_spptrf stdlib_lapack_solve Interface
stdlib_spptri stdlib_lapack_solve Interface
stdlib_spptrs stdlib_lapack_solve Interface
stdlib_spstf2 stdlib_lapack_solve Interface
stdlib_spstrf stdlib_lapack_solve Interface
stdlib_sptcon stdlib_lapack_solve Interface
stdlib_spteqr stdlib_lapack_eig_svd_lsq Interface
stdlib_sptrfs stdlib_lapack_solve Interface
stdlib_sptsv stdlib_lapack_solve Interface
stdlib_sptsvx stdlib_lapack_solve Interface
stdlib_spttrf stdlib_lapack_solve Interface
stdlib_spttrs stdlib_lapack_solve Interface
stdlib_sptts2 stdlib_lapack_solve Interface
stdlib_srot stdlib_blas Interface
stdlib_srotg stdlib_blas Interface
stdlib_srotm stdlib_blas Interface
stdlib_srotmg stdlib_blas Interface
stdlib_sroundup_lwork stdlib_linalg_lapack_aux Function

ROUNDUP_LWORK >= LWORK. ROUNDUP_LWORK is guaranteed to have zero decimal part.

stdlib_srscl stdlib_lapack_base Interface
stdlib_ssb2st_kernels stdlib_lapack_eig_svd_lsq Interface
stdlib_ssbev stdlib_lapack_eig_svd_lsq Interface
stdlib_ssbevd stdlib_lapack_eig_svd_lsq Interface
stdlib_ssbevx stdlib_lapack_eig_svd_lsq Interface
stdlib_ssbgst stdlib_lapack_eig_svd_lsq Interface
stdlib_ssbgv stdlib_lapack_eig_svd_lsq Interface
stdlib_ssbgvd stdlib_lapack_eig_svd_lsq Interface
stdlib_ssbgvx stdlib_lapack_eig_svd_lsq Interface
stdlib_ssbmv stdlib_blas Interface
stdlib_ssbtrd stdlib_lapack_eig_svd_lsq Interface
stdlib_sscal stdlib_blas Interface
stdlib_ssfrk stdlib_lapack_base Interface
stdlib_sspcon stdlib_lapack_solve Interface
stdlib_sspev stdlib_lapack_eig_svd_lsq Interface
stdlib_sspevd stdlib_lapack_eig_svd_lsq Interface
stdlib_sspevx stdlib_lapack_eig_svd_lsq Interface
stdlib_sspgst stdlib_lapack_eig_svd_lsq Interface
stdlib_sspgv stdlib_lapack_eig_svd_lsq Interface
stdlib_sspgvd stdlib_lapack_eig_svd_lsq Interface
stdlib_sspgvx stdlib_lapack_eig_svd_lsq Interface
stdlib_sspmv stdlib_blas Interface
stdlib_sspr stdlib_blas Interface
stdlib_sspr2 stdlib_blas Interface
stdlib_ssprfs stdlib_lapack_solve Interface
stdlib_sspsv stdlib_lapack_solve Interface
stdlib_sspsvx stdlib_lapack_solve Interface
stdlib_ssptrd stdlib_lapack_eig_svd_lsq Interface
stdlib_ssptrf stdlib_lapack_solve Interface
stdlib_ssptri stdlib_lapack_solve Interface
stdlib_ssptrs stdlib_lapack_solve Interface
stdlib_sstebz stdlib_lapack_eig_svd_lsq Interface
stdlib_sstedc stdlib_lapack_eig_svd_lsq Interface
stdlib_sstegr stdlib_lapack_eig_svd_lsq Interface
stdlib_sstein stdlib_lapack_eig_svd_lsq Interface
stdlib_sstemr stdlib_lapack_eig_svd_lsq Interface
stdlib_ssteqr stdlib_lapack_eig_svd_lsq Interface
stdlib_ssterf stdlib_lapack_eig_svd_lsq Interface
stdlib_sstev stdlib_lapack_eig_svd_lsq Interface
stdlib_sstevd stdlib_lapack_eig_svd_lsq Interface
stdlib_sstevr stdlib_lapack_eig_svd_lsq Interface
stdlib_sstevx stdlib_lapack_eig_svd_lsq Interface
stdlib_sswap stdlib_blas Interface
stdlib_ssycon stdlib_lapack_solve Interface
stdlib_ssycon_rook stdlib_lapack_solve Interface
stdlib_ssyconv stdlib_lapack_solve Interface
stdlib_ssyconvf stdlib_lapack_solve Interface
stdlib_ssyconvf_rook stdlib_lapack_solve Interface
stdlib_ssyequb stdlib_lapack_solve Interface
stdlib_ssyev stdlib_lapack_eig_svd_lsq Interface
stdlib_ssyevd stdlib_lapack_eig_svd_lsq Interface
stdlib_ssyevr stdlib_lapack_eig_svd_lsq Interface
stdlib_ssyevx stdlib_lapack_eig_svd_lsq Interface
stdlib_ssygs2 stdlib_lapack_eig_svd_lsq Interface
stdlib_ssygst stdlib_lapack_eig_svd_lsq Interface
stdlib_ssygv stdlib_lapack_eig_svd_lsq Interface
stdlib_ssygvd stdlib_lapack_eig_svd_lsq Interface
stdlib_ssygvx stdlib_lapack_eig_svd_lsq Interface
stdlib_ssymm stdlib_blas Interface
stdlib_ssymv stdlib_blas Interface
stdlib_ssyr stdlib_blas Interface
stdlib_ssyr2 stdlib_blas Interface
stdlib_ssyr2k stdlib_blas Interface
stdlib_ssyrfs stdlib_lapack_solve Interface
stdlib_ssyrk stdlib_blas Interface
stdlib_ssysv stdlib_lapack_solve Interface
stdlib_ssysv_aa stdlib_lapack_solve Interface
stdlib_ssysv_rk stdlib_lapack_solve Interface
stdlib_ssysv_rook stdlib_lapack_solve Interface
stdlib_ssysvx stdlib_lapack_solve Interface
stdlib_ssyswapr stdlib_lapack_solve Interface
stdlib_ssytd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_ssytf2 stdlib_lapack_solve Interface
stdlib_ssytf2_rk stdlib_lapack_solve Interface
stdlib_ssytf2_rook stdlib_lapack_solve Interface
stdlib_ssytrd stdlib_lapack_eig_svd_lsq Interface
stdlib_ssytrd_sb2st stdlib_lapack_eig_svd_lsq Interface
stdlib_ssytrd_sy2sb stdlib_lapack_eig_svd_lsq Interface
stdlib_ssytrf stdlib_lapack_solve Interface
stdlib_ssytrf_aa stdlib_lapack_solve Interface
stdlib_ssytrf_rk stdlib_lapack_solve Interface
stdlib_ssytrf_rook stdlib_lapack_solve Interface
stdlib_ssytri stdlib_lapack_solve Interface
stdlib_ssytri_rook stdlib_lapack_solve Interface
stdlib_ssytrs stdlib_lapack_solve Interface
stdlib_ssytrs2 stdlib_lapack_solve Interface
stdlib_ssytrs_3 stdlib_lapack_solve Interface
stdlib_ssytrs_aa stdlib_lapack_solve Interface
stdlib_ssytrs_rook stdlib_lapack_solve Interface
stdlib_stbcon stdlib_lapack_solve Interface
stdlib_stbmv stdlib_blas Interface
stdlib_stbrfs stdlib_lapack_solve Interface
stdlib_stbsv stdlib_blas Interface
stdlib_stbtrs stdlib_lapack_solve Interface
stdlib_stfsm stdlib_lapack_base Interface
stdlib_stftri stdlib_lapack_solve Interface
stdlib_stfttp stdlib_lapack_base Interface
stdlib_stfttr stdlib_lapack_base Interface
stdlib_stgevc stdlib_lapack_eig_svd_lsq Interface
stdlib_stgex2 stdlib_lapack_eig_svd_lsq Interface
stdlib_stgexc stdlib_lapack_eig_svd_lsq Interface
stdlib_stgsen stdlib_lapack_eig_svd_lsq Interface
stdlib_stgsja stdlib_lapack_eig_svd_lsq Interface
stdlib_stgsna stdlib_lapack_eig_svd_lsq Interface
stdlib_stgsy2 stdlib_lapack_eig_svd_lsq Interface
stdlib_stgsyl stdlib_lapack_eig_svd_lsq Interface
stdlib_stpcon stdlib_lapack_solve Interface
stdlib_stplqt stdlib_lapack_orthogonal_factors Interface
stdlib_stplqt2 stdlib_lapack_orthogonal_factors Interface
stdlib_stpmlqt stdlib_lapack_orthogonal_factors Interface
stdlib_stpmqrt stdlib_lapack_orthogonal_factors Interface
stdlib_stpmv stdlib_blas Interface
stdlib_stpqrt stdlib_lapack_orthogonal_factors Interface
stdlib_stpqrt2 stdlib_lapack_orthogonal_factors Interface
stdlib_stprfb stdlib_lapack_orthogonal_factors Interface
stdlib_stprfs stdlib_lapack_solve Interface
stdlib_stpsv stdlib_blas Interface
stdlib_stptri stdlib_lapack_solve Interface
stdlib_stptrs stdlib_lapack_solve Interface
stdlib_stpttf stdlib_lapack_base Interface
stdlib_stpttr stdlib_lapack_base Interface
stdlib_strcon stdlib_lapack_solve Interface
stdlib_strevc stdlib_lapack_eig_svd_lsq Interface
stdlib_strevc3 stdlib_lapack_eig_svd_lsq Interface
stdlib_strexc stdlib_lapack_eig_svd_lsq Interface
stdlib_strmm stdlib_blas Interface
stdlib_strmv stdlib_blas Interface
stdlib_strrfs stdlib_lapack_solve Interface
stdlib_strsen stdlib_lapack_eig_svd_lsq Interface
stdlib_strsm stdlib_blas Interface
stdlib_strsna stdlib_lapack_eig_svd_lsq Interface
stdlib_strsv stdlib_blas Interface
stdlib_strsyl stdlib_lapack_eig_svd_lsq Interface
stdlib_strti2 stdlib_lapack_solve Interface
stdlib_strtri stdlib_lapack_solve Interface
stdlib_strtrs stdlib_lapack_solve Interface
stdlib_strttf stdlib_lapack_base Interface
stdlib_strttp stdlib_lapack_base Interface
stdlib_stzrzf stdlib_lapack_orthogonal_factors Interface
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_blas Interface
stdlib_zbbcsd stdlib_lapack_eig_svd_lsq Interface
stdlib_zbdsqr stdlib_lapack_eig_svd_lsq Interface
stdlib_zcopy stdlib_blas Interface
stdlib_zdotc stdlib_blas Interface
stdlib_zdotu stdlib_blas Interface
stdlib_zdrot stdlib_blas Interface
stdlib_zdrscl stdlib_lapack_base Interface
stdlib_zdscal stdlib_blas Interface
stdlib_zgbbrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zgbcon stdlib_lapack_solve Interface
stdlib_zgbequ stdlib_lapack_solve Interface
stdlib_zgbequb stdlib_lapack_solve Interface
stdlib_zgbmv stdlib_blas Interface
stdlib_zgbrfs stdlib_lapack_solve Interface
stdlib_zgbsv stdlib_lapack_solve Interface
stdlib_zgbsvx stdlib_lapack_solve Interface
stdlib_zgbtf2 stdlib_lapack_solve Interface
stdlib_zgbtrf stdlib_lapack_solve Interface
stdlib_zgbtrs stdlib_lapack_solve Interface
stdlib_zgebak stdlib_lapack_eig_svd_lsq Interface
stdlib_zgebal stdlib_lapack_eig_svd_lsq Interface
stdlib_zgebd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zgebrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zgecon stdlib_lapack_solve Interface
stdlib_zgeequ stdlib_lapack_solve Interface
stdlib_zgeequb stdlib_lapack_solve Interface
stdlib_zgees stdlib_lapack_eig_svd_lsq Interface
stdlib_zgeesx stdlib_lapack_eig_svd_lsq Interface
stdlib_zgeev stdlib_lapack_eig_svd_lsq Interface
stdlib_zgeevx stdlib_lapack_eig_svd_lsq Interface
stdlib_zgehd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zgehrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zgejsv stdlib_lapack_eig_svd_lsq Interface
stdlib_zgelq stdlib_lapack_orthogonal_factors Interface
stdlib_zgelq2 stdlib_lapack_orthogonal_factors Interface
stdlib_zgelqf stdlib_lapack_orthogonal_factors Interface
stdlib_zgelqt stdlib_lapack_orthogonal_factors Interface
stdlib_zgelqt3 stdlib_lapack_orthogonal_factors Interface
stdlib_zgels stdlib_lapack_eig_svd_lsq Interface
stdlib_zgelsd stdlib_lapack_eig_svd_lsq Interface
stdlib_zgelss stdlib_lapack_eig_svd_lsq Interface
stdlib_zgelsy stdlib_lapack_eig_svd_lsq Interface
stdlib_zgemlq stdlib_lapack_orthogonal_factors Interface
stdlib_zgemlqt stdlib_lapack_orthogonal_factors Interface
stdlib_zgemm stdlib_blas Interface
stdlib_zgemqr stdlib_lapack_orthogonal_factors Interface
stdlib_zgemqrt stdlib_lapack_orthogonal_factors Interface
stdlib_zgemv stdlib_blas Interface
stdlib_zgeql2 stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqlf stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqp3 stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqr stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqr2 stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqr2p stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqrf stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqrfp stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqrt stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqrt2 stdlib_lapack_orthogonal_factors Interface
stdlib_zgeqrt3 stdlib_lapack_orthogonal_factors Interface
stdlib_zgerc stdlib_blas Interface
stdlib_zgerfs stdlib_lapack_solve Interface
stdlib_zgerq2 stdlib_lapack_orthogonal_factors Interface
stdlib_zgerqf stdlib_lapack_orthogonal_factors Interface
stdlib_zgeru stdlib_blas Interface
stdlib_zgesc2 stdlib_lapack_solve Interface
stdlib_zgesdd stdlib_lapack_eig_svd_lsq Interface
stdlib_zgesv stdlib_lapack_solve Interface
stdlib_zgesvd stdlib_lapack_eig_svd_lsq Interface
stdlib_zgesvdq stdlib_lapack_eig_svd_lsq Interface
stdlib_zgesvj stdlib_lapack_eig_svd_lsq Interface
stdlib_zgesvx stdlib_lapack_solve Interface
stdlib_zgetc2 stdlib_lapack_solve Interface
stdlib_zgetf2 stdlib_lapack_solve Interface
stdlib_zgetrf stdlib_lapack_solve Interface
stdlib_zgetrf2 stdlib_lapack_solve Interface
stdlib_zgetri stdlib_lapack_solve Interface
stdlib_zgetrs stdlib_lapack_solve Interface
stdlib_zgetsls stdlib_lapack_eig_svd_lsq Interface
stdlib_zgetsqrhrt stdlib_lapack_orthogonal_factors Interface
stdlib_zggbak stdlib_lapack_eig_svd_lsq Interface
stdlib_zggbal stdlib_lapack_eig_svd_lsq Interface
stdlib_zgges stdlib_lapack_eig_svd_lsq Interface
stdlib_zgges3 stdlib_lapack_eig_svd_lsq Interface
stdlib_zggesx stdlib_lapack_eig_svd_lsq Interface
stdlib_zggev stdlib_lapack_eig_svd_lsq Interface
stdlib_zggev3 stdlib_lapack_eig_svd_lsq Interface
stdlib_zggevx stdlib_lapack_eig_svd_lsq Interface
stdlib_zggglm stdlib_lapack_eig_svd_lsq Interface
stdlib_zgghd3 stdlib_lapack_eig_svd_lsq Interface
stdlib_zgghrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zgglse stdlib_lapack_eig_svd_lsq Interface
stdlib_zggqrf stdlib_lapack_orthogonal_factors Interface
stdlib_zggrqf stdlib_lapack_orthogonal_factors Interface
stdlib_zgsvj0 stdlib_lapack_eig_svd_lsq Interface
stdlib_zgsvj1 stdlib_lapack_eig_svd_lsq Interface
stdlib_zgtcon stdlib_lapack_solve Interface
stdlib_zgtrfs stdlib_lapack_solve Interface
stdlib_zgtsv stdlib_lapack_solve Interface
stdlib_zgtsvx stdlib_lapack_solve Interface
stdlib_zgttrf stdlib_lapack_solve Interface
stdlib_zgttrs stdlib_lapack_solve Interface
stdlib_zgtts2 stdlib_lapack_solve Interface
stdlib_zhb2st_kernels stdlib_lapack_eig_svd_lsq Interface
stdlib_zhbev stdlib_lapack_eig_svd_lsq Interface
stdlib_zhbevd stdlib_lapack_eig_svd_lsq Interface
stdlib_zhbevx stdlib_lapack_eig_svd_lsq Interface
stdlib_zhbgst stdlib_lapack_eig_svd_lsq Interface
stdlib_zhbgv stdlib_lapack_eig_svd_lsq Interface
stdlib_zhbgvd stdlib_lapack_eig_svd_lsq Interface
stdlib_zhbgvx stdlib_lapack_eig_svd_lsq Interface
stdlib_zhbmv stdlib_blas Interface
stdlib_zhbtrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zhecon stdlib_lapack_solve Interface
stdlib_zhecon_rook stdlib_lapack_solve Interface
stdlib_zheequb stdlib_lapack_solve Interface
stdlib_zheev stdlib_lapack_eig_svd_lsq Interface
stdlib_zheevd stdlib_lapack_eig_svd_lsq Interface
stdlib_zheevr stdlib_lapack_eig_svd_lsq Interface
stdlib_zheevx stdlib_lapack_eig_svd_lsq Interface
stdlib_zhegs2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zhegst stdlib_lapack_eig_svd_lsq Interface
stdlib_zhegv stdlib_lapack_eig_svd_lsq Interface
stdlib_zhegvd stdlib_lapack_eig_svd_lsq Interface
stdlib_zhegvx stdlib_lapack_eig_svd_lsq Interface
stdlib_zhemm stdlib_blas Interface
stdlib_zhemv stdlib_blas Interface
stdlib_zher stdlib_blas Interface
stdlib_zher2 stdlib_blas Interface
stdlib_zher2k stdlib_blas Interface
stdlib_zherfs stdlib_lapack_solve Interface
stdlib_zherk stdlib_blas Interface
stdlib_zhesv stdlib_lapack_solve Interface
stdlib_zhesv_aa stdlib_lapack_solve Interface
stdlib_zhesv_rk stdlib_lapack_solve Interface
stdlib_zhesv_rook stdlib_lapack_solve Interface
stdlib_zhesvx stdlib_lapack_solve Interface
stdlib_zheswapr stdlib_lapack_solve Interface
stdlib_zhetd2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zhetf2 stdlib_lapack_solve Interface
stdlib_zhetf2_rk stdlib_lapack_solve Interface
stdlib_zhetf2_rook stdlib_lapack_solve Interface
stdlib_zhetrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zhetrd_hb2st stdlib_lapack_eig_svd_lsq Interface
stdlib_zhetrd_he2hb stdlib_lapack_eig_svd_lsq Interface
stdlib_zhetrf stdlib_lapack_solve Interface
stdlib_zhetrf_aa stdlib_lapack_solve Interface
stdlib_zhetrf_rk stdlib_lapack_solve Interface
stdlib_zhetrf_rook stdlib_lapack_solve Interface
stdlib_zhetri stdlib_lapack_solve Interface
stdlib_zhetri_rook stdlib_lapack_solve Interface
stdlib_zhetrs stdlib_lapack_solve Interface
stdlib_zhetrs2 stdlib_lapack_solve Interface
stdlib_zhetrs_3 stdlib_lapack_solve Interface
stdlib_zhetrs_aa stdlib_lapack_solve Interface
stdlib_zhetrs_rook stdlib_lapack_solve Interface
stdlib_zhfrk stdlib_lapack_base Interface
stdlib_zhgeqz stdlib_lapack_eig_svd_lsq Interface
stdlib_zhpcon stdlib_lapack_solve Interface
stdlib_zhpev stdlib_lapack_eig_svd_lsq Interface
stdlib_zhpevd stdlib_lapack_eig_svd_lsq Interface
stdlib_zhpevx stdlib_lapack_eig_svd_lsq Interface
stdlib_zhpgst stdlib_lapack_eig_svd_lsq Interface
stdlib_zhpgv stdlib_lapack_eig_svd_lsq Interface
stdlib_zhpgvd stdlib_lapack_eig_svd_lsq Interface
stdlib_zhpgvx stdlib_lapack_eig_svd_lsq Interface
stdlib_zhpmv stdlib_blas Interface
stdlib_zhpr stdlib_blas Interface
stdlib_zhpr2 stdlib_blas Interface
stdlib_zhprfs stdlib_lapack_solve Interface
stdlib_zhpsv stdlib_lapack_solve Interface
stdlib_zhpsvx stdlib_lapack_solve Interface
stdlib_zhptrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zhptrf stdlib_lapack_solve Interface
stdlib_zhptri stdlib_lapack_solve Interface
stdlib_zhptrs stdlib_lapack_solve Interface
stdlib_zhsein stdlib_lapack_eig_svd_lsq Interface
stdlib_zhseqr stdlib_lapack_eig_svd_lsq Interface
stdlib_zla_gbamv stdlib_lapack_base Interface
stdlib_zla_gbrcond_c stdlib_lapack_others Interface
stdlib_zla_gbrpvgrw stdlib_lapack_solve Interface
stdlib_zla_geamv stdlib_lapack_base Interface
stdlib_zla_gercond_c stdlib_lapack_others Interface
stdlib_zla_gerpvgrw stdlib_lapack_others Interface
stdlib_zla_heamv stdlib_lapack_base Interface
stdlib_zla_hercond_c stdlib_lapack_others Interface
stdlib_zla_herpvgrw stdlib_lapack_solve Interface
stdlib_zla_lin_berr stdlib_lapack_solve Interface
stdlib_zla_porcond_c stdlib_lapack_others Interface
stdlib_zla_porpvgrw stdlib_lapack_solve Interface
stdlib_zla_syamv stdlib_lapack_others Interface
stdlib_zla_syrcond_c stdlib_lapack_others Interface
stdlib_zla_syrpvgrw stdlib_lapack_others Interface
stdlib_zla_wwaddw stdlib_lapack_base Interface
stdlib_zlabrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zlacgv stdlib_lapack_base Interface
stdlib_zlacn2 stdlib_lapack_solve Interface
stdlib_zlacon stdlib_lapack_solve Interface
stdlib_zlacp2 stdlib_lapack_base Interface
stdlib_zlacpy stdlib_lapack_base Interface
stdlib_zlacrm stdlib_lapack_base Interface
stdlib_zlacrt stdlib_lapack_base Interface
stdlib_zladiv stdlib_lapack_base Interface
stdlib_zlaed0 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaed7 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaed8 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaein stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaesy stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaev2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlags2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlagtm stdlib_lapack_base Interface
stdlib_zlahef stdlib_lapack_solve Interface
stdlib_zlahef_aa stdlib_lapack_solve Interface
stdlib_zlahef_rk stdlib_lapack_solve Interface
stdlib_zlahef_rook stdlib_lapack_solve Interface
stdlib_zlahqr stdlib_lapack_eig_svd_lsq Interface
stdlib_zlahr2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaic1 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlals0 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlalsa stdlib_lapack_eig_svd_lsq Interface
stdlib_zlalsd stdlib_lapack_eig_svd_lsq Interface
stdlib_zlamswlq stdlib_lapack_orthogonal_factors Interface
stdlib_zlamtsqr stdlib_lapack_orthogonal_factors Interface
stdlib_zlangb stdlib_lapack_base Interface
stdlib_zlange stdlib_lapack_base Interface
stdlib_zlangt stdlib_lapack_base Interface
stdlib_zlanhb stdlib_lapack_base Interface
stdlib_zlanhe stdlib_lapack_base Interface
stdlib_zlanhf stdlib_lapack_base Interface
stdlib_zlanhp stdlib_lapack_base Interface
stdlib_zlanhs stdlib_lapack_base Interface
stdlib_zlanht stdlib_lapack_base Interface
stdlib_zlansb stdlib_lapack_base Interface
stdlib_zlansp stdlib_lapack_base Interface
stdlib_zlansy stdlib_lapack_base Interface
stdlib_zlantb stdlib_lapack_base Interface
stdlib_zlantp stdlib_lapack_base Interface
stdlib_zlantr stdlib_lapack_base Interface
stdlib_zlapll stdlib_lapack_eig_svd_lsq Interface
stdlib_zlapmr stdlib_lapack_eig_svd_lsq Interface
stdlib_zlapmt stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqgb stdlib_lapack_solve Interface
stdlib_zlaqge stdlib_lapack_solve Interface
stdlib_zlaqhb stdlib_lapack_solve Interface
stdlib_zlaqhe stdlib_lapack_solve Interface
stdlib_zlaqhp stdlib_lapack_solve Interface
stdlib_zlaqp2 stdlib_lapack_orthogonal_factors Interface
stdlib_zlaqps stdlib_lapack_orthogonal_factors Interface
stdlib_zlaqr0 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqr1 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqr2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqr3 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqr4 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqr5 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqsb stdlib_lapack_base Interface
stdlib_zlaqsp stdlib_lapack_solve Interface
stdlib_zlaqsy stdlib_lapack_solve Interface
stdlib_zlaqz0 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqz1 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqz2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlaqz3 stdlib_lapack_eig_svd_lsq Interface
stdlib_zlar1v stdlib_lapack_eig_svd_lsq Interface
stdlib_zlar2v stdlib_lapack_base Interface
stdlib_zlarcm stdlib_lapack_base Interface
stdlib_zlarf stdlib_lapack_base Interface
stdlib_zlarfb stdlib_lapack_base Interface
stdlib_zlarfb_gett stdlib_lapack_orthogonal_factors Interface
stdlib_zlarfg stdlib_lapack_base Interface
stdlib_zlarfgp stdlib_lapack_base Interface
stdlib_zlarft stdlib_lapack_base Interface
stdlib_zlarfx stdlib_lapack_base Interface
stdlib_zlarfy stdlib_lapack_base Interface
stdlib_zlargv stdlib_lapack_base Interface
stdlib_zlarnv stdlib_lapack_base Interface
stdlib_zlarrv stdlib_lapack_eig_svd_lsq Interface
stdlib_zlartg stdlib_lapack_base Interface
stdlib_zlartv stdlib_lapack_base Interface
stdlib_zlarz stdlib_lapack_orthogonal_factors Interface
stdlib_zlarzb stdlib_lapack_orthogonal_factors Interface
stdlib_zlarzt stdlib_lapack_orthogonal_factors Interface
stdlib_zlascl stdlib_lapack_base Interface
stdlib_zlaset stdlib_lapack_base Interface
stdlib_zlasr stdlib_lapack_base Interface
stdlib_zlassq stdlib_lapack_base Interface
stdlib_zlaswlq stdlib_lapack_orthogonal_factors Interface
stdlib_zlaswp stdlib_lapack_solve Interface
stdlib_zlasyf stdlib_lapack_solve Interface
stdlib_zlasyf_aa stdlib_lapack_solve Interface
stdlib_zlasyf_rk stdlib_lapack_solve Interface
stdlib_zlasyf_rook stdlib_lapack_solve Interface
stdlib_zlatbs stdlib_lapack_solve Interface
stdlib_zlatdf stdlib_lapack_solve Interface
stdlib_zlatps stdlib_lapack_solve Interface
stdlib_zlatrd stdlib_lapack_eig_svd_lsq Interface
stdlib_zlatrs stdlib_lapack_solve Interface
stdlib_zlatrz stdlib_lapack_orthogonal_factors Interface
stdlib_zlatsqr stdlib_lapack_orthogonal_factors Interface
stdlib_zlaunhr_col_getrfnp stdlib_lapack_orthogonal_factors Interface
stdlib_zlaunhr_col_getrfnp2 stdlib_lapack_orthogonal_factors Interface
stdlib_zlauu2 stdlib_lapack_solve Interface
stdlib_zlauum stdlib_lapack_solve Interface
stdlib_zpbcon stdlib_lapack_solve Interface
stdlib_zpbequ stdlib_lapack_solve Interface
stdlib_zpbrfs stdlib_lapack_solve Interface
stdlib_zpbstf stdlib_lapack_eig_svd_lsq Interface
stdlib_zpbsv stdlib_lapack_solve Interface
stdlib_zpbsvx stdlib_lapack_solve Interface
stdlib_zpbtf2 stdlib_lapack_solve Interface
stdlib_zpbtrf stdlib_lapack_solve Interface
stdlib_zpbtrs stdlib_lapack_solve Interface
stdlib_zpftrf stdlib_lapack_solve Interface
stdlib_zpftri stdlib_lapack_solve Interface
stdlib_zpftrs stdlib_lapack_solve Interface
stdlib_zpocon stdlib_lapack_solve Interface
stdlib_zpoequ stdlib_lapack_solve Interface
stdlib_zpoequb stdlib_lapack_solve Interface
stdlib_zporfs stdlib_lapack_solve Interface
stdlib_zposv stdlib_lapack_solve Interface
stdlib_zposvx stdlib_lapack_solve Interface
stdlib_zpotf2 stdlib_lapack_solve Interface
stdlib_zpotrf stdlib_lapack_solve Interface
stdlib_zpotrf2 stdlib_lapack_solve Interface
stdlib_zpotri stdlib_lapack_solve Interface
stdlib_zpotrs stdlib_lapack_solve Interface
stdlib_zppcon stdlib_lapack_solve Interface
stdlib_zppequ stdlib_lapack_solve Interface
stdlib_zpprfs stdlib_lapack_solve Interface
stdlib_zppsv stdlib_lapack_solve Interface
stdlib_zppsvx stdlib_lapack_solve Interface
stdlib_zpptrf stdlib_lapack_solve Interface
stdlib_zpptri stdlib_lapack_solve Interface
stdlib_zpptrs stdlib_lapack_solve Interface
stdlib_zpstf2 stdlib_lapack_solve Interface
stdlib_zpstrf stdlib_lapack_solve Interface
stdlib_zptcon stdlib_lapack_solve Interface
stdlib_zpteqr stdlib_lapack_eig_svd_lsq Interface
stdlib_zptrfs stdlib_lapack_solve Interface
stdlib_zptsv stdlib_lapack_solve Interface
stdlib_zptsvx stdlib_lapack_solve Interface
stdlib_zpttrf stdlib_lapack_solve Interface
stdlib_zpttrs stdlib_lapack_solve Interface
stdlib_zptts2 stdlib_lapack_solve Interface
stdlib_zrot stdlib_lapack_base Interface
stdlib_zrotg stdlib_blas Interface
stdlib_zscal stdlib_blas Interface
stdlib_zspcon stdlib_lapack_solve Interface
stdlib_zspmv stdlib_lapack_base Interface
stdlib_zspr stdlib_lapack_base Interface
stdlib_zsprfs stdlib_lapack_solve Interface
stdlib_zspsv stdlib_lapack_solve Interface
stdlib_zspsvx stdlib_lapack_solve Interface
stdlib_zsptrf stdlib_lapack_solve Interface
stdlib_zsptri stdlib_lapack_solve Interface
stdlib_zsptrs stdlib_lapack_solve Interface
stdlib_zstedc stdlib_lapack_eig_svd_lsq Interface
stdlib_zstegr stdlib_lapack_eig_svd_lsq Interface
stdlib_zstein stdlib_lapack_eig_svd_lsq Interface
stdlib_zstemr stdlib_lapack_eig_svd_lsq Interface
stdlib_zsteqr stdlib_lapack_eig_svd_lsq Interface
stdlib_zswap stdlib_blas Interface
stdlib_zsycon stdlib_lapack_solve Interface
stdlib_zsycon_rook stdlib_lapack_solve Interface
stdlib_zsyconv stdlib_lapack_solve Interface
stdlib_zsyconvf stdlib_lapack_solve Interface
stdlib_zsyconvf_rook stdlib_lapack_solve Interface
stdlib_zsyequb stdlib_lapack_solve Interface
stdlib_zsymm stdlib_blas Interface
stdlib_zsymv stdlib_lapack_base Interface
stdlib_zsyr stdlib_lapack_base Interface
stdlib_zsyr2k stdlib_blas Interface
stdlib_zsyrfs stdlib_lapack_solve Interface
stdlib_zsyrk stdlib_blas Interface
stdlib_zsysv stdlib_lapack_solve Interface
stdlib_zsysv_aa stdlib_lapack_solve Interface
stdlib_zsysv_rk stdlib_lapack_solve Interface
stdlib_zsysv_rook stdlib_lapack_solve Interface
stdlib_zsysvx stdlib_lapack_solve Interface
stdlib_zsyswapr stdlib_lapack_solve Interface
stdlib_zsytf2 stdlib_lapack_solve Interface
stdlib_zsytf2_rk stdlib_lapack_solve Interface
stdlib_zsytf2_rook stdlib_lapack_solve Interface
stdlib_zsytrf stdlib_lapack_solve Interface
stdlib_zsytrf_aa stdlib_lapack_solve Interface
stdlib_zsytrf_rk stdlib_lapack_solve Interface
stdlib_zsytrf_rook stdlib_lapack_solve Interface
stdlib_zsytri stdlib_lapack_solve Interface
stdlib_zsytri_rook stdlib_lapack_solve Interface
stdlib_zsytrs stdlib_lapack_solve Interface
stdlib_zsytrs2 stdlib_lapack_solve Interface
stdlib_zsytrs_3 stdlib_lapack_solve Interface
stdlib_zsytrs_aa stdlib_lapack_solve Interface
stdlib_zsytrs_rook stdlib_lapack_solve Interface
stdlib_ztbcon stdlib_lapack_solve Interface
stdlib_ztbmv stdlib_blas Interface
stdlib_ztbrfs stdlib_lapack_solve Interface
stdlib_ztbsv stdlib_blas Interface
stdlib_ztbtrs stdlib_lapack_solve Interface
stdlib_ztfsm stdlib_lapack_base Interface
stdlib_ztftri stdlib_lapack_solve Interface
stdlib_ztfttp stdlib_lapack_base Interface
stdlib_ztfttr stdlib_lapack_base Interface
stdlib_ztgevc stdlib_lapack_eig_svd_lsq Interface
stdlib_ztgex2 stdlib_lapack_eig_svd_lsq Interface
stdlib_ztgexc stdlib_lapack_eig_svd_lsq Interface
stdlib_ztgsen stdlib_lapack_eig_svd_lsq Interface
stdlib_ztgsja stdlib_lapack_eig_svd_lsq Interface
stdlib_ztgsna stdlib_lapack_eig_svd_lsq Interface
stdlib_ztgsy2 stdlib_lapack_eig_svd_lsq Interface
stdlib_ztgsyl stdlib_lapack_eig_svd_lsq Interface
stdlib_ztpcon stdlib_lapack_solve Interface
stdlib_ztplqt stdlib_lapack_orthogonal_factors Interface
stdlib_ztplqt2 stdlib_lapack_orthogonal_factors Interface
stdlib_ztpmlqt stdlib_lapack_orthogonal_factors Interface
stdlib_ztpmqrt stdlib_lapack_orthogonal_factors Interface
stdlib_ztpmv stdlib_blas Interface
stdlib_ztpqrt stdlib_lapack_orthogonal_factors Interface
stdlib_ztpqrt2 stdlib_lapack_orthogonal_factors Interface
stdlib_ztprfb stdlib_lapack_orthogonal_factors Interface
stdlib_ztprfs stdlib_lapack_solve Interface
stdlib_ztpsv stdlib_blas Interface
stdlib_ztptri stdlib_lapack_solve Interface
stdlib_ztptrs stdlib_lapack_solve Interface
stdlib_ztpttf stdlib_lapack_base Interface
stdlib_ztpttr stdlib_lapack_base Interface
stdlib_ztrcon stdlib_lapack_solve Interface
stdlib_ztrevc stdlib_lapack_eig_svd_lsq Interface
stdlib_ztrevc3 stdlib_lapack_eig_svd_lsq Interface
stdlib_ztrexc stdlib_lapack_eig_svd_lsq Interface
stdlib_ztrmm stdlib_blas Interface
stdlib_ztrmv stdlib_blas Interface
stdlib_ztrrfs stdlib_lapack_solve Interface
stdlib_ztrsen stdlib_lapack_eig_svd_lsq Interface
stdlib_ztrsm stdlib_blas Interface
stdlib_ztrsna stdlib_lapack_eig_svd_lsq Interface
stdlib_ztrsv stdlib_blas Interface
stdlib_ztrsyl stdlib_lapack_eig_svd_lsq Interface
stdlib_ztrti2 stdlib_lapack_solve Interface
stdlib_ztrtri stdlib_lapack_solve Interface
stdlib_ztrtrs stdlib_lapack_solve Interface
stdlib_ztrttf stdlib_lapack_base Interface
stdlib_ztrttp stdlib_lapack_base Interface
stdlib_ztzrzf stdlib_lapack_orthogonal_factors Interface
stdlib_zunbdb stdlib_lapack_eig_svd_lsq Interface
stdlib_zunbdb1 stdlib_lapack_eig_svd_lsq Interface
stdlib_zunbdb2 stdlib_lapack_eig_svd_lsq Interface
stdlib_zunbdb3 stdlib_lapack_eig_svd_lsq Interface
stdlib_zunbdb4 stdlib_lapack_eig_svd_lsq Interface
stdlib_zunbdb5 stdlib_lapack_eig_svd_lsq Interface
stdlib_zunbdb6 stdlib_lapack_eig_svd_lsq Interface
stdlib_zuncsd stdlib_lapack_eig_svd_lsq Interface
stdlib_zuncsd2by1 stdlib_lapack_eig_svd_lsq Interface
stdlib_zung2l stdlib_lapack_orthogonal_factors Interface
stdlib_zung2r stdlib_lapack_orthogonal_factors Interface
stdlib_zungbr stdlib_lapack_eig_svd_lsq Interface
stdlib_zunghr stdlib_lapack_eig_svd_lsq Interface
stdlib_zungl2 stdlib_lapack_orthogonal_factors Interface
stdlib_zunglq stdlib_lapack_orthogonal_factors Interface
stdlib_zungql stdlib_lapack_orthogonal_factors Interface
stdlib_zungqr stdlib_lapack_orthogonal_factors Interface
stdlib_zungr2 stdlib_lapack_orthogonal_factors Interface
stdlib_zungrq stdlib_lapack_orthogonal_factors Interface
stdlib_zungtr stdlib_lapack_eig_svd_lsq Interface
stdlib_zungtsqr stdlib_lapack_orthogonal_factors Interface
stdlib_zungtsqr_row stdlib_lapack_orthogonal_factors Interface
stdlib_zunhr_col stdlib_lapack_orthogonal_factors Interface
stdlib_zunm22 stdlib_lapack_orthogonal_factors Interface
stdlib_zunm2l stdlib_lapack_orthogonal_factors Interface
stdlib_zunm2r stdlib_lapack_orthogonal_factors Interface
stdlib_zunmbr stdlib_lapack_eig_svd_lsq Interface
stdlib_zunmhr stdlib_lapack_eig_svd_lsq Interface
stdlib_zunml2 stdlib_lapack_orthogonal_factors Interface
stdlib_zunmlq stdlib_lapack_orthogonal_factors Interface
stdlib_zunmql stdlib_lapack_orthogonal_factors Interface
stdlib_zunmqr stdlib_lapack_orthogonal_factors Interface
stdlib_zunmr2 stdlib_lapack_orthogonal_factors Interface
stdlib_zunmr3 stdlib_lapack_orthogonal_factors Interface
stdlib_zunmrq stdlib_lapack_orthogonal_factors Interface
stdlib_zunmrz stdlib_lapack_orthogonal_factors Interface
stdlib_zunmtr stdlib_lapack_eig_svd_lsq Interface
stdlib_zupgtr stdlib_lapack_eig_svd_lsq Interface
stdlib_zupmtr stdlib_lapack_eig_svd_lsq Interface
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.

Read more…
svd stdlib_linalg Interface

Computes the singular value decomposition of a real or complex 2d matrix. (Specification)

Read more…
svdvals stdlib_linalg Interface

Computes the singular values of a real or complex 2d matrix. (Specification)

Read more…
swap stdlib_linalg_blas Interface

SWAP interchanges two vectors.

swap stdlib_math Interface

Swap the values of the lhs and rhs arguments (Specification)

Read more…
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_c_char stdlib_strings Interface

Format or transfer other types as a string. (Specification)

to_lower stdlib_ascii Function

Convert character variable to lower case (Specification)

Read more…
to_lower stdlib_string_type Interface

Returns the lowercase version of the character sequence hold by the input string

Read more…
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_ascii Function

Converts character sequence to sentence case (Specification)

Read more…
to_sentence stdlib_string_type Interface

Returns the sentencecase version of the character sequence hold by the input string

Read more…
to_string stdlib_strings Interface

Format or transfer other types as a string. (Specification)

to_string stdlib_ansi Interface
to_title stdlib_ascii Function

Converts character sequence to title case (Specification)

Read more…
to_title stdlib_string_type Interface

Returns the titlecase version of the character sequence hold by the input string

Read more…
to_upper stdlib_ascii Function

Convert character variable to upper case (Specification)

Read more…
to_upper stdlib_string_type Interface

Returns the uppercase version of the character sequence hold by the input string

Read more…
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.

Read more…
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_32bit Function

Uses the "random" odd 32 bit integer seed to map the 32 bit integer key to an unsigned integer value with only nbits bits where nbits is less than 32 (Specification)

universal_mult_hash stdlib_hash_64bit Function

Uses the "random" odd 64 bit integer seed to map the 64 bit integer key to an unsigned integer value with only nbits bits where nbits is less than 64. (Specification)

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.

Read more…
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 set1 to the bitwise xor of the original bits in set1 and set2. The sets must have the same number of bits otherwise the result is undefined. (Specification)

Read more…
zfill stdlib_strings Interface

Left pad the input string with zeros. Specifications