stdlib_sparse_kinds Module

version: experimental

Base sparse type holding the meta data related to the storage capacity of a matrix. version: experimental

COO: COOrdinates compresed format version: experimental

CSR: Compressed sparse row or Yale format version: experimental

CSC: Compressed sparse column version: experimental

Compressed ELLPACK version: experimental

Compressed SELL-C Reference : https://library.eecs.utk.edu/storage/files/ut-eecs-14-727.pdf (re)Allocate matrix memory for the COO type (re)Allocate matrix memory for the CSR type (re)Allocate matrix memory for the CSC type (re)Allocate matrix memory for the ELLPACK type



Derived Types

type, public, extends(COO_type) ::  COO_cdp_type

Components

Type Visibility Attributes Name Initial
complex(kind=dp), 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
procedure, public, non_overridable :: add_block => add_block_coo_cdp
procedure, public, non_overridable :: add_value => add_value_coo_cdp
procedure, public, non_overridable :: at => at_value_coo_cdp
procedure, public :: malloc => malloc_coo

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
procedure, public, non_overridable :: add_block => add_block_coo_csp
procedure, public, non_overridable :: add_value => add_value_coo_csp
procedure, public, non_overridable :: at => at_value_coo_csp
procedure, public :: malloc => malloc_coo

type, public, extends(COO_type) ::  COO_dp_type

Components

Type Visibility Attributes Name Initial
real(kind=dp), 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
procedure, public, non_overridable :: add_block => add_block_coo_dp
procedure, public, non_overridable :: add_value => add_value_coo_dp
procedure, public, non_overridable :: at => at_value_coo_dp
procedure, public :: malloc => malloc_coo

type, public, extends(COO_type) ::  COO_sp_type

Components

Type Visibility Attributes Name Initial
real(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
procedure, public, non_overridable :: add_block => add_block_coo_sp
procedure, public, non_overridable :: add_value => add_value_coo_sp
procedure, public, non_overridable :: at => at_value_coo_sp
procedure, public :: malloc => malloc_coo

type, public, extends(sparse_type) ::  COO_type

Components

Type Visibility Attributes Name Initial
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

procedure, public :: malloc => malloc_coo

type, public, extends(CSC_type) ::  CSC_cdp_type

Components

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

matrix column pointer

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

matrix row pointer

integer, public :: storage = sparse_full

assumed storage symmetry

Type-Bound Procedures

generic, public :: add => add_value, add_block
procedure, public, non_overridable :: add_block => add_block_csc_cdp
procedure, public, non_overridable :: add_value => add_value_csc_cdp
procedure, public, non_overridable :: at => at_value_csc_cdp
procedure, public :: malloc => malloc_csc

type, public, extends(CSC_type) ::  CSC_csp_type

Components

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

matrix column pointer

complex(kind=sp), 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 :: row(:)

matrix row pointer

integer, public :: storage = sparse_full

assumed storage symmetry

Type-Bound Procedures

generic, public :: add => add_value, add_block
procedure, public, non_overridable :: add_block => add_block_csc_csp
procedure, public, non_overridable :: add_value => add_value_csc_csp
procedure, public, non_overridable :: at => at_value_csc_csp
procedure, public :: malloc => malloc_csc

type, public, extends(CSC_type) ::  CSC_dp_type

Components

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

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

matrix row pointer

integer, public :: storage = sparse_full

assumed storage symmetry

Type-Bound Procedures

generic, public :: add => add_value, add_block
procedure, public, non_overridable :: add_block => add_block_csc_dp
procedure, public, non_overridable :: add_value => add_value_csc_dp
procedure, public, non_overridable :: at => at_value_csc_dp
procedure, public :: malloc => malloc_csc

type, public, extends(CSC_type) ::  CSC_sp_type

Components

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

matrix column pointer

real(kind=sp), 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 :: row(:)

matrix row pointer

integer, public :: storage = sparse_full

assumed storage symmetry

Type-Bound Procedures

generic, public :: add => add_value, add_block
procedure, public, non_overridable :: add_block => add_block_csc_sp
procedure, public, non_overridable :: add_value => add_value_csc_sp
procedure, public, non_overridable :: at => at_value_csc_sp
procedure, public :: malloc => malloc_csc

type, public, extends(sparse_type) ::  CSC_type

Components

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

matrix column pointer

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

matrix row pointer

integer, public :: storage = sparse_full

assumed storage symmetry

Type-Bound Procedures

procedure, public :: malloc => malloc_csc

type, public, extends(CSR_type) ::  CSR_cdp_type

Components

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

matrix column pointer

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

matrix row pointer

integer, public :: storage = sparse_full

assumed storage symmetry

Type-Bound Procedures

generic, public :: add => add_value, add_block
procedure, public, non_overridable :: add_block => add_block_csr_cdp
procedure, public, non_overridable :: add_value => add_value_csr_cdp
procedure, public, non_overridable :: at => at_value_csr_cdp
procedure, public :: malloc => malloc_csr

type, public, extends(CSR_type) ::  CSR_csp_type

Components

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

matrix column pointer

complex(kind=sp), 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
procedure, public, non_overridable :: add_block => add_block_csr_csp
procedure, public, non_overridable :: add_value => add_value_csr_csp
procedure, public, non_overridable :: at => at_value_csr_csp
procedure, public :: malloc => malloc_csr

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
procedure, public, non_overridable :: add_block => add_block_csr_dp
procedure, public, non_overridable :: add_value => add_value_csr_dp
procedure, public, non_overridable :: at => at_value_csr_dp
procedure, public :: malloc => malloc_csr

type, public, extends(CSR_type) ::  CSR_sp_type

Components

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

matrix column pointer

real(kind=sp), 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
procedure, public, non_overridable :: add_block => add_block_csr_sp
procedure, public, non_overridable :: add_value => add_value_csr_sp
procedure, public, non_overridable :: at => at_value_csr_sp
procedure, public :: malloc => malloc_csr

type, public, extends(sparse_type) ::  CSR_type

Components

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

matrix column pointer

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

procedure, public :: malloc => malloc_csr

type, public, extends(ELL_type) ::  ELL_cdp_type

Components

Type Visibility Attributes Name Initial
integer, public :: K = 0

maximum number of nonzeros per row

complex(kind=dp), public, allocatable :: data(:,:)
integer(kind=ilp), public, allocatable :: index(:,:)

column indices

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
procedure, public, non_overridable :: add_block => add_block_ell_cdp
procedure, public, non_overridable :: add_value => add_value_ell_cdp
procedure, public, non_overridable :: at => at_value_ell_cdp
procedure, public :: malloc => malloc_ell

type, public, extends(ELL_type) ::  ELL_csp_type

Components

Type Visibility Attributes Name Initial
integer, public :: K = 0

maximum number of nonzeros per row

complex(kind=sp), public, allocatable :: data(:,:)
integer(kind=ilp), public, allocatable :: index(:,:)

column indices

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
procedure, public, non_overridable :: add_block => add_block_ell_csp
procedure, public, non_overridable :: add_value => add_value_ell_csp
procedure, public, non_overridable :: at => at_value_ell_csp
procedure, public :: malloc => malloc_ell

type, public, extends(ELL_type) ::  ELL_dp_type

Components

Type Visibility Attributes Name Initial
integer, public :: K = 0

maximum number of nonzeros per row

real(kind=dp), public, allocatable :: data(:,:)
integer(kind=ilp), public, allocatable :: index(:,:)

column indices

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
procedure, public, non_overridable :: add_block => add_block_ell_dp
procedure, public, non_overridable :: add_value => add_value_ell_dp
procedure, public, non_overridable :: at => at_value_ell_dp
procedure, public :: malloc => malloc_ell

type, public, extends(ELL_type) ::  ELL_sp_type

Components

Type Visibility Attributes Name Initial
integer, public :: K = 0

maximum number of nonzeros per row

real(kind=sp), public, allocatable :: data(:,:)
integer(kind=ilp), public, allocatable :: index(:,:)

column indices

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
procedure, public, non_overridable :: add_block => add_block_ell_sp
procedure, public, non_overridable :: add_value => add_value_ell_sp
procedure, public, non_overridable :: at => at_value_ell_sp
procedure, public :: malloc => malloc_ell

type, public, extends(sparse_type) ::  ELL_type

Components

Type Visibility Attributes Name Initial
integer, public :: K = 0

maximum number of nonzeros per row

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

column indices

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

procedure, public :: malloc => malloc_ell

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
procedure, public, non_overridable :: add_block => add_block_sellc_cdp
procedure, public, non_overridable :: add_value => add_value_sellc_cdp
procedure, public, non_overridable :: at => at_value_sellc_cdp

type, public, extends(SELLC_type) ::  SELLC_csp_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=sp), 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
procedure, public, non_overridable :: add_block => add_block_sellc_csp
procedure, public, non_overridable :: add_value => add_value_sellc_csp
procedure, public, non_overridable :: at => at_value_sellc_csp

type, public, extends(SELLC_type) ::  SELLC_dp_type

Components

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

default chunk size

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

column indices

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

row pointer

integer, public :: storage = sparse_full

assumed storage symmetry

Type-Bound Procedures

generic, public :: add => add_value, add_block
procedure, public, non_overridable :: add_block => add_block_sellc_dp
procedure, public, non_overridable :: add_value => add_value_sellc_dp
procedure, public, non_overridable :: at => at_value_sellc_dp

type, public, extends(SELLC_type) ::  SELLC_sp_type

Components

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

default chunk size

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

column indices

real(kind=sp), 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
procedure, public, non_overridable :: add_block => add_block_sellc_sp
procedure, public, non_overridable :: add_value => add_value_sellc_sp
procedure, public, non_overridable :: at => at_value_sellc_sp

type, public, extends(sparse_type) ::  SELLC_type

Components

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

default chunk size

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

column indices

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, public ::  sparse_type

Components

Type Visibility Attributes Name Initial
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