CSR_dp_type Derived Type

type, public, extends(CSR_type) :: CSR_dp_type


Components

Type Visibility Attributes Name Initial
integer(kind=ilp), public, allocatable :: col(:)

matrix column pointer

real(kind=dp), public, allocatable :: data(:)
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(kind=ilp), public, allocatable :: rowptr(:)

matrix row pointer

integer, public :: storage = sparse_full

assumed storage symmetry


Type-Bound Procedures

generic, public :: add => add_value, add_block

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

    Arguments

    Type IntentOptional Attributes Name
    class(CSR_dp_type), intent(inout) :: self
    integer(kind=ilp), intent(in) :: ik
    integer(kind=ilp), intent(in) :: jk
    real(kind=dp), intent(in) :: val
  • private subroutine add_block_csr_dp(self, ik, jk, val)

    Arguments

    Type IntentOptional Attributes Name
    class(CSR_dp_type), intent(inout) :: self
    integer(kind=ilp), intent(in) :: ik(:)
    integer(kind=ilp), intent(in) :: jk(:)
    real(kind=dp), intent(in) :: val(:,:)

procedure, public, non_overridable :: add_block => add_block_csr_dp

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

    Arguments

    Type IntentOptional Attributes Name
    class(CSR_dp_type), intent(inout) :: self
    integer(kind=ilp), intent(in) :: ik(:)
    integer(kind=ilp), intent(in) :: jk(:)
    real(kind=dp), intent(in) :: val(:,:)

procedure, public, non_overridable :: add_value => add_value_csr_dp

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

    Arguments

    Type IntentOptional Attributes Name
    class(CSR_dp_type), intent(inout) :: self
    integer(kind=ilp), intent(in) :: ik
    integer(kind=ilp), intent(in) :: jk
    real(kind=dp), intent(in) :: val

procedure, public, non_overridable :: at => at_value_csr_dp

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

    Arguments

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

    Return Value real(kind=dp)

procedure, public :: malloc => malloc_csr

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

    Arguments

    Type IntentOptional Attributes Name
    class(CSR_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