Procedures

ProcedureLocationProcedure TypeDescription
adjustlstdlib_string_typeInterface

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

Read more…
adjustrstdlib_string_typeInterface

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

Read more…
all_closestdlib_mathInterface

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

andstdlib_bitsetsInterface

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_notstdlib_bitsetsInterface

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…
arangestdlib_mathInterface

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

argstdlib_mathInterface

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

arg_selectstdlib_selectionInterface

(Specification)

argdstdlib_mathInterface

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

argpistdlib_mathInterface

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

assignment(=)stdlib_bitsetsInterface

Used to define assignment for bitset_large. (Specification)

Read more…
assignment(=)stdlib_string_typeInterface

Assign a character sequence to a string.

bidxstdlib_stringlist_typeInterface

Returns an instance of type 'stringlist_index_type' representing backward index Specifications

bitsstdlib_bitsetsFunction

Returns the number of bit positions in self.

cdf_expstdlib_stats_distribution_exponentialInterface

Version experimental

Read more…
cdf_normalstdlib_stats_distribution_normalInterface

Normal Distribution Cumulative Distribution Function (Specification)

cdf_uniformstdlib_stats_distribution_uniformInterface

Get uniform distribution cumulative distribution function (cdf) for integer, real and complex variables. (Specification)

charstdlib_string_typeInterface

Return the character sequence represented by the string.

Read more…
checkstdlib_errorSubroutine

Checks the value of a logical condition (Specification)

Read more…
chompstdlib_stringsInterface

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

Read more…
clipstdlib_mathInterface
copy_keystdlib_hashmap_wrappersSubroutine

Copies the contents of the key, old_key, to the key, new_key (Specifications)

Read more…
copy_otherstdlib_hashmap_wrappersSubroutine

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

Read more…
corrstdlib_statsInterface

Pearson correlation of array elements (Specification)

countstdlib_stringsInterface

Returns the number of times substring 'pattern' has appeared in the input string 'string' Specifications

covstdlib_statsInterface

Covariance of array elements (Specification)

cross_productstdlib_linalgInterface

Computes the cross product of two vectors, returning a rank-1 and size-3 array (Specification)

diagstdlib_linalgInterface

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

diffstdlib_mathInterface

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

dist_randstdlib_randomInterface

Version experimental

Read more…
dlegendrestdlib_specialfunctionsInterface

First derivative Legendre polynomial

ends_withstdlib_stringsInterface

Check whether a string ends with substring or not

Read more…
error_handlerstdlib_bitsetsSubroutine
error_stopstdlib_errorInterface
extractstdlib_bitsetsInterface

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…
eyestdlib_linalgFunction

Constructs the identity matrix. (Specification)

falselocstdlib_arrayFunction

Return the positions of the false elements in array. Specification

fibonacci_hashstdlib_hash_64bitFunction

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

fibonacci_hashstdlib_hash_32bitFunction

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

fidxstdlib_stringlist_typeInterface

Returns an instance of type 'stringlist_index_type' representing forward index Specifications

findstdlib_stringsInterface

Finds the starting index of substring 'pattern' in the input 'string' Specifications

Read more…
fnv_1_hashstdlib_hash_64bitInterface

FNV_1 interfaces (Specification)

fnv_1_hashstdlib_hash_32bitInterface

FNV_1 interfaces (Specification)

fnv_1_hasherstdlib_hashmap_wrappersFunction

Hashes a key with the FNV_1 algorithm Arguments: key - the key to be hashed

fnv_1a_hashstdlib_hash_64bitInterface

FNV_1A interfaces (Specification)

fnv_1a_hashstdlib_hash_32bitInterface

FNV_1A interfaces (Specification)

fnv_1a_hasherstdlib_hashmap_wrappersFunction

Hashes a key with the FNV_1a algorithm (Specifications)

Read more…
free_keystdlib_hashmap_wrappersSubroutine

Frees the memory in a key (Specifications)

Read more…
free_otherstdlib_hashmap_wrappersSubroutine

Frees the memory in the other data (Specifications)

Read more…
gammastdlib_specialfunctions_gammaInterface

Gamma function for integer and complex numbers

gauss_legendrestdlib_quadratureInterface

Computes Gauss-Legendre quadrature nodes and weights.

gauss_legendre_lobattostdlib_quadratureInterface

Computes Gauss-Legendre-Lobatto quadrature nodes and weights.

gcdstdlib_mathInterface

Returns the greatest common divisor of two integers (Specification)

Read more…
getstdlib_hashmap_wrappersInterface
get_stdlib_versionstdlib_versionSubroutine

Getter function to retrieve standard library version

getlinestdlib_ioInterface

Read a whole line from a formatted unit into a string variable

iacharstdlib_string_typeInterface

Code in ASCII collating sequence.

Read more…
icharstdlib_string_typeInterface

Character-to-integer conversion function.

Read more…
indexstdlib_string_typeInterface

Position of a substring within a string.

Read more…
is_alphastdlib_asciiFunction

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

is_alphanumstdlib_asciiFunction

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

is_asciistdlib_asciiFunction

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

is_blankstdlib_asciiFunction

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

is_closestdlib_mathInterface

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

is_controlstdlib_asciiFunction

Checks whether c is a control character.

is_diagonalstdlib_linalgInterface

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

is_digitstdlib_asciiFunction

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

is_graphicalstdlib_asciiFunction

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

is_hermitianstdlib_linalgInterface

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

is_hessenbergstdlib_linalgInterface

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

is_hex_digitstdlib_asciiFunction

Checks whether c is a digit in base 16 (0 .. 9, A .. F, a .. f).

is_lowerstdlib_asciiFunction

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

is_octal_digitstdlib_asciiFunction

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

is_printablestdlib_asciiFunction

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

is_punctuationstdlib_asciiFunction

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_symmetricstdlib_linalgInterface

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

is_squarestdlib_linalgInterface

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

is_symmetricstdlib_linalgInterface

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

is_triangularstdlib_linalgInterface

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

is_upperstdlib_asciiFunction

Checks whether c is an uppercase ASCII letter (A .. Z).

is_whitestdlib_asciiFunction

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

kronecker_productstdlib_linalgInterface

Computes the Kronecker product of two arrays of size M1xN1, and of M2xN2, returning an (M1M2)x(N1N2) array (Specification)

legendrestdlib_specialfunctionsInterface

Legendre polynomial

lenstdlib_string_typeInterface

Returns the length of the character sequence represented by the string.

Read more…
len_trimstdlib_string_typeInterface

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

Read more…
lgestdlib_string_typeInterface

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…
lgtstdlib_string_typeInterface

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…
linspacestdlib_mathInterface

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…
llestdlib_string_typeInterface

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…
lltstdlib_string_typeInterface

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_npystdlib_io_npyInterface

Load multidimensional array in npy format (Specification)

loadtxtstdlib_ioInterface

Loads a 2D array from a text file (Specification)

log_factorialstdlib_specialfunctions_gammaInterface

Logarithm of factorial n!, integer variable

log_gammastdlib_specialfunctions_gammaInterface

Logarithm of gamma function

log_lower_incomplete_gammastdlib_specialfunctions_gammaInterface

Logarithm of lower incomplete gamma function

log_upper_incomplete_gammastdlib_specialfunctions_gammaInterface

Logarithm of upper incomplete gamma function

logspacestdlib_mathInterface

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_gammastdlib_specialfunctions_gammaInterface

Lower incomplete gamma function

meanstdlib_statsInterface

Mean of array elements (Specification)

medianstdlib_statsInterface

Median of array elements (Specification)

momentstdlib_statsInterface

Central moment of array elements (Specification)

movestdlib_string_typeInterface

Moves the allocated character scalar from 'from' to 'to' Specifications

new_nmhash32_seedstdlib_hash_32bitInterface

(Specification

new_nmhash32x_seedstdlib_hash_32bitInterface

(Specification)

new_pengy_hash_seedstdlib_hash_64bitInterface
new_spooky_hash_seedstdlib_hash_64bitInterface
new_water_hash_seedstdlib_hash_32bitInterface

(Specification)

nmhash32stdlib_hash_32bitInterface

NMHASH32 interfaces (Specification)

nmhash32xstdlib_hash_32bitInterface

NMHASH32X interfaces (Specification)

odd_random_integerstdlib_hash_64bitSubroutine

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

odd_random_integerstdlib_hash_32bitSubroutine

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

openstdlib_ioFunction

Opens a file (Specification)

Read more…
operator(+)stdlib_ansiInterface
operator(//)stdlib_stringlist_typeInterface

Concatenates stringlist with the input entity Returns a new stringlist Specifications

operator(//)stdlib_ansiInterface
operator(//)stdlib_string_typeInterface

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_stringlist_typeInterface

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

operator(/=)stdlib_bitsetsInterface

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_string_typeInterface

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_bitsetsInterface

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_string_typeInterface

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_bitsetsInterface

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_string_typeInterface

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_hashmap_wrappersInterface
operator(==)stdlib_stringlist_typeInterface

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

operator(==)stdlib_bitsetsInterface

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_string_typeInterface

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_bitsetsInterface

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_string_typeInterface

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_bitsetsInterface

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…
operator(>=)stdlib_string_typeInterface

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…
optvalstdlib_optvalInterface

Fallback value for optional arguments (Specification)

orstdlib_bitsetsInterface

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_sortstdlib_sortingInterface

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_productstdlib_linalgInterface

Computes the outer product of two vectors, returning a rank-2 array (Specification)

padlstdlib_stringsInterface

Left pad the input string Specifications

padrstdlib_stringsInterface

Right pad the input string Specifications

parse_modestdlib_ioFunction
pdf_expstdlib_stats_distribution_exponentialInterface

Version experimental

Read more…
pdf_normalstdlib_stats_distribution_normalInterface

Normal Distribution Probability Density Function (Specification)

pdf_uniformstdlib_stats_distribution_uniformInterface

Get uniform distribution probability density (pdf) for integer, real and complex variables. (Specification)

pengy_hashstdlib_hash_64bitInterface

PENGY_HASH interfaces (Specification)

radix_sortstdlib_sortingInterface

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_seedstdlib_randomInterface

Version experimental

Read more…
read(formatted)stdlib_string_typeInterface

Read a character sequence from a connected unformatted unit into the string.

read(unformatted)stdlib_string_typeInterface

Read a character sequence from a connected unformatted unit into the string.

regularized_gamma_pstdlib_specialfunctions_gammaInterface

Regularized (normalized) lower incomplete gamma function, P

regularized_gamma_qstdlib_specialfunctions_gammaInterface

Regularized (normalized) upper incomplete gamma function, Q

repeatstdlib_string_typeInterface

Repeats the character sequence hold by the string by the number of specified copies.

Read more…
replace_allstdlib_stringsInterface

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

reversestdlib_asciiFunction

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

Read more…
reversestdlib_string_typeInterface

Reverses the character sequence hold by the input string

Read more…
rvs_expstdlib_stats_distribution_exponentialInterface

Version experimental

Read more…
rvs_normalstdlib_stats_distribution_normalInterface

Normal Distribution Random Variates (Specification)

rvs_uniformstdlib_stats_distribution_uniformInterface

Get uniformly distributed random variate for integer, real and complex variables. (Specification)

save_npystdlib_io_npyInterface

Save multidimensional array in npy format (Specification)

savetxtstdlib_ioInterface

Saves a 2D array into a text file (Specification)

scanstdlib_string_typeInterface

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…
seeded_nmhash32_hasherstdlib_hashmap_wrappersFunction

Hashes a key with the NMHASH32 hash algorithm (Specifications)

Read more…
seeded_nmhash32x_hasherstdlib_hashmap_wrappersFunction

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_hasherstdlib_hashmap_wrappersFunction

Hashes a key with the waterhash algorithm (Specifications)

Read more…
selectstdlib_selectionInterface

(Specification)

setstdlib_hashmap_wrappersInterface
shufflestdlib_stats_distribution_uniformInterface

Fisher-Yates shuffle algorithm for a rank one array of integer, real and complex variables. (Specification)

simpsstdlib_quadratureInterface

Integrates sampled values using Simpson's rule (Specification)

simps_weightsstdlib_quadratureInterface

Integrates sampled values using trapezoidal rule weights for given abscissas (Specification)

slicestdlib_stringsInterface

Extracts characters from the input string to return a new string

Read more…
sortstdlib_sortingInterface

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

sort_indexstdlib_sortingInterface

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…
spooky_hashstdlib_hash_64bitInterface

SPOOKY_HASH interfaces (Specification)

spookyHash_128stdlib_hash_64bitInterface
starts_withstdlib_stringsInterface

Check whether a string starts with substring or not

Read more…
string_typestdlib_string_typeInterface

Constructor for new string instances

stringlist_typestdlib_stringlist_typeInterface

Constructor for stringlist Returns an instance of type stringlist_type Specifications

stripstdlib_stringsInterface

Remove leading and trailing whitespace characters.

Read more…
to_lowerstdlib_asciiFunction

Convert character variable to lower case (Specification)

Read more…
to_lowerstdlib_string_typeInterface

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

Read more…
to_sentencestdlib_asciiFunction

Converts character sequence to sentence case (Specification)

Read more…
to_sentencestdlib_string_typeInterface

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

Read more…
to_stringstdlib_ansiInterface
to_stringstdlib_stringsInterface

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

to_titlestdlib_asciiFunction

Converts character sequence to title case (Specification)

Read more…
to_titlestdlib_string_typeInterface

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

Read more…
to_upperstdlib_asciiFunction

Convert character variable to upper case (Specification)

Read more…
to_upperstdlib_string_typeInterface

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

Read more…
tracestdlib_linalgInterface

Computes the trace of a matrix (Specification)

trapzstdlib_quadratureInterface

Integrates sampled values using trapezoidal rule (Specification)

trapz_weightsstdlib_quadratureInterface

Integrates sampled values using trapezoidal rule weights for given abscissas (Specification)

trimstdlib_string_typeInterface

Returns the character sequence hold by the string without trailing spaces.

Read more…
truelocstdlib_arrayFunction

Return the positions of the true elements in array. Specification

universal_mult_hashstdlib_hash_64bitFunction

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)

universal_mult_hashstdlib_hash_32bitFunction

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)

upper_incomplete_gammastdlib_specialfunctions_gammaInterface

Upper incomplete gamma function

varstdlib_statsInterface

Variance of array elements (Specification)

verifystdlib_string_typeInterface

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_hashstdlib_hash_32bitInterface

WATER_HASH interfaces (Specification)

write(formatted)stdlib_string_typeInterface

Write the character sequence hold by the string to a connected formatted unit.

write(unformatted)stdlib_string_typeInterface

Write the character sequence hold by the string to a connected unformatted unit.

xorstdlib_bitsetsInterface

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…
zfillstdlib_stringsInterface

Left pad the input string with zeros. Specifications