COO_csp_type Derived Type

type, public, extends(COO_type) :: COO_csp_type


Components

Type Visibility Attributes Name Initial
complex(kind=sp), public, allocatable :: data(:)
integer(kind=ilp), public, allocatable :: index(:,:)

Matrix coordinates index(2,nnz)

logical, public :: is_sorted = .false.

whether the matrix is sorted or not

integer(kind=ilp), public :: ncols = 0

number of columns

integer(kind=ilp), public :: nnz = 0

number of non-zero values

integer(kind=ilp), public :: nrows = 0

number of rows

integer, public :: storage = sparse_full

assumed storage symmetry


Type-Bound Procedures

generic, public :: add => add_value, add_block

  • private subroutine add_value_coo_csp(self, ik, jk, val)

    Arguments

    Type IntentOptional Attributes Name
    class(COO_csp_type), intent(inout) :: self
    integer(kind=ilp), intent(in) :: ik
    integer(kind=ilp), intent(in) :: jk
    complex(kind=sp), intent(in) :: val
  • private subroutine add_block_coo_csp(self, ik, jk, val)

    Arguments

    Type IntentOptional Attributes Name
    class(COO_csp_type), intent(inout) :: self
    integer(kind=ilp), intent(in) :: ik(:)
    integer(kind=ilp), intent(in) :: jk(:)
    complex(kind=sp), intent(in) :: val(:,:)

procedure, public, non_overridable :: add_block => add_block_coo_csp

  • private subroutine add_block_coo_csp(self, ik, jk, val)

    Arguments

    Type IntentOptional Attributes Name
    class(COO_csp_type), intent(inout) :: self
    integer(kind=ilp), intent(in) :: ik(:)
    integer(kind=ilp), intent(in) :: jk(:)
    complex(kind=sp), intent(in) :: val(:,:)

procedure, public, non_overridable :: add_value => add_value_coo_csp

  • private subroutine add_value_coo_csp(self, ik, jk, val)

    Arguments

    Type IntentOptional Attributes Name
    class(COO_csp_type), intent(inout) :: self
    integer(kind=ilp), intent(in) :: ik
    integer(kind=ilp), intent(in) :: jk
    complex(kind=sp), intent(in) :: val

procedure, public, non_overridable :: at => at_value_coo_csp

  • private pure function at_value_coo_csp(self, ik, jk) result(val)

    Arguments

    Type IntentOptional Attributes Name
    class(COO_csp_type), intent(in) :: self
    integer(kind=ilp), intent(in) :: ik
    integer(kind=ilp), intent(in) :: jk

    Return Value complex(kind=sp)

procedure, public :: malloc => malloc_coo

  • private subroutine malloc_coo(self, num_rows, num_cols, nnz)

    Arguments

    Type IntentOptional Attributes Name
    class(COO_type) :: self
    integer(kind=ilp), intent(in) :: num_rows

    number of rows

    integer(kind=ilp), intent(in) :: num_cols

    number of columns

    integer(kind=ilp), intent(in) :: nnz

    number of non zeros