dbcsr_block_access Module

DBCSR block access



Variables

Type Visibility Attributes Name Initial
character(len=*), private, parameter :: moduleN = 'dbcsr_block_access'
logical, private, parameter :: careful_mod = .FALSE.
logical, private, parameter :: debug_mod = .FALSE.
integer, private, parameter :: rpslot_owner = 1
integer, private, parameter :: rpslot_addblks = 2
integer, private, parameter :: rpslot_addoffset = 3
integer, private, parameter :: rpslot_oldblks = 4
integer, private, parameter :: rpslot_oldoffset = 5
integer, private, parameter :: rpslot_totaloffset = 6
integer, private, parameter :: rpnslots = 6
logical, private, parameter :: detailed_timing = .FALSE.

Interfaces

public interface dbcsr_get_block_p

  • private subroutine dbcsr_get_block_p_d(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a 1-d block from a dbcsr matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    real(kind=real_8), DIMENSION(:), POINTER :: block

    the block to get (rank-1 array)

    logical, intent(out) :: tr

    whether the data is transposed

    logical, intent(out) :: found

    whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

  • private subroutine dbcsr_get_block_p_s(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a 1-d block from a dbcsr matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    real(kind=real_4), DIMENSION(:), POINTER :: block

    the block to get (rank-1 array)

    logical, intent(out) :: tr

    whether the data is transposed

    logical, intent(out) :: found

    whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

  • private subroutine dbcsr_get_block_p_z(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a 1-d block from a dbcsr matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    complex(kind=real_8), DIMENSION(:), POINTER :: block

    the block to get (rank-1 array)

    logical, intent(out) :: tr

    whether the data is transposed

    logical, intent(out) :: found

    whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

  • private subroutine dbcsr_get_block_p_c(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a 1-d block from a dbcsr matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    complex(kind=real_4), DIMENSION(:), POINTER :: block

    the block to get (rank-1 array)

    logical, intent(out) :: tr

    whether the data is transposed

    logical, intent(out) :: found

    whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

  • private subroutine dbcsr_get_2d_block_p_d(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a 2-d block from a dbcsr matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    real(kind=real_8), DIMENSION(:, :), POINTER :: block

    the block to get (rank-2 array)

    logical, intent(out) :: tr

    whether the data is transposed

    logical, intent(out) :: found

    whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

  • private subroutine dbcsr_get_2d_block_p_s(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a 2-d block from a dbcsr matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    real(kind=real_4), DIMENSION(:, :), POINTER :: block

    the block to get (rank-2 array)

    logical, intent(out) :: tr

    whether the data is transposed

    logical, intent(out) :: found

    whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

  • private subroutine dbcsr_get_2d_block_p_z(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a 2-d block from a dbcsr matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    complex(kind=real_8), DIMENSION(:, :), POINTER :: block

    the block to get (rank-2 array)

    logical, intent(out) :: tr

    whether the data is transposed

    logical, intent(out) :: found

    whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

  • private subroutine dbcsr_get_2d_block_p_c(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a 2-d block from a dbcsr matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    complex(kind=real_4), DIMENSION(:, :), POINTER :: block

    the block to get (rank-2 array)

    logical, intent(out) :: tr

    whether the data is transposed

    logical, intent(out) :: found

    whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

  • private subroutine dbcsr_get_block_p_area(matrix, row, col, block, tr, found, row_size, col_size)

    Gets a block from a dbcsr matrix as a data area

    Data area The pointer encapsulated in the data area points to data stored in the matrix. It must be 2-dimensional.

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    type(dbcsr_data_obj), intent(inout) :: block

    the block to get

    logical, intent(out) :: tr

    whether the data is transposed whether the block exists in the matrix

    logical, intent(out) :: found

    whether the data is transposed whether the block exists in the matrix

    integer, intent(out), optional :: row_size

    logical row size of block logical column size of block

    integer, intent(out), optional :: col_size

    logical row size of block logical column size of block

public interface dbcsr_put_block

  • private subroutine dbcsr_put_block_area(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    We allow : matrix(dp) [+]= [scale(dp)] * block(dp) matrix(dp) [+]= [scale(dp)] * block(sp) matrix(sp) [+]= [scale(dp)] * block(sp)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    type(dbcsr_data_obj) :: block
    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed
    logical, intent(in), optional :: summation
    integer(kind=int_8), intent(inout), optional :: flop
    type(dbcsr_scalar_type), intent(in), optional :: scale
  • private subroutine dbcsr_put_block_d(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    Inserts a block in a dbcsr matrix. If the block exists, the current data is overwritten.

    @@@

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the logical row the logical column

    integer, intent(in) :: col

    the logical row the logical column

    real(kind=real_8), intent(in), DIMENSION(:), CONTIGUOUS :: block

    the block to put

    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    logical, intent(in), optional :: summation

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    integer(kind=int_8), intent(inout), optional :: flop
    real(kind=real_8), intent(in), optional :: scale

    scale the OBblock being added

  • private subroutine dbcsr_put_block_s(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    Inserts a block in a dbcsr matrix. If the block exists, the current data is overwritten.

    @@@

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the logical row the logical column

    integer, intent(in) :: col

    the logical row the logical column

    real(kind=real_4), intent(in), DIMENSION(:), CONTIGUOUS :: block

    the block to put

    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    logical, intent(in), optional :: summation

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    integer(kind=int_8), intent(inout), optional :: flop
    real(kind=real_4), intent(in), optional :: scale

    scale the OBblock being added

  • private subroutine dbcsr_put_block_z(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    Inserts a block in a dbcsr matrix. If the block exists, the current data is overwritten.

    @@@

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the logical row the logical column

    integer, intent(in) :: col

    the logical row the logical column

    complex(kind=real_8), intent(in), DIMENSION(:), CONTIGUOUS :: block

    the block to put

    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    logical, intent(in), optional :: summation

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    integer(kind=int_8), intent(inout), optional :: flop
    complex(kind=real_8), intent(in), optional :: scale

    scale the OBblock being added

  • private subroutine dbcsr_put_block_c(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    Inserts a block in a dbcsr matrix. If the block exists, the current data is overwritten.

    @@@

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the logical row the logical column

    integer, intent(in) :: col

    the logical row the logical column

    complex(kind=real_4), intent(in), DIMENSION(:), CONTIGUOUS :: block

    the block to put

    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    logical, intent(in), optional :: summation

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    integer(kind=int_8), intent(inout), optional :: flop
    complex(kind=real_4), intent(in), optional :: scale

    scale the OBblock being added

  • private subroutine dbcsr_put_block2d_d(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    Put a 2-D block in a DBCSR matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    real(kind=real_8), intent(in), DIMENSION(:, :), CONTIGUOUS, TARGET :: block

    the block to put

    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    logical, intent(in), optional :: summation

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    integer(kind=int_8), intent(inout), optional :: flop
    real(kind=real_8), intent(in), optional :: scale

    scale the block being added

  • private subroutine dbcsr_put_block2d_s(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    Put a 2-D block in a DBCSR matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    real(kind=real_4), intent(in), DIMENSION(:, :), CONTIGUOUS, TARGET :: block

    the block to put

    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    logical, intent(in), optional :: summation

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    integer(kind=int_8), intent(inout), optional :: flop
    real(kind=real_4), intent(in), optional :: scale

    scale the block being added

  • private subroutine dbcsr_put_block2d_z(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    Put a 2-D block in a DBCSR matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    complex(kind=real_8), intent(in), DIMENSION(:, :), CONTIGUOUS, TARGET :: block

    the block to put

    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    logical, intent(in), optional :: summation

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    integer(kind=int_8), intent(inout), optional :: flop
    complex(kind=real_8), intent(in), optional :: scale

    scale the block being added

  • private subroutine dbcsr_put_block2d_c(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

    Put a 2-D block in a DBCSR matrix

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    complex(kind=real_4), intent(in), DIMENSION(:, :), CONTIGUOUS, TARGET :: block

    the block to put

    integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
    logical, intent(in), optional :: transposed

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    logical, intent(in), optional :: summation

    the block is transposed if block exists, then sum the new block to the old one instead of replacing it

    integer(kind=int_8), intent(inout), optional :: flop
    complex(kind=real_4), intent(in), optional :: scale

    scale the block being added

public interface dbcsr_reserve_block2d

  • private subroutine dbcsr_reserve_block2d_s(matrix, row, col, block, transposed, existed)

    Put a 2-D block in a DBCSR matrix using the btree

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    real(kind=real_4), DIMENSION(:, :), POINTER :: block

    the block to reserve; added if not NULL

    logical, intent(in), optional :: transposed

    the block holds transposed data

    logical, intent(out), optional :: existed

    block already existed

  • private subroutine dbcsr_reserve_block2d_d(matrix, row, col, block, transposed, existed)

    Put a 2-D block in a DBCSR matrix using the btree

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    real(kind=real_8), DIMENSION(:, :), POINTER :: block

    the block to reserve; added if not NULL

    logical, intent(in), optional :: transposed

    the block holds transposed data

    logical, intent(out), optional :: existed

    block already existed

  • private subroutine dbcsr_reserve_block2d_c(matrix, row, col, block, transposed, existed)

    Put a 2-D block in a DBCSR matrix using the btree

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    complex(kind=real_4), DIMENSION(:, :), POINTER :: block

    the block to reserve; added if not NULL

    logical, intent(in), optional :: transposed

    the block holds transposed data

    logical, intent(out), optional :: existed

    block already existed

  • private subroutine dbcsr_reserve_block2d_z(matrix, row, col, block, transposed, existed)

    Put a 2-D block in a DBCSR matrix using the btree

    Arguments

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

    DBCSR matrix

    integer, intent(in) :: row

    the row the column

    integer, intent(in) :: col

    the row the column

    complex(kind=real_8), DIMENSION(:, :), POINTER :: block

    the block to reserve; added if not NULL

    logical, intent(in), optional :: transposed

    the block holds transposed data

    logical, intent(out), optional :: existed

    block already existed

private interface dbcsr_set_block_pointer

  • private subroutine dbcsr_set_block_pointer_any(matrix, pointer_any, rsize, csize, main_tr, base_offset)

    Sets a pointer, possibly using the buffers.

    Arguments

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

    Matrix to use

    type(dbcsr_data_obj), intent(inout) :: pointer_any

    The pointer to set

    integer, intent(in) :: rsize

    Row sizes of block to point to Column sizes of block to point to

    integer, intent(in) :: csize

    Row sizes of block to point to Column sizes of block to point to

    logical, intent(in) :: main_tr

    Whether block is transposed in the matrix

    integer, intent(in) :: base_offset

    The block pointer

  • private subroutine dbcsr_set_block_pointer_2d_s(matrix, pointer_any, rsize, csize, base_offset)

    Sets a pointer, possibly using the buffers.

    Arguments

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

    Matrix to use

    real(kind=real_4), DIMENSION(:, :), POINTER :: pointer_any

    The pointer to set

    integer, intent(in) :: rsize

    Row size of block to point to Column size of block to point to

    integer, intent(in) :: csize

    Row size of block to point to Column size of block to point to

    integer, intent(in) :: base_offset

    The block pointer

  • private subroutine dbcsr_set_block_pointer_2d_d(matrix, pointer_any, rsize, csize, base_offset)

    Sets a pointer, possibly using the buffers.

    Arguments

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

    Matrix to use

    real(kind=real_8), DIMENSION(:, :), POINTER :: pointer_any

    The pointer to set

    integer, intent(in) :: rsize

    Row size of block to point to Column size of block to point to

    integer, intent(in) :: csize

    Row size of block to point to Column size of block to point to

    integer, intent(in) :: base_offset

    The block pointer

  • private subroutine dbcsr_set_block_pointer_2d_c(matrix, pointer_any, rsize, csize, base_offset)

    Sets a pointer, possibly using the buffers.

    Arguments

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

    Matrix to use

    complex(kind=real_4), DIMENSION(:, :), POINTER :: pointer_any

    The pointer to set

    integer, intent(in) :: rsize

    Row size of block to point to Column size of block to point to

    integer, intent(in) :: csize

    Row size of block to point to Column size of block to point to

    integer, intent(in) :: base_offset

    The block pointer

  • private subroutine dbcsr_set_block_pointer_2d_z(matrix, pointer_any, rsize, csize, base_offset)

    Sets a pointer, possibly using the buffers.

    Arguments

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

    Matrix to use

    complex(kind=real_8), DIMENSION(:, :), POINTER :: pointer_any

    The pointer to set

    integer, intent(in) :: rsize

    Row size of block to point to Column size of block to point to

    integer, intent(in) :: csize

    Row size of block to point to Column size of block to point to

    integer, intent(in) :: base_offset

    The block pointer


Derived Types

type, private ::  block_parameters

Components

Type Visibility Attributes Name Initial
logical, public :: tr
integer, public :: logical_rows
integer, public :: logical_cols
integer, public :: offset
integer, public :: nze

type, private ::  dgemm_join

Components

Type Visibility Attributes Name Initial
integer, public :: p_a
integer, public :: p_b
integer, public :: p_c
integer, public :: last_k
integer, public :: last_n
type(dbcsr_scalar_type), public :: alpha
type(dbcsr_scalar_type), public :: beta

Subroutines

public subroutine dbcsr_remove_block(matrix, row, col, block_nze, block_number)

Marks a block for removal from a DBCSR matrix. Handles symmetric matrices.

Arguments

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

DBCSR matrix

integer, intent(in) :: row

row of block to remove column of block to remove

integer, intent(in) :: col

row of block to remove column of block to remove

integer, intent(in) :: block_nze

row of block to remove column of block to remove

integer, intent(in), optional :: block_number

the block number, if it is known

private subroutine dbcsr_get_block_p_area(matrix, row, col, block, tr, found, row_size, col_size)

Gets a block from a dbcsr matrix as a data area

Read more…

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

type(dbcsr_data_obj), intent(inout) :: block

the block to get

logical, intent(out) :: tr

whether the data is transposed whether the block exists in the matrix

logical, intent(out) :: found

whether the data is transposed whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_put_block_area(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

We allow : matrix(dp) [+]= [scale(dp)] * block(dp) matrix(dp) [+]= [scale(dp)] * block(sp) matrix(sp) [+]= [scale(dp)] * block(sp)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
type(dbcsr_data_obj) :: block
integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed
logical, intent(in), optional :: summation
integer(kind=int_8), intent(inout), optional :: flop
type(dbcsr_scalar_type), intent(in), optional :: scale

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.

public subroutine dbcsr_reserve_diag_blocks(matrix)

Inserts diagonal blocks of a dbcsr matrix to make it a matrix with at least all diagonal blocks present

Arguments

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

Matrix into which blocks should be added.

public subroutine dbcsr_reserve_blocks(matrix, rows, columns, blk_pointers)

Inserts block reservations into a matrix, avoiding the work matrix.

Read more…

Arguments

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

Matrix into which blocks should be added.

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

Rows of the blocks to add Columns of the blocks to add

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

Rows of the blocks to add Columns of the blocks to add

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

block pointers to use for new blocks

private subroutine dbcsr_set_block_pointer_any(matrix, pointer_any, rsize, csize, main_tr, base_offset)

Sets a pointer, possibly using the buffers.

Arguments

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

Matrix to use

type(dbcsr_data_obj), intent(inout) :: pointer_any

The pointer to set

integer, intent(in) :: rsize

Row sizes of block to point to Column sizes of block to point to

integer, intent(in) :: csize

Row sizes of block to point to Column sizes of block to point to

logical, intent(in) :: main_tr

Whether block is transposed in the matrix

integer, intent(in) :: base_offset

The block pointer

private subroutine dbcsr_get_2d_block_p_d(matrix, row, col, block, tr, found, row_size, col_size)

Gets a 2-d block from a dbcsr matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

real(kind=real_8), DIMENSION(:, :), POINTER :: block

the block to get (rank-2 array)

logical, intent(out) :: tr

whether the data is transposed

logical, intent(out) :: found

whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_get_block_p_d(matrix, row, col, block, tr, found, row_size, col_size)

Gets a 1-d block from a dbcsr matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

real(kind=real_8), DIMENSION(:), POINTER :: block

the block to get (rank-1 array)

logical, intent(out) :: tr

whether the data is transposed

logical, intent(out) :: found

whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_reserve_block2d_d(matrix, row, col, block, transposed, existed)

Put a 2-D block in a DBCSR matrix using the btree

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

real(kind=real_8), DIMENSION(:, :), POINTER :: block

the block to reserve; added if not NULL

logical, intent(in), optional :: transposed

the block holds transposed data

logical, intent(out), optional :: existed

block already existed

private subroutine dbcsr_put_block2d_d(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

Put a 2-D block in a DBCSR matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

real(kind=real_8), intent(in), DIMENSION(:, :), CONTIGUOUS, TARGET :: block

the block to put

integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

logical, intent(in), optional :: summation

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

integer(kind=int_8), intent(inout), optional :: flop
real(kind=real_8), intent(in), optional :: scale

scale the block being added

private subroutine dbcsr_put_block_d(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

Inserts a block in a dbcsr matrix. If the block exists, the current data is overwritten.

Read more…

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the logical row the logical column

integer, intent(in) :: col

the logical row the logical column

real(kind=real_8), intent(in), DIMENSION(:), CONTIGUOUS :: block

the block to put

integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

logical, intent(in), optional :: summation

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

integer(kind=int_8), intent(inout), optional :: flop
real(kind=real_8), intent(in), optional :: scale

scale the OBblock being added

private subroutine dbcsr_set_block_pointer_2d_d(matrix, pointer_any, rsize, csize, base_offset)

Sets a pointer, possibly using the buffers.

Arguments

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

Matrix to use

real(kind=real_8), DIMENSION(:, :), POINTER :: pointer_any

The pointer to set

integer, intent(in) :: rsize

Row size of block to point to Column size of block to point to

integer, intent(in) :: csize

Row size of block to point to Column size of block to point to

integer, intent(in) :: base_offset

The block pointer

private subroutine dbcsr_get_2d_block_p_s(matrix, row, col, block, tr, found, row_size, col_size)

Gets a 2-d block from a dbcsr matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

real(kind=real_4), DIMENSION(:, :), POINTER :: block

the block to get (rank-2 array)

logical, intent(out) :: tr

whether the data is transposed

logical, intent(out) :: found

whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_get_block_p_s(matrix, row, col, block, tr, found, row_size, col_size)

Gets a 1-d block from a dbcsr matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

real(kind=real_4), DIMENSION(:), POINTER :: block

the block to get (rank-1 array)

logical, intent(out) :: tr

whether the data is transposed

logical, intent(out) :: found

whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_reserve_block2d_s(matrix, row, col, block, transposed, existed)

Put a 2-D block in a DBCSR matrix using the btree

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

real(kind=real_4), DIMENSION(:, :), POINTER :: block

the block to reserve; added if not NULL

logical, intent(in), optional :: transposed

the block holds transposed data

logical, intent(out), optional :: existed

block already existed

private subroutine dbcsr_put_block2d_s(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

Put a 2-D block in a DBCSR matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

real(kind=real_4), intent(in), DIMENSION(:, :), CONTIGUOUS, TARGET :: block

the block to put

integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

logical, intent(in), optional :: summation

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

integer(kind=int_8), intent(inout), optional :: flop
real(kind=real_4), intent(in), optional :: scale

scale the block being added

private subroutine dbcsr_put_block_s(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

Inserts a block in a dbcsr matrix. If the block exists, the current data is overwritten.

Read more…

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the logical row the logical column

integer, intent(in) :: col

the logical row the logical column

real(kind=real_4), intent(in), DIMENSION(:), CONTIGUOUS :: block

the block to put

integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

logical, intent(in), optional :: summation

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

integer(kind=int_8), intent(inout), optional :: flop
real(kind=real_4), intent(in), optional :: scale

scale the OBblock being added

private subroutine dbcsr_set_block_pointer_2d_s(matrix, pointer_any, rsize, csize, base_offset)

Sets a pointer, possibly using the buffers.

Arguments

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

Matrix to use

real(kind=real_4), DIMENSION(:, :), POINTER :: pointer_any

The pointer to set

integer, intent(in) :: rsize

Row size of block to point to Column size of block to point to

integer, intent(in) :: csize

Row size of block to point to Column size of block to point to

integer, intent(in) :: base_offset

The block pointer

private subroutine dbcsr_get_2d_block_p_z(matrix, row, col, block, tr, found, row_size, col_size)

Gets a 2-d block from a dbcsr matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

complex(kind=real_8), DIMENSION(:, :), POINTER :: block

the block to get (rank-2 array)

logical, intent(out) :: tr

whether the data is transposed

logical, intent(out) :: found

whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_get_block_p_z(matrix, row, col, block, tr, found, row_size, col_size)

Gets a 1-d block from a dbcsr matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

complex(kind=real_8), DIMENSION(:), POINTER :: block

the block to get (rank-1 array)

logical, intent(out) :: tr

whether the data is transposed

logical, intent(out) :: found

whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_reserve_block2d_z(matrix, row, col, block, transposed, existed)

Put a 2-D block in a DBCSR matrix using the btree

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

complex(kind=real_8), DIMENSION(:, :), POINTER :: block

the block to reserve; added if not NULL

logical, intent(in), optional :: transposed

the block holds transposed data

logical, intent(out), optional :: existed

block already existed

private subroutine dbcsr_put_block2d_z(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

Put a 2-D block in a DBCSR matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

complex(kind=real_8), intent(in), DIMENSION(:, :), CONTIGUOUS, TARGET :: block

the block to put

integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

logical, intent(in), optional :: summation

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

integer(kind=int_8), intent(inout), optional :: flop
complex(kind=real_8), intent(in), optional :: scale

scale the block being added

private subroutine dbcsr_put_block_z(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

Inserts a block in a dbcsr matrix. If the block exists, the current data is overwritten.

Read more…

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the logical row the logical column

integer, intent(in) :: col

the logical row the logical column

complex(kind=real_8), intent(in), DIMENSION(:), CONTIGUOUS :: block

the block to put

integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

logical, intent(in), optional :: summation

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

integer(kind=int_8), intent(inout), optional :: flop
complex(kind=real_8), intent(in), optional :: scale

scale the OBblock being added

private subroutine dbcsr_set_block_pointer_2d_z(matrix, pointer_any, rsize, csize, base_offset)

Sets a pointer, possibly using the buffers.

Arguments

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

Matrix to use

complex(kind=real_8), DIMENSION(:, :), POINTER :: pointer_any

The pointer to set

integer, intent(in) :: rsize

Row size of block to point to Column size of block to point to

integer, intent(in) :: csize

Row size of block to point to Column size of block to point to

integer, intent(in) :: base_offset

The block pointer

private subroutine dbcsr_get_2d_block_p_c(matrix, row, col, block, tr, found, row_size, col_size)

Gets a 2-d block from a dbcsr matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

complex(kind=real_4), DIMENSION(:, :), POINTER :: block

the block to get (rank-2 array)

logical, intent(out) :: tr

whether the data is transposed

logical, intent(out) :: found

whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_get_block_p_c(matrix, row, col, block, tr, found, row_size, col_size)

Gets a 1-d block from a dbcsr matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

complex(kind=real_4), DIMENSION(:), POINTER :: block

the block to get (rank-1 array)

logical, intent(out) :: tr

whether the data is transposed

logical, intent(out) :: found

whether the block exists in the matrix

integer, intent(out), optional :: row_size

logical row size of block logical column size of block

integer, intent(out), optional :: col_size

logical row size of block logical column size of block

private subroutine dbcsr_reserve_block2d_c(matrix, row, col, block, transposed, existed)

Put a 2-D block in a DBCSR matrix using the btree

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

complex(kind=real_4), DIMENSION(:, :), POINTER :: block

the block to reserve; added if not NULL

logical, intent(in), optional :: transposed

the block holds transposed data

logical, intent(out), optional :: existed

block already existed

private subroutine dbcsr_put_block2d_c(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

Put a 2-D block in a DBCSR matrix

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the row the column

integer, intent(in) :: col

the row the column

complex(kind=real_4), intent(in), DIMENSION(:, :), CONTIGUOUS, TARGET :: block

the block to put

integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

logical, intent(in), optional :: summation

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

integer(kind=int_8), intent(inout), optional :: flop
complex(kind=real_4), intent(in), optional :: scale

scale the block being added

private subroutine dbcsr_put_block_c(matrix, row, col, block, lb_row_col, transposed, summation, flop, scale)

Inserts a block in a dbcsr matrix. If the block exists, the current data is overwritten.

Read more…

Arguments

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

DBCSR matrix

integer, intent(in) :: row

the logical row the logical column

integer, intent(in) :: col

the logical row the logical column

complex(kind=real_4), intent(in), DIMENSION(:), CONTIGUOUS :: block

the block to put

integer, intent(inout), optional, DIMENSION(2) :: lb_row_col
logical, intent(in), optional :: transposed

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

logical, intent(in), optional :: summation

the block is transposed if block exists, then sum the new block to the old one instead of replacing it

integer(kind=int_8), intent(inout), optional :: flop
complex(kind=real_4), intent(in), optional :: scale

scale the OBblock being added

private subroutine dbcsr_set_block_pointer_2d_c(matrix, pointer_any, rsize, csize, base_offset)

Sets a pointer, possibly using the buffers.

Arguments

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

Matrix to use

complex(kind=real_4), DIMENSION(:, :), POINTER :: pointer_any

The pointer to set

integer, intent(in) :: rsize

Row size of block to point to Column size of block to point to

integer, intent(in) :: csize

Row size of block to point to Column size of block to point to

integer, intent(in) :: base_offset

The block pointer