dbcsr_block_operations Module

Routines for basic block transformations.



Variables

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

Interfaces

public interface dbcsr_block_transpose

  • private subroutine block_transpose_inplace_s(extent, rows, columns)

    In-place block transpose.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(inout), DIMENSION(rows*columns) :: extent

    Matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_inplace_d(extent, rows, columns)

    In-place block transpose.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(inout), DIMENSION(rows*columns) :: extent

    Matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_inplace_c(extent, rows, columns)

    In-place block transpose.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(inout), DIMENSION(rows*columns) :: extent

    Matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_inplace_z(extent, rows, columns)

    In-place block transpose.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(inout), DIMENSION(rows*columns) :: extent

    Matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_d(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(:), TARGET :: extent_out

    output matrix in the form of a 1-d array

    real(kind=real_8), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_s(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(:), TARGET :: extent_out

    output matrix in the form of a 1-d array

    real(kind=real_4), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_z(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(:), TARGET :: extent_out

    output matrix in the form of a 1-d array

    complex(kind=real_8), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_c(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(:), TARGET :: extent_out

    output matrix in the form of a 1-d array

    complex(kind=real_4), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_2d1d_d(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(columns, rows), TARGET :: extent_out

    output matrix in the form of a 2-d array

    real(kind=real_8), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_2d1d_s(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(columns, rows), TARGET :: extent_out

    output matrix in the form of a 2-d array

    real(kind=real_4), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_2d1d_z(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(columns, rows), TARGET :: extent_out

    output matrix in the form of a 2-d array

    complex(kind=real_8), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_2d1d_c(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(columns, rows), TARGET :: extent_out

    output matrix in the form of a 2-d array

    complex(kind=real_4), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_1d2d_d(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(:), TARGET :: extent_out

    output matrix in the form of a 1-d array

    real(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_1d2d_s(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(:), TARGET :: extent_out

    output matrix in the form of a 1-d array

    real(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_1d2d_z(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(:), TARGET :: extent_out

    output matrix in the form of a 1-d array

    complex(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private subroutine block_transpose_copy_1d2d_c(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(:), TARGET :: extent_out

    output matrix in the form of a 1-d array

    complex(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • public subroutine dbcsr_block_transpose_aa(dst, src, row_size, col_size, lb, source_lb, scale, lb2, source_lb2)

    Copy data from one data area to another. There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    type(dbcsr_data_obj), intent(in) :: src

    source data area

    integer, intent(in) :: row_size

    row size of existing block column size of existing block

    integer, intent(in) :: col_size

    row size of existing block column size of existing block

    integer, intent(in), optional :: lb

    lower bound for destination (and source if not given explicitly) lower bound of source

    integer, intent(in), optional :: source_lb

    lower bound for destination (and source if not given explicitly) lower bound of source

    type(dbcsr_scalar_type), intent(in), optional :: scale

    scale data

    integer, intent(in), optional :: lb2

    lower bound of 2nd dimension for target lower bound of 2nd dimension for source

    integer, intent(in), optional :: source_lb2

    lower bound of 2nd dimension for target lower bound of 2nd dimension for source

  • private subroutine dbcsr_block_transpose_a(area, row_size, col_size)

    In-place transpose of encapsulated data There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: area

    encapsulated data area

    integer, intent(in) :: row_size

    number of rows in existing block number of columns in existing block

    integer, intent(in) :: col_size

    number of rows in existing block number of columns in existing block

private interface dbcsr_block_copy

  • private pure subroutine block_copy_2d1d_s(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(rows, columns) :: extent_out

    output matrix in the form of a 2-d array

    real(kind=real_4), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_2d1d_d(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(rows, columns) :: extent_out

    output matrix in the form of a 2-d array

    real(kind=real_8), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_2d1d_c(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(rows, columns) :: extent_out

    output matrix in the form of a 2-d array

    complex(kind=real_4), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_2d1d_z(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(rows, columns) :: extent_out

    output matrix in the form of a 2-d array

    complex(kind=real_8), intent(in), DIMENSION(:) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_1d2d_s(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(:) :: extent_out

    output matrix in the form of a 1-d array

    real(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_1d2d_d(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(:) :: extent_out

    output matrix in the form of a 1-d array

    real(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_1d2d_c(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(:) :: extent_out

    output matrix in the form of a 1-d array

    complex(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_1d2d_z(extent_out, extent_in, rows, columns)

    Copy and transpose block.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(:) :: extent_out

    output matrix in the form of a 1-d array

    complex(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_1d1d_s(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(rows*columns) :: extent_out

    output matrix in the form of a 1-d array

    real(kind=real_4), intent(in), DIMENSION(rows*columns) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_1d1d_d(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(rows*columns) :: extent_out

    output matrix in the form of a 1-d array

    real(kind=real_8), intent(in), DIMENSION(rows*columns) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_1d1d_c(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(rows*columns) :: extent_out

    output matrix in the form of a 1-d array

    complex(kind=real_4), intent(in), DIMENSION(rows*columns) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_1d1d_z(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(rows*columns) :: extent_out

    output matrix in the form of a 1-d array

    complex(kind=real_8), intent(in), DIMENSION(rows*columns) :: extent_in

    input matrix in the form of a 1-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_2d2d_s(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(rows, columns) :: extent_out

    output matrix in the form of a 2-d array

    real(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_2d2d_d(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(rows, columns) :: extent_out

    output matrix in the form of a 2-d array

    real(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_2d2d_c(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(rows, columns) :: extent_out

    output matrix in the form of a 2-d array

    complex(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

  • private pure subroutine block_copy_2d2d_z(extent_out, extent_in, rows, columns)

    Copy a block

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(rows, columns) :: extent_out

    output matrix in the form of a 2-d array

    complex(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

    input matrix in the form of a 2-d array

    integer, intent(in) :: rows

    input matrix size input matrix size

    integer, intent(in) :: columns

    input matrix size input matrix size

public interface dbcsr_data_clear

  • private subroutine dbcsr_data_clear_nt(area, lb, ub, value, lb2, ub2, tr)

    Clears a data area, possibly transposed.

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: area
    integer, intent(in), optional :: lb
    integer, intent(in), optional :: ub
    type(dbcsr_scalar_type), intent(in), optional :: value
    integer, intent(in), optional :: lb2
    integer, intent(in), optional :: ub2
    logical, intent(in) :: tr
  • private subroutine dbcsr_data_clear0(area, lb, ub, value, lb2, ub2)

    Clears a data area

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: area

    area with encapsulated data

    integer, intent(in), optional :: lb

    lower bound for clearing lower bound for clearing

    integer, intent(in), optional :: ub

    lower bound for clearing lower bound for clearing

    type(dbcsr_scalar_type), intent(in), optional :: value

    value to use for clearing

    integer, intent(in), optional :: lb2

    upper bound for clearing upper bound for clearing

    integer, intent(in), optional :: ub2

    upper bound for clearing upper bound for clearing

public interface dbcsr_data_set

  • private subroutine dbcsr_data_copy_aa(dst, lb, data_size, src, source_lb, scale, lb2, data_size2, source_lb2)

    Copy data from one data area to another. There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

    type(dbcsr_data_obj), intent(in) :: src

    source data area

    integer, intent(in), optional :: source_lb

    lower bound of source

    type(dbcsr_scalar_type), intent(in), optional :: scale

    scale by this factor

    integer, intent(in), optional :: lb2

    2nd dimension lower bound 2nd dimension data size 2nd dimension lower bound for source

    integer, intent(in), optional :: data_size2

    2nd dimension lower bound 2nd dimension data size 2nd dimension lower bound for source

    integer, intent(in), optional :: source_lb2

    2nd dimension lower bound 2nd dimension data size 2nd dimension lower bound for source

  • private subroutine dbcsr_data_set_as(dst, lb, data_size, src, source_lb)

    Copy data from a double real array to a data area There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

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

    source data array

    integer, intent(in), optional :: source_lb

    lower bound of source

  • private subroutine dbcsr_data_set_ad(dst, lb, data_size, src, source_lb)

    Copy data from a double real array to a data area There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

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

    source data array

    integer, intent(in), optional :: source_lb

    lower bound of source

  • private subroutine dbcsr_data_set_ac(dst, lb, data_size, src, source_lb)

    Copy data from a double real array to a data area There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

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

    source data array

    integer, intent(in), optional :: source_lb

    lower bound of source

  • private subroutine dbcsr_data_set_az(dst, lb, data_size, src, source_lb)

    Copy data from a double real array to a data area There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

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

    source data array

    integer, intent(in), optional :: source_lb

    lower bound of source

public interface dbcsr_data_copy

  • private subroutine dbcsr_data_copy_aa2(dst, dst_lb, dst_sizes, src, src_lb, src_sizes)

    Copy data from one data area to another, the most basic form. There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

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

    lower bounds for destination sizes for destination

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

    lower bounds for destination sizes for destination

    type(dbcsr_data_obj), intent(in) :: src

    source data area

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

    lower bounds for source sizes for source

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

    lower bounds for source sizes for source

  • private subroutine dbcsr_data_set_as(dst, lb, data_size, src, source_lb)

    Copy data from a double real array to a data area There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

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

    source data array

    integer, intent(in), optional :: source_lb

    lower bound of source

  • private subroutine dbcsr_data_set_ad(dst, lb, data_size, src, source_lb)

    Copy data from a double real array to a data area There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

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

    source data array

    integer, intent(in), optional :: source_lb

    lower bound of source

  • private subroutine dbcsr_data_set_ac(dst, lb, data_size, src, source_lb)

    Copy data from a double real array to a data area There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

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

    source data array

    integer, intent(in), optional :: source_lb

    lower bound of source

  • private subroutine dbcsr_data_set_az(dst, lb, data_size, src, source_lb)

    Copy data from a double real array to a data area There are no checks done for correctness!

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: dst

    destination data area

    integer, intent(in) :: lb

    lower bound for destination (and source if not given explicitly) number of elements to copy

    integer, intent(in) :: data_size

    lower bound for destination (and source if not given explicitly) number of elements to copy

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

    source data array

    integer, intent(in), optional :: source_lb

    lower bound of source

public interface block_add

  • private subroutine block_add_anytype(block_a, block_b, len)

    Adds two blocks

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: block_a

    Block to add to

    type(dbcsr_data_obj), intent(in) :: block_b

    Block to add to block_a

    integer, intent(in), optional :: len
  • private subroutine block_add_anytype_bounds(block_a, block_b, lb_a, lb_b, len)

    Adds two blocks

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_data_obj), intent(inout) :: block_a

    Block to add to

    type(dbcsr_data_obj), intent(in) :: block_b

    Block to add to block_a

    integer, intent(in) :: lb_a
    integer, intent(in) :: lb_b
    integer, intent(in) :: len
  • private pure subroutine block_add_s(block_a, block_b, len)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(inout), DIMENSION(len) :: block_a
    real(kind=real_4), intent(in), DIMENSION(len) :: block_b
    integer, intent(in) :: len
  • private pure subroutine block_add_d(block_a, block_b, len)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(inout), DIMENSION(len) :: block_a
    real(kind=real_8), intent(in), DIMENSION(len) :: block_b
    integer, intent(in) :: len
  • private pure subroutine block_add_c(block_a, block_b, len)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(inout), DIMENSION(len) :: block_a
    complex(kind=real_4), intent(in), DIMENSION(len) :: block_b
    integer, intent(in) :: len
  • private pure subroutine block_add_z(block_a, block_b, len)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(inout), DIMENSION(len) :: block_a
    complex(kind=real_8), intent(in), DIMENSION(len) :: block_b
    integer, intent(in) :: len

Subroutines

public subroutine dbcsr_block_transpose_aa(dst, src, row_size, col_size, lb, source_lb, scale, lb2, source_lb2)

Copy data from one data area to another. There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

destination data area

type(dbcsr_data_obj), intent(in) :: src

source data area

integer, intent(in) :: row_size

row size of existing block column size of existing block

integer, intent(in) :: col_size

row size of existing block column size of existing block

integer, intent(in), optional :: lb

lower bound for destination (and source if not given explicitly) lower bound of source

integer, intent(in), optional :: source_lb

lower bound for destination (and source if not given explicitly) lower bound of source

type(dbcsr_scalar_type), intent(in), optional :: scale

scale data

integer, intent(in), optional :: lb2

lower bound of 2nd dimension for target lower bound of 2nd dimension for source

integer, intent(in), optional :: source_lb2

lower bound of 2nd dimension for target lower bound of 2nd dimension for source

public subroutine dbcsr_block_copy_aa(dst, src, row_size, col_size, lb, source_lb, scale)

Copy data from one data area to another. There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

destination data area

type(dbcsr_data_obj), intent(in) :: src

source data area

integer, intent(in) :: row_size

row size of existing block column size of existing block

integer, intent(in) :: col_size

row size of existing block column size of existing block

integer, intent(in), optional :: lb

lower bound for destination (and source if not given explicitly) lower bound of source

integer, intent(in), optional :: source_lb

lower bound for destination (and source if not given explicitly) lower bound of source

type(dbcsr_scalar_type), intent(in), optional :: scale

scale data

public subroutine dbcsr_block_scale(dst, scale, row_size, col_size, lb, lb2)

Scale a data area. There are no checks done for correctness!

Read more…

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst
type(dbcsr_scalar_type), intent(in) :: scale

scale data

integer, intent(in) :: row_size

row size of existing block column size of existing block

integer, intent(in) :: col_size

row size of existing block column size of existing block

integer, intent(in), optional :: lb

lower bound for destination (and source if not given explicitly) lower bound of 2nd dimension for target

integer, intent(in), optional :: lb2

lower bound for destination (and source if not given explicitly) lower bound of 2nd dimension for target

public subroutine dbcsr_block_real_neg(dst, row_size, col_size, lb, lb2)

Negates the real part of a block There are no checks done for correctness!

Read more…

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst
integer, intent(in) :: row_size

row size of existing block column size of existing block

integer, intent(in) :: col_size

row size of existing block column size of existing block

integer, intent(in), optional :: lb

lower bound for destination (and source if not given explicitly) lower bound of 2nd dimension for target

integer, intent(in), optional :: lb2

lower bound for destination (and source if not given explicitly) lower bound of 2nd dimension for target

public subroutine dbcsr_block_conjg(dst, row_size, col_size, lb, lb2)

Conjugate a data area. There are no checks done for correctness!

Read more…

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst
integer, intent(in) :: row_size

row size of existing block column size of existing block

integer, intent(in) :: col_size

row size of existing block column size of existing block

integer, intent(in), optional :: lb

lower bound for destination (and source if not given explicitly) lower bound of 2nd dimension for target

integer, intent(in), optional :: lb2

lower bound for destination (and source if not given explicitly) lower bound of 2nd dimension for target

private subroutine dbcsr_block_transpose_a(area, row_size, col_size)

In-place transpose of encapsulated data There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: area

encapsulated data area

integer, intent(in) :: row_size

number of rows in existing block number of columns in existing block

integer, intent(in) :: col_size

number of rows in existing block number of columns in existing block

private subroutine dbcsr_data_copy_aa(dst, lb, data_size, src, source_lb, scale, lb2, data_size2, source_lb2)

Copy data from one data area to another. There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

destination data area

integer, intent(in) :: lb

lower bound for destination (and source if not given explicitly) number of elements to copy

integer, intent(in) :: data_size

lower bound for destination (and source if not given explicitly) number of elements to copy

type(dbcsr_data_obj), intent(in) :: src

source data area

integer, intent(in), optional :: source_lb

lower bound of source

type(dbcsr_scalar_type), intent(in), optional :: scale

scale by this factor

integer, intent(in), optional :: lb2

2nd dimension lower bound 2nd dimension data size 2nd dimension lower bound for source

integer, intent(in), optional :: data_size2

2nd dimension lower bound 2nd dimension data size 2nd dimension lower bound for source

integer, intent(in), optional :: source_lb2

2nd dimension lower bound 2nd dimension data size 2nd dimension lower bound for source

private subroutine dbcsr_data_copy_aa2(dst, dst_lb, dst_sizes, src, src_lb, src_sizes)

Copy data from one data area to another, the most basic form. There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

destination data area

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

lower bounds for destination sizes for destination

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

lower bounds for destination sizes for destination

type(dbcsr_data_obj), intent(in) :: src

source data area

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

lower bounds for source sizes for source

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

lower bounds for source sizes for source

private subroutine dbcsr_data_clear_nt(area, lb, ub, value, lb2, ub2, tr)

Clears a data area, possibly transposed.

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: area
integer, intent(in), optional :: lb
integer, intent(in), optional :: ub
type(dbcsr_scalar_type), intent(in), optional :: value
integer, intent(in), optional :: lb2
integer, intent(in), optional :: ub2
logical, intent(in) :: tr

private subroutine dbcsr_data_clear0(area, lb, ub, value, lb2, ub2)

Clears a data area

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: area

area with encapsulated data

integer, intent(in), optional :: lb

lower bound for clearing lower bound for clearing

integer, intent(in), optional :: ub

lower bound for clearing lower bound for clearing

type(dbcsr_scalar_type), intent(in), optional :: value

value to use for clearing

integer, intent(in), optional :: lb2

upper bound for clearing upper bound for clearing

integer, intent(in), optional :: ub2

upper bound for clearing upper bound for clearing

public subroutine dbcsr_block_partial_copy(dst, dst_rs, dst_cs, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset, src_offset)

Copies a block subset

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

target data area

integer, intent(in) :: dst_rs

target block row size (logical) target block column size (logical)

integer, intent(in) :: dst_cs

target block row size (logical) target block column size (logical)

logical :: dst_tr

whether target block is transposed

type(dbcsr_data_obj), intent(in) :: src

source data area

integer, intent(in) :: src_rs

source block row size (logical) source block column size (logical)

integer, intent(in) :: src_cs

source block row size (logical) source block column size (logical)

logical :: src_tr

whether source block is transposed

integer, intent(in) :: dst_r_lb

first row in target first column in target first_row in source first column in target number of rows to copy number of columns to copy

integer, intent(in) :: dst_c_lb

first row in target first column in target first_row in source first column in target number of rows to copy number of columns to copy

integer, intent(in) :: src_r_lb

first row in target first column in target first_row in source first column in target number of rows to copy number of columns to copy

integer, intent(in) :: src_c_lb

first row in target first column in target first_row in source first column in target number of rows to copy number of columns to copy

integer, intent(in) :: nrow

first row in target first column in target first_row in source first column in target number of rows to copy number of columns to copy

integer, intent(in) :: ncol

first row in target first column in target first_row in source first column in target number of rows to copy number of columns to copy

integer, intent(in), optional :: dst_offset

offset in target offset in source

integer, intent(in), optional :: src_offset

offset in target offset in source

private subroutine block_add_anytype(block_a, block_b, len)

Adds two blocks

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: block_a

Block to add to

type(dbcsr_data_obj), intent(in) :: block_b

Block to add to block_a

integer, intent(in), optional :: len

private subroutine block_add_anytype_bounds(block_a, block_b, lb_a, lb_b, len)

Adds two blocks

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: block_a

Block to add to

type(dbcsr_data_obj), intent(in) :: block_b

Block to add to block_a

integer, intent(in) :: lb_a
integer, intent(in) :: lb_b
integer, intent(in) :: len

private subroutine block_partial_copy_d(dst, dst_rs, dst_cs, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset, src_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(inout), DIMENSION(:) :: dst
integer, intent(in) :: dst_rs
integer, intent(in) :: dst_cs
logical, intent(in) :: dst_tr
real(kind=real_8), intent(in), DIMENSION(:) :: src
integer, intent(in) :: src_rs
integer, intent(in) :: src_cs
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: dst_offset
integer, intent(in) :: src_offset

private subroutine block_partial_copy_1d2d_d(dst, dst_rs, dst_cs, dst_tr, src, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(inout), DIMENSION(:) :: dst
integer, intent(in) :: dst_rs
integer, intent(in) :: dst_cs
logical, intent(in) :: dst_tr
real(kind=real_8), intent(in), DIMENSION(:, :) :: src
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: dst_offset

private subroutine block_partial_copy_2d1d_d(dst, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, src_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(inout), DIMENSION(:, :) :: dst
logical, intent(in) :: dst_tr
real(kind=real_8), intent(in), DIMENSION(:) :: src
integer, intent(in) :: src_rs
integer, intent(in) :: src_cs
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: src_offset

private subroutine block_partial_copy_2d2d_d(dst, dst_tr, src, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(inout), DIMENSION(:, :) :: dst
logical, intent(in) :: dst_tr
real(kind=real_8), intent(in), DIMENSION(:, :) :: src
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol

public pure subroutine block_copy_d(extent_out, extent_in, n, out_fe, in_fe)

Copy a block

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(*) :: extent_out

output data

real(kind=real_8), intent(in), DIMENSION(*) :: extent_in

input data

integer, intent(in) :: n

number of elements to copy first element of output first element of input

integer, intent(in) :: out_fe

number of elements to copy first element of output first element of input

integer, intent(in) :: in_fe

number of elements to copy first element of output first element of input

private subroutine block_transpose_copy_d(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(:), TARGET :: extent_out

output matrix in the form of a 1-d array

real(kind=real_8), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_2d1d_d(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(rows, columns) :: extent_out

output matrix in the form of a 2-d array

real(kind=real_8), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_1d1d_d(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(rows*columns) :: extent_out

output matrix in the form of a 1-d array

real(kind=real_8), intent(in), DIMENSION(rows*columns) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_2d2d_d(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(rows, columns) :: extent_out

output matrix in the form of a 2-d array

real(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_copy_2d1d_d(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(columns, rows), TARGET :: extent_out

output matrix in the form of a 2-d array

real(kind=real_8), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_1d2d_d(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(:) :: extent_out

output matrix in the form of a 1-d array

real(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_copy_1d2d_d(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(:), TARGET :: extent_out

output matrix in the form of a 1-d array

real(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_inplace_d(extent, rows, columns)

In-place block transpose.

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(inout), DIMENSION(rows*columns) :: extent

Matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine dbcsr_data_set_ad(dst, lb, data_size, src, source_lb)

Copy data from a double real array to a data area There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

destination data area

integer, intent(in) :: lb

lower bound for destination (and source if not given explicitly) number of elements to copy

integer, intent(in) :: data_size

lower bound for destination (and source if not given explicitly) number of elements to copy

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

source data array

integer, intent(in), optional :: source_lb

lower bound of source

private pure subroutine block_add_d(block_a, block_b, len)

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(inout), DIMENSION(len) :: block_a
real(kind=real_8), intent(in), DIMENSION(len) :: block_b
integer, intent(in) :: len

private subroutine block_partial_copy_s(dst, dst_rs, dst_cs, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset, src_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(inout), DIMENSION(:) :: dst
integer, intent(in) :: dst_rs
integer, intent(in) :: dst_cs
logical, intent(in) :: dst_tr
real(kind=real_4), intent(in), DIMENSION(:) :: src
integer, intent(in) :: src_rs
integer, intent(in) :: src_cs
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: dst_offset
integer, intent(in) :: src_offset

private subroutine block_partial_copy_1d2d_s(dst, dst_rs, dst_cs, dst_tr, src, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(inout), DIMENSION(:) :: dst
integer, intent(in) :: dst_rs
integer, intent(in) :: dst_cs
logical, intent(in) :: dst_tr
real(kind=real_4), intent(in), DIMENSION(:, :) :: src
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: dst_offset

private subroutine block_partial_copy_2d1d_s(dst, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, src_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(inout), DIMENSION(:, :) :: dst
logical, intent(in) :: dst_tr
real(kind=real_4), intent(in), DIMENSION(:) :: src
integer, intent(in) :: src_rs
integer, intent(in) :: src_cs
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: src_offset

private subroutine block_partial_copy_2d2d_s(dst, dst_tr, src, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(inout), DIMENSION(:, :) :: dst
logical, intent(in) :: dst_tr
real(kind=real_4), intent(in), DIMENSION(:, :) :: src
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol

public pure subroutine block_copy_s(extent_out, extent_in, n, out_fe, in_fe)

Copy a block

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(*) :: extent_out

output data

real(kind=real_4), intent(in), DIMENSION(*) :: extent_in

input data

integer, intent(in) :: n

number of elements to copy first element of output first element of input

integer, intent(in) :: out_fe

number of elements to copy first element of output first element of input

integer, intent(in) :: in_fe

number of elements to copy first element of output first element of input

private subroutine block_transpose_copy_s(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(:), TARGET :: extent_out

output matrix in the form of a 1-d array

real(kind=real_4), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_2d1d_s(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(rows, columns) :: extent_out

output matrix in the form of a 2-d array

real(kind=real_4), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_1d1d_s(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(rows*columns) :: extent_out

output matrix in the form of a 1-d array

real(kind=real_4), intent(in), DIMENSION(rows*columns) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_2d2d_s(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(rows, columns) :: extent_out

output matrix in the form of a 2-d array

real(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_copy_2d1d_s(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(columns, rows), TARGET :: extent_out

output matrix in the form of a 2-d array

real(kind=real_4), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_1d2d_s(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(:) :: extent_out

output matrix in the form of a 1-d array

real(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_copy_1d2d_s(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(:), TARGET :: extent_out

output matrix in the form of a 1-d array

real(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_inplace_s(extent, rows, columns)

In-place block transpose.

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(inout), DIMENSION(rows*columns) :: extent

Matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine dbcsr_data_set_as(dst, lb, data_size, src, source_lb)

Copy data from a double real array to a data area There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

destination data area

integer, intent(in) :: lb

lower bound for destination (and source if not given explicitly) number of elements to copy

integer, intent(in) :: data_size

lower bound for destination (and source if not given explicitly) number of elements to copy

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

source data array

integer, intent(in), optional :: source_lb

lower bound of source

private pure subroutine block_add_s(block_a, block_b, len)

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(inout), DIMENSION(len) :: block_a
real(kind=real_4), intent(in), DIMENSION(len) :: block_b
integer, intent(in) :: len

private subroutine block_partial_copy_z(dst, dst_rs, dst_cs, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset, src_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(inout), DIMENSION(:) :: dst
integer, intent(in) :: dst_rs
integer, intent(in) :: dst_cs
logical, intent(in) :: dst_tr
complex(kind=real_8), intent(in), DIMENSION(:) :: src
integer, intent(in) :: src_rs
integer, intent(in) :: src_cs
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: dst_offset
integer, intent(in) :: src_offset

private subroutine block_partial_copy_1d2d_z(dst, dst_rs, dst_cs, dst_tr, src, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(inout), DIMENSION(:) :: dst
integer, intent(in) :: dst_rs
integer, intent(in) :: dst_cs
logical, intent(in) :: dst_tr
complex(kind=real_8), intent(in), DIMENSION(:, :) :: src
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: dst_offset

private subroutine block_partial_copy_2d1d_z(dst, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, src_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(inout), DIMENSION(:, :) :: dst
logical, intent(in) :: dst_tr
complex(kind=real_8), intent(in), DIMENSION(:) :: src
integer, intent(in) :: src_rs
integer, intent(in) :: src_cs
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: src_offset

private subroutine block_partial_copy_2d2d_z(dst, dst_tr, src, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(inout), DIMENSION(:, :) :: dst
logical, intent(in) :: dst_tr
complex(kind=real_8), intent(in), DIMENSION(:, :) :: src
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol

public pure subroutine block_copy_z(extent_out, extent_in, n, out_fe, in_fe)

Copy a block

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(*) :: extent_out

output data

complex(kind=real_8), intent(in), DIMENSION(*) :: extent_in

input data

integer, intent(in) :: n

number of elements to copy first element of output first element of input

integer, intent(in) :: out_fe

number of elements to copy first element of output first element of input

integer, intent(in) :: in_fe

number of elements to copy first element of output first element of input

private subroutine block_transpose_copy_z(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(:), TARGET :: extent_out

output matrix in the form of a 1-d array

complex(kind=real_8), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_2d1d_z(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(rows, columns) :: extent_out

output matrix in the form of a 2-d array

complex(kind=real_8), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_1d1d_z(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(rows*columns) :: extent_out

output matrix in the form of a 1-d array

complex(kind=real_8), intent(in), DIMENSION(rows*columns) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_2d2d_z(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(rows, columns) :: extent_out

output matrix in the form of a 2-d array

complex(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_copy_2d1d_z(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(columns, rows), TARGET :: extent_out

output matrix in the form of a 2-d array

complex(kind=real_8), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_1d2d_z(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(:) :: extent_out

output matrix in the form of a 1-d array

complex(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_copy_1d2d_z(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(:), TARGET :: extent_out

output matrix in the form of a 1-d array

complex(kind=real_8), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_inplace_z(extent, rows, columns)

In-place block transpose.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(inout), DIMENSION(rows*columns) :: extent

Matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine dbcsr_data_set_az(dst, lb, data_size, src, source_lb)

Copy data from a double real array to a data area There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

destination data area

integer, intent(in) :: lb

lower bound for destination (and source if not given explicitly) number of elements to copy

integer, intent(in) :: data_size

lower bound for destination (and source if not given explicitly) number of elements to copy

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

source data array

integer, intent(in), optional :: source_lb

lower bound of source

private pure subroutine block_add_z(block_a, block_b, len)

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(inout), DIMENSION(len) :: block_a
complex(kind=real_8), intent(in), DIMENSION(len) :: block_b
integer, intent(in) :: len

private subroutine block_partial_copy_c(dst, dst_rs, dst_cs, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset, src_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(inout), DIMENSION(:) :: dst
integer, intent(in) :: dst_rs
integer, intent(in) :: dst_cs
logical, intent(in) :: dst_tr
complex(kind=real_4), intent(in), DIMENSION(:) :: src
integer, intent(in) :: src_rs
integer, intent(in) :: src_cs
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: dst_offset
integer, intent(in) :: src_offset

private subroutine block_partial_copy_1d2d_c(dst, dst_rs, dst_cs, dst_tr, src, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, dst_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(inout), DIMENSION(:) :: dst
integer, intent(in) :: dst_rs
integer, intent(in) :: dst_cs
logical, intent(in) :: dst_tr
complex(kind=real_4), intent(in), DIMENSION(:, :) :: src
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: dst_offset

private subroutine block_partial_copy_2d1d_c(dst, dst_tr, src, src_rs, src_cs, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol, src_offset)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(inout), DIMENSION(:, :) :: dst
logical, intent(in) :: dst_tr
complex(kind=real_4), intent(in), DIMENSION(:) :: src
integer, intent(in) :: src_rs
integer, intent(in) :: src_cs
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol
integer, intent(in) :: src_offset

private subroutine block_partial_copy_2d2d_c(dst, dst_tr, src, src_tr, dst_r_lb, dst_c_lb, src_r_lb, src_c_lb, nrow, ncol)

Copies a block subset

Read more…

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(inout), DIMENSION(:, :) :: dst
logical, intent(in) :: dst_tr
complex(kind=real_4), intent(in), DIMENSION(:, :) :: src
logical, intent(in) :: src_tr
integer, intent(in) :: dst_r_lb
integer, intent(in) :: dst_c_lb
integer, intent(in) :: src_r_lb
integer, intent(in) :: src_c_lb
integer, intent(in) :: nrow
integer, intent(in) :: ncol

public pure subroutine block_copy_c(extent_out, extent_in, n, out_fe, in_fe)

Copy a block

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(*) :: extent_out

output data

complex(kind=real_4), intent(in), DIMENSION(*) :: extent_in

input data

integer, intent(in) :: n

number of elements to copy first element of output first element of input

integer, intent(in) :: out_fe

number of elements to copy first element of output first element of input

integer, intent(in) :: in_fe

number of elements to copy first element of output first element of input

private subroutine block_transpose_copy_c(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(:), TARGET :: extent_out

output matrix in the form of a 1-d array

complex(kind=real_4), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_2d1d_c(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(rows, columns) :: extent_out

output matrix in the form of a 2-d array

complex(kind=real_4), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_1d1d_c(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(rows*columns) :: extent_out

output matrix in the form of a 1-d array

complex(kind=real_4), intent(in), DIMENSION(rows*columns) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_2d2d_c(extent_out, extent_in, rows, columns)

Copy a block

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(rows, columns) :: extent_out

output matrix in the form of a 2-d array

complex(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_copy_2d1d_c(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(columns, rows), TARGET :: extent_out

output matrix in the form of a 2-d array

complex(kind=real_4), intent(in), DIMENSION(:) :: extent_in

input matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private pure subroutine block_copy_1d2d_c(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(:) :: extent_out

output matrix in the form of a 1-d array

complex(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_copy_1d2d_c(extent_out, extent_in, rows, columns)

Copy and transpose block.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(:), TARGET :: extent_out

output matrix in the form of a 1-d array

complex(kind=real_4), intent(in), DIMENSION(rows, columns) :: extent_in

input matrix in the form of a 2-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine block_transpose_inplace_c(extent, rows, columns)

In-place block transpose.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(inout), DIMENSION(rows*columns) :: extent

Matrix in the form of a 1-d array

integer, intent(in) :: rows

input matrix size input matrix size

integer, intent(in) :: columns

input matrix size input matrix size

private subroutine dbcsr_data_set_ac(dst, lb, data_size, src, source_lb)

Copy data from a double real array to a data area There are no checks done for correctness!

Arguments

Type IntentOptional Attributes Name
type(dbcsr_data_obj), intent(inout) :: dst

destination data area

integer, intent(in) :: lb

lower bound for destination (and source if not given explicitly) number of elements to copy

integer, intent(in) :: data_size

lower bound for destination (and source if not given explicitly) number of elements to copy

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

source data array

integer, intent(in), optional :: source_lb

lower bound of source

private pure subroutine block_add_c(block_a, block_b, len)

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(inout), DIMENSION(len) :: block_a
complex(kind=real_4), intent(in), DIMENSION(len) :: block_b
integer, intent(in) :: len