dbcsr_tensor_types Module

DBCSR tensor framework for block-sparse tensor contraction: Types and create/destroy routines.



Variables

Type Visibility Attributes Name Initial
character(len=*), private, parameter :: moduleN = 'dbcsr_tensor_types'

Interfaces

public interface dbcsr_t_create

  • private subroutine dbcsr_t_create_new(tensor, name, dist, map1_2d, map2_2d, data_type, blk_size_1, blk_size_2, blk_size_3, blk_size_4)

    create a tensor. For performance, the arguments map1_2d and map2_2d (controlling matrix representation of tensor) should be consistent with the the contraction to be performed (see documentation of dbcsr_t_contract).

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(out) :: tensor
    character(len=*), intent(in) :: name
    type(dbcsr_t_distribution_type), intent(inout) :: dist
    integer, intent(in), DIMENSION(:) :: map1_2d

    which nd-indices to map to first 2d index and in which order

    integer, intent(in), DIMENSION(:) :: map2_2d

    which nd-indices to map to first 2d index and in which order

    integer, intent(in), optional :: data_type
    integer, intent(in), optional, DIMENSION(:) :: blk_size_1

    blk sizes in each dimension

    integer, intent(in), optional, DIMENSION(:) :: blk_size_2

    blk sizes in each dimension

    integer, intent(in), optional, DIMENSION(:) :: blk_size_3

    blk sizes in each dimension

    integer, intent(in), optional, DIMENSION(:) :: blk_size_4

    blk sizes in each dimension

  • private subroutine dbcsr_t_create_template(tensor_in, tensor, name, dist, map1_2d, map2_2d, data_type)

    create a tensor from template

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor_in
    type(dbcsr_t_type), intent(out) :: tensor
    character(len=*), intent(in), optional :: name
    type(dbcsr_t_distribution_type), intent(inout), optional :: dist
    integer, intent(in), optional, DIMENSION(:) :: map1_2d
    integer, intent(in), optional, DIMENSION(:) :: map2_2d
    integer, intent(in), optional :: data_type
  • private subroutine dbcsr_t_create_matrix(matrix_in, tensor, order, name)

    Create 2-rank tensor from matrix.

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_in
    type(dbcsr_t_type), intent(out) :: tensor
    integer, intent(in), optional, DIMENSION(2) :: order
    character(len=*), intent(in), optional :: name

private interface dbcsr_tas_dist_t

  • private function new_dbcsr_tas_dist_t(nd_dist, map_blks, map_grid, which_dim)

    Create distribution object for one matrix dimension \return distribution object

    Arguments

    Type IntentOptional Attributes Name
    type(array_list), intent(in) :: nd_dist

    arrays for distribution vectors along all dimensions

    type(nd_to_2d_mapping), intent(in) :: map_blks

    tensor to matrix mapping object for blocks tensor to matrix mapping object for process grid

    type(nd_to_2d_mapping), intent(in) :: map_grid

    tensor to matrix mapping object for blocks tensor to matrix mapping object for process grid

    integer, intent(in) :: which_dim

    for which dimension (1 or 2) distribution should be created

    Return Value type(dbcsr_tas_dist_t)

private interface dbcsr_tas_blk_size_t

  • private function new_dbcsr_tas_blk_size_t(blk_size, map_blks, which_dim)

    Create block size object for one matrix dimension \return block size object

    Arguments

    Type IntentOptional Attributes Name
    type(array_list), intent(in) :: blk_size

    arrays for block sizes along all dimensions

    type(nd_to_2d_mapping), intent(in) :: map_blks

    tensor to matrix mapping object for blocks

    integer, intent(in) :: which_dim

    for which dimension (1 or 2) distribution should be created

    Return Value type(dbcsr_tas_blk_size_t)

public interface dbcsr_t_set

  • private subroutine dbcsr_t_set_r_dp(tensor, alpha)

    As dbcsr_set

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    real(kind=real_8), intent(in) :: alpha
  • private subroutine dbcsr_t_set_r_sp(tensor, alpha)

    As dbcsr_set

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    real(kind=real_4), intent(in) :: alpha
  • private subroutine dbcsr_t_set_c_dp(tensor, alpha)

    As dbcsr_set

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    complex(kind=real_8), intent(in) :: alpha
  • private subroutine dbcsr_t_set_c_sp(tensor, alpha)

    As dbcsr_set

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    complex(kind=real_4), intent(in) :: alpha

public interface dbcsr_t_filter

  • private subroutine dbcsr_t_filter_r_dp(tensor, eps, method, use_absolute)

    As dbcsr_filter

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    real(kind=real_8), intent(in) :: eps
    integer, intent(in), optional :: method
    logical, intent(in), optional :: use_absolute
  • private subroutine dbcsr_t_filter_r_sp(tensor, eps, method, use_absolute)

    As dbcsr_filter

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    real(kind=real_4), intent(in) :: eps
    integer, intent(in), optional :: method
    logical, intent(in), optional :: use_absolute
  • private subroutine dbcsr_t_filter_c_dp(tensor, eps, method, use_absolute)

    As dbcsr_filter

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    complex(kind=real_8), intent(in) :: eps
    integer, intent(in), optional :: method
    logical, intent(in), optional :: use_absolute
  • private subroutine dbcsr_t_filter_c_sp(tensor, eps, method, use_absolute)

    As dbcsr_filter

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    complex(kind=real_4), intent(in) :: eps
    integer, intent(in), optional :: method
    logical, intent(in), optional :: use_absolute

Derived Types

type, public ::  dbcsr_t_pgrid_type

Components

Type Visibility Attributes Name Initial
type(nd_to_2d_mapping), public :: nd_index_grid
type(mp_comm_type), public :: mp_comm_2d
type(dbcsr_tas_split_info), public, ALLOCATABLE :: tas_split_info
integer, public :: nproc

type, public ::  dbcsr_t_contraction_storage

Components

Type Visibility Attributes Name Initial
real(kind=real_8), public :: nsplit_avg
integer, public :: ibatch
type(array_list), public :: batch_ranges
logical, public :: static

type, public ::  dbcsr_t_type

Components

Type Visibility Attributes Name Initial
type(dbcsr_tas_type), public, POINTER :: matrix_rep => NULL()
type(nd_to_2d_mapping), public :: nd_index_blk
type(nd_to_2d_mapping), public :: nd_index
type(array_list), public :: blk_sizes
type(array_list), public :: blk_offsets
type(array_list), public :: nd_dist
type(dbcsr_t_pgrid_type), public :: pgrid
type(array_list), public :: blks_local
integer, public, DIMENSION(:), ALLOCATABLE :: nblks_local
integer, public, DIMENSION(:), ALLOCATABLE :: nfull_local
logical, public :: valid = .FALSE.
logical, public :: owns_matrix = .FALSE.
character(len=default_string_length), public :: name
integer, public, POINTER :: refcount => NULL()
type(dbcsr_t_contraction_storage), public, ALLOCATABLE :: contraction_storage

type, public ::  dbcsr_t_distribution_type

Components

Type Visibility Attributes Name Initial
type(dbcsr_tas_distribution_type), public :: dist
type(dbcsr_t_pgrid_type), public :: pgrid
type(array_list), public :: nd_dist
integer, public, POINTER :: refcount => NULL()

type, private, extends(dbcsr_tas_distribution) ::  dbcsr_tas_dist_t

Components

Type Visibility Attributes Name Initial
integer, public :: nprowcol
integer(kind=int_8), public :: nmrowcol
integer, public, DIMENSION(:), ALLOCATABLE :: dims
integer, public, DIMENSION(:), ALLOCATABLE :: dims_grid
type(array_list), public :: nd_dist

Constructor

private function new_dbcsr_tas_dist_t (nd_dist, map_blks, map_grid, which_dim)

Create distribution object for one matrix dimension \return distribution object

Type-Bound Procedures

procedure, public :: dist => tas_dist_t
procedure, public :: rowcols => tas_rowcols_t

type, private, extends(dbcsr_tas_rowcol_data) ::  dbcsr_tas_blk_size_t

Components

Type Visibility Attributes Name Initial
integer(kind=int_8), public :: nmrowcol
integer(kind=int_8), public :: nfullrowcol
integer, public, DIMENSION(:), ALLOCATABLE :: dims
type(array_list), public :: blk_size

Constructor

private function new_dbcsr_tas_blk_size_t (blk_size, map_blks, which_dim)

Create block size object for one matrix dimension \return block size object

Type-Bound Procedures

procedure, public :: data => tas_blk_size_t

Functions

private function new_dbcsr_tas_dist_t(nd_dist, map_blks, map_grid, which_dim)

Create distribution object for one matrix dimension \return distribution object

Arguments

Type IntentOptional Attributes Name
type(array_list), intent(in) :: nd_dist

arrays for distribution vectors along all dimensions

type(nd_to_2d_mapping), intent(in) :: map_blks

tensor to matrix mapping object for blocks tensor to matrix mapping object for process grid

type(nd_to_2d_mapping), intent(in) :: map_grid

tensor to matrix mapping object for blocks tensor to matrix mapping object for process grid

integer, intent(in) :: which_dim

for which dimension (1 or 2) distribution should be created

Return Value type(dbcsr_tas_dist_t)

private function tas_dist_t(t, rowcol)

Arguments

Type IntentOptional Attributes Name
class(dbcsr_tas_dist_t), intent(in) :: t
integer(kind=int_8), intent(in) :: rowcol

Return Value integer

private function tas_rowcols_t(t, dist)

Arguments

Type IntentOptional Attributes Name
class(dbcsr_tas_dist_t), intent(in) :: t
integer, intent(in) :: dist

Return Value integer(kind=int_8), DIMENSION(:), ALLOCATABLE

private function new_dbcsr_tas_blk_size_t(blk_size, map_blks, which_dim)

Create block size object for one matrix dimension \return block size object

Arguments

Type IntentOptional Attributes Name
type(array_list), intent(in) :: blk_size

arrays for block sizes along all dimensions

type(nd_to_2d_mapping), intent(in) :: map_blks

tensor to matrix mapping object for blocks

integer, intent(in) :: which_dim

for which dimension (1 or 2) distribution should be created

Return Value type(dbcsr_tas_blk_size_t)

private function tas_blk_size_t(t, rowcol)

Arguments

Type IntentOptional Attributes Name
class(dbcsr_tas_blk_size_t), intent(in) :: t
integer(kind=int_8), intent(in) :: rowcol

Return Value integer

public function dbcsr_t_nd_mp_comm(comm_2d, map1_2d, map2_2d, dims_nd, dims1_nd, dims2_nd, pdims_2d, tdims, nsplit, dimsplit)

Create a default nd process topology that is consistent with a given 2d topology. Purpose: a nd tensor defined on the returned process grid can be represented as a DBCSR matrix with the given 2d topology. This is needed to enable contraction of 2 tensors (must have the same 2d process grid). \return with nd cartesian grid

Arguments

Type IntentOptional Attributes Name
type(mp_comm_type), intent(in) :: comm_2d

communicator with 2-dimensional topology

integer, intent(in), DIMENSION(:) :: map1_2d

which nd-indices map to first matrix index and in which order which nd-indices map to second matrix index and in which order

integer, intent(in), DIMENSION(:) :: map2_2d

which nd-indices map to first matrix index and in which order which nd-indices map to second matrix index and in which order

integer, intent(in), optional, DIMENSION(SIZE(map1_2d) + SIZE(map2_2d)) :: dims_nd

nd dimensions

integer, intent(in), optional, DIMENSION(SIZE(map1_2d)) :: dims1_nd
integer, intent(in), optional, DIMENSION(SIZE(map2_2d)) :: dims2_nd
integer, intent(in), optional, DIMENSION(2) :: pdims_2d

if comm_2d does not have a cartesian topology associated, can input dimensions with pdims_2d

integer, intent(in), optional, DIMENSION(SIZE(map1_2d) + SIZE(map2_2d)) :: tdims

tensor block dimensions. If present, process grid dimensions are created such that good load balancing is ensured even if some of the tensor dimensions are small (i.e. on the same order or smaller than nproc**(1/ndim) where ndim is the tensor rank)

integer, intent(in), optional :: nsplit
integer, intent(in), optional :: dimsplit

Return Value type(dbcsr_t_pgrid_type)

private pure function accept_pdims_loadbalancing(pdims_avail, pdim, tdim, lb_ratio)

load balancing criterion whether to accept process grid dimension based on total number of cores and tensor dimension

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: pdims_avail

available process grid dimensions (total number of cores)

integer, intent(in) :: pdim

process grid dimension to test

integer, intent(in) :: tdim

tensor dimension corresponding to pdim

real(kind=real_8), intent(in) :: lb_ratio

load imbalance acceptance factor

Return Value logical

public function dbcsr_t_distribution(tensor)

get distribution from tensor \return distribution

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value type(dbcsr_t_distribution_type)

public pure function dbcsr_t_nblks_total(tensor, idim)

total numbers of blocks along dimension idim

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(in) :: idim

Return Value integer

public pure function dbcsr_t_nblks_local(tensor, idim)

local number of blocks along dimension idim

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(in) :: idim

Return Value integer

public pure function ndims_tensor(tensor)

tensor rank

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer

public function dbcsr_t_get_data_type(tensor) result(data_type)

tensor data type

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer

public pure function dbcsr_t_get_num_blocks(tensor) result(num_blocks)

As dbcsr_get_num_blocks: get number of local blocks

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer

public function dbcsr_t_get_num_blocks_total(tensor) result(num_blocks)

Get total number of blocks

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer(kind=int_8)

public function dbcsr_t_get_data_size(tensor) result(data_size)

As dbcsr_get_data_size

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer

public pure function dbcsr_t_get_nze(tensor)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer

public function dbcsr_t_get_nze_total(tensor)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer(kind=int_8)

public pure function dbcsr_t_blk_size(tensor, ind, idim)

block size of block with index ind along dimension idim

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(in), DIMENSION(ndims_tensor(tensor)) :: ind
integer, intent(in) :: idim

Return Value integer

public pure function ndims_matrix_row(tensor)

how many tensor dimensions are mapped to matrix row

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer(kind=int_8)

public pure function ndims_matrix_column(tensor)

how many tensor dimensions are mapped to matrix column

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer(kind=int_8)

public pure function dbcsr_t_max_nblks_local(tensor) result(blk_count)

returns an estimate of maximum number of local blocks in tensor (irrespective of the actual number of currently present blocks) this estimate is based on the following assumption: tensor data is dense and load balancing is within a factor of 2

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

Return Value integer


Subroutines

public recursive subroutine dbcsr_t_mp_dims_create(nodes, dims, tensor_dims, lb_ratio)

Create process grid dimensions corresponding to one dimension of the matrix representation of a tensor, imposing that no process grid dimension is greater than the corresponding tensor dimension.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nodes

Total number of nodes available for this matrix dimension

integer, intent(inout), DIMENSION(:) :: dims

process grid dimension corresponding to tensor_dims

integer, intent(in), DIMENSION(:) :: tensor_dims

tensor dimensions

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

load imbalance acceptance factor

public subroutine dbcsr_t_nd_mp_free(mp_comm)

Release the MPI communicator.

Arguments

Type IntentOptional Attributes Name
type(mp_comm_type), intent(inout) :: mp_comm

public subroutine dbcsr_t_distribution_new(dist, pgrid, nd_dist_1, nd_dist_2, nd_dist_3, nd_dist_4)

Create a tensor distribution.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_distribution_type), intent(out) :: dist
type(dbcsr_t_pgrid_type), intent(in) :: pgrid

process grid

integer, intent(in), optional, DIMENSION(:) :: nd_dist_1

distribution vectors for all tensor dimensions

integer, intent(in), optional, DIMENSION(:) :: nd_dist_2

distribution vectors for all tensor dimensions

integer, intent(in), optional, DIMENSION(:) :: nd_dist_3

distribution vectors for all tensor dimensions

integer, intent(in), optional, DIMENSION(:) :: nd_dist_4

distribution vectors for all tensor dimensions

public subroutine dbcsr_t_distribution_new_expert(dist, pgrid, map1_2d, map2_2d, nd_dist_1, nd_dist_2, nd_dist_3, nd_dist_4, own_comm)

Create a tensor distribution.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_distribution_type), intent(out) :: dist
type(dbcsr_t_pgrid_type), intent(in) :: pgrid

process grid

integer, intent(in), DIMENSION(:) :: map1_2d

which nd-indices map to first matrix index and in which order

integer, intent(in), DIMENSION(:) :: map2_2d

which nd-indices map to second matrix index and in which order

integer, intent(in), optional, DIMENSION(:) :: nd_dist_1
integer, intent(in), optional, DIMENSION(:) :: nd_dist_2
integer, intent(in), optional, DIMENSION(:) :: nd_dist_3
integer, intent(in), optional, DIMENSION(:) :: nd_dist_4
logical, intent(in), optional :: own_comm

whether distribution should own communicator

public subroutine dbcsr_t_distribution_destroy(dist)

Destroy tensor distribution

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_distribution_type), intent(inout) :: dist

private subroutine dbcsr_t_distribution_hold(dist)

reference counting for distribution (only needed for communicator handle that must be freed when no longer needed)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_distribution_type), intent(in) :: dist

private subroutine dbcsr_t_create_new(tensor, name, dist, map1_2d, map2_2d, data_type, blk_size_1, blk_size_2, blk_size_3, blk_size_4)

create a tensor. For performance, the arguments map1_2d and map2_2d (controlling matrix representation of tensor) should be consistent with the the contraction to be performed (see documentation of dbcsr_t_contract).

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(out) :: tensor
character(len=*), intent(in) :: name
type(dbcsr_t_distribution_type), intent(inout) :: dist
integer, intent(in), DIMENSION(:) :: map1_2d

which nd-indices to map to first 2d index and in which order

integer, intent(in), DIMENSION(:) :: map2_2d

which nd-indices to map to first 2d index and in which order

integer, intent(in), optional :: data_type
integer, intent(in), optional, DIMENSION(:) :: blk_size_1

blk sizes in each dimension

integer, intent(in), optional, DIMENSION(:) :: blk_size_2

blk sizes in each dimension

integer, intent(in), optional, DIMENSION(:) :: blk_size_3

blk sizes in each dimension

integer, intent(in), optional, DIMENSION(:) :: blk_size_4

blk sizes in each dimension

public subroutine dbcsr_t_hold(tensor)

reference counting for tensors (only needed for communicator handle that must be freed when no longer needed)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor

private subroutine dbcsr_t_create_template(tensor_in, tensor, name, dist, map1_2d, map2_2d, data_type)

create a tensor from template

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor_in
type(dbcsr_t_type), intent(out) :: tensor
character(len=*), intent(in), optional :: name
type(dbcsr_t_distribution_type), intent(inout), optional :: dist
integer, intent(in), optional, DIMENSION(:) :: map1_2d
integer, intent(in), optional, DIMENSION(:) :: map2_2d
integer, intent(in), optional :: data_type

private subroutine dbcsr_t_create_matrix(matrix_in, tensor, order, name)

Create 2-rank tensor from matrix.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_in
type(dbcsr_t_type), intent(out) :: tensor
integer, intent(in), optional, DIMENSION(2) :: order
character(len=*), intent(in), optional :: name

public subroutine dbcsr_t_destroy(tensor)

Destroy a tensor

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor

public subroutine dims_tensor(tensor, dims)

tensor dimensions

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(out), DIMENSION(ndims_tensor(tensor)) :: dims

public subroutine blk_dims_tensor(tensor, dims)

tensor block dimensions

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(out), DIMENSION(ndims_tensor(tensor)) :: dims

public subroutine dbcsr_t_blk_sizes(tensor, ind, blk_size)

Size of tensor block

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(in), DIMENSION(ndims_tensor(tensor)) :: ind
integer, intent(out), DIMENSION(ndims_tensor(tensor)) :: blk_size

public subroutine dbcsr_t_blk_offsets(tensor, ind, blk_offset)

offset of tensor block

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(in), DIMENSION(ndims_tensor(tensor)) :: ind

block index

integer, intent(out), DIMENSION(ndims_tensor(tensor)) :: blk_offset

block offset

public subroutine dbcsr_t_get_stored_coordinates(tensor, ind_nd, processor)

Generalization of dbcsr_get_stored_coordinates for tensors.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(in), DIMENSION(ndims_tensor(tensor)) :: ind_nd
integer, intent(out) :: processor

public subroutine dbcsr_t_pgrid_create(mp_comm, dims, pgrid, tensor_dims)

Arguments

Type IntentOptional Attributes Name
type(mp_comm_type), intent(in) :: mp_comm
integer, intent(inout), DIMENSION(:) :: dims
type(dbcsr_t_pgrid_type), intent(out) :: pgrid
integer, intent(in), optional, DIMENSION(:) :: tensor_dims

public subroutine dbcsr_t_pgrid_create_expert(mp_comm, dims, pgrid, map1_2d, map2_2d, tensor_dims, nsplit, dimsplit)

Create an n-dimensional process grid. We can not use a n-dimensional MPI cartesian grid for tensors since the mapping between n-dim. and 2-dim. index allows for an arbitrary reordering of tensor index. Therefore we can not use n-dim. MPI Cartesian grid because it may not be consistent with the respective 2d grid. The 2d Cartesian MPI grid is the reference grid (since tensor data is stored as DBCSR matrix) and this routine creates an object that is a n-dim. interface to this grid. map1_2d and map2_2d don't need to be specified (correctly), grid may be redefined in dbcsr_t_distribution_new Note that pgrid is equivalent to a MPI cartesian grid only if map1_2d and map2_2d don't reorder indices (which is the case if [map1_2d, map2_2d] == [1, 2, ..., ndims]). Otherwise the mapping of grid coordinates to processes depends on the ordering of the indices and is not equivalent to a MPI cartesian grid.

Arguments

Type IntentOptional Attributes Name
type(mp_comm_type), intent(in) :: mp_comm

simple MPI Communicator

integer, intent(inout), DIMENSION(:) :: dims

grid dimensions - if entries are 0, dimensions are chosen automatically.

type(dbcsr_t_pgrid_type), intent(out) :: pgrid

n-dimensional grid object

integer, intent(in), DIMENSION(:) :: map1_2d

which nd-indices map to first matrix index and in which order which nd-indices map to first matrix index and in which order

integer, intent(in), DIMENSION(:) :: map2_2d

which nd-indices map to first matrix index and in which order which nd-indices map to first matrix index and in which order

integer, intent(in), optional, DIMENSION(:) :: tensor_dims

tensor block dimensions. If present, process grid dimensions are created such that good load balancing is ensured even if some of the tensor dimensions are small (i.e. on the same order or smaller than nproc**(1/ndim) where ndim is the tensor rank)

integer, intent(in), optional :: nsplit

impose a constant split factor which matrix dimension to split

integer, intent(in), optional :: dimsplit

impose a constant split factor which matrix dimension to split

public subroutine dbcsr_t_pgrid_destroy(pgrid, keep_comm)

destroy process grid

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_pgrid_type), intent(inout) :: pgrid
logical, intent(in), optional :: keep_comm

if .TRUE. communicator is not freed

public subroutine dbcsr_t_pgrid_set_strict_split(pgrid)

freeze current split factor such that it is never changed during contraction

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_pgrid_type), intent(inout) :: pgrid

private subroutine dbcsr_t_pgrid_remap(pgrid_in, map1_2d, map2_2d, pgrid_out)

remap a process grid (needed when mapping between tensor and matrix index is changed)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_pgrid_type), intent(in) :: pgrid_in
integer, intent(in), DIMENSION(:) :: map1_2d

new mapping new mapping

integer, intent(in), DIMENSION(:) :: map2_2d

new mapping new mapping

type(dbcsr_t_pgrid_type), intent(out) :: pgrid_out

public subroutine dbcsr_t_pgrid_change_dims(pgrid, pdims)

change dimensions of an existing process grid.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_pgrid_type), intent(inout) :: pgrid

process grid to be changed

integer, intent(inout), DIMENSION(:) :: pdims

new process grid dimensions, should all be set > 0

private subroutine dbcsr_t_distribution_remap(dist_in, map1_2d, map2_2d, dist_out)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_distribution_type), intent(in) :: dist_in
integer, intent(in), DIMENSION(:) :: map1_2d
integer, intent(in), DIMENSION(:) :: map2_2d
type(dbcsr_t_distribution_type), intent(out) :: dist_out

public subroutine mp_environ_pgrid(pgrid, dims, task_coor)

as mp_environ but for special pgrid type

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_pgrid_type), intent(in) :: pgrid
integer, intent(out), DIMENSION(ndims_mapping(pgrid%nd_index_grid)) :: dims
integer, intent(out), DIMENSION(ndims_mapping(pgrid%nd_index_grid)) :: task_coor

private subroutine dbcsr_t_set_r_dp(tensor, alpha)

As dbcsr_set

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
real(kind=real_8), intent(in) :: alpha

private subroutine dbcsr_t_set_r_sp(tensor, alpha)

As dbcsr_set

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
real(kind=real_4), intent(in) :: alpha

private subroutine dbcsr_t_set_c_dp(tensor, alpha)

As dbcsr_set

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
complex(kind=real_8), intent(in) :: alpha

private subroutine dbcsr_t_set_c_sp(tensor, alpha)

As dbcsr_set

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
complex(kind=real_4), intent(in) :: alpha

private subroutine dbcsr_t_filter_r_dp(tensor, eps, method, use_absolute)

As dbcsr_filter

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
real(kind=real_8), intent(in) :: eps
integer, intent(in), optional :: method
logical, intent(in), optional :: use_absolute

private subroutine dbcsr_t_filter_r_sp(tensor, eps, method, use_absolute)

As dbcsr_filter

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
real(kind=real_4), intent(in) :: eps
integer, intent(in), optional :: method
logical, intent(in), optional :: use_absolute

private subroutine dbcsr_t_filter_c_dp(tensor, eps, method, use_absolute)

As dbcsr_filter

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
complex(kind=real_8), intent(in) :: eps
integer, intent(in), optional :: method
logical, intent(in), optional :: use_absolute

private subroutine dbcsr_t_filter_c_sp(tensor, eps, method, use_absolute)

As dbcsr_filter

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
complex(kind=real_4), intent(in) :: eps
integer, intent(in), optional :: method
logical, intent(in), optional :: use_absolute

public subroutine dbcsr_t_get_info(tensor, nblks_total, nfull_total, nblks_local, nfull_local, pdims, my_ploc, blks_local_1, blks_local_2, blks_local_3, blks_local_4, proc_dist_1, proc_dist_2, proc_dist_3, proc_dist_4, blk_size_1, blk_size_2, blk_size_3, blk_size_4, blk_offset_1, blk_offset_2, blk_offset_3, blk_offset_4, distribution, name, data_type)

As dbcsr_get_info but for tensors

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor
integer, intent(out), optional, DIMENSION(ndims_tensor(tensor)) :: nblks_total

number of blocks along each dimension

integer, intent(out), optional, DIMENSION(ndims_tensor(tensor)) :: nfull_total

number of elements along each dimension

integer, intent(out), optional, DIMENSION(ndims_tensor(tensor)) :: nblks_local

local number of blocks along each dimension

integer, intent(out), optional, DIMENSION(ndims_tensor(tensor)) :: nfull_local

local number of elements along each dimension

integer, intent(out), optional, DIMENSION(ndims_tensor(tensor)) :: pdims

process grid dimensions

integer, intent(out), optional, DIMENSION(ndims_tensor(tensor)) :: my_ploc

process coordinates in process grid

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_local(tensor, 1)) :: blks_local_1

local blocks along dimension 1

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_local(tensor, 2)) :: blks_local_2

local blocks along dimension 2

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_local(tensor, 3)) :: blks_local_3

local blocks along dimension 3

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_local(tensor, 4)) :: blks_local_4

local blocks along dimension 4

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 1)) :: proc_dist_1

distribution along dimension 1

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 2)) :: proc_dist_2

distribution along dimension 2

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 3)) :: proc_dist_3

distribution along dimension 3

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 4)) :: proc_dist_4

distribution along dimension 4

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 1)) :: blk_size_1

block sizes along dimension 1

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 2)) :: blk_size_2

block sizes along dimension 2

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 3)) :: blk_size_3

block sizes along dimension 3

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 4)) :: blk_size_4

block sizes along dimension 4

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 1)) :: blk_offset_1

block offsets along dimension 1

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 2)) :: blk_offset_2

block offsets along dimension 2

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 3)) :: blk_offset_3

block offsets along dimension 3

integer, intent(out), optional, DIMENSION(dbcsr_t_nblks_total(tensor, 4)) :: blk_offset_4

block offsets along dimension 4

type(dbcsr_t_distribution_type), intent(out), optional :: distribution

distribution object

character(len=*), intent(out), optional :: name

name of tensor

integer, intent(out), optional :: data_type

data type of tensor

public subroutine dbcsr_t_clear(tensor)

Clear tensor (s.t. it does not contain any blocks)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor

public subroutine dbcsr_t_finalize(tensor)

Finalize tensor, as dbcsr_finalize. This should be taken care of internally in dbcsr tensors, there should not be any need to call this routine outside of dbcsr tensors.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor

public subroutine dbcsr_t_scale(tensor, alpha)

as dbcsr_scale

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
type(dbcsr_scalar_type), intent(in) :: alpha

public subroutine dbcsr_t_default_distvec(nblk, nproc, blk_size, dist)

get a load-balanced and randomized distribution along one tensor dimension

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nblk

number of blocks (along one tensor dimension)

integer, intent(in) :: nproc

number of processes (along one process grid dimension)

integer, intent(in), DIMENSION(nblk) :: blk_size

block sizes

integer, intent(out), DIMENSION(nblk) :: dist

distribution

public subroutine dbcsr_t_copy_contraction_storage(tensor_in, tensor_out)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(in) :: tensor_in
type(dbcsr_t_type), intent(inout) :: tensor_out