csr_create_new Subroutine

public subroutine csr_create_new(csr_mat, nrows_total, ncols_total, nze_total, nze_local, nrows_local, mp_group, data_type)

Create a new CSR matrix and allocate all internal data (excluding dbcsr_mapping)

Arguments

Type IntentOptional Attributes Name
type(csr_type), intent(out) :: csr_mat

CSR matrix to return

integer, intent(in) :: nrows_total

total number of rows total number of columns

integer, intent(in) :: ncols_total

total number of rows total number of columns

integer(kind=int_8) :: nze_total

total number of non-zero elements

integer, intent(in) :: nze_local

local number of non-zero elements local number of rows

integer, intent(in) :: nrows_local

local number of non-zero elements local number of rows

type(mp_comm_type), intent(in) :: mp_group
integer, intent(in), optional :: data_type

data type of the CSR matrix (default real double prec.)


Source Code

   SUBROUTINE csr_create_new(csr_mat, nrows_total, ncols_total, nze_total, &
                             nze_local, nrows_local, mp_group, data_type)
      !! Create a new CSR matrix and allocate all internal data (excluding dbcsr_mapping)

      TYPE(csr_type), INTENT(OUT)                        :: csr_mat
         !! CSR matrix to return
      INTEGER, INTENT(IN)                                :: nrows_total, ncols_total
         !! total number of rows
         !! total number of columns
      INTEGER(KIND=int_8)                                :: nze_total
         !! total number of non-zero elements
      INTEGER, INTENT(IN)                                :: nze_local, nrows_local
         !! local number of non-zero elements
         !! local number of rows
      TYPE(mp_comm_type), INTENT(IN)                     :: mp_group
      INTEGER, INTENT(IN), OPTIONAL                      :: data_type
         !! data type of the CSR matrix (default real double prec.)

      CHARACTER(LEN=*), PARAMETER :: routineN = 'csr_create_new'
      INTEGER                                            :: handle

      CALL timeset(routineN, handle)

      IF (nrows_total .LT. nrows_local) &
         DBCSR_ABORT("local number of rows must not exceed total number of rows")

      IF (nze_total .LT. nze_local) CALL dbcsr_abort(__LOCATION__, "local number of non-zero "// &
                                                     "elements must not exceed total number of non-zero elements")

      IF (INT(nrows_total, kind=int_8)*INT(ncols_total, kind=int_8) .LT. nze_total) &
         DBCSR_ABORT("Total number of non-zero elements must not exceed total matrix size")

      IF (INT(nrows_local, kind=int_8)*INT(ncols_total, kind=int_8) .LT. nze_local) &
         DBCSR_ABORT("Local number of non-zero elements must not exceed local matrix size")

      csr_mat%ncols_total = ncols_total
      csr_mat%nrows_total = nrows_total
      csr_mat%nze_total = nze_total
      csr_mat%nze_local = nze_local
      ALLOCATE (csr_mat%colind_local(nze_local))
      csr_mat%nrows_local = nrows_local
      ALLOCATE (csr_mat%rowptr_local(nrows_local + 1))
      ALLOCATE (csr_mat%nzerow_local(nrows_local))

      IF (PRESENT(data_type)) THEN
         csr_mat%nzval_local%data_type = data_type
      ELSE
         csr_mat%nzval_local%data_type = dbcsr_type_real_default
      END IF

      SELECT CASE (csr_mat%nzval_local%data_type)
      CASE (dbcsr_type_real_4)
         ALLOCATE (csr_mat%nzval_local%r_sp(nze_local))
      CASE (dbcsr_type_real_8)
         ALLOCATE (csr_mat%nzval_local%r_dp(nze_local))
      CASE (dbcsr_type_complex_4)
         ALLOCATE (csr_mat%nzval_local%c_sp(nze_local))
      CASE (dbcsr_type_complex_8)
         ALLOCATE (csr_mat%nzval_local%c_dp(nze_local))
      CASE DEFAULT
         DBCSR_ABORT("Invalid matrix type")
      END SELECT

      csr_mat%mp_group = mp_group

      csr_mat%valid = .TRUE.
      csr_mat%has_mapping = .FALSE.
      csr_mat%has_indices = .FALSE.

      CALL timestop(handle)

   END SUBROUTINE csr_create_new