SELLC_cdp_type Derived Type

type, public, extends(SELLC_type) :: SELLC_cdp_type


Components

Type Visibility Attributes Name Initial
integer, public :: chunk_size = 8

default chunk size

integer(kind=ilp), public, allocatable :: col(:,:)

column indices

complex(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(:)

row pointer

integer, public :: storage = sparse_full

assumed storage symmetry


Type-Bound Procedures

generic, public :: add => add_value, add_block

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

    Arguments

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

    Arguments

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

procedure, public, non_overridable :: add_block => add_block_sellc_cdp

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

    Arguments

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

procedure, public, non_overridable :: add_value => add_value_sellc_cdp

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

    Arguments

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

procedure, public, non_overridable :: at => at_value_sellc_cdp

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

    Arguments

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

    Return Value complex(kind=dp)