MathClass Module

This module defines numerious basic mathematical operations, mainly for scalar and vector computation. It also contains some converter among string, characters and othe datatypes.



Variables

Type Visibility Attributes Name Initial
integer(kind=int32), public :: i_i = 0
integer(kind=int32), public :: j_j = 0
integer(kind=int32), public :: k_k = 0
logical, public :: true = .True.
logical, public :: False = .False.
integer(kind=int32), public, parameter :: complex64 = real64

Interfaces

public interface nchoosek

It computes nCr (combination number)

  • public pure function comb(n, r) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(in) :: r

    Return Value real(kind=real64)

public interface choose

It computes nCr (combination number)

  • public pure function comb(n, r) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(in) :: r

    Return Value real(kind=real64)

public interface fact

It computes factorial.

  • public pure recursive function factorialInt32(n) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n

    Return Value integer(kind=int64)

  • public pure recursive function factorialReal64(n) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: n

    Return Value real(kind=real64)

public interface imag

It takes a imaginary part of a complex number.

  • public pure function imaginary_partComplex64(complexValue) result(imgpart)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: complexValue

    Return Value real(kind=real64)

  • public pure function imaginary_partComplex32(complexValue) result(imgpart)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real32), intent(in) :: complexValue

    Return Value real(kind=real32)

public interface arg

It takes a arg() of a complex number.

  • public function arg_complex64(comp) result(theta)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: comp

    Return Value real(kind=real64)

  • public function arg_complex64_vector(comp) result(theta)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: comp(:)

    Return Value real(kind=real64), allocatable, (:)

  • public function arg_complex64_tensor(comp) result(theta)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: comp(:,:)

    Return Value real(kind=real64), allocatable, (:,:)

public interface norm

It computes L^2 norm of a tensor.

  • public function norm_mat(vec) result(a)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: vec(:,:)

    Return Value real(kind=real64)

  • public function norm_vec(vec) result(a)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: vec(:)

    Return Value real(kind=real64)

  • public function norm_vec_real32(vec) result(a)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real32), intent(in) :: vec(:)

    Return Value real(kind=real32)

  • public function norm_vec_complex64(vec) result(a)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: vec(:)

    Return Value real(kind=real64)

public interface det_mat

It computes determinant of a regular matrix.

  • public recursive function det_mat_real64(a, n) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: a(n,n)
    integer(kind=int32), intent(in) :: n

    Return Value real(kind=real64)

  • public recursive function det_mat_complex64(a, n) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: a(n,n)
    integer(kind=int32), intent(in) :: n

    Return Value complex(kind=real64)

public interface int

It converts an array of character into a integer

  • public function fint(ch) result(a)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: ch

    Return Value integer(kind=int32)

public interface float

It converts an array of character into a float (real32)

  • public function freal(ch) result(a)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: ch

    Return Value real(kind=real64)

public interface trace

It returns the trace of a matrix.

  • public function trace_complex64(a) result(b)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: a(:,:)

    Return Value complex(kind=real64)

  • public function trace_real64(a) result(b)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: a(:,:)

    Return Value real(kind=real64)

public interface factorial

It returns factorial.

  • public pure recursive function factorialInt32(n) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n

    Return Value integer(kind=int64)

  • public pure recursive function factorialReal64(n) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: n

    Return Value real(kind=real64)

public interface Bessel_J0

It returns Bessel function of 0th kind by complex number.

  • public function Bessel_J0_complex(z) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: z

    Return Value complex(kind=real64)

public interface Bessel_J1

It returns Bessel function of 1st kind by complex number.

  • public function Bessel_J1_complex(z) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: z

    Return Value complex(kind=real64)

public interface sort

It sorts integer vector

  • public function sort_int32(vec) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: vec(:)

    Return Value integer(kind=int32), allocatable, (:)

public interface heapsort

It sorts integer vector by heap sort.

  • public pure subroutine heapsortInt32(n, array, val)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(inout) :: array(1:n)
    real(kind=real64), intent(inout), optional :: val(1:n)
  • public pure subroutine heapsortInt32Int32(n, array, val)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(inout) :: array(1:n)
    integer(kind=int32), intent(inout) :: val(1:n)
  • public pure subroutine heapsortReal64Int32(n, array, val)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n
    real(kind=real64), intent(inout) :: array(1:n)
    integer(kind=int32), intent(inout) :: val(1:n)
  • public subroutine heapsortReal64(n, array, val)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n
    real(kind=real64), intent(inout) :: array(1:n)
    real(kind=real64), intent(inout), optional :: val(1:n)
  • public subroutine heapsortReal32(n, array, val)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: n
    real(kind=real32), intent(inout) :: array(1:n)
    real(kind=real32), intent(inout), optional :: val(1:n)
  • public recursive subroutine heapsort_int32_array(array, order, exec_row_sort)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout) :: array(:,:)
    integer(kind=int32), intent(inout), optional, allocatable :: order(:)
    logical, intent(in), optional :: exec_row_sort
  • public recursive subroutine heapsort_real64_array(array, order, exec_row_sort)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(inout) :: array(:,:)
    integer(kind=int32), intent(inout), optional, allocatable :: order(:)
    logical, intent(in), optional :: exec_row_sort

public interface sort_and_remove_duplication

It sorts integer vector and removes duplication.

  • public subroutine sort_and_remove_duplication_int32(array, order)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout), allocatable :: array(:,:)
    integer(kind=int32), intent(inout), optional, allocatable :: order(:)
  • public subroutine sort_and_remove_duplication_real64(array, order)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(inout), allocatable :: array(:,:)
    integer(kind=int32), intent(inout), optional, allocatable :: order(:)

public interface str

It converts valiables into a string.

  • public pure function fstring_int(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: x

    Return Value character(len=:), allocatable

  • public pure function fstring_int64(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: x

    Return Value character(len=:), allocatable

  • public pure function fstring_real(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x

    Return Value character(len=:), allocatable

  • public pure function fstring_real32(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real32), intent(in) :: x

    Return Value character(len=:), allocatable

  • public pure function fstring_complex(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=kind(0d0)), intent(in) :: x

    Return Value character(len=:), allocatable

  • public pure function fstring_int_len(x, length) result(a)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: x
    integer(kind=int32), intent(in) :: length

    Return Value character(len=length)

  • public pure function fstring_real_len(x, length) result(a)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x
    integer(kind=int32), intent(in) :: length

    Return Value character(len=60)

  • public pure function fstring_logical(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    logical, intent(in) :: x

    Return Value character(len=5)

  • public pure function fstring_String(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    type(string_), intent(in) :: x

    Return Value character(len=:), allocatable

  • public function stringFromChar(charval) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: charval

    Return Value type(string_)

public interface fstring

It converts valiables into a string.

  • public pure function fstring_int(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: x

    Return Value character(len=:), allocatable

  • public pure function fstring_int64(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: x

    Return Value character(len=:), allocatable

  • public pure function fstring_real(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x

    Return Value character(len=:), allocatable

  • public pure function fstring_int_len(x, length) result(a)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: x
    integer(kind=int32), intent(in) :: length

    Return Value character(len=length)

  • public pure function fstring_real_len(x, length) result(a)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x
    integer(kind=int32), intent(in) :: length

    Return Value character(len=60)

  • public pure function fstring_logical(x) result(a)

    Arguments

    Type IntentOptional Attributes Name
    logical, intent(in) :: x

    Return Value character(len=5)

public interface int

It converts logical array into int.

  • public function int_from_logical(logical_value) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    logical, intent(in) :: logical_value

    Return Value integer(kind=int32)

  • public function int_from_logical_vector(logical_value) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    logical, intent(in) :: logical_value(:)

    Return Value integer(kind=int32), allocatable, (:)

public interface input

It returns a value from defalut value when no optional value is given, and returns the optional value only if it is given.

  • public function input_Int(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: default
    integer(kind=int32), intent(in), optional :: option

    Return Value integer(kind=int32)

  • public function input_Real(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: default
    real(kind=real64), intent(in), optional :: option

    Return Value real(kind=real64)

  • public function input_Real32(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real32), intent(in) :: default
    real(kind=real32), intent(in), optional :: option

    Return Value real(kind=real32)

  • public function input_Complex(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: default
    complex(kind=real64), intent(in), optional :: option

    Return Value complex(kind=real64)

  • public function input_IntVec(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: default(:)
    integer(kind=int32), intent(in), optional :: option(:)

    Return Value integer(kind=int32), allocatable, (:)

  • public function input_Realvec(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: default(:)
    real(kind=real64), intent(in), optional :: option(:)

    Return Value real(kind=real64), allocatable, (:)

  • public function input_IntArray(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: default(:,:)
    integer(kind=int32), intent(in), optional :: option(:,:)

    Return Value integer(kind=int32), allocatable, (:,:)

  • public function input_RealArray(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: default(:,:)
    real(kind=real64), intent(in), optional :: option(:,:)

    Return Value real(kind=real64), allocatable, (:,:)

  • public function input_String(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: default
    character(len=*), intent(in), optional :: option

    Return Value character(len=200)

  • public function input_logical(default, option) result(val)

    Arguments

    Type IntentOptional Attributes Name
    logical, intent(in) :: default
    logical, intent(in), optional :: option

    Return Value logical

public interface zeroif

It returns zero if some value is positive/negative.

  • public function zeroif_Int(val, negative, positive) result(retval)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: val
    logical, intent(in), optional :: negative
    logical, intent(in), optional :: positive

    Return Value integer(kind=int32)

  • public function zeroif_Real(val, negative, positive) result(retval)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: val
    logical, intent(in), optional :: negative
    logical, intent(in), optional :: positive

    Return Value real(kind=real64)

public interface removeWord

It removes a character from string.

  • public subroutine removeWord_String(str, keyword, itr, Compare)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(inout) :: str
    character(len=*), intent(in) :: keyword
    integer(kind=int32), intent(in), optional :: itr
    logical, intent(in), optional :: Compare

public interface tensor_product

It computes tensor product.

  • public function tensor_product_complex(a, b) result(c)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: a(:)
    complex(kind=real64), intent(in) :: b(:)

    Return Value complex(kind=real64), allocatable, (:,:)

  • public function tensor_product_real64(a, b) result(c)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: a(:)
    real(kind=real64), intent(in) :: b(:)

    Return Value real(kind=real64), allocatable, (:,:)

public interface radian

It converts deg. to rad.

  • public function radianreal32(deg) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real32), intent(in) :: deg

    Return Value real(kind=real64)

  • public function radianreal64(deg) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: deg

    Return Value real(kind=real64)

  • public function radianreal64Vec(degs) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: degs(:)

    Return Value real(kind=real64), allocatable, (:)

  • public function radianint(deg) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: deg

    Return Value real(kind=real64)

public interface array

It allocates array.

  • public function arrayDim1Real64(size1) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: size1

    Return Value real(kind=real64), allocatable, (:)

  • public function arrayDim2Real64(size1, size2) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: size1
    integer(kind=int32), intent(in) :: size2

    Return Value real(kind=real64), allocatable, (:,:)

  • public function arrayDim3Real64(size1, size2, size3) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: size1
    integer(kind=int32), intent(in) :: size2
    integer(kind=int32), intent(in) :: size3

    Return Value real(kind=real64), allocatable, (:,:,:)

public interface RickerFunction

It returns the Ricker's function.

  • public pure function RickerFunctionReal64(t, sigma, center) result(ft)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: t
    real(kind=real64), intent(in) :: sigma
    real(kind=real64), intent(in), optional :: center

    Return Value real(kind=real64)

  • public pure function RickerFunctionReal64Vector(t, sigma, center) result(ft)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: t(:)
    real(kind=real64), intent(in) :: sigma
    real(kind=real64), intent(in), optional :: center

    Return Value real(kind=real64), allocatable, (:)

public interface derivative

It gives a numerical derivative.

  • public function derivative_scalar(func, x, eps)

    Arguments

    Type IntentOptional Attributes Name
    public function func(x)
    Arguments
    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x
    Return Value real(kind=real64)
    real(kind=real64), intent(in) :: x
    real(kind=real64), intent(in), optional :: eps

    Return Value real(kind=real64)

  • public function derivative_vector(func, x, dim_num, eps) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    public function func(x) result(ret)
    Arguments
    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x(:)
    Return Value real(kind=real64), allocatable, (:)
    real(kind=real64), intent(in) :: x(1:dim_num)
    integer(kind=int32), intent(in) :: dim_num
    real(kind=real64), intent(in), optional :: eps

    Return Value real(kind=real64), allocatable, (:)

public interface der

It gives a numerical derivative.

  • public function derivative_scalar(func, x, eps)

    Arguments

    Type IntentOptional Attributes Name
    public function func(x)
    Arguments
    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x
    Return Value real(kind=real64)
    real(kind=real64), intent(in) :: x
    real(kind=real64), intent(in), optional :: eps

    Return Value real(kind=real64)

  • public function derivative_vector(func, x, dim_num, eps) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    public function func(x) result(ret)
    Arguments
    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x(:)
    Return Value real(kind=real64), allocatable, (:)
    real(kind=real64), intent(in) :: x(1:dim_num)
    integer(kind=int32), intent(in) :: dim_num
    real(kind=real64), intent(in), optional :: eps

    Return Value real(kind=real64), allocatable, (:)

public interface d_dx

It gives a numerical derivative.

  • public function derivative_scalar(func, x, eps)

    Arguments

    Type IntentOptional Attributes Name
    public function func(x)
    Arguments
    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x
    Return Value real(kind=real64)
    real(kind=real64), intent(in) :: x
    real(kind=real64), intent(in), optional :: eps

    Return Value real(kind=real64)

  • public function derivative_vector(func, x, dim_num, eps) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    public function func(x) result(ret)
    Arguments
    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x(:)
    Return Value real(kind=real64), allocatable, (:)
    real(kind=real64), intent(in) :: x(1:dim_num)
    integer(kind=int32), intent(in) :: dim_num
    real(kind=real64), intent(in), optional :: eps

    Return Value real(kind=real64), allocatable, (:)

public interface FFT

It computes the fact Fourier transformation.

  • public function FFT1D(x, T, window) result(hatx)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=kind(0d0)), intent(in) :: x(:)
    real(kind=real64), intent(in), optional :: T(2)
    character(len=*), intent(in), optional :: window

    Return Value complex(kind=kind(0d0)), allocatable, (:)

  • public function FFT2D_real(xy) result(hatx)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: xy(:,:)

    Return Value complex(kind=real64), allocatable, (:,:)

  • public function FFT2D_comp(xy) result(hatx)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real64), intent(in) :: xy(:,:)

    Return Value complex(kind=real64), allocatable, (:,:)

  • public function FFT_file_to_file(infile, outfile, window_size, dt, column, as_abs) result(FourierSpectrum)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: infile
    character(len=*), intent(in) :: outfile
    integer(kind=int32), intent(in) :: window_size
    real(kind=real64), intent(in) :: dt
    integer(kind=int32), intent(in) :: column
    logical, intent(in), optional :: as_abs

    Return Value complex(kind=real64), allocatable, (:,:)

public interface PSD

It computes the power spectral density function from datafile.

  • public function PSD_file_to_file(infile, outfile, window_size, dt, column) result(FourierSpectrum)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: infile
    character(len=*), intent(in) :: outfile
    integer(kind=int32), intent(in) :: window_size
    real(kind=real64) :: dt
    integer(kind=int32), intent(in) :: column

    Return Value complex(kind=real64), allocatable, (:,:)

public interface SpectralWhitening

It performs spectral whitening.

  • public function SpectralWhitening_real64(x, auto) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: x(:)
    logical, intent(in), optional :: auto

    Return Value real(kind=real64), allocatable, (:)

public interface exp

It computes matrix exponential by the Taylor expansion.

  • public function matrix_exponential_real64(mat, order) result(ret)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in) :: mat(:,:)
    integer(kind=int32), intent(in) :: order

    Return Value real(kind=real64), allocatable, (:,:)

public interface assignment(=)

  • public subroutine assign_real64(x, y)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(inout) :: x
    character(len=*), intent(in) :: y
  • public subroutine assign_int32(x, y)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout) :: x
    character(len=*), intent(in) :: y

Derived Types

type, public ::  Math_

Components

Type Visibility Attributes Name Initial
real(kind=real64), public :: PI = 3.14159265358979323846d0

For saving the computation time, this uses a fixed value for PI.

real(kind=real64), public :: E = 2.718281828459045d0

For saving the computation time, this uses a fixed value for e.

complex(kind=kind(0d0)), public :: i = (0.0d0, 1.0d0)
complex(kind=kind(0d0)), public :: j = (0.0d0, 1.0d0)

It is a unit imaginary value.

type, public ::  Real64Ptr_

A real64-type pointer.

Components

Type Visibility Attributes Name Initial
real(kind=real64), public, pointer :: ptr

Functions

public function SpectralWhitening_real64(x, auto) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x(:)
logical, intent(in), optional :: auto

Return Value real(kind=real64), allocatable, (:)

public function FFT_file_to_file(infile, outfile, window_size, dt, column, as_abs) result(FourierSpectrum)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: infile
character(len=*), intent(in) :: outfile
integer(kind=int32), intent(in) :: window_size
real(kind=real64), intent(in) :: dt
integer(kind=int32), intent(in) :: column
logical, intent(in), optional :: as_abs

Return Value complex(kind=real64), allocatable, (:,:)

public function PSD_file_to_file(infile, outfile, window_size, dt, column) result(FourierSpectrum)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: infile
character(len=*), intent(in) :: outfile
integer(kind=int32), intent(in) :: window_size
real(kind=real64) :: dt
integer(kind=int32), intent(in) :: column

Return Value complex(kind=real64), allocatable, (:,:)

public function FFT2D_real(xy) result(hatx)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: xy(:,:)

Return Value complex(kind=real64), allocatable, (:,:)

public function FFT2D_comp(xy) result(hatx)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: xy(:,:)

Return Value complex(kind=real64), allocatable, (:,:)

public function FFT1D(x, T, window) result(hatx)

Arguments

Type IntentOptional Attributes Name
complex(kind=kind(0d0)), intent(in) :: x(:)
real(kind=real64), intent(in), optional :: T(2)
character(len=*), intent(in), optional :: window

Return Value complex(kind=kind(0d0)), allocatable, (:)

public function hann(L) result(hann_window)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: L

Return Value real(kind=real64), (1:L)

public recursive function FFT_core(x) result(hatx)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: x(:)

Return Value complex(kind=real64), allocatable, (:)

public function IFFT(x, T) result(hatx)

Arguments

Type IntentOptional Attributes Name
complex(kind=kind(0d0)), intent(in) :: x(:)
real(kind=real64), intent(in), optional :: T(2)

Return Value complex(kind=kind(0d0)), allocatable, (:)

public recursive function IFFT_core(x) result(hatx)

Arguments

Type IntentOptional Attributes Name
complex(kind=kind(0d0)), intent(in) :: x(:)

Return Value complex(kind=kind(0d0)), allocatable, (:)

public function arrayDim1Real64(size1) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: size1

Return Value real(kind=real64), allocatable, (:)

public function arrayDim2Real64(size1, size2) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: size1
integer(kind=int32), intent(in) :: size2

Return Value real(kind=real64), allocatable, (:,:)

public function arrayDim3Real64(size1, size2, size3) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: size1
integer(kind=int32), intent(in) :: size2
integer(kind=int32), intent(in) :: size3

Return Value real(kind=real64), allocatable, (:,:,:)

public function radianreal32(deg) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real32), intent(in) :: deg

Return Value real(kind=real64)

public function radianreal64(deg) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: deg

Return Value real(kind=real64)

public function radianreal64Vec(degs) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: degs(:)

Return Value real(kind=real64), allocatable, (:)

public function radianint(deg) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: deg

Return Value real(kind=real64)

public function degrees(rad) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: rad

Return Value real(kind=real64)

public function norm_vec(vec) result(a)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: vec(:)

Return Value real(kind=real64)

public function norm_vec_real32(vec) result(a)

Arguments

Type IntentOptional Attributes Name
real(kind=real32), intent(in) :: vec(:)

Return Value real(kind=real32)

public function norm_vec_complex64(vec) result(a)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: vec(:)

Return Value real(kind=real64)

public function norm_mat(vec) result(a)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: vec(:,:)

Return Value real(kind=real64)

public pure function SearchNearestValueID(Vector, x) result(id)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: Vector(:)
real(kind=real64), intent(in) :: x

Return Value integer(kind=int32)

public function SearchNearestValueIDs(Vector, x, num) result(id)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: Vector(:)
real(kind=real64), intent(in) :: x
integer(kind=int32), intent(in) :: num

Return Value integer(kind=int32), (num)

public function SearchNearestValue(Vector, x) result(val)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: Vector(:)
real(kind=real64), intent(in) :: x

Return Value real(kind=real64)

public function SearchNearestCoord(Array, x) result(id)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: Array(:,:)
real(kind=real64), intent(in) :: x(:)

Return Value integer(kind=int32)

public function SearchIDIntVec(Vec, val) result(id_)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: Vec(:)
integer(kind=int32), intent(in) :: val

Return Value integer(kind=int32)

public function sort_int32(vec) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: vec(:)

Return Value integer(kind=int32), allocatable, (:)

public pure function cross_product(a, b) result(c)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(:)
real(kind=real64), intent(in) :: b(:)

Return Value real(kind=real64), allocatable, (:)

public function diadic(a, b) result(c)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(:)
real(kind=real64), intent(in) :: b(:)

Return Value real(kind=real64), allocatable, (:,:)

public function tensor_product_real64(a, b) result(c)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(:)
real(kind=real64), intent(in) :: b(:)

Return Value real(kind=real64), allocatable, (:,:)

public function tensor_product_complex(a, b) result(c)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: a(:)
complex(kind=real64), intent(in) :: b(:)

Return Value complex(kind=real64), allocatable, (:,:)

public function arg_complex64(comp) result(theta)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: comp

Return Value real(kind=real64)

public function arg_complex64_vector(comp) result(theta)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: comp(:)

Return Value real(kind=real64), allocatable, (:)

public function arg_complex64_tensor(comp) result(theta)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: comp(:,:)

Return Value real(kind=real64), allocatable, (:,:)

public function cubic_equation(a, b, c, d) result(x)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a
real(kind=real64), intent(in) :: b
real(kind=real64), intent(in) :: c
real(kind=real64), intent(in) :: d

Return Value real(kind=real64), (3)

public function signmm(a) result(b)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a

Return Value real(kind=real64)

public recursive function det_mat_real64(a, n) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(n,n)
integer(kind=int32), intent(in) :: n

Return Value real(kind=real64)

public recursive function det_mat_complex64(a, n) result(ret)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: a(n,n)
integer(kind=int32), intent(in) :: n

Return Value complex(kind=real64)

public recursive function det(a, n) result(det_v)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(n,n)
integer(kind=int32), intent(in) :: n

Return Value real(kind=real64)

public function trans1(A) result(A_T)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: A(:)

Return Value real(kind=real64), allocatable, (:,:)

public function trans2(A) result(A_T)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: A(:,:)

Return Value real(kind=real64), allocatable, (:,:)

public function inverse(A) result(A_inv)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: A(:,:)

Return Value real(kind=real64), allocatable, (:,:)

public function identity_matrix(n) result(mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n

Return Value real(kind=real64), (n,n)

public function zero_matrix(n) result(mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n

Return Value real(kind=real64), (n,n)

public function GetNormRe(a) result(b)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(:)

Return Value real(kind=real64)

public function GetNormMatRe(a) result(b)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(:,:)

Return Value real(kind=real64)

public function trace_real64(a) result(b)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(:,:)

Return Value real(kind=real64)

public function trace_complex64(a) result(b)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: a(:,:)

Return Value complex(kind=real64)

public function sym(a, n) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(:,:)
integer(kind=int32) :: n

Return Value real(kind=real64), (n,n)

public function asym(a, n) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: a(:,:)
integer(kind=int32) :: n

Return Value real(kind=real64), (n,n)

public function pi_value(n) result(res)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n

Return Value real(kind=real64)

public pure function fstring_int(x) result(a)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: x

Return Value character(len=:), allocatable

public pure function fstring_int64(x) result(a)

Arguments

Type IntentOptional Attributes Name
integer(kind=int64), intent(in) :: x

Return Value character(len=:), allocatable

public pure function fstring_logical(x) result(a)

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: x

Return Value character(len=5)

public pure function fstring_String(x) result(a)

Arguments

Type IntentOptional Attributes Name
type(string_), intent(in) :: x

Return Value character(len=:), allocatable

public pure function fstring_int_len(x, length) result(a)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: x
integer(kind=int32), intent(in) :: length

Return Value character(len=length)

public pure function fstring_real(x) result(a)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x

Return Value character(len=:), allocatable

public pure function fstring_real32(x) result(a)

Arguments

Type IntentOptional Attributes Name
real(kind=real32), intent(in) :: x

Return Value character(len=:), allocatable

public pure function fstring_complex(x) result(a)

Arguments

Type IntentOptional Attributes Name
complex(kind=kind(0d0)), intent(in) :: x

Return Value character(len=:), allocatable

public pure function fstring_real_len(x, length) result(a)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x
integer(kind=int32), intent(in) :: length

Return Value character(len=60)

public function fint(ch) result(a)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: ch

Return Value integer(kind=int32)

public function fint16(ch) result(a)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: ch

Return Value integer(kind=int16)

public function fint32(ch) result(a)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: ch

Return Value integer(kind=int32)

public function fint64(ch) result(a)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: ch

Return Value integer(kind=int64)

public function freal(ch) result(a)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: ch

Return Value real(kind=real64)

public function freal32(ch) result(a)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: ch

Return Value real(kind=real32)

public function freal64(ch) result(a)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: ch

Return Value real(kind=real64)

public function freal128(ch) result(a)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: ch

Return Value real(kind=real64)

public function input_Int(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: default
integer(kind=int32), intent(in), optional :: option

Return Value integer(kind=int32)

public function input_Real(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: default
real(kind=real64), intent(in), optional :: option

Return Value real(kind=real64)

public function input_Real32(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
real(kind=real32), intent(in) :: default
real(kind=real32), intent(in), optional :: option

Return Value real(kind=real32)

public function input_Complex(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: default
complex(kind=real64), intent(in), optional :: option

Return Value complex(kind=real64)

public function input_IntVec(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: default(:)
integer(kind=int32), intent(in), optional :: option(:)

Return Value integer(kind=int32), allocatable, (:)

public function input_Realvec(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: default(:)
real(kind=real64), intent(in), optional :: option(:)

Return Value real(kind=real64), allocatable, (:)

public function input_IntArray(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: default(:,:)
integer(kind=int32), intent(in), optional :: option(:,:)

Return Value integer(kind=int32), allocatable, (:,:)

public function input_RealArray(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: default(:,:)
real(kind=real64), intent(in), optional :: option(:,:)

Return Value real(kind=real64), allocatable, (:,:)

public function input_String(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: default
character(len=*), intent(in), optional :: option

Return Value character(len=200)

public function input_logical(default, option) result(val)

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: default
logical, intent(in), optional :: option

Return Value logical

public function zeroif_Int(val, negative, positive) result(retval)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: val
logical, intent(in), optional :: negative
logical, intent(in), optional :: positive

Return Value integer(kind=int32)

public function zeroif_Real(val, negative, positive) result(retval)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: val
logical, intent(in), optional :: negative
logical, intent(in), optional :: positive

Return Value real(kind=real64)

public function Invariant_I1(sigma) result(I1)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: sigma(:,:)

Return Value real(kind=real64)

public function Invariant_J2(sigma) result(J2)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: sigma(:,:)

Return Value real(kind=real64)

public function Invariant_J3(sigma) result(J3)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: sigma(:,:)

Return Value real(kind=real64)

public function Invariant_theta(sigma) result(theta)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: sigma(:,:)

Return Value real(kind=real64)

public function inv_mod(a_in, m_in, ItrMax) result(x)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: a_in
integer(kind=int32), intent(in) :: m_in
integer(kind=int32), intent(in), optional :: ItrMax

Return Value integer(kind=int32)

public function gcd(a, b, ItrMax) result(c)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: a
integer(kind=int32), intent(in) :: b
integer(kind=int32), intent(in), optional :: ItrMax

Return Value integer(kind=int32)

public function lcm(a, b, ItrMax) result(c)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: a
integer(kind=int32), intent(in) :: b
integer(kind=int32), intent(in), optional :: ItrMax

Return Value integer(kind=int32)

public function convertStringToInteger(message) result(ret)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: message

Return Value character(len=2)

public function convertIntegerToString(message) result(ret)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: message

Return Value character(len=len(message))

public function rsa_encrypt(id_rsa_pub, message) result(ciphertext)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: id_rsa_pub(2)
integer(kind=int32), intent(in) :: message

Return Value integer(kind=int32)

public function rsa_decrypt(id_rsa, ciphertext) result(message)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: id_rsa(2)
integer(kind=int32), intent(in) :: ciphertext

Return Value integer(kind=int32)

public function IsItNumber(char) result(res)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(inout) :: char

Return Value logical

public function RectangularWindow(original_data, Width) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: original_data(:)
integer(kind=int32), intent(in) :: Width

Return Value real(kind=real64), allocatable, (:)

public function DigitalWindow(original_data) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: original_data(:)

Return Value real(kind=real64), allocatable, (:)

public function HanningWindow(Width, DataSize) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: Width
integer(kind=int32), intent(in) :: DataSize

Return Value real(kind=real64), (DataSize)

public function HammingWindow(Width, DataSize) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: Width
integer(kind=int32), intent(in) :: DataSize

Return Value real(kind=real64), (DataSize)

public function log2(x) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x

Return Value real(kind=real64)

public pure function day(unit) result(ret)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: unit

Return Value real(kind=real64)

public pure recursive function factorialInt32(n) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n

Return Value integer(kind=int64)

public pure recursive function factorialReal64(n) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: n

Return Value real(kind=real64)

public pure function comb(n, r) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: r

Return Value real(kind=real64)

public function stringFromChar(charval) result(ret)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: charval

Return Value type(string_)

public pure function zfill(intval, n) result(ret)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: intval
integer(kind=int32), intent(in) :: n

Return Value character(len=n)

public pure function imaginary_partComplex64(complexValue) result(imgpart)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: complexValue

Return Value real(kind=real64)

public pure function imaginary_partComplex32(complexValue) result(imgpart)

Arguments

Type IntentOptional Attributes Name
complex(kind=real32), intent(in) :: complexValue

Return Value real(kind=real32)

public function hilbert(wave) result(h_top_wave)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: wave(:)

Return Value complex(kind=real64), allocatable, (:)

public function short_time_FFT(wave, frame) result(spectre)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: wave(:)
integer(kind=int32), intent(in) :: frame

Return Value complex(kind=real64), allocatable, (:,:)

public pure function RickerFunctionReal64(t, sigma, center) result(ft)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: t
real(kind=real64), intent(in) :: sigma
real(kind=real64), intent(in), optional :: center

Return Value real(kind=real64)

public pure function RickerFunctionReal64Vector(t, sigma, center) result(ft)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: t(:)
real(kind=real64), intent(in) :: sigma
real(kind=real64), intent(in), optional :: center

Return Value real(kind=real64), allocatable, (:)

public function derivative_scalar(func, x, eps)

Arguments

Type IntentOptional Attributes Name
public function func(x)
Arguments
Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x
Return Value real(kind=real64)
real(kind=real64), intent(in) :: x
real(kind=real64), intent(in), optional :: eps

Return Value real(kind=real64)

public function derivative_vector(func, x, dim_num, eps) result(ret)

Arguments

Type IntentOptional Attributes Name
public function func(x) result(ret)
Arguments
Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x(:)
Return Value real(kind=real64), allocatable, (:)
real(kind=real64), intent(in) :: x(1:dim_num)
integer(kind=int32), intent(in) :: dim_num
real(kind=real64), intent(in), optional :: eps

Return Value real(kind=real64), allocatable, (:)

public function polynomial(x, params)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x
real(kind=real64), intent(in) :: params(:)

Return Value real(kind=real64)

public function sigmoid(x, params)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x
real(kind=real64), intent(in) :: params(:)

Return Value real(kind=real64)

public function logit(x, params)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: x
real(kind=real64), intent(in) :: params(:)

Return Value real(kind=real64)

public function int_from_logical(logical_value) result(ret)

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: logical_value

Return Value integer(kind=int32)

public function int_from_logical_vector(logical_value) result(ret)

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: logical_value(:)

Return Value integer(kind=int32), allocatable, (:)

public function matrix_exponential_real64(mat, order) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: mat(:,:)
integer(kind=int32), intent(in) :: order

Return Value real(kind=real64), allocatable, (:,:)

public function Bessel_J0_complex(z) result(ret)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: z

Return Value complex(kind=real64)

public function Bessel_J1_complex(z) result(ret)

Arguments

Type IntentOptional Attributes Name
complex(kind=real64), intent(in) :: z

Return Value complex(kind=real64)


Subroutines

public subroutine heapsortReal64(n, array, val)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n
real(kind=real64), intent(inout) :: array(1:n)
real(kind=real64), intent(inout), optional :: val(1:n)

public subroutine heapsortReal32(n, array, val)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n
real(kind=real32), intent(inout) :: array(1:n)
real(kind=real32), intent(inout), optional :: val(1:n)

public pure subroutine heapsortInt32(n, array, val)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(inout) :: array(1:n)
real(kind=real64), intent(inout), optional :: val(1:n)

public pure subroutine heapsortInt32Int32(n, array, val)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(inout) :: array(1:n)
integer(kind=int32), intent(inout) :: val(1:n)

public pure subroutine heapsortReal64Int32(n, array, val)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: n
real(kind=real64), intent(inout) :: array(1:n)
integer(kind=int32), intent(inout) :: val(1:n)

public subroutine calcgz(x2, x11, x12, nod_coord, gzi)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: x2
integer(kind=int32), intent(in) :: x11
integer(kind=int32), intent(in) :: x12
real(kind=real64), intent(in) :: nod_coord(:,:)
real(kind=real64), intent(out) :: gzi

public subroutine eigen_2d(Amat, eigenvector)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: Amat(:,:)
real(kind=real64), intent(inout), allocatable :: eigenvector(:,:)

public subroutine trans_rank_2(A, A_T)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: A(:,:)
real(kind=real64), intent(out), allocatable :: A_T(:,:)

public subroutine inverse_rank_2(A, A_inv)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: A(:,:)
real(kind=real64), allocatable :: A_inv(:,:)

public subroutine tensor_exponential(A, expA, TOL, itr_tol)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: A(:,:)
real(kind=real64), intent(inout), allocatable :: expA(:,:)
real(kind=real64), intent(in) :: TOL
integer(kind=int32), intent(in) :: itr_tol

public subroutine tensor_expo_der(A, expA_A, TOL, itr_tol)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(in) :: A(:,:)
real(kind=real64), intent(inout), allocatable :: expA_A(:,:,:,:)
real(kind=real64), intent(in) :: TOL
integer(kind=int32), intent(in) :: itr_tol

public subroutine removeWord_String(str, keyword, itr, Compare)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(inout) :: str
character(len=*), intent(in) :: keyword
integer(kind=int32), intent(in), optional :: itr
logical, intent(in), optional :: Compare

public subroutine rsa_keygen(prime1, prime2, seed, id_rsa, id_rsa_pub)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: prime1
integer(kind=int32), intent(in) :: prime2
integer(kind=int32), intent(in) :: seed
integer(kind=int32), intent(out) :: id_rsa(2)
integer(kind=int32), intent(out) :: id_rsa_pub(2)

public recursive subroutine heapsort_int32_array(array, order, exec_row_sort)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(inout) :: array(:,:)
integer(kind=int32), intent(inout), optional, allocatable :: order(:)
logical, intent(in), optional :: exec_row_sort

public recursive subroutine heapsort_real64_array(array, order, exec_row_sort)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(inout) :: array(:,:)
integer(kind=int32), intent(inout), optional, allocatable :: order(:)
logical, intent(in), optional :: exec_row_sort

public subroutine sort_and_remove_duplication_int32(array, order)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(inout), allocatable :: array(:,:)
integer(kind=int32), intent(inout), optional, allocatable :: order(:)

public subroutine sort_and_remove_duplication_real64(array, order)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(inout), allocatable :: array(:,:)
integer(kind=int32), intent(inout), optional, allocatable :: order(:)

public subroutine assign_real64(x, y)

Arguments

Type IntentOptional Attributes Name
real(kind=real64), intent(inout) :: x
character(len=*), intent(in) :: y

public subroutine assign_int32(x, y)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(inout) :: x
character(len=*), intent(in) :: y