@brief Module containing interfaces used in the modules of the Numerical Recipes book software.
@details For details we refer the user to "FORTRAN Numerical Recipes: Numerical recipes in FORTRAN 90".
Variables
Type | Visibility |
Attributes | | Name | | Initial | |
integer(kind=I4B), |
public, |
parameter | :: |
NPAR_ARTH | = | 16 | |
integer(kind=I4B), |
public, |
parameter | :: |
NPAR2_ARTH | = | 8 | |
integer(kind=I4B), |
public, |
parameter | :: |
NPAR_GEOP | = | 4 | |
integer(kind=I4B), |
public, |
parameter | :: |
NPAR2_GEOP | = | 2 | |
integer(kind=I4B), |
public, |
parameter | :: |
NPAR_CUMSUM | = | 16 | |
integer(kind=I4B), |
public, |
parameter | :: |
NPAR_CUMPROD | = | 8 | |
integer(kind=I4B), |
public, |
parameter | :: |
NPAR_POLY | = | 8 | |
integer(kind=I4B), |
public, |
parameter | :: |
NPAR_POLYTERM | = | 8 | |
Interfaces
-
public subroutine array_copy_r(src, dest, n_copied, n_not_copied)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
src | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_copied | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_not_copied | |
-
public subroutine array_copy_d(src, dest, n_copied, n_not_copied)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
src | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_copied | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_not_copied | |
-
public subroutine array_copy_i(src, dest, n_copied, n_not_copied)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
src | |
integer(kind=I4B), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_copied | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_not_copied | |
-
public subroutine swap_i(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
a | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
b | |
-
public subroutine swap_r(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout) |
|
| :: |
a | |
real(kind=SP), |
intent(inout) |
|
| :: |
b | |
-
public subroutine swap_rv(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
-
public subroutine swap_c(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout) |
|
| :: |
a | |
complex(kind=SPC), |
intent(inout) |
|
| :: |
b | |
-
public subroutine swap_cv(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
-
public subroutine swap_cm(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
b | |
-
public subroutine swap_z(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=DPC), |
intent(inout) |
|
| :: |
a | |
complex(kind=DPC), |
intent(inout) |
|
| :: |
b | |
-
public subroutine swap_zv(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
-
public subroutine swap_zm(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
b | |
-
public subroutine masked_swap_rs(a, b, mask)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout) |
|
| :: |
a | |
real(kind=SP), |
intent(inout) |
|
| :: |
b | |
logical(kind=LGT), |
intent(in) |
|
| :: |
mask | |
-
public subroutine masked_swap_rv(a, b, mask)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
mask | |
-
public subroutine masked_swap_rm(a, b, mask)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
b | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:,:) | :: |
mask | |
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
|
|
DIMENSION(:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(:), POINTER
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
|
|
DIMENSION(:,:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
Return Value real(kind=SP),
DIMENSION(:,:), POINTER
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
|
|
DIMENSION(:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value integer(kind=I4B),
DIMENSION(:), POINTER
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
|
|
DIMENSION(:,:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
Return Value integer(kind=I4B),
DIMENSION(:,:), POINTER
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=1), |
|
|
DIMENSION(:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value character(len=1),
DIMENSION(:), POINTER
-
public function imaxloc_r(arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
Return Value integer(kind=I4B)
-
public function imaxloc_i(iarr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
iarr | |
Return Value integer(kind=I4B)
-
public subroutine assert1(n1, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in) |
|
| :: |
n1 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
-
public subroutine assert2(n1, n2, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in) |
|
| :: |
n1 | |
logical, |
intent(in) |
|
| :: |
n2 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
-
public subroutine assert3(n1, n2, n3, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in) |
|
| :: |
n1 | |
logical, |
intent(in) |
|
| :: |
n2 | |
logical, |
intent(in) |
|
| :: |
n3 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
-
public subroutine assert4(n1, n2, n3, n4, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in) |
|
| :: |
n1 | |
logical, |
intent(in) |
|
| :: |
n2 | |
logical, |
intent(in) |
|
| :: |
n3 | |
logical, |
intent(in) |
|
| :: |
n4 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
-
public subroutine assert_v(n, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in), |
|
DIMENSION(:) | :: |
n | |
character(len=*), |
intent(in) |
|
| :: |
string | |
-
public function assert_eq2(n1, n2, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer, |
intent(in) |
|
| :: |
n1 | |
integer, |
intent(in) |
|
| :: |
n2 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Return Value integer
-
public function assert_eq3(n1, n2, n3, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer, |
intent(in) |
|
| :: |
n1 | |
integer, |
intent(in) |
|
| :: |
n2 | |
integer, |
intent(in) |
|
| :: |
n3 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Return Value integer
-
public function assert_eq4(n1, n2, n3, n4, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer, |
intent(in) |
|
| :: |
n1 | |
integer, |
intent(in) |
|
| :: |
n2 | |
integer, |
intent(in) |
|
| :: |
n3 | |
integer, |
intent(in) |
|
| :: |
n4 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Return Value integer
-
public function assert_eqn(nn, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer, |
intent(in), |
|
DIMENSION(:) | :: |
nn | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Return Value integer
-
public function arth_r(first, increment, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
first | |
real(kind=SP), |
intent(in) |
|
| :: |
increment | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(n)
-
public function arth_d(first, increment, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
first | |
real(kind=DP), |
intent(in) |
|
| :: |
increment | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=DP),
DIMENSION(n)
-
public function arth_i(first, increment, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
first | |
integer(kind=I4B), |
intent(in) |
|
| :: |
increment | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value integer(kind=I4B),
DIMENSION(n)
-
public function geop_r(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
first | |
real(kind=SP), |
intent(in) |
|
| :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(n)
-
public function geop_d(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
first | |
real(kind=DP), |
intent(in) |
|
| :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=DP),
DIMENSION(n)
-
public function geop_i(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
first | |
integer(kind=I4B), |
intent(in) |
|
| :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value integer(kind=I4B),
DIMENSION(n)
-
public function geop_c(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SP), |
intent(in) |
|
| :: |
first | |
complex(kind=SP), |
intent(in) |
|
| :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value complex(kind=SP),
DIMENSION(n)
-
public function geop_dv(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
first | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=DP),
DIMENSION(size(first),n)
-
public recursive function cumsum_r(arr, seed) result(ans)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
real(kind=SP), |
intent(in), |
optional |
| :: |
seed | |
Return Value real(kind=SP),
DIMENSION(size(arr))
-
public recursive function cumsum_i(arr, seed) result(ans)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
integer(kind=I4B), |
intent(in), |
optional |
| :: |
seed | |
Return Value integer(kind=I4B),
DIMENSION(size(arr))
-
public function poly_rr(x, coeffs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value real(kind=SP)
-
public function poly_rrv(x, coeffs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function poly_dd(x, coeffs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value real(kind=DP)
-
public function poly_ddv(x, coeffs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value real(kind=DP),
DIMENSION(size(x))
-
public function poly_rc(x, coeffs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value complex(kind=SPC)
-
public function poly_cc(x, coeffs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in) |
|
| :: |
x | |
complex(kind=SPC), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value complex(kind=SPC)
-
public function poly_msk_rrv(x, coeffs, mask)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
mask | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function poly_msk_ddv(x, coeffs, mask)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
mask | |
Return Value real(kind=DP),
DIMENSION(size(x))
-
public recursive function poly_term_rr(a, b) result(u)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
Return Value real(kind=SP),
DIMENSION(size(a))
-
public recursive function poly_term_cc(a, b) result(u)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
complex(kind=SPC), |
intent(in) |
|
| :: |
b | |
Return Value complex(kind=SPC),
DIMENSION(size(a))
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=SP),
DIMENSION(size(a),size(b))
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=DP),
DIMENSION(size(a),size(b))
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=SP),
DIMENSION(size(a),size(b))
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=DP),
DIMENSION(size(a),size(b))
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value integer(kind=I4B),
DIMENSION(size(a),size(b))
-
public subroutine scatter_add_r(dest, source, dest_index)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
source | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
dest_index | |
-
public subroutine scatter_add_d(dest, source, dest_index)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
source | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
dest_index | |
-
public subroutine scatter_max_r(dest, source, dest_index)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
source | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
dest_index | |
-
public subroutine scatter_max_d(dest, source, dest_index)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
source | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
dest_index | |
-
public subroutine diagadd_rv(mat, diag)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
diag | |
-
public subroutine diagadd_r(mat, diag)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
real(kind=SP), |
intent(in) |
|
| :: |
diag | |
-
public subroutine diagmult_rv(mat, diag)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
diag | |
-
public subroutine diagmult_r(mat, diag)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
real(kind=SP), |
intent(in) |
|
| :: |
diag | |
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
mat | |
Return Value real(kind=SP),
DIMENSION(size(mat,1))
-
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
mat | |
Return Value real(kind=DP),
DIMENSION(size(mat,1))
-
public subroutine put_diag_rv(diagv, mat)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
diagv | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
-
public subroutine put_diag_r(scal, mat)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
scal | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
Functions
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
|
|
DIMENSION(:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(:), POINTER
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
|
|
DIMENSION(:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value integer(kind=I4B),
DIMENSION(:), POINTER
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=1), |
|
|
DIMENSION(:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value character(len=1),
DIMENSION(:), POINTER
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
|
|
DIMENSION(:,:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
Return Value real(kind=SP),
DIMENSION(:,:), POINTER
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
|
|
DIMENSION(:,:), POINTER | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
Return Value integer(kind=I4B),
DIMENSION(:,:), POINTER
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
mask | |
Return Value integer(kind=I4B)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
Return Value integer(kind=I4B)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
iarr | |
Return Value integer(kind=I4B)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
Return Value integer(kind=I4B)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer, |
intent(in) |
|
| :: |
n1 | |
integer, |
intent(in) |
|
| :: |
n2 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Return Value integer
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer, |
intent(in) |
|
| :: |
n1 | |
integer, |
intent(in) |
|
| :: |
n2 | |
integer, |
intent(in) |
|
| :: |
n3 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Return Value integer
public function assert_eq4(n1, n2, n3, n4, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer, |
intent(in) |
|
| :: |
n1 | |
integer, |
intent(in) |
|
| :: |
n2 | |
integer, |
intent(in) |
|
| :: |
n3 | |
integer, |
intent(in) |
|
| :: |
n4 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Return Value integer
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer, |
intent(in), |
|
DIMENSION(:) | :: |
nn | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Return Value integer
public function arth_r(first, increment, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
first | |
real(kind=SP), |
intent(in) |
|
| :: |
increment | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(n)
public function arth_d(first, increment, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
first | |
real(kind=DP), |
intent(in) |
|
| :: |
increment | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=DP),
DIMENSION(n)
public function arth_i(first, increment, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
first | |
integer(kind=I4B), |
intent(in) |
|
| :: |
increment | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value integer(kind=I4B),
DIMENSION(n)
public function geop_r(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
first | |
real(kind=SP), |
intent(in) |
|
| :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(n)
public function geop_d(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
first | |
real(kind=DP), |
intent(in) |
|
| :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=DP),
DIMENSION(n)
public function geop_i(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
first | |
integer(kind=I4B), |
intent(in) |
|
| :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value integer(kind=I4B),
DIMENSION(n)
public function geop_c(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SP), |
intent(in) |
|
| :: |
first | |
complex(kind=SP), |
intent(in) |
|
| :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value complex(kind=SP),
DIMENSION(n)
public function geop_dv(first, factor, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
first | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
factor | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=DP),
DIMENSION(size(first),n)
public recursive function cumsum_r(arr, seed) result(ans)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
real(kind=SP), |
intent(in), |
optional |
| :: |
seed | |
Return Value real(kind=SP),
DIMENSION(size(arr))
public recursive function cumsum_i(arr, seed) result(ans)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
integer(kind=I4B), |
intent(in), |
optional |
| :: |
seed | |
Return Value integer(kind=I4B),
DIMENSION(size(arr))
public recursive function cumprod(arr, seed) result(ans)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
real(kind=SP), |
intent(in), |
optional |
| :: |
seed | |
Return Value real(kind=SP),
DIMENSION(size(arr))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value real(kind=SP)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value real(kind=DP)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value complex(kind=SPC)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in) |
|
| :: |
x | |
complex(kind=SPC), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value complex(kind=SPC)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value real(kind=SP),
DIMENSION(size(x))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
Return Value real(kind=DP),
DIMENSION(size(x))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
mask | |
Return Value real(kind=SP),
DIMENSION(size(x))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
coeffs | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
mask | |
Return Value real(kind=DP),
DIMENSION(size(x))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
Return Value real(kind=SP),
DIMENSION(size(a))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
complex(kind=SPC), |
intent(in) |
|
| :: |
b | |
Return Value complex(kind=SPC),
DIMENSION(size(a))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nn | |
Return Value complex(kind=SPC),
DIMENSION(nn)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=SP),
DIMENSION(size(a),size(b))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=DP),
DIMENSION(size(a),size(b))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=SP),
DIMENSION(size(a),size(b))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=SP),
DIMENSION(size(a),size(b))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=SP),
DIMENSION(size(a),size(b))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value real(kind=DP),
DIMENSION(size(a),size(b))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value integer(kind=I4B),
DIMENSION(size(a),size(b))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
Return Value logical(kind=LGT),
DIMENSION(size(a),size(b))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
mat | |
Return Value real(kind=SP),
DIMENSION(size(mat,1))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
mat | |
Return Value real(kind=DP),
DIMENSION(size(mat,1))
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
j | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k | |
integer(kind=I4B), |
intent(in), |
optional |
| :: |
extra | |
Return Value logical(kind=LGT),
DIMENSION(j,k)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
j | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k | |
integer(kind=I4B), |
intent(in), |
optional |
| :: |
extra | |
Return Value logical(kind=LGT),
DIMENSION(j,k)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
v | |
Return Value real(kind=SP)
Subroutines
public subroutine array_copy_r(src, dest, n_copied, n_not_copied)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
src | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_copied | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_not_copied | |
public subroutine array_copy_d(src, dest, n_copied, n_not_copied)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
src | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_copied | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_not_copied | |
public subroutine array_copy_i(src, dest, n_copied, n_not_copied)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
src | |
integer(kind=I4B), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_copied | |
integer(kind=I4B), |
intent(out) |
|
| :: |
n_not_copied | |
public subroutine swap_i(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
a | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
b | |
public subroutine swap_r(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout) |
|
| :: |
a | |
real(kind=SP), |
intent(inout) |
|
| :: |
b | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
public subroutine swap_c(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout) |
|
| :: |
a | |
complex(kind=SPC), |
intent(inout) |
|
| :: |
b | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
b | |
public subroutine swap_z(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=DPC), |
intent(inout) |
|
| :: |
a | |
complex(kind=DPC), |
intent(inout) |
|
| :: |
b | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
b | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout) |
|
| :: |
a | |
real(kind=SP), |
intent(inout) |
|
| :: |
b | |
logical(kind=LGT), |
intent(in) |
|
| :: |
mask | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
mask | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
b | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:,:) | :: |
mask | |
public subroutine assert1(n1, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in) |
|
| :: |
n1 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
public subroutine assert2(n1, n2, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in) |
|
| :: |
n1 | |
logical, |
intent(in) |
|
| :: |
n2 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
public subroutine assert3(n1, n2, n3, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in) |
|
| :: |
n1 | |
logical, |
intent(in) |
|
| :: |
n2 | |
logical, |
intent(in) |
|
| :: |
n3 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
public subroutine assert4(n1, n2, n3, n4, string)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in) |
|
| :: |
n1 | |
logical, |
intent(in) |
|
| :: |
n2 | |
logical, |
intent(in) |
|
| :: |
n3 | |
logical, |
intent(in) |
|
| :: |
n4 | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
logical, |
intent(in), |
|
DIMENSION(:) | :: |
n | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=*), |
intent(in) |
|
| :: |
string | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
source | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
dest_index | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
source | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
dest_index | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
source | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
dest_index | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
dest | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
source | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
dest_index | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
diag | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
real(kind=SP), |
intent(in) |
|
| :: |
diag | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
diag | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
real(kind=SP), |
intent(in) |
|
| :: |
diag | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
diagv | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
scal | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
mat | |
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
mat | |