MathClass Module



Contents


Variables

TypeVisibility AttributesNameInitial
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

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

    Arguments

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

    Return Value real(kind=real64)

public interface choose

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

    Arguments

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

    Return Value real(kind=real64)

public interface fact

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

    Arguments

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

    Return Value integer(kind=int64)

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

    Arguments

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

    Return Value real(kind=real64)

public interface factorial

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

    Arguments

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

    Return Value integer(kind=int64)

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

    Arguments

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

    Return Value real(kind=real64)

public interface heapsort

  • public subroutine heapsortInt32(n, array, val)

    Arguments

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

    Arguments

    Type IntentOptional AttributesName
    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 AttributesName
    integer(kind=int32), intent(in) :: n
    real(kind=real32), intent(inout) :: array(1:n)
    real(kind=real32), intent(inout), optional :: val(1:n)

public interface str

  • public function fstring_int(x) result(a)

    Arguments

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

    Return Value character(len=:), allocatable

  • public function fstring_real(x) result(a)

    Arguments

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

    Return Value character(len=:), allocatable

  • public function fstring_real32(x) result(a)

    Arguments

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

    Return Value character(len=:), allocatable

  • public function fstring_complex(x) result(a)

    Arguments

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

    Return Value character(len=:), allocatable

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

    Arguments

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

    Return Value character(len=length)

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

    Arguments

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

    Return Value character(len=60)

  • public function fstring_logical(x) result(a)

    Arguments

    Type IntentOptional AttributesName
    logical, intent(in) :: x

    Return Value character(len=5)

  • public function fstring_String(x) result(a)

    Arguments

    Type IntentOptional AttributesName
    type(string_), intent(in) :: x

    Return Value character(len=:), allocatable

  • public function stringFromChar(charval) result(ret)

    Arguments

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

    Return Value type(string_)

public interface fstring

  • public function fstring_int(x) result(a)

    Arguments

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

    Return Value character(len=:), allocatable

  • public function fstring_real(x) result(a)

    Arguments

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

    Return Value character(len=:), allocatable

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

    Arguments

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

    Return Value character(len=length)

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

    Arguments

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

    Return Value character(len=60)

  • public function fstring_logical(x) result(a)

    Arguments

    Type IntentOptional AttributesName
    logical, intent(in) :: x

    Return Value character(len=5)

public interface input

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

    Arguments

    Type IntentOptional AttributesName
    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 AttributesName
    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 AttributesName
    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 AttributesName
    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 AttributesName
    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 AttributesName
    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 AttributesName
    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 AttributesName
    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 AttributesName
    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 AttributesName
    logical, intent(in) :: default
    logical, intent(in), optional :: option

    Return Value logical

public interface zeroif

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

    Arguments

    Type IntentOptional AttributesName
    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 AttributesName
    real(kind=real64), intent(in) :: val
    logical, intent(in), optional :: negative
    logical, intent(in), optional :: positive

    Return Value real(kind=real64)

public interface removeWord

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

    Arguments

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

public interface radian

  • public function radianreal32(deg) result(ret)

    Arguments

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

    Return Value real(kind=real64)

  • public function radianreal64(deg) result(ret)

    Arguments

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

    Return Value real(kind=real64)

  • public function radianint(deg) result(ret)

    Arguments

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

    Return Value real(kind=real64)

public interface array

  • public function arrayDim1Real64(size1) result(ret)

    Arguments

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

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

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

    Arguments

    Type IntentOptional AttributesName
    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 AttributesName
    integer(kind=int32), intent(in) :: size1
    integer(kind=int32), intent(in) :: size2
    integer(kind=int32), intent(in) :: size3

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


Derived Types

type, public :: Math_

Components

TypeVisibility AttributesNameInitial
real(kind=real64), public :: PI =3.141592653589793d0
real(kind=real64), public :: E =2.718281828459045d0
complex(kind=kind(0d0)), public :: i =(0.0d0, 1.0d0)
complex(kind=kind(0d0)), public :: j =(0.0d0, 1.0d0)

type, public :: Real64Ptr_

Components

TypeVisibility AttributesNameInitial
real(kind=real64), public, pointer:: ptr

Functions

public recursive function FFT(x) result(hatx)

Arguments

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

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

public function IFFT(x) result(hatx)

Arguments

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

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

public recursive function IFFT_core(x) result(hatx)

Arguments

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

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

public function arrayDim1Real64(size1) result(ret)

Arguments

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

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

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
real(kind=real32), intent(in) :: deg

Return Value real(kind=real64)

public function radianreal64(deg) result(ret)

Arguments

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

Return Value real(kind=real64)

public function radianint(deg) result(ret)

Arguments

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

Return Value real(kind=real64)

public function degrees(rad) result(ret)

Arguments

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

Return Value real(kind=real64)

public function norm(vec) result(a)

Arguments

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

Return Value real(kind=real64)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
integer(kind=int32), intent(in) :: Vec(:)
integer(kind=int32), intent(in) :: val

Return Value integer(kind=int32)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
real(kind=real64), intent(in) :: a(:)
real(kind=real64), intent(in) :: b(:)

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

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

Arguments

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

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

public function arg(comp) result(theta)

Arguments

Type IntentOptional AttributesName
complex, intent(in) :: comp

Return Value real(kind=real64)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
real(kind=real64), intent(in) :: a

Return Value real(kind=real64)

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

Arguments

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

Return Value real(kind=real64)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
real(kind=real64), intent(in) :: A(:)

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

public function trans2(A) result(A_T)

Arguments

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

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

public function inverse(A) result(A_inv)

Arguments

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

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

public function identity_matrix(n) result(mat)

Arguments

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

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

public function zero_matrix(n) result(mat)

Arguments

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

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

public function GetNormRe(a) result(b)

Arguments

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

Return Value real(kind=real64)

public function GetNormMatRe(a) result(b)

Arguments

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

Return Value real(kind=real64)

public function trace(a) result(b)

Arguments

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

Return Value real(kind=real64)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
integer(kind=int32), intent(in) :: n

Return Value real(kind=real64)

public function fstring_int(x) result(a)

Arguments

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

Return Value character(len=:), allocatable

public function fstring_logical(x) result(a)

Arguments

Type IntentOptional AttributesName
logical, intent(in) :: x

Return Value character(len=5)

public function fstring_String(x) result(a)

Arguments

Type IntentOptional AttributesName
type(string_), intent(in) :: x

Return Value character(len=:), allocatable

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

Arguments

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

Return Value character(len=length)

public function fstring_real(x) result(a)

Arguments

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

Return Value character(len=:), allocatable

public function fstring_real32(x) result(a)

Arguments

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

Return Value character(len=:), allocatable

public function fstring_complex(x) result(a)

Arguments

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

Return Value character(len=:), allocatable

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
character(len=*), intent(in) :: ch

Return Value integer(kind=int32)

public function fint16(ch) result(a)

Arguments

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

Return Value integer(kind=int16)

public function fint32(ch) result(a)

Arguments

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

Return Value integer(kind=int32)

public function fint64(ch) result(a)

Arguments

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

Return Value integer(kind=int64)

public function freal(ch) result(a)

Arguments

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

Return Value real(kind=real64)

public function freal32(ch) result(a)

Arguments

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

Return Value real(kind=real32)

public function freal64(ch) result(a)

Arguments

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

Return Value real(kind=real64)

public function freal128(ch) result(a)

Arguments

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

Return Value real(kind=real64)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
logical, intent(in) :: default
logical, intent(in), optional :: option

Return Value logical

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
real(kind=real64), intent(in) :: sigma(:,:)

Return Value real(kind=real64)

public function Invariant_J2(sigma) result(J2)

Arguments

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

Return Value real(kind=real64)

public function Invariant_J3(sigma) result(J3)

Arguments

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

Return Value real(kind=real64)

public function Invariant_theta(sigma) result(theta)

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
character(len=*), intent(in) :: message

Return Value character(len=2*len(message))

public function convertIntegerToString(message) result(ret)

Arguments

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

Return Value character(len=len(message))

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
character(len=*), intent(inout) :: char

Return Value logical

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

Arguments

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

Return Value real(kind=real64) (DataSize)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
real(kind=real64), intent(in) :: x

Return Value real(kind=real64)

public pure function day(unit) result(ret)

Arguments

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

Return Value real(kind=real64)

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

Arguments

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

Return Value integer(kind=int64)

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

Arguments

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

Return Value real(kind=real64)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
character(len=*), intent(in) :: charval

Return Value type(string_)

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

Arguments

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

Return Value character(len=n)


Subroutines

public subroutine heapsortReal64(n, array, val)

Arguments

Type IntentOptional AttributesName
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 AttributesName
integer(kind=int32), intent(in) :: n
real(kind=real32), intent(inout) :: array(1:n)
real(kind=real32), intent(inout), optional :: val(1:n)

public subroutine heapsortInt32(n, array, val)

Arguments

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

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
real(kind=real64), intent(in) :: Amat(:,:)
real(kind=real64), intent(inout), allocatable:: eigenvector(:,:)

public subroutine trans_rank_2(A, A_T)

Arguments

Type IntentOptional AttributesName
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 AttributesName
real(kind=real64), intent(in) :: A(:,:)
real(kind=real64), allocatable:: A_inv(:,:)

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

Arguments

Type IntentOptional AttributesName
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 AttributesName
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 AttributesName
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 AttributesName
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)