@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, |
private |
| :: |
private_dummy | | | |
Interfaces
interface
-
public subroutine airy(x, ai, bi, aip, bip)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
ai | |
real(kind=SP), |
intent(out) |
|
| :: |
bi | |
real(kind=SP), |
intent(out) |
|
| :: |
aip | |
real(kind=SP), |
intent(out) |
|
| :: |
bip | |
interface
-
public subroutine amebsa(p, y, pb, yb, ftol, func, iter, temptr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
p | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
pb | |
real(kind=SP), |
intent(inout) |
|
| :: |
yb | |
real(kind=SP), |
intent(in) |
|
| :: |
ftol | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP)
|
integer(kind=I4B), |
intent(inout) |
|
| :: |
iter | |
real(kind=SP), |
intent(in) |
|
| :: |
temptr | |
interface
-
public subroutine amoeba(p, y, ftol, func, iter)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
p | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in) |
|
| :: |
ftol | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP)
|
integer(kind=I4B), |
intent(out) |
|
| :: |
iter | |
interface
-
public subroutine anneal(x, y, iorder)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
integer(kind=I4B), |
intent(inout), |
|
DIMENSION(:) | :: |
iorder | |
interface
-
public subroutine asolve(b, x, itrnsp)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
integer(kind=I4B), |
intent(in) |
|
| :: |
itrnsp | |
interface
-
public subroutine atimes(x, r, itrnsp)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
r | |
integer(kind=I4B), |
intent(in) |
|
| :: |
itrnsp | |
interface
-
public subroutine avevar(data, ave, var)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data | |
real(kind=SP), |
intent(out) |
|
| :: |
ave | |
real(kind=SP), |
intent(out) |
|
| :: |
var | |
interface
-
public subroutine balanc(a)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
interface
-
public subroutine banbks(a, m1, m2, al, indx, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m1 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m2 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
al | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
indx | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
interface
-
public subroutine bandec(a, m1, m2, al, indx, d)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m1 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m2 | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
al | |
integer(kind=I4B), |
intent(out), |
|
DIMENSION(:) | :: |
indx | |
real(kind=SP), |
intent(out) |
|
| :: |
d | |
interface
-
public subroutine banmul(a, m1, m2, x, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m1 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m2 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
b | |
interface
-
public subroutine bcucof(y, y1, y2, y12, d1, d2, c)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(4) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(4) | :: |
y1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(4) | :: |
y2 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(4) | :: |
y12 | |
real(kind=SP), |
intent(in) |
|
| :: |
d1 | |
real(kind=SP), |
intent(in) |
|
| :: |
d2 | |
real(kind=SP), |
intent(out), |
|
DIMENSION(4,4) | :: |
c | |
interface
-
public subroutine bcuint(y, y1, y2, y12, x1l, x1u, x2l, x2u, x1, x2, ansy, ansy1, ansy2)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(4) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(4) | :: |
y1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(4) | :: |
y2 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(4) | :: |
y12 | |
real(kind=SP), |
intent(in) |
|
| :: |
x1l | |
real(kind=SP), |
intent(in) |
|
| :: |
x1u | |
real(kind=SP), |
intent(in) |
|
| :: |
x2l | |
real(kind=SP), |
intent(in) |
|
| :: |
x2u | |
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(out) |
|
| :: |
ansy | |
real(kind=SP), |
intent(out) |
|
| :: |
ansy1 | |
real(kind=SP), |
intent(out) |
|
| :: |
ansy2 | |
-
public subroutine beschb_s(x, gam1, gam2, gampl, gammi)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
x | |
real(kind=DP), |
intent(out) |
|
| :: |
gam1 | |
real(kind=DP), |
intent(out) |
|
| :: |
gam2 | |
real(kind=DP), |
intent(out) |
|
| :: |
gampl | |
real(kind=DP), |
intent(out) |
|
| :: |
gammi | |
-
public subroutine beschb_v(x, gam1, gam2, gampl, gammi)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
gam1 | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
gam2 | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
gampl | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
gammi | |
-
public function bessi_s(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessi_v(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessi0_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessi0_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessi1_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessi1_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
interface
-
public subroutine bessik(x, xnu, ri, rk, rip, rkp)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
xnu | |
real(kind=SP), |
intent(out) |
|
| :: |
ri | |
real(kind=SP), |
intent(out) |
|
| :: |
rk | |
real(kind=SP), |
intent(out) |
|
| :: |
rip | |
real(kind=SP), |
intent(out) |
|
| :: |
rkp | |
-
public function bessj_s(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessj_v(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessj0_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessj0_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessj1_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessj1_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public subroutine bessjy_s(x, xnu, rj, ry, rjp, ryp)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
xnu | |
real(kind=SP), |
intent(out) |
|
| :: |
rj | |
real(kind=SP), |
intent(out) |
|
| :: |
ry | |
real(kind=SP), |
intent(out) |
|
| :: |
rjp | |
real(kind=SP), |
intent(out) |
|
| :: |
ryp | |
-
public subroutine bessjy_v(x, xnu, rj, ry, rjp, ryp)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
xnu | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
rj | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
ry | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
rjp | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
ryp | |
-
public function bessk_s(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessk_v(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessk0_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessk0_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessk1_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessk1_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessy_s(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessy_v(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessy0_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessy0_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function bessy1_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function bessy1_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function beta_s(z, w)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
z | |
real(kind=SP), |
intent(in) |
|
| :: |
w | |
Return Value real(kind=SP)
-
public function beta_v(z, w)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
z | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
w | |
Return Value real(kind=SP),
DIMENSION(size(z))
-
public function betacf_s(a, b, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function betacf_v(a, b, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function betai_s(a, b, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function betai_v(a, b, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(a))
-
public function bico_s(n, k)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k | |
Return Value real(kind=SP)
-
public function bico_v(n, k)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
n | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
k | |
Return Value real(kind=SP),
DIMENSION(size(n))
interface
-
public function bnldev(pp, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
pp | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP)
interface
-
public function brent(ax, bx, cx, func, tol, xmin)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
ax | |
real(kind=SP), |
intent(in) |
|
| :: |
bx | |
real(kind=SP), |
intent(in) |
|
| :: |
cx | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
tol | |
real(kind=SP), |
intent(out) |
|
| :: |
xmin | |
Return Value real(kind=SP)
interface
-
public subroutine broydn(x, check)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
x | |
logical(kind=LGT), |
intent(out) |
|
| :: |
check | |
interface
-
public subroutine bsstep(y, dydx, x, htry, eps, yscal, hdid, hnext, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(inout) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
htry | |
real(kind=SP), |
intent(in) |
|
| :: |
eps | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
yscal | |
real(kind=SP), |
intent(out) |
|
| :: |
hdid | |
real(kind=SP), |
intent(out) |
|
| :: |
hnext | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine caldat(julian, mm, id, iyyy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
julian | |
integer(kind=I4B), |
intent(out) |
|
| :: |
mm | |
integer(kind=I4B), |
intent(out) |
|
| :: |
id | |
integer(kind=I4B), |
intent(out) |
|
| :: |
iyyy | |
interface
-
public function chder(a, b, c)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
Return Value real(kind=SP),
DIMENSION(size(c))
-
public function chebev_s(a, b, c, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function chebev_v(a, b, c, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
interface
-
public function chebft(a, b, n, func)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
Return Value real(kind=SP),
DIMENSION(n)
interface
-
public function chebpc(c)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
Return Value real(kind=SP),
DIMENSION(size(c))
interface
-
public function chint(a, b, c)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
Return Value real(kind=SP),
DIMENSION(size(c))
interface
-
public subroutine choldc(a, p)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
p | |
interface
-
public subroutine cholsl(a, p, b, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
p | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
x | |
interface
-
public subroutine chsone(bins, ebins, knstrn, df, chsq, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
bins | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ebins | |
integer(kind=I4B), |
intent(in) |
|
| :: |
knstrn | |
real(kind=SP), |
intent(out) |
|
| :: |
df | |
real(kind=SP), |
intent(out) |
|
| :: |
chsq | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine chstwo(bins1, bins2, knstrn, df, chsq, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
bins1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
bins2 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
knstrn | |
real(kind=SP), |
intent(out) |
|
| :: |
df | |
real(kind=SP), |
intent(out) |
|
| :: |
chsq | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine cisi(x, ci, si)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
ci | |
real(kind=SP), |
intent(out) |
|
| :: |
si | |
interface
-
public subroutine cntab1(nn, chisq, df, prob, cramrv, ccc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:,:) | :: |
nn | |
real(kind=SP), |
intent(out) |
|
| :: |
chisq | |
real(kind=SP), |
intent(out) |
|
| :: |
df | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
real(kind=SP), |
intent(out) |
|
| :: |
cramrv | |
real(kind=SP), |
intent(out) |
|
| :: |
ccc | |
interface
-
public subroutine cntab2(nn, h, hx, hy, hygx, hxgy, uygx, uxgy, uxy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:,:) | :: |
nn | |
real(kind=SP), |
intent(out) |
|
| :: |
h | |
real(kind=SP), |
intent(out) |
|
| :: |
hx | |
real(kind=SP), |
intent(out) |
|
| :: |
hy | |
real(kind=SP), |
intent(out) |
|
| :: |
hygx | |
real(kind=SP), |
intent(out) |
|
| :: |
hxgy | |
real(kind=SP), |
intent(out) |
|
| :: |
uygx | |
real(kind=SP), |
intent(out) |
|
| :: |
uxgy | |
real(kind=SP), |
intent(out) |
|
| :: |
uxy | |
interface
-
public function convlv(data, respns, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
respns | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
Return Value real(kind=SP),
DIMENSION(size(data))
interface
-
public function correl(data1, data2)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
Return Value real(kind=SP),
DIMENSION(size(data1))
interface
-
public subroutine cosft1(y)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
interface
-
public subroutine cosft2(y, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine covsrt(covar, maska)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
covar | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
maska | |
interface
-
public subroutine cyclic(a, b, c, alpha, beta, r, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
real(kind=SP), |
intent(in) |
|
| :: |
alpha | |
real(kind=SP), |
intent(in) |
|
| :: |
beta | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
r | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
interface
-
public subroutine daub4(a, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
-
public function dawson_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function dawson_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
interface
-
public function dbrent(ax, bx, cx, func, dbrent_dfunc, tol, xmin)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
ax | |
real(kind=SP), |
intent(in) |
|
| :: |
bx | |
real(kind=SP), |
intent(in) |
|
| :: |
cx | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
function dbrent_dfunc(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
tol | |
real(kind=SP), |
intent(out) |
|
| :: |
xmin | |
Return Value real(kind=SP)
interface
-
public subroutine ddpoly(c, x, pd)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
pd | |
interface
-
public function decchk(string, ch)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=1), |
intent(in), |
|
DIMENSION(:) | :: |
string | |
character(len=1), |
intent(out) |
|
| :: |
ch | |
Return Value logical(kind=LGT)
interface
-
public subroutine dfpmin(p, gtol, iter, fret, func, dfunc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
p | |
real(kind=SP), |
intent(in) |
|
| :: |
gtol | |
integer(kind=I4B), |
intent(out) |
|
| :: |
iter | |
real(kind=SP), |
intent(out) |
|
| :: |
fret | |
function func(p)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
p | |
Return Value real(kind=SP)
|
function dfunc(p)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
p | |
Return Value real(kind=SP),
DIMENSION(size(p))
|
interface
-
public function dfridr(func, x, h, err)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
h | |
real(kind=SP), |
intent(out) |
|
| :: |
err | |
Return Value real(kind=SP)
interface
-
public subroutine dftcor(w, delta, a, b, endpts, corre, corim, corfac)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
w | |
real(kind=SP), |
intent(in) |
|
| :: |
delta | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
endpts | |
real(kind=SP), |
intent(out) |
|
| :: |
corre | |
real(kind=SP), |
intent(out) |
|
| :: |
corim | |
real(kind=SP), |
intent(out) |
|
| :: |
corfac | |
interface
-
public subroutine dftint(func, a, b, w, cosint, sinint)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in) |
|
| :: |
w | |
real(kind=SP), |
intent(out) |
|
| :: |
cosint | |
real(kind=SP), |
intent(out) |
|
| :: |
sinint | |
interface
-
public subroutine difeq(k, k1, k2, jsf, is1, isf, indexv, s, y)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k1 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k2 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
jsf | |
integer(kind=I4B), |
intent(in) |
|
| :: |
is1 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isf | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
indexv | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
s | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
y | |
interface
-
public function eclass(lista, listb, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
lista | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
listb | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value integer(kind=I4B),
DIMENSION(n)
interface
-
public function eclazz(equiv, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function equiv(i, j)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
i | |
integer(kind=I4B), |
intent(in) |
|
| :: |
j | |
Return Value logical(kind=LGT)
|
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value integer(kind=I4B),
DIMENSION(n)
interface
-
public function ei(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
interface
-
public subroutine eigsrt(d, v)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
d | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
v | |
-
public function elle_s(phi, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
phi | |
real(kind=SP), |
intent(in) |
|
| :: |
ak | |
Return Value real(kind=SP)
-
public function elle_v(phi, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
phi | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ak | |
Return Value real(kind=SP),
DIMENSION(size(phi))
-
public function ellf_s(phi, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
phi | |
real(kind=SP), |
intent(in) |
|
| :: |
ak | |
Return Value real(kind=SP)
-
public function ellf_v(phi, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
phi | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ak | |
Return Value real(kind=SP),
DIMENSION(size(phi))
-
public function ellpi_s(phi, en, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
phi | |
real(kind=SP), |
intent(in) |
|
| :: |
en | |
real(kind=SP), |
intent(in) |
|
| :: |
ak | |
Return Value real(kind=SP)
-
public function ellpi_v(phi, en, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
phi | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
en | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ak | |
Return Value real(kind=SP),
DIMENSION(size(phi))
interface
-
public subroutine elmhes(a)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
-
public function erf_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function erf_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function erfc_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function erfc_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function erfcc_s(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function erfcc_v(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
interface
-
public subroutine eulsum(sum, term, jterm)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout) |
|
| :: |
sum | |
real(kind=SP), |
intent(in) |
|
| :: |
term | |
integer(kind=I4B), |
intent(in) |
|
| :: |
jterm | |
interface
-
public function evlmem(fdt, d, xms)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
fdt | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
d | |
real(kind=SP), |
intent(in) |
|
| :: |
xms | |
Return Value real(kind=SP)
-
public subroutine expdev_s(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out) |
|
| :: |
harvest | |
-
public subroutine expdev_v(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
harvest | |
interface
-
public function expint(n, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function factln_s(n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP)
-
public function factln_v(n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
n | |
Return Value real(kind=SP),
DIMENSION(size(n))
-
public function factrl_s(n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP)
-
public function factrl_v(n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
n | |
Return Value real(kind=SP),
DIMENSION(size(n))
interface
-
public subroutine fasper(x, y, ofac, hifac, px, py, jmax, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in) |
|
| :: |
ofac | |
real(kind=SP), |
intent(in) |
|
| :: |
hifac | |
real(kind=SP), |
|
|
DIMENSION(:), POINTER | :: |
px | |
real(kind=SP), |
|
|
DIMENSION(:), POINTER | :: |
py | |
integer(kind=I4B), |
intent(out) |
|
| :: |
jmax | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine fdjac(x, fvec, df)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
fvec | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
df | |
interface
-
public subroutine fgauss(x, a, y, dyda)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
dyda | |
interface
-
public subroutine fit(x, y, a, b, siga, sigb, chi2, q, sig)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out) |
|
| :: |
a | |
real(kind=SP), |
intent(out) |
|
| :: |
b | |
real(kind=SP), |
intent(out) |
|
| :: |
siga | |
real(kind=SP), |
intent(out) |
|
| :: |
sigb | |
real(kind=SP), |
intent(out) |
|
| :: |
chi2 | |
real(kind=SP), |
intent(out) |
|
| :: |
q | |
real(kind=SP), |
intent(in), |
optional |
DIMENSION(:) | :: |
sig | |
interface
-
public subroutine fitexy(x, y, sigx, sigy, a, b, siga, sigb, chi2, q)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
sigx | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
sigy | |
real(kind=SP), |
intent(out) |
|
| :: |
a | |
real(kind=SP), |
intent(out) |
|
| :: |
b | |
real(kind=SP), |
intent(out) |
|
| :: |
siga | |
real(kind=SP), |
intent(out) |
|
| :: |
sigb | |
real(kind=SP), |
intent(out) |
|
| :: |
chi2 | |
real(kind=SP), |
intent(out) |
|
| :: |
q | |
interface
-
public subroutine fixrts(d)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
d | |
interface
-
public function fleg(x, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(n)
interface
-
public subroutine flmoon(n, nph, jd, frac)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nph | |
integer(kind=I4B), |
intent(out) |
|
| :: |
jd | |
real(kind=SP), |
intent(out) |
|
| :: |
frac | |
-
public subroutine four1_dp(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
-
public subroutine four1_sp(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine four1_alt(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine four1_gather(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine four2(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine four2_alt(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine four3(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine four3_alt(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine fourcol(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine fourcol_3d(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine fourn_gather(data, nn, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:) | :: |
data | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
nn | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
-
public subroutine fourrow_dp(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=DPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
-
public subroutine fourrow_sp(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine fourrow_3d(data, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(inout), |
|
DIMENSION(:,:,:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public function fpoly(x, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(n)
interface
-
public subroutine fred2(a, b, t, f, w, g, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
t | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
f | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
function g(t)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
t | |
Return Value real(kind=SP),
DIMENSION(size(t))
|
function ak(t, s)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
t | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
s | |
Return Value real(kind=SP),
DIMENSION(size(t),size(s))
|
interface
-
public function fredin(x, a, b, t, f, w, g, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
t | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
f | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
w | |
function g(t)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
t | |
Return Value real(kind=SP),
DIMENSION(size(t))
|
function ak(t, s)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
t | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
s | |
Return Value real(kind=SP),
DIMENSION(size(t),size(s))
|
Return Value real(kind=SP),
DIMENSION(size(x))
interface
-
public subroutine frenel(x, s, c)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
s | |
real(kind=SP), |
intent(out) |
|
| :: |
c | |
interface
-
public subroutine frprmn(p, ftol, iter, fret)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
p | |
real(kind=SP), |
intent(in) |
|
| :: |
ftol | |
integer(kind=I4B), |
intent(out) |
|
| :: |
iter | |
real(kind=SP), |
intent(out) |
|
| :: |
fret | |
interface
-
public subroutine ftest(data1, data2, f, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
real(kind=SP), |
intent(out) |
|
| :: |
f | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public function gamdev(ia)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
ia | |
Return Value real(kind=SP)
-
public function gammln_s(xx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
xx | |
Return Value real(kind=SP)
-
public function gammln_v(xx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xx | |
Return Value real(kind=SP),
DIMENSION(size(xx))
-
public function gammp_s(a, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function gammp_v(a, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(a))
-
public function gammq_s(a, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function gammq_v(a, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(a))
-
public subroutine gasdev_s(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out) |
|
| :: |
harvest | |
-
public subroutine gasdev_v(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
harvest | |
interface
-
public subroutine gaucof(a, b, amu0, x, w)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(in) |
|
| :: |
amu0 | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
interface
-
public subroutine gauher(x, w)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
interface
-
public subroutine gaujac(x, w, alf, bet)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
real(kind=SP), |
intent(in) |
|
| :: |
alf | |
real(kind=SP), |
intent(in) |
|
| :: |
bet | |
interface
-
public subroutine gaulag(x, w, alf)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
real(kind=SP), |
intent(in) |
|
| :: |
alf | |
interface
-
public subroutine gauleg(x1, x2, x, w)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
interface
-
public subroutine gaussj(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
b | |
-
public function gcf_s(a, x, gln)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out), |
optional |
| :: |
gln | |
Return Value real(kind=SP)
-
public function gcf_v(a, x, gln)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
optional |
DIMENSION(:) | :: |
gln | |
Return Value real(kind=SP),
DIMENSION(size(a))
interface
-
public function golden(ax, bx, cx, func, tol, xmin)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
ax | |
real(kind=SP), |
intent(in) |
|
| :: |
bx | |
real(kind=SP), |
intent(in) |
|
| :: |
cx | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
tol | |
real(kind=SP), |
intent(out) |
|
| :: |
xmin | |
Return Value real(kind=SP)
-
public function gser_s(a, x, gln)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out), |
optional |
| :: |
gln | |
Return Value real(kind=SP)
-
public function gser_v(a, x, gln)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
optional |
DIMENSION(:) | :: |
gln | |
Return Value real(kind=SP),
DIMENSION(size(a))
interface
-
public subroutine hqr(a, wr, wi)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
wr | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
wi | |
interface
-
public subroutine hunt(xx, x, jlo)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xx | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
jlo | |
interface
-
public subroutine hypdrv(s, ry, rdyds)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
s | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ry | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
rdyds | |
interface
-
public function hypgeo(a, b, c, z)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in) |
|
| :: |
a | |
complex(kind=SPC), |
intent(in) |
|
| :: |
b | |
complex(kind=SPC), |
intent(in) |
|
| :: |
c | |
complex(kind=SPC), |
intent(in) |
|
| :: |
z | |
Return Value complex(kind=SPC)
interface
-
public subroutine hypser(a, b, c, z, series, deriv)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in) |
|
| :: |
a | |
complex(kind=SPC), |
intent(in) |
|
| :: |
b | |
complex(kind=SPC), |
intent(in) |
|
| :: |
c | |
complex(kind=SPC), |
intent(in) |
|
| :: |
z | |
complex(kind=SPC), |
intent(out) |
|
| :: |
series | |
complex(kind=SPC), |
intent(out) |
|
| :: |
deriv | |
interface
-
public function icrc(crc, buf, jinit, jrev)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I2B), |
intent(in) |
|
| :: |
crc | |
character(len=1), |
intent(in), |
|
DIMENSION(:) | :: |
buf | |
integer(kind=I2B), |
intent(in) |
|
| :: |
jinit | |
integer(kind=I4B), |
intent(in) |
|
| :: |
jrev | |
Return Value integer(kind=I2B)
interface
-
public function igray(n, is)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
is | |
Return Value integer(kind=I4B)
interface
-
public subroutine index_bypack(arr, index, partial)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
integer(kind=I4B), |
intent(inout), |
|
DIMENSION(:) | :: |
index | |
integer, |
intent(in), |
optional |
| :: |
partial | |
-
public subroutine indexx_sp(arr, index)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
integer(kind=I4B), |
intent(out), |
|
DIMENSION(:) | :: |
index | |
-
public subroutine indexx_i4b(iarr, index)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
iarr | |
integer(kind=I4B), |
intent(out), |
|
DIMENSION(:) | :: |
index | |
interface
-
public function interp(uc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
uc | |
Return Value real(kind=DP),
DIMENSION(2*size(uc,1)-1,2*size(uc,1)-1)
interface
-
public function rank(indx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
indx | |
Return Value integer(kind=I4B),
DIMENSION(size(indx))
interface
-
public function irbit1(iseed)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
iseed | |
Return Value integer(kind=I4B)
interface
-
public function irbit2(iseed)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
iseed | |
Return Value integer(kind=I4B)
interface
-
public subroutine jacobi(a, d, v, nrot)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
d | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
v | |
integer(kind=I4B), |
intent(out) |
|
| :: |
nrot | |
interface
-
public subroutine jacobn(x, y, dfdx, dfdy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dfdx | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
dfdy | |
interface
-
public function julday(mm, id, iyyy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
mm | |
integer(kind=I4B), |
intent(in) |
|
| :: |
id | |
integer(kind=I4B), |
intent(in) |
|
| :: |
iyyy | |
Return Value integer(kind=I4B)
interface
-
public subroutine kendl1(data1, data2, tau, z, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
real(kind=SP), |
intent(out) |
|
| :: |
tau | |
real(kind=SP), |
intent(out) |
|
| :: |
z | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine kendl2(tab, tau, z, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
tab | |
real(kind=SP), |
intent(out) |
|
| :: |
tau | |
real(kind=SP), |
intent(out) |
|
| :: |
z | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public function kermom(y, m)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
y | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
Return Value real(kind=DP),
DIMENSION(m)
interface
-
public subroutine ks2d1s(x1, y1, quadvl, d1, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y1 | |
subroutine quadvl(x, y, fa, fb, fc, fd)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
y | |
real(kind=SP), |
intent(out) |
|
| :: |
fa | |
real(kind=SP), |
intent(out) |
|
| :: |
fb | |
real(kind=SP), |
intent(out) |
|
| :: |
fc | |
real(kind=SP), |
intent(out) |
|
| :: |
fd | |
|
real(kind=SP), |
intent(out) |
|
| :: |
d1 | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine ks2d2s(x1, y1, x2, y2, d, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x2 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y2 | |
real(kind=SP), |
intent(out) |
|
| :: |
d | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine ksone(data, func, d, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
data | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(out) |
|
| :: |
d | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine kstwo(data1, data2, d, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
real(kind=SP), |
intent(out) |
|
| :: |
d | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine laguer(a, x, its)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
complex(kind=SPC), |
intent(inout) |
|
| :: |
x | |
integer(kind=I4B), |
intent(out) |
|
| :: |
its | |
interface
-
public subroutine lfit(x, y, sig, a, maska, covar, chisq, funcs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
sig | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
maska | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
covar | |
real(kind=SP), |
intent(out) |
|
| :: |
chisq | |
subroutine funcs(x, arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
arr | |
|
interface
-
public subroutine linbcg(b, x, itol, tol, itmax, iter, err)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:) | :: |
x | |
integer(kind=I4B), |
intent(in) |
|
| :: |
itol | |
real(kind=DP), |
intent(in) |
|
| :: |
tol | |
integer(kind=I4B), |
intent(in) |
|
| :: |
itmax | |
integer(kind=I4B), |
intent(out) |
|
| :: |
iter | |
real(kind=DP), |
intent(out) |
|
| :: |
err | |
interface
-
public subroutine linmin(p, xi, fret)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:), TARGET | :: |
p | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:), TARGET | :: |
xi | |
real(kind=SP), |
intent(out) |
|
| :: |
fret | |
interface
-
public subroutine lnsrch(xold, fold, g, p, x, f, stpmax, check, func)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xold | |
real(kind=SP), |
intent(in) |
|
| :: |
fold | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
g | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
p | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
f | |
real(kind=SP), |
intent(in) |
|
| :: |
stpmax | |
logical(kind=LGT), |
intent(out) |
|
| :: |
check | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP)
|
interface
-
public function locate(xx, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xx | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value integer(kind=I4B)
interface
-
public function lop(u)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
u | |
Return Value real(kind=DP),
DIMENSION(size(u,1),size(u,1))
interface
-
public subroutine lubksb(a, indx, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
indx | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
interface
-
public subroutine ludcmp(a, indx, d)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
integer(kind=I4B), |
intent(out), |
|
DIMENSION(:) | :: |
indx | |
real(kind=SP), |
intent(out) |
|
| :: |
d | |
interface
-
public subroutine machar(ibeta, it, irnd, ngrd, machep, negep, iexp, minexp, maxexp, eps, epsneg, xmin, xmax)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(out) |
|
| :: |
ibeta | |
integer(kind=I4B), |
intent(out) |
|
| :: |
it | |
integer(kind=I4B), |
intent(out) |
|
| :: |
irnd | |
integer(kind=I4B), |
intent(out) |
|
| :: |
ngrd | |
integer(kind=I4B), |
intent(out) |
|
| :: |
machep | |
integer(kind=I4B), |
intent(out) |
|
| :: |
negep | |
integer(kind=I4B), |
intent(out) |
|
| :: |
iexp | |
integer(kind=I4B), |
intent(out) |
|
| :: |
minexp | |
integer(kind=I4B), |
intent(out) |
|
| :: |
maxexp | |
real(kind=SP), |
intent(out) |
|
| :: |
eps | |
real(kind=SP), |
intent(out) |
|
| :: |
epsneg | |
real(kind=SP), |
intent(out) |
|
| :: |
xmin | |
real(kind=SP), |
intent(out) |
|
| :: |
xmax | |
interface
-
public subroutine medfit(x, y, a, b, abdev)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out) |
|
| :: |
a | |
real(kind=SP), |
intent(out) |
|
| :: |
b | |
real(kind=SP), |
intent(out) |
|
| :: |
abdev | |
interface
-
public subroutine memcof(data, xms, d)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data | |
real(kind=SP), |
intent(out) |
|
| :: |
xms | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
d | |
interface
-
public subroutine mgfas(u, maxcyc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
u | |
integer(kind=I4B), |
intent(in) |
|
| :: |
maxcyc | |
interface
-
public subroutine mglin(u, ncycle)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
u | |
integer(kind=I4B), |
intent(in) |
|
| :: |
ncycle | |
interface
-
public subroutine midexp(funk, aa, bb, s, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function funk(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
aa | |
real(kind=SP), |
intent(in) |
|
| :: |
bb | |
real(kind=SP), |
intent(inout) |
|
| :: |
s | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
interface
-
public subroutine midinf(funk, aa, bb, s, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function funk(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
aa | |
real(kind=SP), |
intent(in) |
|
| :: |
bb | |
real(kind=SP), |
intent(inout) |
|
| :: |
s | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
interface
-
public subroutine midpnt(func, a, b, s, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(inout) |
|
| :: |
s | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
interface
-
public subroutine midsql(funk, aa, bb, s, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function funk(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
aa | |
real(kind=SP), |
intent(in) |
|
| :: |
bb | |
real(kind=SP), |
intent(inout) |
|
| :: |
s | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
interface
-
public subroutine midsqu(funk, aa, bb, s, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function funk(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
aa | |
real(kind=SP), |
intent(in) |
|
| :: |
bb | |
real(kind=SP), |
intent(inout) |
|
| :: |
s | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
interface
-
public subroutine miser(func, regn, ndim, npts, dith, ave, var)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
regn | |
integer(kind=I4B), |
intent(in) |
|
| :: |
ndim | |
integer(kind=I4B), |
intent(in) |
|
| :: |
npts | |
real(kind=SP), |
intent(in) |
|
| :: |
dith | |
real(kind=SP), |
intent(out) |
|
| :: |
ave | |
real(kind=SP), |
intent(out) |
|
| :: |
var | |
interface
-
public subroutine mmid(y, dydx, xs, htot, nstep, yout, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(in) |
|
| :: |
xs | |
real(kind=SP), |
intent(in) |
|
| :: |
htot | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nstep | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yout | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine mnbrak(ax, bx, cx, fa, fb, fc, func)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout) |
|
| :: |
ax | |
real(kind=SP), |
intent(inout) |
|
| :: |
bx | |
real(kind=SP), |
intent(out) |
|
| :: |
cx | |
real(kind=SP), |
intent(out) |
|
| :: |
fa | |
real(kind=SP), |
intent(out) |
|
| :: |
fb | |
real(kind=SP), |
intent(out) |
|
| :: |
fc | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
interface
-
public subroutine mnewt(ntrial, x, tolx, tolf, usrfun)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
ntrial | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
tolx | |
real(kind=SP), |
intent(in) |
|
| :: |
tolf | |
subroutine usrfun(x, fvec, fjac)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
fvec | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
fjac | |
|
interface
-
public subroutine moment(data, ave, adev, sdev, var, skew, curt)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data | |
real(kind=SP), |
intent(out) |
|
| :: |
ave | |
real(kind=SP), |
intent(out) |
|
| :: |
adev | |
real(kind=SP), |
intent(out) |
|
| :: |
sdev | |
real(kind=SP), |
intent(out) |
|
| :: |
var | |
real(kind=SP), |
intent(out) |
|
| :: |
skew | |
real(kind=SP), |
intent(out) |
|
| :: |
curt | |
interface
-
public subroutine mp2dfr(a, s, n, m)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=1), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
character(len=1), |
intent(out), |
|
DIMENSION(:) | :: |
s | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(out) |
|
| :: |
m | |
interface
-
public subroutine mpdiv(q, r, u, v, n, m)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=1), |
intent(out), |
|
DIMENSION(:) | :: |
q | |
character(len=1), |
intent(out), |
|
DIMENSION(:) | :: |
r | |
character(len=1), |
intent(in), |
|
DIMENSION(:) | :: |
u | |
character(len=1), |
intent(in), |
|
DIMENSION(:) | :: |
v | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
interface
-
public subroutine mpinv(u, v, n, m)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=1), |
intent(out), |
|
DIMENSION(:) | :: |
u | |
character(len=1), |
intent(in), |
|
DIMENSION(:) | :: |
v | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
interface
-
public subroutine mpmul(w, u, v, n, m)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=1), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
character(len=1), |
intent(in), |
|
DIMENSION(:) | :: |
u | |
character(len=1), |
intent(in), |
|
DIMENSION(:) | :: |
v | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
interface
-
public subroutine mppi(n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
interface
-
public subroutine mprove(a, alud, indx, b, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
alud | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
indx | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
x | |
interface
-
public subroutine mpSQRT(w, u, v, n, m)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
character(len=1), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
character(len=1), |
intent(out), |
|
DIMENSION(:) | :: |
u | |
character(len=1), |
intent(in), |
|
DIMENSION(:) | :: |
v | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
interface
-
public subroutine mrqcof(x, y, sig, a, maska, alpha, beta, chisq, funcs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
sig | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
maska | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
alpha | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
beta | |
real(kind=SP), |
intent(out) |
|
| :: |
chisq | |
subroutine funcs(x, a, yfit, dyda)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yfit | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
dyda | |
|
interface
-
public subroutine mrqmin(x, y, sig, a, maska, covar, alpha, chisq, funcs, alamda)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
sig | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
logical(kind=LGT), |
intent(in), |
|
DIMENSION(:) | :: |
maska | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
covar | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
alpha | |
real(kind=SP), |
intent(out) |
|
| :: |
chisq | |
subroutine funcs(x, a, yfit, dyda)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yfit | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
dyda | |
|
real(kind=SP), |
intent(inout) |
|
| :: |
alamda | |
interface
-
public subroutine newt(x, check)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
x | |
logical(kind=LGT), |
intent(out) |
|
| :: |
check | |
interface
-
public subroutine odeint(ystart, x1, x2, eps, h1, hmin, derivs, rkqs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
ystart | |
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(in) |
|
| :: |
eps | |
real(kind=SP), |
intent(in) |
|
| :: |
h1 | |
real(kind=SP), |
intent(in) |
|
| :: |
hmin | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
subroutine rkqs(y, dydx, x, htry, eps, yscal, hdid, hnext, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(inout) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
htry | |
real(kind=SP), |
intent(in) |
|
| :: |
eps | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
yscal | |
real(kind=SP), |
intent(out) |
|
| :: |
hdid | |
real(kind=SP), |
intent(out) |
|
| :: |
hnext | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
|
interface
-
public subroutine orthog(anu, alpha, beta, a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
anu | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
alpha | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
beta | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
b | |
interface
-
public subroutine pade(cof, resid)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:) | :: |
cof | |
real(kind=SP), |
intent(out) |
|
| :: |
resid | |
interface
-
public function pccheb(d)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
d | |
Return Value real(kind=SP),
DIMENSION(size(d))
interface
-
public subroutine pcshft(a, b, d)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
d | |
interface
-
public subroutine pearsn(x, y, r, prob, z)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out) |
|
| :: |
r | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
real(kind=SP), |
intent(out) |
|
| :: |
z | |
interface
-
public subroutine period(x, y, ofac, hifac, px, py, jmax, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in) |
|
| :: |
ofac | |
real(kind=SP), |
intent(in) |
|
| :: |
hifac | |
real(kind=SP), |
|
|
DIMENSION(:), POINTER | :: |
px | |
real(kind=SP), |
|
|
DIMENSION(:), POINTER | :: |
py | |
integer(kind=I4B), |
intent(out) |
|
| :: |
jmax | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
-
public function plgndr_s(l, m, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
l | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public function plgndr_v(l, m, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
l | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
interface
-
public function poidev(xm)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
xm | |
Return Value real(kind=SP)
interface
-
public function polcoe(x, y)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
Return Value real(kind=SP),
DIMENSION(size(x))
interface
-
public function polcof(xa, ya)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xa | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ya | |
Return Value real(kind=SP),
DIMENSION(size(xa))
interface
-
public subroutine poldiv(u, v, q, r)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
u | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
v | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
q | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
r | |
interface
-
public subroutine polin2(x1a, x2a, ya, x1, x2, y, dy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x1a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x2a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
ya | |
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(out) |
|
| :: |
y | |
real(kind=SP), |
intent(out) |
|
| :: |
dy | |
interface
-
public subroutine polint(xa, ya, x, y, dy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xa | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ya | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
y | |
real(kind=SP), |
intent(out) |
|
| :: |
dy | |
interface
-
public subroutine powell(p, xi, ftol, iter, fret)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
p | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
xi | |
real(kind=SP), |
intent(in) |
|
| :: |
ftol | |
integer(kind=I4B), |
intent(out) |
|
| :: |
iter | |
real(kind=SP), |
intent(out) |
|
| :: |
fret | |
interface
-
public function predic(data, d, nfut)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
d | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nfut | |
Return Value real(kind=SP),
DIMENSION(nfut)
interface
-
public function probks(alam)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
alam | |
Return Value real(kind=SP)
-
public subroutine psdes_s(lword, rword)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
lword | |
integer(kind=I4B), |
intent(inout) |
|
| :: |
rword | |
-
public subroutine psdes_v(lword, rword)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(inout), |
|
DIMENSION(:) | :: |
lword | |
integer(kind=I4B), |
intent(inout), |
|
DIMENSION(:) | :: |
rword | |
interface
-
public subroutine pwt(a, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine pwtset(n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
-
public function pythag_dp(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
a | |
real(kind=DP), |
intent(in) |
|
| :: |
b | |
Return Value real(kind=DP)
-
public function pythag_sp(a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
Return Value real(kind=SP)
interface
-
public subroutine pzextr(iest, xest, yest, yz, dy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
iest | |
real(kind=SP), |
intent(in) |
|
| :: |
xest | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
yest | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yz | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dy | |
interface
-
public subroutine qrdcmp(a, c, d, sing)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
c | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
d | |
logical(kind=LGT), |
intent(out) |
|
| :: |
sing | |
interface
-
public function qromb(func, a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
Return Value real(kind=SP)
interface
-
public function qromo(func, a, b, choose)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
subroutine choose(funk, aa, bb, s, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function funk(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
aa | |
real(kind=SP), |
intent(in) |
|
| :: |
bb | |
real(kind=SP), |
intent(inout) |
|
| :: |
s | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
|
Return Value real(kind=SP)
interface
-
public subroutine qroot(p, b, c, eps)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
p | |
real(kind=SP), |
intent(inout) |
|
| :: |
b | |
real(kind=SP), |
intent(inout) |
|
| :: |
c | |
real(kind=SP), |
intent(in) |
|
| :: |
eps | |
interface
-
public subroutine qrsolv(a, c, d, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
d | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
interface
-
public subroutine qrupdt(r, qt, u, v)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
r | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
qt | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
u | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
v | |
interface
-
public function qsimp(func, a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
Return Value real(kind=SP)
interface
-
public function qtrap(func, a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
Return Value real(kind=SP)
interface
-
public subroutine quadct(x, y, xx, yy, fa, fb, fc, fd)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xx | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
yy | |
real(kind=SP), |
intent(out) |
|
| :: |
fa | |
real(kind=SP), |
intent(out) |
|
| :: |
fb | |
real(kind=SP), |
intent(out) |
|
| :: |
fc | |
real(kind=SP), |
intent(out) |
|
| :: |
fd | |
interface
-
public subroutine quadmx(a)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
a | |
interface
-
public subroutine quadvl(x, y, fa, fb, fc, fd)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
y | |
real(kind=SP), |
intent(out) |
|
| :: |
fa | |
real(kind=SP), |
intent(out) |
|
| :: |
fb | |
real(kind=SP), |
intent(out) |
|
| :: |
fc | |
real(kind=SP), |
intent(out) |
|
| :: |
fd | |
interface
-
public function ran(idum)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=selected_int_kind(9)), |
intent(inout) |
|
| :: |
idum | |
Return Value real
-
public subroutine ran0_s(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out) |
|
| :: |
harvest | |
-
public subroutine ran0_v(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
harvest | |
-
public subroutine ran1_s(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out) |
|
| :: |
harvest | |
-
public subroutine ran1_v(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
harvest | |
-
public subroutine ran2_s(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out) |
|
| :: |
harvest | |
-
public subroutine ran2_v(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
harvest | |
-
public subroutine ran3_s(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out) |
|
| :: |
harvest | |
-
public subroutine ran3_v(harvest)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
harvest | |
interface
-
public subroutine ratint(xa, ya, x, y, dy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xa | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ya | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
y | |
real(kind=SP), |
intent(out) |
|
| :: |
dy | |
interface
-
public subroutine ratlsq(func, a, b, mm, kk, cof, dev)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=DP),
DIMENSION(size(x))
|
real(kind=DP), |
intent(in) |
|
| :: |
a | |
real(kind=DP), |
intent(in) |
|
| :: |
b | |
integer(kind=I4B), |
intent(in) |
|
| :: |
mm | |
integer(kind=I4B), |
intent(in) |
|
| :: |
kk | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
cof | |
real(kind=DP), |
intent(out) |
|
| :: |
dev | |
-
public function ratval_s(x, cof, mm, kk)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(mm+kk+1) | :: |
cof | |
integer(kind=I4B), |
intent(in) |
|
| :: |
mm | |
integer(kind=I4B), |
intent(in) |
|
| :: |
kk | |
Return Value real(kind=DP)
-
public function ratval_v(x, cof, mm, kk)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(mm+kk+1) | :: |
cof | |
integer(kind=I4B), |
intent(in) |
|
| :: |
mm | |
integer(kind=I4B), |
intent(in) |
|
| :: |
kk | |
Return Value real(kind=DP),
DIMENSION(size(x))
-
public function rc_s(x, y)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
y | |
Return Value real(kind=SP)
-
public function rc_v(x, y)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function rd_s(x, y, z)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
y | |
real(kind=SP), |
intent(in) |
|
| :: |
z | |
Return Value real(kind=SP)
-
public function rd_v(x, y, z)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
z | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public subroutine realft_dp(data, isign, zdata)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
complex(kind=DPC), |
|
optional |
DIMENSION(:), TARGET | :: |
zdata | |
-
public subroutine realft_sp(data, isign, zdata)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
data | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
complex(kind=SPC), |
|
optional |
DIMENSION(:), TARGET | :: |
zdata | |
interface
-
public recursive function recur1(a, b) result(u)
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))
interface
-
public function recur2(a, b, c)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
Return Value real(kind=SP),
DIMENSION(size(a))
interface
-
public subroutine relax(u, rhs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
u | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
rhs | |
interface
-
public subroutine relax2(u, rhs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
u | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
rhs | |
interface
-
public function resid(u, rhs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
u | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
rhs | |
Return Value real(kind=DP),
DIMENSION(size(u,1),size(u,1))
-
public function rf_s(x, y, z)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
y | |
real(kind=SP), |
intent(in) |
|
| :: |
z | |
Return Value real(kind=SP)
-
public function rf_v(x, y, z)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
z | |
Return Value real(kind=SP),
DIMENSION(size(x))
-
public function rj_s(x, y, z, p)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
y | |
real(kind=SP), |
intent(in) |
|
| :: |
z | |
real(kind=SP), |
intent(in) |
|
| :: |
p | |
Return Value real(kind=SP)
-
public function rj_v(x, y, z, p)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
z | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
p | |
Return Value real(kind=SP),
DIMENSION(size(x))
interface
-
public subroutine rk4(y, dydx, x, h, yout, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
h | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yout | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine rkck(y, dydx, x, h, yout, yerr, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
h | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yout | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yerr | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine rkdumb(vstart, x1, x2, nstep, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
vstart | |
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nstep | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine rkqs(y, dydx, x, htry, eps, yscal, hdid, hnext, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(inout) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
htry | |
real(kind=SP), |
intent(in) |
|
| :: |
eps | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
yscal | |
real(kind=SP), |
intent(out) |
|
| :: |
hdid | |
real(kind=SP), |
intent(out) |
|
| :: |
hnext | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine rlft2(data, spec, speq, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
data | |
complex(kind=SPC), |
intent(out), |
|
DIMENSION(:,:) | :: |
spec | |
complex(kind=SPC), |
intent(out), |
|
DIMENSION(:) | :: |
speq | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine rlft3(data, spec, speq, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:,:) | :: |
data | |
complex(kind=SPC), |
intent(out), |
|
DIMENSION(:,:,:) | :: |
spec | |
complex(kind=SPC), |
intent(out), |
|
DIMENSION(:,:) | :: |
speq | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
interface
-
public subroutine rotate(r, qt, i, a, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:), TARGET | :: |
r | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:), TARGET | :: |
qt | |
integer(kind=I4B), |
intent(in) |
|
| :: |
i | |
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
interface
-
public subroutine rsolv(a, d, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
d | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
b | |
interface
-
public function rstrct(uf)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
uf | |
Return Value real(kind=DP),
DIMENSION((size(uf,1)+1)/2,(size(uf,1)+1)/2)
interface
-
public function rtbis(func, x1, x2, xacc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(in) |
|
| :: |
xacc | |
Return Value real(kind=SP)
interface
-
public function rtflsp(func, x1, x2, xacc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(in) |
|
| :: |
xacc | |
Return Value real(kind=SP)
interface
-
public function rtnewt(funcd, x1, x2, xacc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
subroutine funcd(x, fval, fderiv)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
fval | |
real(kind=SP), |
intent(out) |
|
| :: |
fderiv | |
|
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(in) |
|
| :: |
xacc | |
Return Value real(kind=SP)
interface
-
public function rtsafe(funcd, x1, x2, xacc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
subroutine funcd(x, fval, fderiv)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
fval | |
real(kind=SP), |
intent(out) |
|
| :: |
fderiv | |
|
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(in) |
|
| :: |
xacc | |
Return Value real(kind=SP)
interface
-
public function rtsec(func, x1, x2, xacc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(in) |
|
| :: |
xacc | |
Return Value real(kind=SP)
interface
-
public subroutine rzextr(iest, xest, yest, yz, dy)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
iest | |
real(kind=SP), |
intent(in) |
|
| :: |
xest | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
yest | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yz | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dy | |
interface
-
public function savgol(nl, nrr, ld, m)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nl | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nrr | |
integer(kind=I4B), |
intent(in) |
|
| :: |
ld | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
Return Value real(kind=SP),
DIMENSION(nl+nrr+1)
interface
-
public subroutine scrsho(func)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
interface
-
public function select(k, arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
Return Value real(kind=SP)
interface
-
public function select_bypack(k, arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
Return Value real(kind=SP)
interface
-
public subroutine select_heap(arr, heap)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
heap | |
interface
-
public function select_inplace(k, arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
arr | |
Return Value real(kind=SP)
interface
-
public subroutine simplx(a, m1, m2, m3, icase, izrov, iposv)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m1 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m2 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m3 | |
integer(kind=I4B), |
intent(out) |
|
| :: |
icase | |
integer(kind=I4B), |
intent(out), |
|
DIMENSION(:) | :: |
izrov | |
integer(kind=I4B), |
intent(out), |
|
DIMENSION(:) | :: |
iposv | |
interface
-
public subroutine simpr(y, dydx, dfdx, dfdy, xs, htot, nstep, yout, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dfdx | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
dfdy | |
real(kind=SP), |
intent(in) |
|
| :: |
xs | |
real(kind=SP), |
intent(in) |
|
| :: |
htot | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nstep | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yout | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine sinft(y)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
interface
-
public subroutine slvsm2(u, rhs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(out), |
|
DIMENSION(3,3) | :: |
u | |
real(kind=DP), |
intent(in), |
|
DIMENSION(3,3) | :: |
rhs | |
interface
-
public subroutine slvsml(u, rhs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(out), |
|
DIMENSION(3,3) | :: |
u | |
real(kind=DP), |
intent(in), |
|
DIMENSION(3,3) | :: |
rhs | |
interface
-
public subroutine sncndn(uu, emmc, sn, cn, dn)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
uu | |
real(kind=SP), |
intent(in) |
|
| :: |
emmc | |
real(kind=SP), |
intent(out) |
|
| :: |
sn | |
real(kind=SP), |
intent(out) |
|
| :: |
cn | |
real(kind=SP), |
intent(out) |
|
| :: |
dn | |
interface
-
public function snrm(sx, itol)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
sx | |
integer(kind=I4B), |
intent(in) |
|
| :: |
itol | |
Return Value real(kind=DP)
interface
-
public subroutine sobseq(x, init)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
integer(kind=I4B), |
intent(in), |
optional |
| :: |
init | |
interface
-
public subroutine solvde(itmax, conv, slowc, scalv, indexv, nb, y)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
itmax | |
real(kind=SP), |
intent(in) |
|
| :: |
conv | |
real(kind=SP), |
intent(in) |
|
| :: |
slowc | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
scalv | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
indexv | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nb | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
y | |
interface
-
public subroutine sor(a, b, c, d, e, f, u, rjac)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
b | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
c | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
d | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
e | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
f | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
u | |
real(kind=DP), |
intent(in) |
|
| :: |
rjac | |
interface
-
public subroutine sort(arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
interface
-
public subroutine sort2(arr, slave)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
slave | |
interface
-
public subroutine sort3(arr, slave1, slave2)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
slave1 | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
slave2 | |
interface
-
public subroutine sort_bypack(arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
interface
-
public subroutine sort_byreshape(arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
interface
-
public subroutine sort_heap(arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
interface
-
public subroutine sort_pick(arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
interface
-
public subroutine sort_radix(arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
interface
-
public subroutine sort_shell(arr)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
arr | |
interface
-
public subroutine spctrm(p, k, ovrlap, unit, n_window)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
p | |
integer(kind=I4B), |
intent(in) |
|
| :: |
k | |
logical(kind=LGT), |
intent(in) |
|
| :: |
ovrlap | |
integer(kind=I4B), |
intent(in), |
optional |
| :: |
unit | |
integer(kind=I4B), |
intent(in), |
optional |
| :: |
n_window | |
interface
-
public subroutine spear(data1, data2, d, zd, probd, rs, probrs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
real(kind=SP), |
intent(out) |
|
| :: |
d | |
real(kind=SP), |
intent(out) |
|
| :: |
zd | |
real(kind=SP), |
intent(out) |
|
| :: |
probd | |
real(kind=SP), |
intent(out) |
|
| :: |
rs | |
real(kind=SP), |
intent(out) |
|
| :: |
probrs | |
-
public subroutine sphbes_s(n, x, sj, sy, sjp, syp)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(out) |
|
| :: |
sj | |
real(kind=SP), |
intent(out) |
|
| :: |
sy | |
real(kind=SP), |
intent(out) |
|
| :: |
sjp | |
real(kind=SP), |
intent(out) |
|
| :: |
syp | |
-
public subroutine sphbes_v(n, x, sj, sy, sjp, syp)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
sj | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
sy | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
sjp | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
syp | |
interface
-
public subroutine splie2(x1a, x2a, ya, y2a)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x1a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x2a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
ya | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
y2a | |
interface
-
public function splin2(x1a, x2a, ya, y2a, x1, x2)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x1a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x2a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
ya | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
y2a | |
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
Return Value real(kind=SP)
interface
-
public subroutine spline(x, y, yp1, ypn, y2)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in) |
|
| :: |
yp1 | |
real(kind=SP), |
intent(in) |
|
| :: |
ypn | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
y2 | |
interface
-
public function splint(xa, ya, y2a, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
xa | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
ya | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y2a | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
-
public subroutine sprsax_dp(sa, x, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
type(sprs2_dp), |
intent(in) |
|
| :: |
sa | |
real(kind=DP), |
intent(in), |
|
DIMENSION (:) | :: |
x | |
real(kind=DP), |
intent(out), |
|
DIMENSION (:) | :: |
b | |
-
public subroutine sprsax_sp(sa, x, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
type(sprs2_sp), |
intent(in) |
|
| :: |
sa | |
real(kind=SP), |
intent(in), |
|
DIMENSION (:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION (:) | :: |
b | |
-
public subroutine sprsdiag_dp(sa, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
type(sprs2_dp), |
intent(in) |
|
| :: |
sa | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
b | |
-
public subroutine sprsdiag_sp(sa, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
type(sprs2_sp), |
intent(in) |
|
| :: |
sa | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
b | |
-
public subroutine sprsin_sp(a, thresh, sa)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
thresh | |
type(sprs2_sp), |
intent(out) |
|
| :: |
sa | |
-
public subroutine sprsin_dp(a, thresh, sa)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=DP), |
intent(in) |
|
| :: |
thresh | |
type(sprs2_dp), |
intent(out) |
|
| :: |
sa | |
interface
-
public subroutine sprstp(sa)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
type(sprs2_sp), |
intent(inout) |
|
| :: |
sa | |
-
public subroutine sprstx_dp(sa, x, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
type(sprs2_dp), |
intent(in) |
|
| :: |
sa | |
real(kind=DP), |
intent(in), |
|
DIMENSION (:) | :: |
x | |
real(kind=DP), |
intent(out), |
|
DIMENSION (:) | :: |
b | |
-
public subroutine sprstx_sp(sa, x, b)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
type(sprs2_sp), |
intent(in) |
|
| :: |
sa | |
real(kind=SP), |
intent(in), |
|
DIMENSION (:) | :: |
x | |
real(kind=SP), |
intent(out), |
|
DIMENSION (:) | :: |
b | |
interface
-
public subroutine stifbs(y, dydx, x, htry, eps, yscal, hdid, hnext, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(inout) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
htry | |
real(kind=SP), |
intent(in) |
|
| :: |
eps | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
yscal | |
real(kind=SP), |
intent(out) |
|
| :: |
hdid | |
real(kind=SP), |
intent(out) |
|
| :: |
hnext | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine stiff(y, dydx, x, htry, eps, yscal, hdid, hnext, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
dydx | |
real(kind=SP), |
intent(inout) |
|
| :: |
x | |
real(kind=SP), |
intent(in) |
|
| :: |
htry | |
real(kind=SP), |
intent(in) |
|
| :: |
eps | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
yscal | |
real(kind=SP), |
intent(out) |
|
| :: |
hdid | |
real(kind=SP), |
intent(out) |
|
| :: |
hnext | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
interface
-
public subroutine stoerm(y, d2y, xs, htot, nstep, yout, derivs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
d2y | |
real(kind=SP), |
intent(in) |
|
| :: |
xs | |
real(kind=SP), |
intent(in) |
|
| :: |
htot | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nstep | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
yout | |
subroutine derivs(x, y, dydx)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
dydx | |
|
-
public subroutine svbksb_dp(u, w, v, b, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
u | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
w | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:,:) | :: |
v | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
-
public subroutine svbksb_sp(u, w, v, b, x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
u | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
w | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
v | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
x | |
-
public subroutine svdcmp_dp(a, w, v)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
real(kind=DP), |
intent(out), |
|
DIMENSION(:,:) | :: |
v | |
-
public subroutine svdcmp_sp(a, w, v)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
v | |
interface
-
public subroutine svdfit(x, y, sig, a, v, w, chisq, funcs)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
sig | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
v | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
w | |
real(kind=SP), |
intent(out) |
|
| :: |
chisq | |
function funcs(x, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
Return Value real(kind=SP),
DIMENSION(n)
|
interface
-
public subroutine svdvar(v, w, cvm)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:,:) | :: |
v | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
w | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
cvm | |
interface
-
public function toeplz(r, y)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
r | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
y | |
Return Value real(kind=SP),
DIMENSION(size(y))
interface
-
public subroutine tptest(data1, data2, t, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
real(kind=SP), |
intent(out) |
|
| :: |
t | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine tqli(d, e, z)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
d | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
e | |
real(kind=SP), |
intent(inout), |
optional |
DIMENSION(:,:) | :: |
z | |
interface
-
public subroutine trapzd(func, a, b, s, n)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
Return Value real(kind=SP),
DIMENSION(size(x))
|
real(kind=SP), |
intent(in) |
|
| :: |
a | |
real(kind=SP), |
intent(in) |
|
| :: |
b | |
real(kind=SP), |
intent(inout) |
|
| :: |
s | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
interface
-
public subroutine tred2(a, d, e, novectors)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:,:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
d | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
e | |
logical(kind=LGT), |
intent(in), |
optional |
| :: |
novectors | |
-
public subroutine tridag_par(a, b, c, r, u)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
r | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
u | |
interface
-
public subroutine tridag_ser(a, b, c, r, u)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
b | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
c | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
r | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
u | |
interface
-
public subroutine ttest(data1, data2, t, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
real(kind=SP), |
intent(out) |
|
| :: |
t | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine tutest(data1, data2, t, prob)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
real(kind=SP), |
intent(out) |
|
| :: |
t | |
real(kind=SP), |
intent(out) |
|
| :: |
prob | |
interface
-
public subroutine twofft(data1, data2, fft1, fft2)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data1 | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
data2 | |
complex(kind=SPC), |
intent(out), |
|
DIMENSION(:) | :: |
fft1 | |
complex(kind=SPC), |
intent(out), |
|
DIMENSION(:) | :: |
fft2 | |
interface
-
public function vander(x, q)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
x | |
real(kind=DP), |
intent(in), |
|
DIMENSION(:) | :: |
q | |
Return Value real(kind=DP),
DIMENSION(size(x))
interface
-
public subroutine vegas(region, func, init, ncall, itmx, nprn, tgral, sd, chi2a)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
region | |
function func(pt, wgt)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
pt | |
real(kind=SP), |
intent(in) |
|
| :: |
wgt | |
Return Value real(kind=SP)
|
integer(kind=I4B), |
intent(in) |
|
| :: |
init | |
integer(kind=I4B), |
intent(in) |
|
| :: |
ncall | |
integer(kind=I4B), |
intent(in) |
|
| :: |
itmx | |
integer(kind=I4B), |
intent(in) |
|
| :: |
nprn | |
real(kind=SP), |
intent(out) |
|
| :: |
tgral | |
real(kind=SP), |
intent(out) |
|
| :: |
sd | |
real(kind=SP), |
intent(out) |
|
| :: |
chi2a | |
interface
-
public subroutine voltra(t0, h, t, f, g, ak)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
t0 | |
real(kind=SP), |
intent(in) |
|
| :: |
h | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
t | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:,:) | :: |
f | |
function g(t)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
t | |
Return Value real(kind=SP),
DIMENSION(:), POINTER
|
function ak(t, s)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
t | |
real(kind=SP), |
intent(in) |
|
| :: |
s | |
Return Value real(kind=SP),
DIMENSION(:,:), POINTER
|
interface
-
public subroutine wt1(a, isign, wtstep)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
subroutine wtstep(a, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
|
interface
-
public subroutine wtn(a, nn, isign, wtstep)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
integer(kind=I4B), |
intent(in), |
|
DIMENSION(:) | :: |
nn | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
subroutine wtstep(a, isign)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(inout), |
|
DIMENSION(:) | :: |
a | |
integer(kind=I4B), |
intent(in) |
|
| :: |
isign | |
|
interface
-
public function wwghts(n, h, kermom)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
intent(in) |
|
| :: |
h | |
function kermom(y, m)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=DP), |
intent(in) |
|
| :: |
y | |
integer(kind=I4B), |
intent(in) |
|
| :: |
m | |
Return Value real(kind=DP),
DIMENSION(m)
|
Return Value real(kind=SP),
DIMENSION(n)
interface
-
public subroutine zbrac(func, x1, x2, succes)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(inout) |
|
| :: |
x1 | |
real(kind=SP), |
intent(inout) |
|
| :: |
x2 | |
logical(kind=LGT), |
intent(out) |
|
| :: |
succes | |
interface
-
public subroutine zbrak(func, x1, x2, n, xb1, xb2, nb)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
integer(kind=I4B), |
intent(in) |
|
| :: |
n | |
real(kind=SP), |
|
|
DIMENSION(:), POINTER | :: |
xb1 | |
real(kind=SP), |
|
|
DIMENSION(:), POINTER | :: |
xb2 | |
integer(kind=I4B), |
intent(out) |
|
| :: |
nb | |
interface
-
public function zbrent(func, x1, x2, tol)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(in) |
|
| :: |
tol | |
Return Value real(kind=SP)
interface
-
public subroutine zrhqr(a, rtr, rti)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
rtr | |
real(kind=SP), |
intent(out), |
|
DIMENSION(:) | :: |
rti | |
interface
-
public function zriddr(func, x1, x2, xacc)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
function func(x)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
real(kind=SP), |
intent(in) |
|
| :: |
x | |
Return Value real(kind=SP)
|
real(kind=SP), |
intent(in) |
|
| :: |
x1 | |
real(kind=SP), |
intent(in) |
|
| :: |
x2 | |
real(kind=SP), |
intent(in) |
|
| :: |
xacc | |
Return Value real(kind=SP)
interface
-
public subroutine zroots(a, roots, polish)
Arguments
Type |
Intent | Optional |
Attributes | | Name | |
complex(kind=SPC), |
intent(in), |
|
DIMENSION(:) | :: |
a | |
complex(kind=SPC), |
intent(out), |
|
DIMENSION(:) | :: |
roots | |
logical(kind=LGT), |
intent(in) |
|
| :: |
polish | |