dbcsr_reserve_all_blocks Subroutine

public subroutine dbcsr_reserve_all_blocks(matrix)

Inserts all blocks of a dbcsr matrix to make it a full matrix. Thus obviously not linear scaling.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix

Matrix into which blocks should be added.


Source Code

   SUBROUTINE dbcsr_reserve_all_blocks(matrix)
      !! Inserts all blocks of a dbcsr matrix to make it a full matrix.
      !! Thus obviously not linear scaling.

      TYPE(dbcsr_type), INTENT(INOUT)                    :: matrix
         !! Matrix into which blocks should be added.

      CHARACTER(len=*), PARAMETER :: routineN = 'dbcsr_reserve_all_blocks'

      INTEGER                                            :: blk_count, col, col_local, col_s, &
                                                            error_handle, myrank, rank, row, &
                                                            row_local, row_s
      INTEGER, ALLOCATABLE, DIMENSION(:)                 :: columns, rows
      INTEGER, DIMENSION(:), POINTER                     :: local_cols, local_rows
      LOGICAL                                            :: tr

      CALL timeset(routineN, error_handle)

      myrank = dbcsr_mp_mynode(dbcsr_distribution_mp(dbcsr_distribution(matrix)))
      local_rows => dbcsr_distribution_local_rows(dbcsr_distribution(matrix))
      local_cols => dbcsr_distribution_local_cols(dbcsr_distribution(matrix))

      blk_count = 0
      ! should be possible to loop only over the local blockrows/blockcols
      DO row_local = 1, SIZE(local_rows)
         DO col_local = 1, SIZE(local_cols)
            tr = .FALSE.
            row = local_rows(row_local)
            col = local_cols(col_local)
            row_s = row; col_s = col
            CALL dbcsr_get_stored_coordinates(matrix, row_s, col_s, rank)
            ! is that the correct condition for symmetric matrices ?
            IF (rank .EQ. myrank .AND. row_s .EQ. row .AND. col_s .EQ. col) blk_count = blk_count + 1
         END DO
      END DO

      ALLOCATE (rows(blk_count), columns(blk_count))

      blk_count = 0
      DO row_local = 1, SIZE(local_rows)
         DO col_local = 1, SIZE(local_cols)
            tr = .FALSE.
            row = local_rows(row_local)
            col = local_cols(col_local)
            row_s = row; col_s = col
            CALL dbcsr_get_stored_coordinates(matrix, row_s, col_s, rank)
            IF (rank .EQ. myrank .AND. row_s .EQ. row .AND. col_s .EQ. col) THEN
               blk_count = blk_count + 1
               rows(blk_count) = row
               columns(blk_count) = col
            END IF
         END DO
      END DO

      CALL dbcsr_reserve_blocks(matrix, rows, columns)

      CALL timestop(error_handle)

   END SUBROUTINE dbcsr_reserve_all_blocks