LinearSolverClass Module



Contents


Interfaces

public interface BiCGSTAB

  • public subroutine bicgstab_real32(a, b, x, n, itrmax, er)

    Arguments

    Type IntentOptional AttributesName
    real(kind=real32), intent(in) :: a(n,n)
    real(kind=real32), intent(in) :: b(n)
    real(kind=real32), intent(inout) :: x(n)
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(in) :: itrmax
    real(kind=real32), intent(in) :: er
  • public subroutine bicgstab_real64(a, b, x, n, itrmax, er)

    Arguments

    Type IntentOptional AttributesName
    real(kind=real64), intent(in) :: a(n,n)
    real(kind=real64), intent(in) :: b(n)
    real(kind=real64), intent(inout) :: x(n)
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(in) :: itrmax
    real(kind=real64), intent(in) :: er
  • public subroutine bicgstab_complex64(a, b, x, n, itrmax, er)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=real64), intent(in) :: a(n,n)
    complex(kind=real64), intent(in) :: b(n)
    complex(kind=real64), intent(inout) :: x(n)
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(in) :: itrmax
    complex(kind=real64), intent(in) :: er

public interface GPBiCG

  • public subroutine GPBiCG_real32(a, b, x, n, itrmax, er)

    Arguments

    Type IntentOptional AttributesName
    real(kind=real32), intent(in) :: a(n,n)
    real(kind=real32), intent(in) :: b(n)
    real(kind=real32), intent(inout) :: x(n)
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(in), optional :: itrmax
    real(kind=real32), intent(in), optional :: er
  • public subroutine GPBiCG_real64(a, b, x, n, itrmax, er)

    Arguments

    Type IntentOptional AttributesName
    real(kind=real64), intent(in) :: a(n,n)
    real(kind=real64), intent(in) :: b(n)
    real(kind=real64), intent(inout) :: x(n)
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(in), optional :: itrmax
    real(kind=real64), intent(in), optional :: er
  • public subroutine GPBiCG_complex64(a, b, x, n, itrmax, er)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=real64), intent(in) :: a(n,n)
    complex(kind=real64), intent(in) :: b(n)
    complex(kind=real64), intent(inout) :: x(n)
    integer(kind=int32), intent(in) :: n
    integer(kind=int32), intent(in), optional :: itrmax
    complex(kind=real64), intent(in), optional :: er

public interface Gauss_Jordan_PV

  • public subroutine gauss_jordan_pv_real32(a0, x, b, n)

    Arguments

    Type IntentOptional AttributesName
    real(kind=real32), intent(in) :: a0(n,n)
    real(kind=real32), intent(out) :: x(n)
    real(kind=real32), intent(in) :: b(n)
    integer(kind=int32), intent(in) :: n
  • public subroutine gauss_jordan_pv_real64(a0, x, b, n)

    Arguments

    Type IntentOptional AttributesName
    real(kind=real64), intent(in) :: a0(n,n)
    real(kind=real64), intent(out) :: x(n)
    real(kind=real64), intent(in) :: b(n)
    integer(kind=int32), intent(in) :: n
  • public subroutine gauss_jordan_pv_complex64(a0, x, b, n)

    Arguments

    Type IntentOptional AttributesName
    complex(kind=real64), intent(in) :: a0(n,n)
    complex(kind=real64), intent(out) :: x(n)
    complex(kind=real64), intent(in) :: b(n)
    integer(kind=int32), intent(in) :: n

Derived Types

type, public :: LinearSolver_

Components

TypeVisibility AttributesNameInitial
real(kind=real64), public, allocatable:: a(:,:)
real(kind=real64), public, allocatable:: b(:)
real(kind=real64), public, allocatable:: x(:)
real(kind=real64), public, allocatable:: a_e(:,:,:)
real(kind=real64), public, allocatable:: b_e(:,:)
real(kind=real64), public, allocatable:: x_e(:,:)
real(kind=real64), public, allocatable:: val(:)
integer(kind=int32), public, allocatable:: index_I(:)
integer(kind=int32), public, allocatable:: index_J(:)
integer(kind=int32), public, allocatable:: row_domain_id(:)
integer(kind=int32), public, allocatable:: column_domain_id(:)
real(kind=real64), public, allocatable:: CRS_val(:)
integer(kind=int32), public, allocatable:: CRS_index_I(:)
integer(kind=int32), public, allocatable:: CRS_index_J(:)
integer(kind=int32), public, allocatable:: CRS_row_domain_id(:)
integer(kind=int32), public, allocatable:: CRS_column_domain_id(:)
integer(kind=int32), public, allocatable:: b_Index_J(:)
integer(kind=int32), public, allocatable:: b_Domain_ID(:)
logical, public, allocatable:: Locked(:)
integer(kind=int32), public, allocatable:: NumberOfNode(:)
integer(kind=int32), public :: DOF =1
logical, public :: debug =.false.
integer(kind=int32), public, allocatable:: connectivity(:,:)
integer(kind=int32), public :: itrmax =1000000
integer(kind=int32), public :: currentID =1
integer(kind=int32), public :: b_currentID =1
real(kind=real64), public :: er0 =dble(1.0e-08)
logical, public :: ReadyForFix =.false.

Type-Bound Procedures

procedure, public :: init => initLinearSolver
procedure, public :: set => setLinearSolver
procedure, public :: assemble => assembleLinearSolver
procedure, public :: import => importLinearSolver
procedure, public :: fix => fixLinearSolver
procedure, public :: solve => solveLinearSolver
procedure, public :: show => showLinearSolver
procedure, public :: globalMatrix => globalMatrixLinearSolver
procedure, public :: globalVector => globalVectorLinearSolver
procedure, public :: convertCOOtoCRS => convertCOOtoCRSLinearSolver
procedure, public :: matmulCRS => matmulCRSLinearSolver
procedure, public :: matmulCOO => matmulCOOLinearSolver
procedure, public :: prepareFix => prepareFixLinearSolver
procedure, public :: getCOOFormat => getCOOFormatLinearSolver
procedure, public :: exportAsCOO => exportAsCOOLinearSolver
procedure, public :: exportRHS => exportRHSLinearSolver

Functions

public function eigen_3d(tensor) result(eigenvector)

Arguments

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

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

public function globalMatrixLinearSolver(obj) result(ret)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(in) :: obj

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

public function globalVectorLinearSolver(obj) result(ret)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(in) :: obj

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

public function matmulCRSLinearSolver(obj, openMP) result(mm)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
logical, intent(in), optional :: openMP

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

public function matmulCOOLinearSolver(obj, openMP) result(mm)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
logical, intent(in), optional :: openMP

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


Subroutines

public subroutine initLinearSolver(obj, NumberOfNode, DOF)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
integer(kind=int32), intent(in), optional :: NumberOfNode(:)
integer(kind=int32), intent(in), optional :: DOF

public recursive subroutine assembleLinearSolver(obj, connectivity, DOF, eMatrix, eVector, DomainIDs)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
integer(kind=int32), intent(in) :: connectivity(:)
integer(kind=int32), intent(in) :: DOF
real(kind=real64), intent(in), optional :: eMatrix(:,:)
real(kind=real64), intent(in), optional :: eVector(:)
integer(kind=int32), intent(in), optional :: DomainIDs(:)

public recursive subroutine fixLinearSolver(obj, nodeid, entryvalue, entryID, DOF, row_DomainID, debug)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
integer(kind=int32), intent(in) :: nodeid
real(kind=real64), intent(in) :: entryvalue
integer(kind=int32), intent(in), optional :: entryID
integer(kind=int32), intent(in), optional :: DOF
integer(kind=int32), intent(in), optional :: row_DomainID
logical, intent(in), optional :: debug

public recursive subroutine setLinearSolver(obj, low, column, entryvalue, init, row_DomainID, column_DomainID)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
integer(kind=int32), intent(in), optional :: low
integer(kind=int32), intent(in), optional :: column
real(kind=real64), intent(in), optional :: entryvalue
logical, intent(in), optional :: init
integer(kind=int32), intent(in), optional :: row_DomainID
integer(kind=int32), intent(in), optional :: column_DomainID

public subroutine importLinearSolver(obj, a, x, b, a_e, b_e, x_e, connectivity, val, index_I, index_J)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
real(kind=8), intent(in), optional :: a(:,:)
real(kind=8), intent(in), optional :: x(:)
real(kind=8), intent(in), optional :: b(:)
real(kind=8), intent(in), optional :: a_e(:,:,:)
real(kind=8), intent(in), optional :: b_e(:,:)
real(kind=8), intent(in), optional :: x_e(:,:)
integer(kind=int32), intent(in), optional :: connectivity(:,:)
real(kind=8), intent(in), optional :: val(:)
integer(kind=int32), intent(in), optional :: index_I(:)
integer(kind=int32), intent(in), optional :: index_J(:)

public subroutine prepareFixLinearSolver(obj, debug)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
logical, intent(in), optional :: debug

public subroutine solveLinearSolver(obj, Solver, MPI, OpenCL, CUDAC, preconditioning, CRS)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
character(len=*), intent(in) :: Solver
logical, intent(in), optional :: MPI
logical, intent(in), optional :: OpenCL
logical, intent(in), optional :: CUDAC
logical, intent(in), optional :: preconditioning
logical, intent(in), optional :: CRS

public subroutine gauss_seidel(a, b, x, n, itrmax, er0)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(n,n)
real(kind=real64), intent(in) :: b(n)
real(kind=real64), intent(out) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
real(kind=real64), intent(in) :: er0

public subroutine gauss_jordan_pv_real64(a0, x, b, n)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a0(n,n)
real(kind=real64), intent(out) :: x(n)
real(kind=real64), intent(in) :: b(n)
integer(kind=int32), intent(in) :: n

public subroutine gauss_jordan_pv_real32(a0, x, b, n)

Arguments

Type IntentOptional AttributesName
real(kind=real32), intent(in) :: a0(n,n)
real(kind=real32), intent(out) :: x(n)
real(kind=real32), intent(in) :: b(n)
integer(kind=int32), intent(in) :: n

public subroutine gauss_jordan_pv_complex64(a0, x, b, n)

Arguments

Type IntentOptional AttributesName
complex(kind=real64), intent(in) :: a0(n,n)
complex(kind=real64), intent(out) :: x(n)
complex(kind=real64), intent(in) :: b(n)
integer(kind=int32), intent(in) :: n

public subroutine bicgstab_diffusion(a, b, x, n, itrmax, er, DBC, DBCVal)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(n,n)
real(kind=real64), intent(in) :: b(n)
real(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
real(kind=real64), intent(in) :: er
integer(kind=int32), intent(in) :: DBC(:,:)
real(kind=real64), intent(in) :: DBCVal(:,:)

public subroutine bicgstab_CRS(a, ptr_i, index_j, x, b, itrmax, er, debug)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(inout) :: a(:)
integer(kind=int32), intent(inout) :: ptr_i(:)
integer(kind=int32), intent(inout) :: index_j(:)
real(kind=real64), intent(inout) :: x(:)
real(kind=real64), intent(inout) :: b(:)
integer(kind=int32), intent(inout) :: itrmax
real(kind=real64), intent(inout) :: er
logical, intent(in), optional :: debug

public subroutine bicgstab_COO(a, index_i, index_j, x, b, itrmax, er, debug)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(inout) :: a(:)
integer(kind=int32), intent(inout) :: index_i(:)
integer(kind=int32), intent(inout) :: index_j(:)
real(kind=real64), intent(inout) :: x(:)
real(kind=real64), intent(inout) :: b(:)
integer(kind=int32), intent(inout) :: itrmax
real(kind=real64), intent(inout) :: er
logical, intent(in), optional :: debug

public subroutine bicgstab_real64(a, b, x, n, itrmax, er)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(n,n)
real(kind=real64), intent(in) :: b(n)
real(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
real(kind=real64), intent(in) :: er

public subroutine bicgstab_real32(a, b, x, n, itrmax, er)

Arguments

Type IntentOptional AttributesName
real(kind=real32), intent(in) :: a(n,n)
real(kind=real32), intent(in) :: b(n)
real(kind=real32), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
real(kind=real32), intent(in) :: er

public subroutine bicgstab_complex64(a, b, x, n, itrmax, er)

Arguments

Type IntentOptional AttributesName
complex(kind=real64), intent(in) :: a(n,n)
complex(kind=real64), intent(in) :: b(n)
complex(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
complex(kind=real64), intent(in) :: er

public subroutine bicgstab1d(a, b, x, n, itrmax, er)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(n,n)
real(kind=real64), intent(in) :: b(n)
real(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
real(kind=real64), intent(in) :: er

public subroutine bicgstab_nr(a, b, x, n, itrmax, er, u_nod_x, u_nod_y)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(n,n)
real(kind=real64), intent(in) :: b(n)
real(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
real(kind=real64), intent(in) :: er
integer(kind=int32), intent(in) :: u_nod_x(:)
integer(kind=int32), intent(in) :: u_nod_y(:)

public subroutine bicgstab_nr1(a, b, x, n, itrmax, er, u_nod_x, u_nod_y, u_nod_dis_x, u_nod_dis_y)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(n,n)
real(kind=real64), intent(in) :: b(n)
real(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
real(kind=real64), intent(in) :: er
integer(kind=int32), intent(in) :: u_nod_x(:)
integer(kind=int32), intent(in) :: u_nod_y(:)
real(kind=real64), intent(in) :: u_nod_dis_x(:)
real(kind=real64), intent(in) :: u_nod_dis_y(:)

public subroutine bicgstab_dirichlet(a, b, x, n, itrmax, er, DBoundNodID, DBoundVal, SetBC)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(n,n)
real(kind=real64), intent(in) :: b(n)
real(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in) :: itrmax
real(kind=real64), intent(in) :: er
integer(kind=int32), intent(in) :: DBoundNodID(:,:)
real(kind=real64), intent(in) :: DBoundVal(:,:)
integer(kind=int32), intent(in) :: SetBC

public subroutine modify_residual_1(r, x, u_nod_x, u_nod_y, u_nod_dis_x, u_nod_dis_y)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(inout) :: r(:)
real(kind=real64), intent(inout) :: x(:)
integer(kind=int32), intent(in) :: u_nod_x(:)
integer(kind=int32), intent(in) :: u_nod_y(:)
real(kind=real64), intent(in) :: u_nod_dis_x(:)
real(kind=real64), intent(in) :: u_nod_dis_y(:)

public subroutine modify_residual(r, u_nod_x, u_nod_y)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(inout) :: r(:)
integer(kind=int32), intent(in) :: u_nod_x(:)
integer(kind=int32), intent(in) :: u_nod_y(:)

public subroutine modify_residual_dirichlet(r, x, DBoundNodID, DBoundVal, SetBC)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(inout) :: r(:)
real(kind=real64), intent(inout) :: x(:)
integer(kind=int32), intent(in) :: DBoundNodID(:,:)
real(kind=real64), intent(in) :: DBoundVal(:,:)
integer(kind=int32), intent(in) :: SetBC

public subroutine GPBiCG_real64(a, b, x, n, itrmax, er)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(n,n)
real(kind=real64), intent(in) :: b(n)
real(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in), optional :: itrmax
real(kind=real64), intent(in), optional :: er

public subroutine GPBiCG_real32(a, b, x, n, itrmax, er)

Arguments

Type IntentOptional AttributesName
real(kind=real32), intent(in) :: a(n,n)
real(kind=real32), intent(in) :: b(n)
real(kind=real32), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in), optional :: itrmax
real(kind=real32), intent(in), optional :: er

public subroutine GPBiCG_complex64(a, b, x, n, itrmax, er)

Arguments

Type IntentOptional AttributesName
complex(kind=real64), intent(in) :: a(n,n)
complex(kind=real64), intent(in) :: b(n)
complex(kind=real64), intent(inout) :: x(n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in), optional :: itrmax
complex(kind=real64), intent(in), optional :: er

public subroutine preconditioned_GPBiCG(a, b, x, n, itrmax, er)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(in) :: a(1:n,1:n)
real(kind=real64), intent(in) :: b(1:n)
real(kind=real64), intent(inout) :: x(1:n)
integer(kind=int32), intent(in) :: n
integer(kind=int32), intent(in), optional :: itrmax
real(kind=real64), intent(in), optional :: er

public subroutine icres(L, d, r, u, n)

Arguments

Type IntentOptional AttributesName
real(kind=real64), intent(inout) :: L(1:n,1:n)
real(kind=real64), intent(inout) :: d(1:n)
real(kind=real64), intent(inout) :: r(1:n)
real(kind=real64), intent(inout) :: u(1:n)
integer(kind=int32), intent(in) :: n

public subroutine showLinearSolver(obj)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(in) :: obj

public subroutine convertCOOtoCRSLinearSolver(obj, OpenMP)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
logical, intent(in), optional :: OpenMP

public subroutine getCOOFormatLinearSolver(obj)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj

public subroutine exportAsCOOLinearSolver(obj, name)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
character(len=*), intent(in) :: name

public subroutine exportRHSLinearSolver(obj, name)

Arguments

Type IntentOptional AttributesName
class(LinearSolver_), intent(inout) :: obj
character(len=*), intent(in) :: name