nrutil Module

@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".


Uses

  • module~~nrutil~~UsesGraph module~nrutil nrutil module~nrtype nrtype module~nrutil->module~nrtype

Used by

  • module~~nrutil~~UsedByGraph module~nrutil nrutil proc~chebev_s chebev_s proc~chebev_s->module~nrutil proc~bessik bessik proc~bessik->module~nrutil proc~chebev_v chebev_v proc~chebev_v->module~nrutil

Contents


Variables

TypeVisibility AttributesNameInitial
integer(kind=I4B), public, parameter:: NPAR_ARTH =16
integer(kind=I4B), public, parameter:: NPAR2_ARTH =8
integer(kind=I4B), public, parameter:: NPAR_GEOP =4
integer(kind=I4B), public, parameter:: NPAR2_GEOP =2
integer(kind=I4B), public, parameter:: NPAR_CUMSUM =16
integer(kind=I4B), public, parameter:: NPAR_CUMPROD =8
integer(kind=I4B), public, parameter:: NPAR_POLY =8
integer(kind=I4B), public, parameter:: NPAR_POLYTERM =8

Interfaces

public interface array_copy

  • public subroutine array_copy_r(src, dest, n_copied, n_not_copied)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: src
    real(kind=SP), intent(out), DIMENSION(:):: dest
    integer(kind=I4B), intent(out) :: n_copied
    integer(kind=I4B), intent(out) :: n_not_copied
  • public subroutine array_copy_d(src, dest, n_copied, n_not_copied)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in), DIMENSION(:):: src
    real(kind=DP), intent(out), DIMENSION(:):: dest
    integer(kind=I4B), intent(out) :: n_copied
    integer(kind=I4B), intent(out) :: n_not_copied
  • public subroutine array_copy_i(src, dest, n_copied, n_not_copied)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), intent(in), DIMENSION(:):: src
    integer(kind=I4B), intent(out), DIMENSION(:):: dest
    integer(kind=I4B), intent(out) :: n_copied
    integer(kind=I4B), intent(out) :: n_not_copied

public interface swap

  • public subroutine swap_i(a, b)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), intent(inout) :: a
    integer(kind=I4B), intent(inout) :: b
  • public subroutine swap_r(a, b)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout) :: a
    real(kind=SP), intent(inout) :: b
  • public subroutine swap_rv(a, b)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout), DIMENSION(:):: a
    real(kind=SP), intent(inout), DIMENSION(:):: b
  • public subroutine swap_c(a, b)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=SPC), intent(inout) :: a
    complex(kind=SPC), intent(inout) :: b
  • public subroutine swap_cv(a, b)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=SPC), intent(inout), DIMENSION(:):: a
    complex(kind=SPC), intent(inout), DIMENSION(:):: b
  • public subroutine swap_cm(a, b)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=SPC), intent(inout), DIMENSION(:,:):: a
    complex(kind=SPC), intent(inout), DIMENSION(:,:):: b
  • public subroutine swap_z(a, b)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=DPC), intent(inout) :: a
    complex(kind=DPC), intent(inout) :: b
  • public subroutine swap_zv(a, b)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=DPC), intent(inout), DIMENSION(:):: a
    complex(kind=DPC), intent(inout), DIMENSION(:):: b
  • public subroutine swap_zm(a, b)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=DPC), intent(inout), DIMENSION(:,:):: a
    complex(kind=DPC), intent(inout), DIMENSION(:,:):: b
  • public subroutine masked_swap_rs(a, b, mask)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout) :: a
    real(kind=SP), intent(inout) :: b
    logical(kind=LGT), intent(in) :: mask
  • public subroutine masked_swap_rv(a, b, mask)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout), DIMENSION(:):: a
    real(kind=SP), intent(inout), DIMENSION(:):: b
    logical(kind=LGT), intent(in), DIMENSION(:):: mask
  • public subroutine masked_swap_rm(a, b, mask)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout), DIMENSION(:,:):: a
    real(kind=SP), intent(inout), DIMENSION(:,:):: b
    logical(kind=LGT), intent(in), DIMENSION(:,:):: mask

public interface reallocate

  • public function reallocate_rv(p, n)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), DIMENSION(:), POINTER:: p
    integer(kind=I4B), intent(in) :: n

    Return Value real(kind=SP), DIMENSION(:), POINTER

  • public function reallocate_rm(p, n, m)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), DIMENSION(:,:), POINTER:: p
    integer(kind=I4B), intent(in) :: n
    integer(kind=I4B), intent(in) :: m

    Return Value real(kind=SP), DIMENSION(:,:), POINTER

  • public function reallocate_iv(p, n)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), DIMENSION(:), POINTER:: p
    integer(kind=I4B), intent(in) :: n

    Return Value integer(kind=I4B), DIMENSION(:), POINTER

  • public function reallocate_im(p, n, m)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), DIMENSION(:,:), POINTER:: p
    integer(kind=I4B), intent(in) :: n
    integer(kind=I4B), intent(in) :: m

    Return Value integer(kind=I4B), DIMENSION(:,:), POINTER

  • public function reallocate_hv(p, n)

    Arguments

    Type IntentOptional AttributesName
    character(len=1), DIMENSION(:), POINTER:: p
    integer(kind=I4B), intent(in) :: n

    Return Value character(len=1), DIMENSION(:), POINTER

public interface imaxloc

  • public function imaxloc_r(arr)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: arr

    Return Value integer(kind=I4B)

  • public function imaxloc_i(iarr)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), intent(in), DIMENSION(:):: iarr

    Return Value integer(kind=I4B)

public interface assert

  • public subroutine assert1(n1, string)

    Arguments

    Type IntentOptional AttributesName
    logical, intent(in) :: n1
    character(len=*), intent(in) :: string
  • public subroutine assert2(n1, n2, string)

    Arguments

    Type IntentOptional AttributesName
    logical, intent(in) :: n1
    logical, intent(in) :: n2
    character(len=*), intent(in) :: string
  • public subroutine assert3(n1, n2, n3, string)

    Arguments

    Type IntentOptional AttributesName
    logical, intent(in) :: n1
    logical, intent(in) :: n2
    logical, intent(in) :: n3
    character(len=*), intent(in) :: string
  • public subroutine assert4(n1, n2, n3, n4, string)

    Arguments

    Type IntentOptional AttributesName
    logical, intent(in) :: n1
    logical, intent(in) :: n2
    logical, intent(in) :: n3
    logical, intent(in) :: n4
    character(len=*), intent(in) :: string
  • public subroutine assert_v(n, string)

    Arguments

    Type IntentOptional AttributesName
    logical, intent(in), DIMENSION(:):: n
    character(len=*), intent(in) :: string

public interface assert_eq

  • public function assert_eq2(n1, n2, string)

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: n1
    integer, intent(in) :: n2
    character(len=*), intent(in) :: string

    Return Value integer

  • public function assert_eq3(n1, n2, n3, string)

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: n1
    integer, intent(in) :: n2
    integer, intent(in) :: n3
    character(len=*), intent(in) :: string

    Return Value integer

  • public function assert_eq4(n1, n2, n3, n4, string)

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: n1
    integer, intent(in) :: n2
    integer, intent(in) :: n3
    integer, intent(in) :: n4
    character(len=*), intent(in) :: string

    Return Value integer

  • public function assert_eqn(nn, string)

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in), DIMENSION(:):: nn
    character(len=*), intent(in) :: string

    Return Value integer

public interface arth

  • public function arth_r(first, increment, n)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in) :: first
    real(kind=SP), intent(in) :: increment
    integer(kind=I4B), intent(in) :: n

    Return Value real(kind=SP), DIMENSION(n)

  • public function arth_d(first, increment, n)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in) :: first
    real(kind=DP), intent(in) :: increment
    integer(kind=I4B), intent(in) :: n

    Return Value real(kind=DP), DIMENSION(n)

  • public function arth_i(first, increment, n)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), intent(in) :: first
    integer(kind=I4B), intent(in) :: increment
    integer(kind=I4B), intent(in) :: n

    Return Value integer(kind=I4B), DIMENSION(n)

public interface geop

  • public function geop_r(first, factor, n)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in) :: first
    real(kind=SP), intent(in) :: factor
    integer(kind=I4B), intent(in) :: n

    Return Value real(kind=SP), DIMENSION(n)

  • public function geop_d(first, factor, n)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in) :: first
    real(kind=DP), intent(in) :: factor
    integer(kind=I4B), intent(in) :: n

    Return Value real(kind=DP), DIMENSION(n)

  • public function geop_i(first, factor, n)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), intent(in) :: first
    integer(kind=I4B), intent(in) :: factor
    integer(kind=I4B), intent(in) :: n

    Return Value integer(kind=I4B), DIMENSION(n)

  • public function geop_c(first, factor, n)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=SP), intent(in) :: first
    complex(kind=SP), intent(in) :: factor
    integer(kind=I4B), intent(in) :: n

    Return Value complex(kind=SP), DIMENSION(n)

  • public function geop_dv(first, factor, n)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in), DIMENSION(:):: first
    real(kind=DP), intent(in), DIMENSION(:):: factor
    integer(kind=I4B), intent(in) :: n

    Return Value real(kind=DP), DIMENSION(size(first),n)

public interface cumsum

  • public recursive function cumsum_r(arr, seed) result(ans)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: arr
    real(kind=SP), intent(in), optional :: seed

    Return Value real(kind=SP), DIMENSION(size(arr))

  • public recursive function cumsum_i(arr, seed) result(ans)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), intent(in), DIMENSION(:):: arr
    integer(kind=I4B), intent(in), optional :: seed

    Return Value integer(kind=I4B), DIMENSION(size(arr))

public interface poly

  • public function poly_rr(x, coeffs)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in) :: x
    real(kind=SP), intent(in), DIMENSION(:):: coeffs

    Return Value real(kind=SP)

  • public function poly_rrv(x, coeffs)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: x
    real(kind=SP), intent(in), DIMENSION(:):: coeffs

    Return Value real(kind=SP), DIMENSION(size(x))

  • public function poly_dd(x, coeffs)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in) :: x
    real(kind=DP), intent(in), DIMENSION(:):: coeffs

    Return Value real(kind=DP)

  • public function poly_ddv(x, coeffs)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in), DIMENSION(:):: x
    real(kind=DP), intent(in), DIMENSION(:):: coeffs

    Return Value real(kind=DP), DIMENSION(size(x))

  • public function poly_rc(x, coeffs)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=SPC), intent(in) :: x
    real(kind=SP), intent(in), DIMENSION(:):: coeffs

    Return Value complex(kind=SPC)

  • public function poly_cc(x, coeffs)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=SPC), intent(in) :: x
    complex(kind=SPC), intent(in), DIMENSION(:):: coeffs

    Return Value complex(kind=SPC)

  • public function poly_msk_rrv(x, coeffs, mask)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: x
    real(kind=SP), intent(in), DIMENSION(:):: coeffs
    logical(kind=LGT), intent(in), DIMENSION(:):: mask

    Return Value real(kind=SP), DIMENSION(size(x))

  • public function poly_msk_ddv(x, coeffs, mask)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in), DIMENSION(:):: x
    real(kind=DP), intent(in), DIMENSION(:):: coeffs
    logical(kind=LGT), intent(in), DIMENSION(:):: mask

    Return Value real(kind=DP), DIMENSION(size(x))

public interface poly_term

  • public recursive function poly_term_rr(a, b) result(u)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: a
    real(kind=SP), intent(in) :: b

    Return Value real(kind=SP), DIMENSION(size(a))

  • public recursive function poly_term_cc(a, b) result(u)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=SPC), intent(in), DIMENSION(:):: a
    complex(kind=SPC), intent(in) :: b

    Return Value complex(kind=SPC), DIMENSION(size(a))

public interface outerprod

  • public function outerprod_r(a, b)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: a
    real(kind=SP), intent(in), DIMENSION(:):: b

    Return Value real(kind=SP), DIMENSION(size(a),size(b))

  • public function outerprod_d(a, b)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in), DIMENSION(:):: a
    real(kind=DP), intent(in), DIMENSION(:):: b

    Return Value real(kind=DP), DIMENSION(size(a),size(b))

public interface outerdiff

  • public function outerdiff_r(a, b)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: a
    real(kind=SP), intent(in), DIMENSION(:):: b

    Return Value real(kind=SP), DIMENSION(size(a),size(b))

  • public function outerdiff_d(a, b)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in), DIMENSION(:):: a
    real(kind=DP), intent(in), DIMENSION(:):: b

    Return Value real(kind=DP), DIMENSION(size(a),size(b))

  • public function outerdiff_i(a, b)

    Arguments

    Type IntentOptional AttributesName
    integer(kind=I4B), intent(in), DIMENSION(:):: a
    integer(kind=I4B), intent(in), DIMENSION(:):: b

    Return Value integer(kind=I4B), DIMENSION(size(a),size(b))

public interface scatter_add

  • public subroutine scatter_add_r(dest, source, dest_index)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(out), DIMENSION(:):: dest
    real(kind=SP), intent(in), DIMENSION(:):: source
    integer(kind=I4B), intent(in), DIMENSION(:):: dest_index
  • public subroutine scatter_add_d(dest, source, dest_index)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(out), DIMENSION(:):: dest
    real(kind=DP), intent(in), DIMENSION(:):: source
    integer(kind=I4B), intent(in), DIMENSION(:):: dest_index

public interface scatter_max

  • public subroutine scatter_max_r(dest, source, dest_index)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(out), DIMENSION(:):: dest
    real(kind=SP), intent(in), DIMENSION(:):: source
    integer(kind=I4B), intent(in), DIMENSION(:):: dest_index
  • public subroutine scatter_max_d(dest, source, dest_index)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(out), DIMENSION(:):: dest
    real(kind=DP), intent(in), DIMENSION(:):: source
    integer(kind=I4B), intent(in), DIMENSION(:):: dest_index

public interface diagadd

  • public subroutine diagadd_rv(mat, diag)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout), DIMENSION(:,:):: mat
    real(kind=SP), intent(in), DIMENSION(:):: diag
  • public subroutine diagadd_r(mat, diag)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout), DIMENSION(:,:):: mat
    real(kind=SP), intent(in) :: diag

public interface diagmult

  • public subroutine diagmult_rv(mat, diag)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout), DIMENSION(:,:):: mat
    real(kind=SP), intent(in), DIMENSION(:):: diag
  • public subroutine diagmult_r(mat, diag)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(inout), DIMENSION(:,:):: mat
    real(kind=SP), intent(in) :: diag

public interface get_diag

  • public function get_diag_rv(mat)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:,:):: mat

    Return Value real(kind=SP), DIMENSION(size(mat,1))

  • public function get_diag_dv(mat)

    Arguments

    Type IntentOptional AttributesName
    real(kind=DP), intent(in), DIMENSION(:,:):: mat

    Return Value real(kind=DP), DIMENSION(size(mat,1))

public interface put_diag

  • public subroutine put_diag_rv(diagv, mat)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in), DIMENSION(:):: diagv
    real(kind=SP), intent(inout), DIMENSION(:,:):: mat
  • public subroutine put_diag_r(scal, mat)

    Arguments

    Type IntentOptional AttributesName
    real(kind=SP), intent(in) :: scal
    real(kind=SP), intent(inout), DIMENSION(:,:):: mat

Functions

public function reallocate_rv(p, n)

Arguments

Type IntentOptional AttributesName
real(kind=SP), DIMENSION(:), POINTER:: p
integer(kind=I4B), intent(in) :: n

Return Value real(kind=SP), DIMENSION(:), POINTER

public function reallocate_iv(p, n)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), DIMENSION(:), POINTER:: p
integer(kind=I4B), intent(in) :: n

Return Value integer(kind=I4B), DIMENSION(:), POINTER

public function reallocate_hv(p, n)

Arguments

Type IntentOptional AttributesName
character(len=1), DIMENSION(:), POINTER:: p
integer(kind=I4B), intent(in) :: n

Return Value character(len=1), DIMENSION(:), POINTER

public function reallocate_rm(p, n, m)

Arguments

Type IntentOptional AttributesName
real(kind=SP), DIMENSION(:,:), POINTER:: p
integer(kind=I4B), intent(in) :: n
integer(kind=I4B), intent(in) :: m

Return Value real(kind=SP), DIMENSION(:,:), POINTER

public function reallocate_im(p, n, m)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), DIMENSION(:,:), POINTER:: p
integer(kind=I4B), intent(in) :: n
integer(kind=I4B), intent(in) :: m

Return Value integer(kind=I4B), DIMENSION(:,:), POINTER

public function ifirstloc(mask)

Arguments

Type IntentOptional AttributesName
logical(kind=LGT), intent(in), DIMENSION(:):: mask

Return Value integer(kind=I4B)

public function imaxloc_r(arr)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: arr

Return Value integer(kind=I4B)

public function imaxloc_i(iarr)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in), DIMENSION(:):: iarr

Return Value integer(kind=I4B)

public function iminloc(arr)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: arr

Return Value integer(kind=I4B)

public function assert_eq2(n1, n2, string)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: n1
integer, intent(in) :: n2
character(len=*), intent(in) :: string

Return Value integer

public function assert_eq3(n1, n2, n3, string)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: n1
integer, intent(in) :: n2
integer, intent(in) :: n3
character(len=*), intent(in) :: string

Return Value integer

public function assert_eq4(n1, n2, n3, n4, string)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: n1
integer, intent(in) :: n2
integer, intent(in) :: n3
integer, intent(in) :: n4
character(len=*), intent(in) :: string

Return Value integer

public function assert_eqn(nn, string)

Arguments

Type IntentOptional AttributesName
integer, intent(in), DIMENSION(:):: nn
character(len=*), intent(in) :: string

Return Value integer

public function arth_r(first, increment, n)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in) :: first
real(kind=SP), intent(in) :: increment
integer(kind=I4B), intent(in) :: n

Return Value real(kind=SP), DIMENSION(n)

public function arth_d(first, increment, n)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in) :: first
real(kind=DP), intent(in) :: increment
integer(kind=I4B), intent(in) :: n

Return Value real(kind=DP), DIMENSION(n)

public function arth_i(first, increment, n)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in) :: first
integer(kind=I4B), intent(in) :: increment
integer(kind=I4B), intent(in) :: n

Return Value integer(kind=I4B), DIMENSION(n)

public function geop_r(first, factor, n)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in) :: first
real(kind=SP), intent(in) :: factor
integer(kind=I4B), intent(in) :: n

Return Value real(kind=SP), DIMENSION(n)

public function geop_d(first, factor, n)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in) :: first
real(kind=DP), intent(in) :: factor
integer(kind=I4B), intent(in) :: n

Return Value real(kind=DP), DIMENSION(n)

public function geop_i(first, factor, n)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in) :: first
integer(kind=I4B), intent(in) :: factor
integer(kind=I4B), intent(in) :: n

Return Value integer(kind=I4B), DIMENSION(n)

public function geop_c(first, factor, n)

Arguments

Type IntentOptional AttributesName
complex(kind=SP), intent(in) :: first
complex(kind=SP), intent(in) :: factor
integer(kind=I4B), intent(in) :: n

Return Value complex(kind=SP), DIMENSION(n)

public function geop_dv(first, factor, n)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in), DIMENSION(:):: first
real(kind=DP), intent(in), DIMENSION(:):: factor
integer(kind=I4B), intent(in) :: n

Return Value real(kind=DP), DIMENSION(size(first),n)

public recursive function cumsum_r(arr, seed) result(ans)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: arr
real(kind=SP), intent(in), optional :: seed

Return Value real(kind=SP), DIMENSION(size(arr))

public recursive function cumsum_i(arr, seed) result(ans)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in), DIMENSION(:):: arr
integer(kind=I4B), intent(in), optional :: seed

Return Value integer(kind=I4B), DIMENSION(size(arr))

public recursive function cumprod(arr, seed) result(ans)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: arr
real(kind=SP), intent(in), optional :: seed

Return Value real(kind=SP), DIMENSION(size(arr))

public function poly_rr(x, coeffs)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in) :: x
real(kind=SP), intent(in), DIMENSION(:):: coeffs

Return Value real(kind=SP)

public function poly_dd(x, coeffs)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in) :: x
real(kind=DP), intent(in), DIMENSION(:):: coeffs

Return Value real(kind=DP)

public function poly_rc(x, coeffs)

Arguments

Type IntentOptional AttributesName
complex(kind=SPC), intent(in) :: x
real(kind=SP), intent(in), DIMENSION(:):: coeffs

Return Value complex(kind=SPC)

public function poly_cc(x, coeffs)

Arguments

Type IntentOptional AttributesName
complex(kind=SPC), intent(in) :: x
complex(kind=SPC), intent(in), DIMENSION(:):: coeffs

Return Value complex(kind=SPC)

public function poly_rrv(x, coeffs)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: x
real(kind=SP), intent(in), DIMENSION(:):: coeffs

Return Value real(kind=SP), DIMENSION(size(x))

public function poly_ddv(x, coeffs)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in), DIMENSION(:):: x
real(kind=DP), intent(in), DIMENSION(:):: coeffs

Return Value real(kind=DP), DIMENSION(size(x))

public function poly_msk_rrv(x, coeffs, mask)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: x
real(kind=SP), intent(in), DIMENSION(:):: coeffs
logical(kind=LGT), intent(in), DIMENSION(:):: mask

Return Value real(kind=SP), DIMENSION(size(x))

public function poly_msk_ddv(x, coeffs, mask)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in), DIMENSION(:):: x
real(kind=DP), intent(in), DIMENSION(:):: coeffs
logical(kind=LGT), intent(in), DIMENSION(:):: mask

Return Value real(kind=DP), DIMENSION(size(x))

public recursive function poly_term_rr(a, b) result(u)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: a
real(kind=SP), intent(in) :: b

Return Value real(kind=SP), DIMENSION(size(a))

public recursive function poly_term_cc(a, b) result(u)

Arguments

Type IntentOptional AttributesName
complex(kind=SPC), intent(in), DIMENSION(:):: a
complex(kind=SPC), intent(in) :: b

Return Value complex(kind=SPC), DIMENSION(size(a))

public function zroots_unity(n, nn)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in) :: n
integer(kind=I4B), intent(in) :: nn

Return Value complex(kind=SPC), DIMENSION(nn)

public function outerprod_r(a, b)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: a
real(kind=SP), intent(in), DIMENSION(:):: b

Return Value real(kind=SP), DIMENSION(size(a),size(b))

public function outerprod_d(a, b)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in), DIMENSION(:):: a
real(kind=DP), intent(in), DIMENSION(:):: b

Return Value real(kind=DP), DIMENSION(size(a),size(b))

public function outerdiv(a, b)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: a
real(kind=SP), intent(in), DIMENSION(:):: b

Return Value real(kind=SP), DIMENSION(size(a),size(b))

public function outersum(a, b)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: a
real(kind=SP), intent(in), DIMENSION(:):: b

Return Value real(kind=SP), DIMENSION(size(a),size(b))

public function outerdiff_r(a, b)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: a
real(kind=SP), intent(in), DIMENSION(:):: b

Return Value real(kind=SP), DIMENSION(size(a),size(b))

public function outerdiff_d(a, b)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in), DIMENSION(:):: a
real(kind=DP), intent(in), DIMENSION(:):: b

Return Value real(kind=DP), DIMENSION(size(a),size(b))

public function outerdiff_i(a, b)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in), DIMENSION(:):: a
integer(kind=I4B), intent(in), DIMENSION(:):: b

Return Value integer(kind=I4B), DIMENSION(size(a),size(b))

public function outerand(a, b)

Arguments

Type IntentOptional AttributesName
logical(kind=LGT), intent(in), DIMENSION(:):: a
logical(kind=LGT), intent(in), DIMENSION(:):: b

Return Value logical(kind=LGT), DIMENSION(size(a),size(b))

public function get_diag_rv(mat)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:,:):: mat

Return Value real(kind=SP), DIMENSION(size(mat,1))

public function get_diag_dv(mat)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in), DIMENSION(:,:):: mat

Return Value real(kind=DP), DIMENSION(size(mat,1))

public function upper_triangle(j, k, extra)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in) :: j
integer(kind=I4B), intent(in) :: k
integer(kind=I4B), intent(in), optional :: extra

Return Value logical(kind=LGT), DIMENSION(j,k)

public function lower_triangle(j, k, extra)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in) :: j
integer(kind=I4B), intent(in) :: k
integer(kind=I4B), intent(in), optional :: extra

Return Value logical(kind=LGT), DIMENSION(j,k)

public function vabs(v)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: v

Return Value real(kind=SP)


Subroutines

public subroutine array_copy_r(src, dest, n_copied, n_not_copied)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: src
real(kind=SP), intent(out), DIMENSION(:):: dest
integer(kind=I4B), intent(out) :: n_copied
integer(kind=I4B), intent(out) :: n_not_copied

public subroutine array_copy_d(src, dest, n_copied, n_not_copied)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(in), DIMENSION(:):: src
real(kind=DP), intent(out), DIMENSION(:):: dest
integer(kind=I4B), intent(out) :: n_copied
integer(kind=I4B), intent(out) :: n_not_copied

public subroutine array_copy_i(src, dest, n_copied, n_not_copied)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(in), DIMENSION(:):: src
integer(kind=I4B), intent(out), DIMENSION(:):: dest
integer(kind=I4B), intent(out) :: n_copied
integer(kind=I4B), intent(out) :: n_not_copied

public subroutine swap_i(a, b)

Arguments

Type IntentOptional AttributesName
integer(kind=I4B), intent(inout) :: a
integer(kind=I4B), intent(inout) :: b

public subroutine swap_r(a, b)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout) :: a
real(kind=SP), intent(inout) :: b

public subroutine swap_rv(a, b)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout), DIMENSION(:):: a
real(kind=SP), intent(inout), DIMENSION(:):: b

public subroutine swap_c(a, b)

Arguments

Type IntentOptional AttributesName
complex(kind=SPC), intent(inout) :: a
complex(kind=SPC), intent(inout) :: b

public subroutine swap_cv(a, b)

Arguments

Type IntentOptional AttributesName
complex(kind=SPC), intent(inout), DIMENSION(:):: a
complex(kind=SPC), intent(inout), DIMENSION(:):: b

public subroutine swap_cm(a, b)

Arguments

Type IntentOptional AttributesName
complex(kind=SPC), intent(inout), DIMENSION(:,:):: a
complex(kind=SPC), intent(inout), DIMENSION(:,:):: b

public subroutine swap_z(a, b)

Arguments

Type IntentOptional AttributesName
complex(kind=DPC), intent(inout) :: a
complex(kind=DPC), intent(inout) :: b

public subroutine swap_zv(a, b)

Arguments

Type IntentOptional AttributesName
complex(kind=DPC), intent(inout), DIMENSION(:):: a
complex(kind=DPC), intent(inout), DIMENSION(:):: b

public subroutine swap_zm(a, b)

Arguments

Type IntentOptional AttributesName
complex(kind=DPC), intent(inout), DIMENSION(:,:):: a
complex(kind=DPC), intent(inout), DIMENSION(:,:):: b

public subroutine masked_swap_rs(a, b, mask)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout) :: a
real(kind=SP), intent(inout) :: b
logical(kind=LGT), intent(in) :: mask

public subroutine masked_swap_rv(a, b, mask)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout), DIMENSION(:):: a
real(kind=SP), intent(inout), DIMENSION(:):: b
logical(kind=LGT), intent(in), DIMENSION(:):: mask

public subroutine masked_swap_rm(a, b, mask)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout), DIMENSION(:,:):: a
real(kind=SP), intent(inout), DIMENSION(:,:):: b
logical(kind=LGT), intent(in), DIMENSION(:,:):: mask

public subroutine assert1(n1, string)

Arguments

Type IntentOptional AttributesName
logical, intent(in) :: n1
character(len=*), intent(in) :: string

public subroutine assert2(n1, n2, string)

Arguments

Type IntentOptional AttributesName
logical, intent(in) :: n1
logical, intent(in) :: n2
character(len=*), intent(in) :: string

public subroutine assert3(n1, n2, n3, string)

Arguments

Type IntentOptional AttributesName
logical, intent(in) :: n1
logical, intent(in) :: n2
logical, intent(in) :: n3
character(len=*), intent(in) :: string

public subroutine assert4(n1, n2, n3, n4, string)

Arguments

Type IntentOptional AttributesName
logical, intent(in) :: n1
logical, intent(in) :: n2
logical, intent(in) :: n3
logical, intent(in) :: n4
character(len=*), intent(in) :: string

public subroutine assert_v(n, string)

Arguments

Type IntentOptional AttributesName
logical, intent(in), DIMENSION(:):: n
character(len=*), intent(in) :: string

public subroutine nrerror(string)

Arguments

Type IntentOptional AttributesName
character(len=*), intent(in) :: string

public subroutine scatter_add_r(dest, source, dest_index)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(out), DIMENSION(:):: dest
real(kind=SP), intent(in), DIMENSION(:):: source
integer(kind=I4B), intent(in), DIMENSION(:):: dest_index

public subroutine scatter_add_d(dest, source, dest_index)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(out), DIMENSION(:):: dest
real(kind=DP), intent(in), DIMENSION(:):: source
integer(kind=I4B), intent(in), DIMENSION(:):: dest_index

public subroutine scatter_max_r(dest, source, dest_index)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(out), DIMENSION(:):: dest
real(kind=SP), intent(in), DIMENSION(:):: source
integer(kind=I4B), intent(in), DIMENSION(:):: dest_index

public subroutine scatter_max_d(dest, source, dest_index)

Arguments

Type IntentOptional AttributesName
real(kind=DP), intent(out), DIMENSION(:):: dest
real(kind=DP), intent(in), DIMENSION(:):: source
integer(kind=I4B), intent(in), DIMENSION(:):: dest_index

public subroutine diagadd_rv(mat, diag)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout), DIMENSION(:,:):: mat
real(kind=SP), intent(in), DIMENSION(:):: diag

public subroutine diagadd_r(mat, diag)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout), DIMENSION(:,:):: mat
real(kind=SP), intent(in) :: diag

public subroutine diagmult_rv(mat, diag)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout), DIMENSION(:,:):: mat
real(kind=SP), intent(in), DIMENSION(:):: diag

public subroutine diagmult_r(mat, diag)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(inout), DIMENSION(:,:):: mat
real(kind=SP), intent(in) :: diag

public subroutine put_diag_rv(diagv, mat)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in), DIMENSION(:):: diagv
real(kind=SP), intent(inout), DIMENSION(:,:):: mat

public subroutine put_diag_r(scal, mat)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(in) :: scal
real(kind=SP), intent(inout), DIMENSION(:,:):: mat

public subroutine unit_matrix(mat)

Arguments

Type IntentOptional AttributesName
real(kind=SP), intent(out), DIMENSION(:,:):: mat