dbcsr_api Module

This is the start of a dbcsr_api, all publicly needed functions are exported here. The others remain private to the library. Currently, this is the CP2K used set. Ultimately, a reduced subset and well defined api will remain, possibly grouped in to standard and expert api. Currently, this is work in progress.



Variables

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

Interfaces

public interface dbcsr_create

  • private subroutine dbcsr_create_new(matrix, name, dist, matrix_type, row_blk_size, col_blk_size, nze, data_type, reuse, reuse_arrays, mutable_work, replication_type)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    character(len=*), intent(in) :: name
    type(dbcsr_distribution_type), intent(in) :: dist
    character(len=1), intent(in) :: matrix_type
    integer, intent(inout), DIMENSION(:), POINTER :: row_blk_size
    integer, intent(inout), DIMENSION(:), POINTER :: col_blk_size
    integer, intent(in), optional :: nze
    integer, intent(in), optional :: data_type
    logical, intent(in), optional :: reuse
    logical, intent(in), optional :: reuse_arrays
    logical, intent(in), optional :: mutable_work
    character(len=1), intent(in), optional :: replication_type
  • private subroutine dbcsr_create_template(matrix, name, template, dist, matrix_type, row_blk_size, col_blk_size, nze, data_type, reuse_arrays, mutable_work, replication_type)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    character(len=*), intent(in), optional :: name
    type(dbcsr_type), intent(in) :: template
    type(dbcsr_distribution_type), intent(in), optional :: dist
    character(len=1), intent(in), optional :: matrix_type
    integer, intent(inout), optional, DIMENSION(:), POINTER :: row_blk_size
    integer, intent(inout), optional, DIMENSION(:), POINTER :: col_blk_size
    integer, intent(in), optional :: nze
    integer, intent(in), optional :: data_type
    logical, intent(in), optional :: reuse_arrays
    logical, intent(in), optional :: mutable_work
    character(len=1), intent(in), optional :: replication_type

public interface dbcsr_trace

  • private subroutine dbcsr_trace_d(matrix_a, trace)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_a
    real(kind=real_8), intent(out) :: trace
  • private subroutine dbcsr_trace_s(matrix_a, trace)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_a
    real(kind=real_4), intent(out) :: trace
  • private subroutine dbcsr_trace_z(matrix_a, trace)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_a
    complex(kind=real_8), intent(out) :: trace
  • private subroutine dbcsr_trace_c(matrix_a, trace)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_a
    complex(kind=real_4), intent(out) :: trace

public interface dbcsr_dot

  • private subroutine dbcsr_dot_d(matrix_a, matrix_b, result)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    real(kind=real_8), intent(inout) :: result
  • private subroutine dbcsr_dot_s(matrix_a, matrix_b, result)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    real(kind=real_4), intent(inout) :: result
  • private subroutine dbcsr_dot_z(matrix_a, matrix_b, result)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    complex(kind=real_8), intent(inout) :: result
  • private subroutine dbcsr_dot_c(matrix_a, matrix_b, result)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    complex(kind=real_4), intent(inout) :: result

public interface dbcsr_set

  • private subroutine dbcsr_set_d(matrix, alpha)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    real(kind=real_8), intent(in) :: alpha
  • private subroutine dbcsr_set_s(matrix, alpha)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    real(kind=real_4), intent(in) :: alpha
  • private subroutine dbcsr_set_c(matrix, alpha)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    complex(kind=real_4), intent(in) :: alpha
  • private subroutine dbcsr_set_z(matrix, alpha)

    Arguments

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

public interface dbcsr_add

  • private subroutine dbcsr_add_d(matrix_a, matrix_b, alpha_scalar, beta_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    real(kind=real_8), intent(in) :: alpha_scalar
    real(kind=real_8), intent(in) :: beta_scalar
  • private subroutine dbcsr_add_s(matrix_a, matrix_b, alpha_scalar, beta_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    real(kind=real_4), intent(in) :: alpha_scalar
    real(kind=real_4), intent(in) :: beta_scalar
  • private subroutine dbcsr_add_c(matrix_a, matrix_b, alpha_scalar, beta_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    complex(kind=real_4), intent(in) :: alpha_scalar
    complex(kind=real_4), intent(in) :: beta_scalar
  • private subroutine dbcsr_add_z(matrix_a, matrix_b, alpha_scalar, beta_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    complex(kind=real_8), intent(in) :: alpha_scalar
    complex(kind=real_8), intent(in) :: beta_scalar

public interface dbcsr_add_on_diag

  • private subroutine dbcsr_add_on_diag_d(matrix, alpha_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    real(kind=real_8), intent(in) :: alpha_scalar
  • private subroutine dbcsr_add_on_diag_s(matrix, alpha_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    real(kind=real_4), intent(in) :: alpha_scalar
  • private subroutine dbcsr_add_on_diag_c(matrix, alpha_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    complex(kind=real_4), intent(in) :: alpha_scalar
  • private subroutine dbcsr_add_on_diag_z(matrix, alpha_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    complex(kind=real_8), intent(in) :: alpha_scalar

public interface dbcsr_get_diag

  • private subroutine dbcsr_get_diag_d(matrix, diag)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    real(kind=real_8), intent(out), DIMENSION(:) :: diag
  • private subroutine dbcsr_get_diag_s(matrix, diag)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    real(kind=real_4), intent(out), DIMENSION(:) :: diag
  • private subroutine dbcsr_get_diag_c(matrix, diag)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    complex(kind=real_4), intent(out), DIMENSION(:) :: diag
  • private subroutine dbcsr_get_diag_z(matrix, diag)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    complex(kind=real_8), intent(out), DIMENSION(:) :: diag

public interface dbcsr_set_diag

  • private subroutine dbcsr_set_diag_d(matrix, diag)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    real(kind=real_8), intent(in), DIMENSION(:) :: diag
  • private subroutine dbcsr_set_diag_s(matrix, diag)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    real(kind=real_4), intent(in), DIMENSION(:) :: diag
  • private subroutine dbcsr_set_diag_c(matrix, diag)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    complex(kind=real_4), intent(in), DIMENSION(:) :: diag
  • private subroutine dbcsr_set_diag_z(matrix, diag)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    complex(kind=real_8), intent(in), DIMENSION(:) :: diag

public interface dbcsr_scale

  • private subroutine dbcsr_scale_d(matrix_a, alpha_scalar, last_column)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    real(kind=real_8), intent(in) :: alpha_scalar
    integer, intent(in), optional :: last_column
  • private subroutine dbcsr_scale_s(matrix_a, alpha_scalar, last_column)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    real(kind=real_4), intent(in) :: alpha_scalar
    integer, intent(in), optional :: last_column
  • private subroutine dbcsr_scale_c(matrix_a, alpha_scalar, last_column)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    complex(kind=real_4), intent(in) :: alpha_scalar
    integer, intent(in), optional :: last_column
  • private subroutine dbcsr_scale_z(matrix_a, alpha_scalar, last_column)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    complex(kind=real_8), intent(in) :: alpha_scalar
    integer, intent(in), optional :: last_column

public interface dbcsr_scale_by_vector

  • private subroutine dbcsr_scale_by_vector_d(matrix_a, alpha, side)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    real(kind=real_8), intent(in), DIMENSION(:), TARGET :: alpha
    character(len=*), intent(in) :: side
  • private subroutine dbcsr_scale_by_vector_s(matrix_a, alpha, side)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    real(kind=real_4), intent(in), DIMENSION(:), TARGET :: alpha
    character(len=*), intent(in) :: side
  • private subroutine dbcsr_scale_by_vector_c(matrix_a, alpha, side)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    complex(kind=real_4), intent(in), DIMENSION(:), TARGET :: alpha
    character(len=*), intent(in) :: side
  • private subroutine dbcsr_scale_by_vector_z(matrix_a, alpha, side)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix_a
    complex(kind=real_8), intent(in), DIMENSION(:), TARGET :: alpha
    character(len=*), intent(in) :: side

public interface dbcsr_multiply

  • private subroutine dbcsr_multiply_d(transa, transb, alpha, matrix_a, matrix_b, beta, matrix_c, first_row, last_row, first_column, last_column, first_k, last_k, retain_sparsity, filter_eps, flop)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    real(kind=real_8), intent(in) :: alpha
    type(dbcsr_type), intent(in) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    real(kind=real_8), intent(in) :: beta
    type(dbcsr_type), intent(inout) :: matrix_c
    integer, intent(in), optional :: first_row
    integer, intent(in), optional :: last_row
    integer, intent(in), optional :: first_column
    integer, intent(in), optional :: last_column
    integer, intent(in), optional :: first_k
    integer, intent(in), optional :: last_k
    logical, intent(in), optional :: retain_sparsity
    real(kind=real_8), intent(in), optional :: filter_eps
    integer(kind=int_8), intent(out), optional :: flop
  • private subroutine dbcsr_multiply_s(transa, transb, alpha, matrix_a, matrix_b, beta, matrix_c, first_row, last_row, first_column, last_column, first_k, last_k, retain_sparsity, filter_eps, flop)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    real(kind=real_4), intent(in) :: alpha
    type(dbcsr_type), intent(in) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    real(kind=real_4), intent(in) :: beta
    type(dbcsr_type), intent(inout) :: matrix_c
    integer, intent(in), optional :: first_row
    integer, intent(in), optional :: last_row
    integer, intent(in), optional :: first_column
    integer, intent(in), optional :: last_column
    integer, intent(in), optional :: first_k
    integer, intent(in), optional :: last_k
    logical, intent(in), optional :: retain_sparsity
    real(kind=real_8), intent(in), optional :: filter_eps
    integer(kind=int_8), intent(out), optional :: flop
  • private subroutine dbcsr_multiply_c(transa, transb, alpha, matrix_a, matrix_b, beta, matrix_c, first_row, last_row, first_column, last_column, first_k, last_k, retain_sparsity, filter_eps, flop)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    complex(kind=real_4), intent(in) :: alpha
    type(dbcsr_type), intent(in) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    complex(kind=real_4), intent(in) :: beta
    type(dbcsr_type), intent(inout) :: matrix_c
    integer, intent(in), optional :: first_row
    integer, intent(in), optional :: last_row
    integer, intent(in), optional :: first_column
    integer, intent(in), optional :: last_column
    integer, intent(in), optional :: first_k
    integer, intent(in), optional :: last_k
    logical, intent(in), optional :: retain_sparsity
    real(kind=real_8), intent(in), optional :: filter_eps
    integer(kind=int_8), intent(out), optional :: flop
  • private subroutine dbcsr_multiply_z(transa, transb, alpha, matrix_a, matrix_b, beta, matrix_c, first_row, last_row, first_column, last_column, first_k, last_k, retain_sparsity, filter_eps, flop)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    complex(kind=real_8), intent(in) :: alpha
    type(dbcsr_type), intent(in) :: matrix_a
    type(dbcsr_type), intent(in) :: matrix_b
    complex(kind=real_8), intent(in) :: beta
    type(dbcsr_type), intent(inout) :: matrix_c
    integer, intent(in), optional :: first_row
    integer, intent(in), optional :: last_row
    integer, intent(in), optional :: first_column
    integer, intent(in), optional :: last_column
    integer, intent(in), optional :: first_k
    integer, intent(in), optional :: last_k
    logical, intent(in), optional :: retain_sparsity
    real(kind=real_8), intent(in), optional :: filter_eps
    integer(kind=int_8), intent(out), optional :: flop

public interface dbcsr_get_block_p

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

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_8), DIMENSION(:), POINTER :: block
    logical, intent(out) :: tr
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_block_p_s(matrix, row, col, block, tr, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_4), DIMENSION(:), POINTER :: block
    logical, intent(out) :: tr
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_block_p_z(matrix, row, col, block, tr, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_8), DIMENSION(:), POINTER :: block
    logical, intent(out) :: tr
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_block_p_c(matrix, row, col, block, tr, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_4), DIMENSION(:), POINTER :: block
    logical, intent(out) :: tr
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_2d_block_p_d(matrix, row, col, block, tr, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_8), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: tr
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_2d_block_p_s(matrix, row, col, block, tr, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_4), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: tr
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_2d_block_p_z(matrix, row, col, block, tr, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_8), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: tr
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_2d_block_p_c(matrix, row, col, block, tr, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_4), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: tr
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_block_notrans_p_d(matrix, row, col, block, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_8), DIMENSION(:), POINTER :: block
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_block_notrans_p_s(matrix, row, col, block, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_4), DIMENSION(:), POINTER :: block
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_block_notrans_p_z(matrix, row, col, block, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_8), DIMENSION(:), POINTER :: block
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_block_notrans_p_c(matrix, row, col, block, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_4), DIMENSION(:), POINTER :: block
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_2d_block_notrans_p_d(matrix, row, col, block, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_8), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_2d_block_notrans_p_s(matrix, row, col, block, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_4), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_2d_block_notrans_p_z(matrix, row, col, block, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_8), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
  • private subroutine dbcsr_get_2d_block_notrans_p_c(matrix, row, col, block, found, row_size, col_size)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_4), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: found
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size

public interface dbcsr_put_block

  • private subroutine dbcsr_put_block_d(matrix, row, col, block, summation, scale)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_8), intent(in), DIMENSION(:) :: block
    logical, intent(in), optional :: summation
    real(kind=real_8), intent(in), optional :: scale
  • private subroutine dbcsr_put_block_s(matrix, row, col, block, summation, scale)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_4), intent(in), DIMENSION(:) :: block
    logical, intent(in), optional :: summation
    real(kind=real_4), intent(in), optional :: scale
  • private subroutine dbcsr_put_block_z(matrix, row, col, block, summation, scale)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_8), intent(in), DIMENSION(:) :: block
    logical, intent(in), optional :: summation
    complex(kind=real_8), intent(in), optional :: scale
  • private subroutine dbcsr_put_block_c(matrix, row, col, block, summation, scale)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_4), intent(in), DIMENSION(:) :: block
    logical, intent(in), optional :: summation
    complex(kind=real_4), intent(in), optional :: scale
  • private subroutine dbcsr_put_block2d_d(matrix, row, col, block, summation, scale)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_8), intent(in), DIMENSION(:, :) :: block
    logical, intent(in), optional :: summation
    real(kind=real_8), intent(in), optional :: scale
  • private subroutine dbcsr_put_block2d_s(matrix, row, col, block, summation, scale)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_4), intent(in), DIMENSION(:, :) :: block
    logical, intent(in), optional :: summation
    real(kind=real_4), intent(in), optional :: scale
  • private subroutine dbcsr_put_block2d_z(matrix, row, col, block, summation, scale)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_8), intent(in), DIMENSION(:, :) :: block
    logical, intent(in), optional :: summation
    complex(kind=real_8), intent(in), optional :: scale
  • private subroutine dbcsr_put_block2d_c(matrix, row, col, block, summation, scale)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_4), intent(in), DIMENSION(:, :) :: block
    logical, intent(in), optional :: summation
    complex(kind=real_4), intent(in), optional :: scale

public interface dbcsr_iterator_next_block

  • private subroutine dbcsr_iterator_next_block_index(iterator, row, column, blk, blk_p)

    Gets the index information of the next block, no data.

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator

    the iterator

    integer, intent(out) :: row

    row of the data block column of the data block block number

    integer, intent(out) :: column

    row of the data block column of the data block block number

    integer, intent(out) :: blk

    row of the data block column of the data block block number

    integer, intent(out), optional :: blk_p

    index into block data array

  • private subroutine dbcsr_iterator_next_2d_block_d(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    real(kind=real_8), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: transposed
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_2d_block_s(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    real(kind=real_4), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: transposed
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_2d_block_c(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    complex(kind=real_4), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: transposed
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_2d_block_z(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    complex(kind=real_8), DIMENSION(:, :), POINTER :: block
    logical, intent(out) :: transposed
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_1d_block_d(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    real(kind=real_8), DIMENSION(:), POINTER :: block
    logical, intent(out) :: transposed
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_1d_block_s(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    real(kind=real_4), DIMENSION(:), POINTER :: block
    logical, intent(out) :: transposed
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_1d_block_c(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    complex(kind=real_4), DIMENSION(:), POINTER :: block
    logical, intent(out) :: transposed
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_1d_block_z(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    complex(kind=real_8), DIMENSION(:), POINTER :: block
    logical, intent(out) :: transposed
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_2d_block_notrans_d(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    real(kind=real_8), DIMENSION(:, :), POINTER :: block
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_2d_block_notrans_s(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    real(kind=real_4), DIMENSION(:, :), POINTER :: block
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_2d_block_notrans_c(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    complex(kind=real_4), DIMENSION(:, :), POINTER :: block
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_2d_block_notrans_z(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    complex(kind=real_8), DIMENSION(:, :), POINTER :: block
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_1d_block_notrans_d(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    real(kind=real_8), DIMENSION(:), POINTER :: block
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_1d_block_notrans_s(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    real(kind=real_4), DIMENSION(:), POINTER :: block
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_1d_block_notrans_c(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    complex(kind=real_4), DIMENSION(:), POINTER :: block
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset
  • private subroutine dbcsr_iterator_next_1d_block_notrans_z(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_iterator_type), intent(inout) :: iterator
    integer, intent(out) :: row
    integer, intent(out) :: column
    complex(kind=real_8), DIMENSION(:), POINTER :: block
    integer, intent(out), optional :: block_number
    integer, intent(out), optional :: row_size
    integer, intent(out), optional :: col_size
    integer, intent(out), optional :: row_offset
    integer, intent(out), optional :: col_offset

public interface dbcsr_reserve_block2d

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

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_8), DIMENSION(:, :), POINTER :: block
    logical, intent(in), optional :: transposed
    logical, intent(out), optional :: existed
  • private subroutine dbcsr_reserve_block2d_s(matrix, row, col, block, transposed, existed)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    real(kind=real_4), DIMENSION(:, :), POINTER :: block
    logical, intent(in), optional :: transposed
    logical, intent(out), optional :: existed
  • private subroutine dbcsr_reserve_block2d_c(matrix, row, col, block, transposed, existed)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_4), DIMENSION(:, :), POINTER :: block
    logical, intent(in), optional :: transposed
    logical, intent(out), optional :: existed
  • private subroutine dbcsr_reserve_block2d_z(matrix, row, col, block, transposed, existed)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout) :: matrix
    integer, intent(in) :: row
    integer, intent(in) :: col
    complex(kind=real_8), DIMENSION(:, :), POINTER :: block
    logical, intent(in), optional :: transposed
    logical, intent(out), optional :: existed

public interface dbcsr_csr_create

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

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_csr_type), intent(out) :: csr_mat
    integer, intent(in) :: nrows_total
    integer, intent(in) :: ncols_total
    integer(kind=int_8) :: nze_total
    integer, intent(in) :: nze_local
    integer, intent(in) :: nrows_local
    integer, intent(in) :: mp_group
    integer, intent(in), optional :: data_type
  • public subroutine csr_create_template(matrix_b, matrix_a)

    Create a new CSR matrix and allocate all internal data using an existing CSR matrix. Copies the indices but no actual matrix data.

    Arguments

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

    Target CSR matrix

    type(csr_type), intent(in) :: matrix_a

    Source CSR matrix

public interface dbcsr_get_wms_data_p

  • private function dbcsr_get_wms_data_s(matrix, index_matrix, select_data_type, lb, ub) result(DATA)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: index_matrix
    real(kind=real_4), intent(in) :: select_data_type
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub

    Return Value real(kind=real_4), DIMENSION(:), POINTER

  • private function dbcsr_get_wms_data_c(matrix, index_matrix, select_data_type, lb, ub) result(DATA)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: index_matrix
    complex(kind=real_4), intent(in) :: select_data_type
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub

    Return Value complex(kind=real_4), DIMENSION(:), POINTER

  • private function dbcsr_get_wms_data_d(matrix, index_matrix, select_data_type, lb, ub) result(DATA)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: index_matrix
    real(kind=real_8), intent(in) :: select_data_type
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub

    Return Value real(kind=real_8), DIMENSION(:), POINTER

  • private function dbcsr_get_wms_data_z(matrix, index_matrix, select_data_type, lb, ub) result(DATA)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    integer, intent(in) :: index_matrix
    complex(kind=real_8), intent(in) :: select_data_type
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub

    Return Value complex(kind=real_8), DIMENSION(:), POINTER

public interface dbcsr_get_data_p

  • private function dbcsr_get_data_s(matrix, select_data_type, lb, ub) result(DATA)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    real(kind=real_4), intent(in) :: select_data_type
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub

    Return Value real(kind=real_4), DIMENSION(:), POINTER

  • private function dbcsr_get_data_c(matrix, select_data_type, lb, ub) result(DATA)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    complex(kind=real_4), intent(in) :: select_data_type
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub

    Return Value complex(kind=real_4), DIMENSION(:), POINTER

  • private function dbcsr_get_data_d(matrix, select_data_type, lb, ub) result(DATA)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    real(kind=real_8), intent(in) :: select_data_type
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub

    Return Value real(kind=real_8), DIMENSION(:), POINTER

  • private function dbcsr_get_data_z(matrix, select_data_type, lb, ub) result(DATA)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in) :: matrix
    complex(kind=real_8), intent(in) :: select_data_type
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub

    Return Value complex(kind=real_8), DIMENSION(:), POINTER

public interface dbcsr_norm

  • private subroutine dbcsr_norm_scalar(matrix, which_norm, norm_scalar)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout), TARGET :: matrix
    integer, intent(in) :: which_norm
    real(kind=dp), intent(out) :: norm_scalar
  • private subroutine dbcsr_norm_r8_vec(matrix, which_norm, norm_vector)

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(inout), TARGET :: matrix
    integer, intent(in) :: which_norm
    real(kind=dp), intent(out), DIMENSION(:) :: norm_vector

Derived Types

type, public ::  dbcsr_type

Components

Type Visibility Attributes Name Initial
type(dbcsr_type), private :: prv

type, public ::  dbcsr_p_type

Components

Type Visibility Attributes Name Initial
type(dbcsr_type), public, POINTER :: matrix => Null()

type, public ::  dbcsr_distribution_type

Components

Type Visibility Attributes Name Initial
type(dbcsr_distribution_obj), private :: prv

type, public ::  dbcsr_iterator_type

Components

Type Visibility Attributes Name Initial
type(dbcsr_iterator), private :: prv

Functions

public function dbcsr_gershgorin_norm(matrix) result(norm)

Arguments

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

Return Value real(kind=real_8)

public function dbcsr_frobenius_norm(matrix, local) result(norm)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
logical, intent(in), optional :: local

Return Value real(kind=real_8)

public function dbcsr_maxabs(matrix) result(norm)

Arguments

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

Return Value real(kind=real_8)

public pure function dbcsr_get_data_type(matrix) result(data_type)

Arguments

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

Return Value integer

public pure function dbcsr_valid_index(matrix) result(valid_index)

Arguments

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

Return Value logical

public pure function dbcsr_get_num_blocks(matrix) result(num_blocks)

Arguments

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

Return Value integer

public function dbcsr_get_data_size(matrix) result(data_size)

Arguments

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

Return Value integer

public pure function dbcsr_get_matrix_type(matrix) result(matrix_type)

Arguments

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

Return Value character(len=1)

public function dbcsr_get_occupation(matrix) result(occupation)

Arguments

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

Return Value real(kind=real_8)

public function dbcsr_nblkrows_total(matrix) result(nblkrows_total)

Arguments

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

Return Value integer

public function dbcsr_nblkcols_total(matrix) result(nblkcols_total)

Arguments

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

Return Value integer

public function dbcsr_nblkrows_local(matrix) result(nblkrows_local)

Arguments

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

Return Value integer

public function dbcsr_nblkcols_local(matrix) result(nblkcols_local)

Arguments

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

Return Value integer

public function dbcsr_nfullrows_total(matrix) result(nfullrows_total)

Arguments

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

Return Value integer

public function dbcsr_nfullcols_total(matrix) result(nfullcols_total)

Arguments

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

Return Value integer

public pure function dbcsr_iterator_blocks_left(iterator) result(blocks_left)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(in) :: iterator

Return Value logical

public function dbcsr_checksum(matrix, local, pos) result(checksum)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
logical, intent(in), optional :: local
logical, intent(in), optional :: pos

Return Value real(kind=dp)

public pure function dbcsr_has_symmetry(matrix) result(has_symmetry)

Arguments

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

Return Value logical

private function dbcsr_get_wms_data_d(matrix, index_matrix, select_data_type, lb, ub) result(DATA)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: index_matrix
real(kind=real_8), intent(in) :: select_data_type
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub

Return Value real(kind=real_8), DIMENSION(:), POINTER

private function dbcsr_get_data_d(matrix, select_data_type, lb, ub) result(DATA)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
real(kind=real_8), intent(in) :: select_data_type
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub

Return Value real(kind=real_8), DIMENSION(:), POINTER

private function dbcsr_get_wms_data_s(matrix, index_matrix, select_data_type, lb, ub) result(DATA)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: index_matrix
real(kind=real_4), intent(in) :: select_data_type
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub

Return Value real(kind=real_4), DIMENSION(:), POINTER

private function dbcsr_get_data_s(matrix, select_data_type, lb, ub) result(DATA)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
real(kind=real_4), intent(in) :: select_data_type
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub

Return Value real(kind=real_4), DIMENSION(:), POINTER

private function dbcsr_get_wms_data_z(matrix, index_matrix, select_data_type, lb, ub) result(DATA)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: index_matrix
complex(kind=real_8), intent(in) :: select_data_type
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub

Return Value complex(kind=real_8), DIMENSION(:), POINTER

private function dbcsr_get_data_z(matrix, select_data_type, lb, ub) result(DATA)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
complex(kind=real_8), intent(in) :: select_data_type
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub

Return Value complex(kind=real_8), DIMENSION(:), POINTER

private function dbcsr_get_wms_data_c(matrix, index_matrix, select_data_type, lb, ub) result(DATA)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: index_matrix
complex(kind=real_4), intent(in) :: select_data_type
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub

Return Value complex(kind=real_4), DIMENSION(:), POINTER

private function dbcsr_get_data_c(matrix, select_data_type, lb, ub) result(DATA)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
complex(kind=real_4), intent(in) :: select_data_type
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub

Return Value complex(kind=real_4), DIMENSION(:), POINTER


Subroutines

public subroutine dbcsr_mp_grid_setup(dist)

Arguments

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

public subroutine dbcsr_setname(matrix, newname)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
character(len=*), intent(in) :: newname

public subroutine dbcsr_complete_redistribute(matrix, redist, keep_sparsity, summation)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
type(dbcsr_type), intent(inout) :: redist
logical, intent(in), optional :: keep_sparsity
logical, intent(in), optional :: summation

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in), DIMENSION(:) :: rows
integer, intent(in), DIMENSION(:) :: cols
integer, intent(in), optional, DIMENSION(:) :: blk_pointers

public subroutine dbcsr_reserve_all_blocks(matrix)

Arguments

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

public subroutine dbcsr_reserve_diag_blocks(matrix)

Arguments

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

public subroutine dbcsr_add_work_coordinate(matrix, index_matrix, row, col, blk, index)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: index_matrix
integer, intent(in) :: row
integer, intent(in) :: col
integer, intent(in), optional :: blk
integer, intent(out), optional :: index

public subroutine dbcsr_set_work_size(matrix, index_matrix, newvalue)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: index_matrix
integer, intent(in) :: newvalue

public subroutine dbcsr_init_random(matrix, keep_sparsity, mini_seed)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
logical, optional :: keep_sparsity
integer, intent(in), optional :: mini_seed

public subroutine dbcsr_get_stored_coordinates(matrix, row, column, processor)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: column
integer, intent(out), optional :: processor

public subroutine dbcsr_iterator_stop(iterator)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator

public subroutine dbcsr_iterator_start(iterator, matrix, shared, dynamic, dynamic_byrows, contiguous_pointers, read_only)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(out) :: iterator
type(dbcsr_type), intent(in) :: matrix
logical, intent(in), optional :: shared
logical, intent(in), optional :: dynamic
logical, intent(in), optional :: dynamic_byrows
logical, intent(in), optional :: contiguous_pointers
logical, intent(in), optional :: read_only

private subroutine dbcsr_iterator_next_block_index(iterator, row, column, blk, blk_p)

Gets the index information of the next block, no data.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator

the iterator

integer, intent(out) :: row

row of the data block column of the data block block number

integer, intent(out) :: column

row of the data block column of the data block block number

integer, intent(out) :: blk

row of the data block column of the data block block number

integer, intent(out), optional :: blk_p

index into block data array

public subroutine dbcsr_get_info(matrix, nblkrows_total, nblkcols_total, nfullrows_total, nfullcols_total, nblkrows_local, nblkcols_local, nfullrows_local, nfullcols_local, my_prow, my_pcol, local_rows, local_cols, proc_row_dist, proc_col_dist, row_blk_size, col_blk_size, row_blk_offset, col_blk_offset, distribution, name, matrix_type, data_type, group)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(out), optional :: nblkrows_total
integer, intent(out), optional :: nblkcols_total
integer, intent(out), optional :: nfullrows_total
integer, intent(out), optional :: nfullcols_total
integer, intent(out), optional :: nblkrows_local
integer, intent(out), optional :: nblkcols_local
integer, intent(out), optional :: nfullrows_local
integer, intent(out), optional :: nfullcols_local
integer, intent(out), optional :: my_prow
integer, intent(out), optional :: my_pcol
integer, optional, DIMENSION(:), POINTER :: local_rows
integer, optional, DIMENSION(:), POINTER :: local_cols
integer, optional, DIMENSION(:), POINTER :: proc_row_dist
integer, optional, DIMENSION(:), POINTER :: proc_col_dist
integer, optional, DIMENSION(:), POINTER :: row_blk_size
integer, optional, DIMENSION(:), POINTER :: col_blk_size
integer, optional, DIMENSION(:), POINTER :: row_blk_offset
integer, optional, DIMENSION(:), POINTER :: col_blk_offset
type(dbcsr_distribution_type), intent(out), optional :: distribution
character(len=*), intent(out), optional :: name
character(len=1), intent(out), optional :: matrix_type
integer, intent(out), optional :: data_type
integer, intent(out), optional :: group

public subroutine dbcsr_distribution_get(dist, row_dist, col_dist, nrows, ncols, has_threads, group, mynode, numnodes, nprows, npcols, myprow, mypcol, pgrid, subgroups_defined, prow_group, pcol_group)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_distribution_type), intent(in) :: dist
integer, optional, DIMENSION(:), POINTER :: row_dist
integer, optional, DIMENSION(:), POINTER :: col_dist
integer, intent(out), optional :: nrows
integer, intent(out), optional :: ncols
logical, intent(out), optional :: has_threads
integer, intent(out), optional :: group
integer, intent(out), optional :: mynode
integer, intent(out), optional :: numnodes
integer, intent(out), optional :: nprows
integer, intent(out), optional :: npcols
integer, intent(out), optional :: myprow
integer, intent(out), optional :: mypcol
integer, optional, DIMENSION(:, :), POINTER :: pgrid
logical, intent(out), optional :: subgroups_defined
integer, intent(out), optional :: prow_group
integer, intent(out), optional :: pcol_group

public subroutine dbcsr_distribution_hold(dist)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_distribution_type) :: dist

public subroutine dbcsr_distribution_release(dist)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_distribution_type) :: dist

private subroutine dbcsr_norm_scalar(matrix, which_norm, norm_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout), TARGET :: matrix
integer, intent(in) :: which_norm
real(kind=dp), intent(out) :: norm_scalar

private subroutine dbcsr_norm_r8_vec(matrix, which_norm, norm_vector)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout), TARGET :: matrix
integer, intent(in) :: which_norm
real(kind=dp), intent(out), DIMENSION(:) :: norm_vector

public subroutine dbcsr_replicate_all(matrix)

Arguments

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

public subroutine dbcsr_distribute(matrix, fast)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
logical, intent(in), optional :: fast

public subroutine dbcsr_release_p(matrix)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), POINTER :: matrix

public subroutine dbcsr_release(matrix)

Arguments

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

public subroutine dbcsr_init_p(matrix)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), POINTER :: matrix

public subroutine dbcsr_print(matrix, nodata, matlab_format, variable_name, unit_nr)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
logical, intent(in), optional :: nodata
logical, intent(in), optional :: matlab_format
character(len=*), intent(in), optional :: variable_name
integer, optional :: unit_nr

public subroutine dbcsr_print_block_sum(matrix, unit_nr)

Prints the sum of the elements in each block

Arguments

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

public subroutine dbcsr_sum_replicated(matrix)

Arguments

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

public subroutine dbcsr_triu(matrix)

Arguments

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

public subroutine dbcsr_verify_matrix(matrix, verbosity, local)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in), optional :: verbosity
logical, intent(in), optional :: local

public subroutine dbcsr_distribution_new(dist, template, group, pgrid, row_dist, col_dist, reuse_arrays)

Creates new distribution from blockr distributions

Arguments

Type IntentOptional Attributes Name
type(dbcsr_distribution_type), intent(out) :: dist

distribution

type(dbcsr_distribution_type), intent(in), optional :: template
integer, intent(in), optional :: group
integer, optional, DIMENSION(:, :), POINTER :: pgrid
integer, intent(inout), DIMENSION(:), POINTER :: row_dist
integer, intent(inout), DIMENSION(:), POINTER :: col_dist
logical, intent(in), optional :: reuse_arrays

public subroutine dbcsr_print_statistics(print_timers, callgraph_filename)

Print statistics

Arguments

Type IntentOptional Attributes Name
logical, intent(in), optional :: print_timers
character(len=*), intent(in), optional :: callgraph_filename

public subroutine dbcsr_finalize(matrix, reshuffle)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
logical, intent(in), optional :: reshuffle

public subroutine dbcsr_work_create(matrix, nblks_guess, sizedata_guess, n, work_mutable)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in), optional :: nblks_guess
integer, intent(in), optional :: sizedata_guess
integer, intent(in), optional :: n
logical, intent(in), optional :: work_mutable

private subroutine dbcsr_create_new(matrix, name, dist, matrix_type, row_blk_size, col_blk_size, nze, data_type, reuse, reuse_arrays, mutable_work, replication_type)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
character(len=*), intent(in) :: name
type(dbcsr_distribution_type), intent(in) :: dist
character(len=1), intent(in) :: matrix_type
integer, intent(inout), DIMENSION(:), POINTER :: row_blk_size
integer, intent(inout), DIMENSION(:), POINTER :: col_blk_size
integer, intent(in), optional :: nze
integer, intent(in), optional :: data_type
logical, intent(in), optional :: reuse
logical, intent(in), optional :: reuse_arrays
logical, intent(in), optional :: mutable_work
character(len=1), intent(in), optional :: replication_type

private subroutine dbcsr_create_template(matrix, name, template, dist, matrix_type, row_blk_size, col_blk_size, nze, data_type, reuse_arrays, mutable_work, replication_type)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
character(len=*), intent(in), optional :: name
type(dbcsr_type), intent(in) :: template
type(dbcsr_distribution_type), intent(in), optional :: dist
character(len=1), intent(in), optional :: matrix_type
integer, intent(inout), optional, DIMENSION(:), POINTER :: row_blk_size
integer, intent(inout), optional, DIMENSION(:), POINTER :: col_blk_size
integer, intent(in), optional :: nze
integer, intent(in), optional :: data_type
logical, intent(in), optional :: reuse_arrays
logical, intent(in), optional :: mutable_work
character(len=1), intent(in), optional :: replication_type

public subroutine dbcsr_filter(matrix, eps, method, use_absolute, filter_diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
real(kind=dp), intent(in) :: eps
integer, intent(in), optional :: method
logical, intent(in), optional :: use_absolute
logical, intent(in), optional :: filter_diag

public subroutine dbcsr_get_block_diag(matrix, diag)

Arguments

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

public subroutine dbcsr_binary_write(matrix, filepath)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
character(len=*), intent(in) :: filepath

public subroutine dbcsr_binary_read(filepath, distribution, matrix_new)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filepath
type(dbcsr_distribution_type), intent(in) :: distribution
type(dbcsr_type), intent(inout) :: matrix_new

public subroutine dbcsr_copy(matrix_b, matrix_a, name, keep_sparsity, shallow_data, keep_imaginary, matrix_type)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_b
type(dbcsr_type), intent(in) :: matrix_a
character(len=*), intent(in), optional :: name
logical, intent(in), optional :: keep_sparsity
logical, intent(in), optional :: shallow_data
logical, intent(in), optional :: keep_imaginary
character(len=1), intent(in), optional :: matrix_type

public subroutine dbcsr_copy_into_existing(matrix_b, matrix_a)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_b
type(dbcsr_type), intent(in) :: matrix_a

public subroutine dbcsr_desymmetrize(matrix_a, matrix_b)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(inout) :: matrix_b

public subroutine dbcsr_transposed(transposed, normal, shallow_data_copy, transpose_data, transpose_distribution, use_distribution)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: transposed
type(dbcsr_type), intent(in) :: normal
logical, intent(in), optional :: shallow_data_copy
logical, intent(in), optional :: transpose_data
logical, intent(in), optional :: transpose_distribution
type(dbcsr_distribution_type), intent(in), optional :: use_distribution

public subroutine dbcsr_function_of_elements(matrix_a, func, a0, a1, a2)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
integer, intent(in) :: func
real(kind=dp), intent(in), optional :: a0
real(kind=dp), intent(in), optional :: a1
real(kind=dp), intent(in), optional :: a2

public subroutine dbcsr_hadamard_product(matrix_a, matrix_b, matrix_c, b_assume_value)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
type(dbcsr_type), intent(inout) :: matrix_c
real(kind=dp), intent(in), optional :: b_assume_value

public subroutine dbcsr_deallocate_matrix(matrix)

Deallocates a DBCSR matrix for compatibility with CP2K

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), POINTER :: matrix

DBCSR matrix

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_csr_type), intent(out) :: csr_mat
integer, intent(in) :: nrows_total
integer, intent(in) :: ncols_total
integer(kind=int_8) :: nze_total
integer, intent(in) :: nze_local
integer, intent(in) :: nrows_local
integer, intent(in) :: mp_group
integer, intent(in), optional :: data_type

public subroutine dbcsr_csr_create_from_dbcsr(dbcsr_mat, csr_mat, dist_format, csr_sparsity, numnodes)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: dbcsr_mat
type(dbcsr_csr_type), intent(out) :: csr_mat
integer :: dist_format
type(dbcsr_type), intent(in), optional :: csr_sparsity
integer, intent(in), optional :: numnodes

public subroutine dbcsr_convert_csr_to_dbcsr(dbcsr_mat, csr_mat)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: dbcsr_mat
type(dbcsr_csr_type), intent(inout) :: csr_mat

public subroutine dbcsr_convert_dbcsr_to_csr(dbcsr_mat, csr_mat)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: dbcsr_mat
type(dbcsr_csr_type), intent(inout) :: csr_mat

public subroutine dbcsr_to_csr_filter(dbcsr_mat, csr_sparsity, eps)

Apply filtering threshold eps to DBCSR blocks in order to improve CSR sparsity (currently only used for testing purposes)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: dbcsr_mat
type(dbcsr_type), intent(out) :: csr_sparsity
real(kind=real_8), intent(in) :: eps

public subroutine dbcsr_clear(dbcsr_mat)

Clear a matrix

Arguments

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

public subroutine dbcsr_add_block_node(matrix, block_row, block_col, block)

Emulation of sparse_matrix_types/add_block_node mapped to add_real_matrix_block.... should not be used any longer It adds a block to the dbcsr matrix and returns a rank-2 pointer to the block. Currently it only and always uses the mutable data.

Arguments

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

DBCSR matrix

integer, intent(in) :: block_row

the row the column

integer, intent(in) :: block_col

the row the column

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

the block to put

public subroutine dbcsr_run_tests(mp_group, io_unit, nproc, matrix_sizes, trs, bs_m, bs_n, bs_k, sparsities, alpha, beta, data_type, test_type, n_loops, eps, retain_sparsity, always_checksum)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: mp_group
integer, intent(in) :: io_unit
integer, DIMENSION(:), POINTER :: nproc
integer, intent(in), DIMENSION(:) :: matrix_sizes
logical, intent(in), DIMENSION(2) :: trs
integer, DIMENSION(:), POINTER :: bs_m
integer, DIMENSION(:), POINTER :: bs_n
integer, DIMENSION(:), POINTER :: bs_k
real(kind=dp), intent(in), DIMENSION(3) :: sparsities
real(kind=dp), intent(in) :: alpha
real(kind=dp), intent(in) :: beta
integer, intent(in) :: data_type
integer, intent(in) :: test_type
integer, intent(in) :: n_loops
real(kind=dp), intent(in) :: eps
logical, intent(in) :: retain_sparsity
logical, intent(in) :: always_checksum

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_8), DIMENSION(:, :), POINTER :: block
logical, intent(in), optional :: transposed
logical, intent(out), optional :: existed

private subroutine dbcsr_iterator_next_2d_block_d(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
real(kind=real_8), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: transposed
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_2d_block_notrans_d(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
real(kind=real_8), DIMENSION(:, :), POINTER :: block
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_1d_block_d(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
real(kind=real_8), DIMENSION(:), POINTER :: block
logical, intent(out) :: transposed
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_1d_block_notrans_d(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
real(kind=real_8), DIMENSION(:), POINTER :: block
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_8), intent(in), DIMENSION(:, :) :: block
logical, intent(in), optional :: summation
real(kind=real_8), intent(in), optional :: scale

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_8), intent(in), DIMENSION(:) :: block
logical, intent(in), optional :: summation
real(kind=real_8), intent(in), optional :: scale

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_8), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: tr
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_8), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_8), DIMENSION(:), POINTER :: block
logical, intent(out) :: tr
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_8), DIMENSION(:), POINTER :: block
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

private subroutine dbcsr_trace_d(matrix_a, trace)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
real(kind=real_8), intent(out) :: trace

private subroutine dbcsr_dot_d(matrix_a, matrix_b, result)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
real(kind=real_8), intent(inout) :: result

private subroutine dbcsr_multiply_d(transa, transb, alpha, matrix_a, matrix_b, beta, matrix_c, first_row, last_row, first_column, last_column, first_k, last_k, retain_sparsity, filter_eps, flop)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: transa
character(len=1), intent(in) :: transb
real(kind=real_8), intent(in) :: alpha
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
real(kind=real_8), intent(in) :: beta
type(dbcsr_type), intent(inout) :: matrix_c
integer, intent(in), optional :: first_row
integer, intent(in), optional :: last_row
integer, intent(in), optional :: first_column
integer, intent(in), optional :: last_column
integer, intent(in), optional :: first_k
integer, intent(in), optional :: last_k
logical, intent(in), optional :: retain_sparsity
real(kind=real_8), intent(in), optional :: filter_eps
integer(kind=int_8), intent(out), optional :: flop

private subroutine dbcsr_scale_by_vector_d(matrix_a, alpha, side)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
real(kind=real_8), intent(in), DIMENSION(:), TARGET :: alpha
character(len=*), intent(in) :: side

private subroutine dbcsr_scale_d(matrix_a, alpha_scalar, last_column)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
real(kind=real_8), intent(in) :: alpha_scalar
integer, intent(in), optional :: last_column

private subroutine dbcsr_set_d(matrix, alpha)

Arguments

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

private subroutine dbcsr_add_d(matrix_a, matrix_b, alpha_scalar, beta_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
real(kind=real_8), intent(in) :: alpha_scalar
real(kind=real_8), intent(in) :: beta_scalar

private subroutine dbcsr_add_on_diag_d(matrix, alpha_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
real(kind=real_8), intent(in) :: alpha_scalar

private subroutine dbcsr_set_diag_d(matrix, diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
real(kind=real_8), intent(in), DIMENSION(:) :: diag

private subroutine dbcsr_get_diag_d(matrix, diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
real(kind=real_8), intent(out), DIMENSION(:) :: diag

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_4), DIMENSION(:, :), POINTER :: block
logical, intent(in), optional :: transposed
logical, intent(out), optional :: existed

private subroutine dbcsr_iterator_next_2d_block_s(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
real(kind=real_4), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: transposed
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_2d_block_notrans_s(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
real(kind=real_4), DIMENSION(:, :), POINTER :: block
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_1d_block_s(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
real(kind=real_4), DIMENSION(:), POINTER :: block
logical, intent(out) :: transposed
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_1d_block_notrans_s(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
real(kind=real_4), DIMENSION(:), POINTER :: block
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_4), intent(in), DIMENSION(:, :) :: block
logical, intent(in), optional :: summation
real(kind=real_4), intent(in), optional :: scale

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_4), intent(in), DIMENSION(:) :: block
logical, intent(in), optional :: summation
real(kind=real_4), intent(in), optional :: scale

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_4), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: tr
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_4), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_4), DIMENSION(:), POINTER :: block
logical, intent(out) :: tr
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
real(kind=real_4), DIMENSION(:), POINTER :: block
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

private subroutine dbcsr_trace_s(matrix_a, trace)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
real(kind=real_4), intent(out) :: trace

private subroutine dbcsr_dot_s(matrix_a, matrix_b, result)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
real(kind=real_4), intent(inout) :: result

private subroutine dbcsr_multiply_s(transa, transb, alpha, matrix_a, matrix_b, beta, matrix_c, first_row, last_row, first_column, last_column, first_k, last_k, retain_sparsity, filter_eps, flop)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: transa
character(len=1), intent(in) :: transb
real(kind=real_4), intent(in) :: alpha
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
real(kind=real_4), intent(in) :: beta
type(dbcsr_type), intent(inout) :: matrix_c
integer, intent(in), optional :: first_row
integer, intent(in), optional :: last_row
integer, intent(in), optional :: first_column
integer, intent(in), optional :: last_column
integer, intent(in), optional :: first_k
integer, intent(in), optional :: last_k
logical, intent(in), optional :: retain_sparsity
real(kind=real_8), intent(in), optional :: filter_eps
integer(kind=int_8), intent(out), optional :: flop

private subroutine dbcsr_scale_by_vector_s(matrix_a, alpha, side)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
real(kind=real_4), intent(in), DIMENSION(:), TARGET :: alpha
character(len=*), intent(in) :: side

private subroutine dbcsr_scale_s(matrix_a, alpha_scalar, last_column)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
real(kind=real_4), intent(in) :: alpha_scalar
integer, intent(in), optional :: last_column

private subroutine dbcsr_set_s(matrix, alpha)

Arguments

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

private subroutine dbcsr_add_s(matrix_a, matrix_b, alpha_scalar, beta_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
real(kind=real_4), intent(in) :: alpha_scalar
real(kind=real_4), intent(in) :: beta_scalar

private subroutine dbcsr_add_on_diag_s(matrix, alpha_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
real(kind=real_4), intent(in) :: alpha_scalar

private subroutine dbcsr_set_diag_s(matrix, diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
real(kind=real_4), intent(in), DIMENSION(:) :: diag

private subroutine dbcsr_get_diag_s(matrix, diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
real(kind=real_4), intent(out), DIMENSION(:) :: diag

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_8), DIMENSION(:, :), POINTER :: block
logical, intent(in), optional :: transposed
logical, intent(out), optional :: existed

private subroutine dbcsr_iterator_next_2d_block_z(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
complex(kind=real_8), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: transposed
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_2d_block_notrans_z(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
complex(kind=real_8), DIMENSION(:, :), POINTER :: block
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_1d_block_z(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
complex(kind=real_8), DIMENSION(:), POINTER :: block
logical, intent(out) :: transposed
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_1d_block_notrans_z(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
complex(kind=real_8), DIMENSION(:), POINTER :: block
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_8), intent(in), DIMENSION(:, :) :: block
logical, intent(in), optional :: summation
complex(kind=real_8), intent(in), optional :: scale

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_8), intent(in), DIMENSION(:) :: block
logical, intent(in), optional :: summation
complex(kind=real_8), intent(in), optional :: scale

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_8), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: tr
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_8), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_8), DIMENSION(:), POINTER :: block
logical, intent(out) :: tr
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_8), DIMENSION(:), POINTER :: block
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

private subroutine dbcsr_trace_z(matrix_a, trace)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
complex(kind=real_8), intent(out) :: trace

private subroutine dbcsr_dot_z(matrix_a, matrix_b, result)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
complex(kind=real_8), intent(inout) :: result

private subroutine dbcsr_multiply_z(transa, transb, alpha, matrix_a, matrix_b, beta, matrix_c, first_row, last_row, first_column, last_column, first_k, last_k, retain_sparsity, filter_eps, flop)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: transa
character(len=1), intent(in) :: transb
complex(kind=real_8), intent(in) :: alpha
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
complex(kind=real_8), intent(in) :: beta
type(dbcsr_type), intent(inout) :: matrix_c
integer, intent(in), optional :: first_row
integer, intent(in), optional :: last_row
integer, intent(in), optional :: first_column
integer, intent(in), optional :: last_column
integer, intent(in), optional :: first_k
integer, intent(in), optional :: last_k
logical, intent(in), optional :: retain_sparsity
real(kind=real_8), intent(in), optional :: filter_eps
integer(kind=int_8), intent(out), optional :: flop

private subroutine dbcsr_scale_by_vector_z(matrix_a, alpha, side)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
complex(kind=real_8), intent(in), DIMENSION(:), TARGET :: alpha
character(len=*), intent(in) :: side

private subroutine dbcsr_scale_z(matrix_a, alpha_scalar, last_column)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
complex(kind=real_8), intent(in) :: alpha_scalar
integer, intent(in), optional :: last_column

private subroutine dbcsr_set_z(matrix, alpha)

Arguments

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

private subroutine dbcsr_add_z(matrix_a, matrix_b, alpha_scalar, beta_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
complex(kind=real_8), intent(in) :: alpha_scalar
complex(kind=real_8), intent(in) :: beta_scalar

private subroutine dbcsr_add_on_diag_z(matrix, alpha_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
complex(kind=real_8), intent(in) :: alpha_scalar

private subroutine dbcsr_set_diag_z(matrix, diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
complex(kind=real_8), intent(in), DIMENSION(:) :: diag

private subroutine dbcsr_get_diag_z(matrix, diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
complex(kind=real_8), intent(out), DIMENSION(:) :: diag

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_4), DIMENSION(:, :), POINTER :: block
logical, intent(in), optional :: transposed
logical, intent(out), optional :: existed

private subroutine dbcsr_iterator_next_2d_block_c(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
complex(kind=real_4), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: transposed
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_2d_block_notrans_c(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
complex(kind=real_4), DIMENSION(:, :), POINTER :: block
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_1d_block_c(iterator, row, column, block, transposed, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
complex(kind=real_4), DIMENSION(:), POINTER :: block
logical, intent(out) :: transposed
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

private subroutine dbcsr_iterator_next_1d_block_notrans_c(iterator, row, column, block, block_number, row_size, col_size, row_offset, col_offset)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_iterator_type), intent(inout) :: iterator
integer, intent(out) :: row
integer, intent(out) :: column
complex(kind=real_4), DIMENSION(:), POINTER :: block
integer, intent(out), optional :: block_number
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size
integer, intent(out), optional :: row_offset
integer, intent(out), optional :: col_offset

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_4), intent(in), DIMENSION(:, :) :: block
logical, intent(in), optional :: summation
complex(kind=real_4), intent(in), optional :: scale

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_4), intent(in), DIMENSION(:) :: block
logical, intent(in), optional :: summation
complex(kind=real_4), intent(in), optional :: scale

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_4), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: tr
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_4), DIMENSION(:, :), POINTER :: block
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_4), DIMENSION(:), POINTER :: block
logical, intent(out) :: tr
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

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

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
integer, intent(in) :: row
integer, intent(in) :: col
complex(kind=real_4), DIMENSION(:), POINTER :: block
logical, intent(out) :: found
integer, intent(out), optional :: row_size
integer, intent(out), optional :: col_size

private subroutine dbcsr_trace_c(matrix_a, trace)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
complex(kind=real_4), intent(out) :: trace

private subroutine dbcsr_dot_c(matrix_a, matrix_b, result)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
complex(kind=real_4), intent(inout) :: result

private subroutine dbcsr_multiply_c(transa, transb, alpha, matrix_a, matrix_b, beta, matrix_c, first_row, last_row, first_column, last_column, first_k, last_k, retain_sparsity, filter_eps, flop)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: transa
character(len=1), intent(in) :: transb
complex(kind=real_4), intent(in) :: alpha
type(dbcsr_type), intent(in) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
complex(kind=real_4), intent(in) :: beta
type(dbcsr_type), intent(inout) :: matrix_c
integer, intent(in), optional :: first_row
integer, intent(in), optional :: last_row
integer, intent(in), optional :: first_column
integer, intent(in), optional :: last_column
integer, intent(in), optional :: first_k
integer, intent(in), optional :: last_k
logical, intent(in), optional :: retain_sparsity
real(kind=real_8), intent(in), optional :: filter_eps
integer(kind=int_8), intent(out), optional :: flop

private subroutine dbcsr_scale_by_vector_c(matrix_a, alpha, side)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
complex(kind=real_4), intent(in), DIMENSION(:), TARGET :: alpha
character(len=*), intent(in) :: side

private subroutine dbcsr_scale_c(matrix_a, alpha_scalar, last_column)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
complex(kind=real_4), intent(in) :: alpha_scalar
integer, intent(in), optional :: last_column

private subroutine dbcsr_set_c(matrix, alpha)

Arguments

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

private subroutine dbcsr_add_c(matrix_a, matrix_b, alpha_scalar, beta_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix_a
type(dbcsr_type), intent(in) :: matrix_b
complex(kind=real_4), intent(in) :: alpha_scalar
complex(kind=real_4), intent(in) :: beta_scalar

private subroutine dbcsr_add_on_diag_c(matrix, alpha_scalar)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
complex(kind=real_4), intent(in) :: alpha_scalar

private subroutine dbcsr_set_diag_c(matrix, diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(inout) :: matrix
complex(kind=real_4), intent(in), DIMENSION(:) :: diag

private subroutine dbcsr_get_diag_c(matrix, diag)

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in) :: matrix
complex(kind=real_4), intent(out), DIMENSION(:) :: diag