dbcsr_mm_multrec Module

Second layer of the dbcsr matrix-matrix multiplication. It divides the multiplication in a cache-oblivious manner. Modification history: - 2010-02-23 Moved from dbcsr_operations - 2011-11 Moved parameter-stack processing routines to dbcsr_mm_methods. - 2013-01 extensive refactoring (Ole Schuett)



Variables

Type Visibility Attributes Name Initial
character(len=*), private, parameter :: moduleN = 'dbcsr_mm_multrec'
logical, private, parameter :: careful_mod = .FALSE.

Derived Types

type, public ::  dbcsr_mm_multrec_type

Used to carry data among the various calls. Each thread has its own private copy.

Components

Type Visibility Attributes Name Initial
logical, private :: c_has_symmetry

The product matrix has symmetry Sparsity of C matrix should be kept Use on-the-fly filtering

logical, private :: keep_sparsity

The product matrix has symmetry Sparsity of C matrix should be kept Use on-the-fly filtering

logical, private :: keep_product_data

The product matrix has symmetry Sparsity of C matrix should be kept Use on-the-fly filtering

logical, private :: use_eps

The product matrix has symmetry Sparsity of C matrix should be kept Use on-the-fly filtering

integer, private, DIMENSION(:), POINTER :: m_sizes

Block sizes of A and C matrix rows, indexed locally Block sizes of B and C matrix columns, indexed locally Block sizes of A matrix columns and B matrix rows, indexed locally

integer, private, DIMENSION(:), POINTER :: n_sizes

Block sizes of A and C matrix rows, indexed locally Block sizes of B and C matrix columns, indexed locally Block sizes of A matrix columns and B matrix rows, indexed locally

integer, private, DIMENSION(:), POINTER :: k_sizes

Block sizes of A and C matrix rows, indexed locally Block sizes of B and C matrix columns, indexed locally Block sizes of A matrix columns and B matrix rows, indexed locally

integer, private, DIMENSION(:), POINTER :: m_global_sizes
integer, private, DIMENSION(:), POINTER :: n_global_sizes
integer, private, DIMENSION(:), POINTER :: c_local_rows

C and A matrix local rows. Map from local row (index) to global row (value). C and B matrix local columns. Map from local column (index) to global column (value). A matrix local columns and B matrix local rows. Map from local row/column (index) to global row/column (value). C and A matrix global rows. Map from global rows (index) to local rows (value). C and B matrix global columns. Map from global columns (index) to local columns (value).

integer, private, DIMENSION(:), POINTER :: c_local_cols

C and A matrix local rows. Map from local row (index) to global row (value). C and B matrix local columns. Map from local column (index) to global column (value). A matrix local columns and B matrix local rows. Map from local row/column (index) to global row/column (value). C and A matrix global rows. Map from global rows (index) to local rows (value). C and B matrix global columns. Map from global columns (index) to local columns (value).

integer, private, DIMENSION(:), POINTER :: k_locals

C and A matrix local rows. Map from local row (index) to global row (value). C and B matrix local columns. Map from local column (index) to global column (value). A matrix local columns and B matrix local rows. Map from local row/column (index) to global row/column (value). C and A matrix global rows. Map from global rows (index) to local rows (value). C and B matrix global columns. Map from global columns (index) to local columns (value).

integer, private, DIMENSION(:), POINTER :: c_global_rows

C and A matrix local rows. Map from local row (index) to global row (value). C and B matrix local columns. Map from local column (index) to global column (value). A matrix local columns and B matrix local rows. Map from local row/column (index) to global row/column (value). C and A matrix global rows. Map from global rows (index) to local rows (value). C and B matrix global columns. Map from global columns (index) to local columns (value).

integer, private, DIMENSION(:), POINTER :: c_global_cols

C and A matrix local rows. Map from local row (index) to global row (value). C and B matrix local columns. Map from local column (index) to global column (value). A matrix local columns and B matrix local rows. Map from local row/column (index) to global row/column (value). C and A matrix global rows. Map from global rows (index) to local rows (value). C and B matrix global columns. Map from global columns (index) to local columns (value).

real(kind=sp), private, DIMENSION(:), POINTER :: row_max_epss

Maximum eps to be used for one row. Norms of A matrix blocks. Norms of B matrix blocks.

real(kind=sp), private, DIMENSION(:), POINTER :: a_norms

Maximum eps to be used for one row. Norms of A matrix blocks. Norms of B matrix blocks.

real(kind=sp), private, DIMENSION(:), POINTER :: b_norms

Maximum eps to be used for one row. Norms of A matrix blocks. Norms of B matrix blocks.

real(kind=real_8), private :: eps
integer, private :: original_lastblk

Number of work matrix blocks before addition

integer(kind=int_8), private :: flop

flop count

type(dbcsr_work_type), private, POINTER :: product_wm => Null()
type(dbcsr_mm_csr_type), private :: csr
logical, private :: new_row_max_epss = .FALSE.
logical, private :: initialized = .FALSE.

Functions

public function dbcsr_mm_multrec_get_nblks(this) result(nblks)

Return number of blocks

Arguments

Type IntentOptional Attributes Name
type(dbcsr_mm_multrec_type), intent(in) :: this

Return Value integer

public function dbcsr_mm_multrec_get_nze(this) result(nze)

Return data size

Arguments

Type IntentOptional Attributes Name
type(dbcsr_mm_multrec_type), intent(in) :: this

Return Value integer

private pure function find_cut_row(ai, af, a, val) result(res)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ai
integer, intent(in) :: af
integer, intent(in), DIMENSION(3, 1:af) :: a
integer, intent(in) :: val

Return Value integer

private pure function find_cut_col(ai, af, a, val) result(res)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ai
integer, intent(in) :: af
integer, intent(in), DIMENSION(3, 1:af) :: a
integer, intent(in) :: val

Return Value integer


Subroutines

public subroutine dbcsr_mm_multrec_lib_init()

Initialize the library

Arguments

None

public subroutine dbcsr_mm_multrec_lib_finalize()

Finalize the library

Arguments

None

public subroutine dbcsr_mm_multrec_init(this, left, right, product, keep_sparsity, eps, row_max_epss, block_estimate, right_row_blk_size, m_sizes, n_sizes, nlayers, keep_product_data)

Sets up recursive multiplication

Arguments

Type IntentOptional Attributes Name
type(dbcsr_mm_multrec_type), intent(out) :: this
type(dbcsr_type), intent(in), optional :: left

left DBCSR matrix right DBCSR matrix

type(dbcsr_type), intent(in), optional :: right

left DBCSR matrix right DBCSR matrix

type(dbcsr_type), intent(inout) :: product

resulting DBCSR product matrix

logical, intent(in) :: keep_sparsity

retain the sparsity of the existing product matrix, default is no

real(kind=real_8), intent(in), optional :: eps

on-the-fly filtering epsilon

real(kind=sp), intent(in), DIMENSION(:), TARGET :: row_max_epss
integer, intent(in) :: block_estimate
integer, intent(in), DIMENSION(:) :: right_row_blk_size
integer, intent(in), DIMENSION(:), POINTER :: m_sizes
integer, intent(in), DIMENSION(:), POINTER :: n_sizes
integer, optional :: nlayers
logical, intent(in), optional :: keep_product_data

Perform final reduction on C data, default is yes

public subroutine dbcsr_mm_multrec_multiply(this, left, right, flop, a_norms, b_norms, k_sizes)

Multiplies two DBCSR matrices using recursive algorithm This routine sets up the multiplication. Specifically, it

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_mm_multrec_type), intent(inout) :: this
    type(dbcsr_type), intent(in) :: left

    left DBCSR matrix right DBCSR matrix

    type(dbcsr_type), intent(in) :: right

    left DBCSR matrix right DBCSR matrix

    integer(kind=int_8), intent(inout) :: flop

    number of effective double-precision floating point operations performed

    real(kind=sp), intent(in), DIMENSION(:), TARGET :: a_norms

    norms of left-matrix blocks norms of right-matrix blocks

    real(kind=sp), intent(in), DIMENSION(:), TARGET :: b_norms

    norms of left-matrix blocks norms of right-matrix blocks

    integer, intent(in), DIMENSION(:), POINTER :: k_sizes

public subroutine dbcsr_mm_multrec_dev2host_init(this)

Sets up recursive multiplication

Arguments

Type IntentOptional Attributes Name
type(dbcsr_mm_multrec_type), intent(inout) :: this

public subroutine dbcsr_mm_multrec_finalize(this, meta_buffer)

Sets up recursive multiplication

Arguments

Type IntentOptional Attributes Name
type(dbcsr_mm_multrec_type), intent(inout) :: this
integer, intent(inout), optional, DIMENSION(:) :: meta_buffer

private subroutine multrec_filtering(this)

Applying in-place filtering on the workspace

Arguments

Type IntentOptional Attributes Name
type(dbcsr_mm_multrec_type), intent(inout) :: this

public subroutine dbcsr_mm_multrec_red3D(this, meta_buffer, data_buffer, flop, g2l_map_rows, g2l_map_cols)

Make the reduction of the 3D layers in the local multrec object

Arguments

Type IntentOptional Attributes Name
type(dbcsr_mm_multrec_type), intent(inout) :: this
integer, intent(in), DIMENSION(:) :: meta_buffer
type(dbcsr_data_obj), intent(in) :: data_buffer
integer(kind=int_8), intent(inout) :: flop
integer, intent(in), DIMENSION(:) :: g2l_map_rows
integer, intent(in), DIMENSION(:) :: g2l_map_cols

private recursive subroutine sparse_multrec(this, left, right, mi, mf, ni, nf, ki, kf, ai, af, a_index, bi, bf, b_index, d)

Performs recursive multiplication

Arguments

Type IntentOptional Attributes Name
type(dbcsr_mm_multrec_type), intent(inout) :: this
type(dbcsr_type), intent(in) :: left
type(dbcsr_type), intent(in) :: right
integer, intent(in) :: mi
integer, intent(in) :: mf
integer, intent(in) :: ni
integer, intent(in) :: nf
integer, intent(in) :: ki
integer, intent(in) :: kf
integer, intent(in) :: ai
integer, intent(in) :: af
integer, intent(in), DIMENSION(3, 1:af) :: a_index
integer, intent(in) :: bi
integer, intent(in) :: bf
integer, intent(in), DIMENSION(3, 1:bf) :: b_index
integer, intent(in) :: d

private pure subroutine remap_local2global(row_i, col_i, local_rows, local_cols, first, last)

Packs a globally-indexed array into a locally-indexed array.

Arguments

Type IntentOptional Attributes Name
integer, intent(inout), DIMENSION(1:last) :: row_i
integer, intent(inout), DIMENSION(1:last) :: col_i
integer, intent(in), DIMENSION(:) :: local_rows
integer, intent(in), DIMENSION(:) :: local_cols
integer, intent(in) :: first
integer, intent(in) :: last

private pure subroutine local_filter_sp(full_data, nle, local_elements, local_data)

Gathers the local elements from all data (full_data) for single precision elements.

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(in), DIMENSION(:) :: full_data
integer, intent(in) :: nle
integer, intent(in), DIMENSION(1:nle) :: local_elements
real(kind=sp), intent(out), DIMENSION(1:nle) :: local_data

private subroutine multrec_filtering_d(filter_eps, nblks, rowi, coli, blkp, rbs, cbs, nze, DATA)

Applying in-place filtering on the workspace. \brief Use Frobenius norm

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(in) :: filter_eps
integer, intent(inout) :: nblks
integer, intent(inout), DIMENSION(1:nblks) :: rowi
integer, intent(inout), DIMENSION(1:nblks) :: coli
integer, intent(inout), DIMENSION(1:nblks) :: blkp
integer, intent(in), DIMENSION(:) :: rbs
integer, intent(in), DIMENSION(:) :: cbs
integer, intent(inout) :: nze
real(kind=real_8), intent(inout), DIMENSION(:) :: DATA

private subroutine multrec_filtering_s(filter_eps, nblks, rowi, coli, blkp, rbs, cbs, nze, DATA)

Applying in-place filtering on the workspace. \brief Use Frobenius norm

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(in) :: filter_eps
integer, intent(inout) :: nblks
integer, intent(inout), DIMENSION(1:nblks) :: rowi
integer, intent(inout), DIMENSION(1:nblks) :: coli
integer, intent(inout), DIMENSION(1:nblks) :: blkp
integer, intent(in), DIMENSION(:) :: rbs
integer, intent(in), DIMENSION(:) :: cbs
integer, intent(inout) :: nze
real(kind=real_4), intent(inout), DIMENSION(:) :: DATA

private subroutine multrec_filtering_z(filter_eps, nblks, rowi, coli, blkp, rbs, cbs, nze, DATA)

Applying in-place filtering on the workspace. \brief Use Frobenius norm

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(in) :: filter_eps
integer, intent(inout) :: nblks
integer, intent(inout), DIMENSION(1:nblks) :: rowi
integer, intent(inout), DIMENSION(1:nblks) :: coli
integer, intent(inout), DIMENSION(1:nblks) :: blkp
integer, intent(in), DIMENSION(:) :: rbs
integer, intent(in), DIMENSION(:) :: cbs
integer, intent(inout) :: nze
complex(kind=real_8), intent(inout), DIMENSION(:) :: DATA

private subroutine multrec_filtering_c(filter_eps, nblks, rowi, coli, blkp, rbs, cbs, nze, DATA)

Applying in-place filtering on the workspace. \brief Use Frobenius norm

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(in) :: filter_eps
integer, intent(inout) :: nblks
integer, intent(inout), DIMENSION(1:nblks) :: rowi
integer, intent(inout), DIMENSION(1:nblks) :: coli
integer, intent(inout), DIMENSION(1:nblks) :: blkp
integer, intent(in), DIMENSION(:) :: rbs
integer, intent(in), DIMENSION(:) :: cbs
integer, intent(inout) :: nze
complex(kind=real_4), intent(inout), DIMENSION(:) :: DATA