dbcsr_tensor_block Module

Methods to operate on n-dimensional tensor blocks.



Variables

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

Interfaces

public interface create_block

  • private subroutine create_block_data_r_dp(block, sizes, array)

    Create block from array, array can be n-dimensional.

    Arguments

    Type IntentOptional Attributes Name
    type(block_nd), intent(out) :: block
    integer, intent(in), DIMENSION(:) :: sizes
    real(kind=real_8), intent(in), DIMENSION(PRODUCT(sizes)) :: array
  • private subroutine create_block_data_r_sp(block, sizes, array)

    Create block from array, array can be n-dimensional.

    Arguments

    Type IntentOptional Attributes Name
    type(block_nd), intent(out) :: block
    integer, intent(in), DIMENSION(:) :: sizes
    real(kind=real_4), intent(in), DIMENSION(PRODUCT(sizes)) :: array
  • private subroutine create_block_data_c_dp(block, sizes, array)

    Create block from array, array can be n-dimensional.

    Arguments

    Type IntentOptional Attributes Name
    type(block_nd), intent(out) :: block
    integer, intent(in), DIMENSION(:) :: sizes
    complex(kind=real_8), intent(in), DIMENSION(PRODUCT(sizes)) :: array
  • private subroutine create_block_data_c_sp(block, sizes, array)

    Create block from array, array can be n-dimensional.

    Arguments

    Type IntentOptional Attributes Name
    type(block_nd), intent(out) :: block
    integer, intent(in), DIMENSION(:) :: sizes
    complex(kind=real_4), intent(in), DIMENSION(PRODUCT(sizes)) :: array
  • private subroutine create_block_nodata(block, sizes, data_type)

    Create block without data

    Arguments

    Type IntentOptional Attributes Name
    type(block_nd), intent(out) :: block
    integer, intent(in), DIMENSION(:) :: sizes
    integer, intent(in) :: data_type

public interface dbcsr_t_put_block

  • private subroutine dbcsr_t_put_2d_block_r_dp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(2) :: sizes

    block size

    real(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

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

    scaling factor

  • private subroutine dbcsr_t_put_3d_block_r_dp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(3) :: sizes

    block size

    real(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

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

    scaling factor

  • private subroutine dbcsr_t_put_4d_block_r_dp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(4) :: sizes

    block size

    real(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

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

    scaling factor

  • private subroutine dbcsr_t_put_2d_block_r_sp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(2) :: sizes

    block size

    real(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    real(kind=real_4), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_3d_block_r_sp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(3) :: sizes

    block size

    real(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    real(kind=real_4), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_4d_block_r_sp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(4) :: sizes

    block size

    real(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    real(kind=real_4), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_2d_block_c_dp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(2) :: sizes

    block size

    complex(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    complex(kind=real_8), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_3d_block_c_dp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(3) :: sizes

    block size

    complex(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    complex(kind=real_8), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_4d_block_c_dp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(4) :: sizes

    block size

    complex(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    complex(kind=real_8), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_2d_block_c_sp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(2) :: sizes

    block size

    complex(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    complex(kind=real_4), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_3d_block_c_sp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(3) :: sizes

    block size

    complex(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    complex(kind=real_4), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_4d_block_c_sp(tensor, ind, sizes, block, summation, scale)

    Template for dbcsr_t_put_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(4) :: sizes

    block size

    complex(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)), TARGET :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

    complex(kind=real_4), intent(in), optional :: scale

    scaling factor

  • private subroutine dbcsr_t_put_anyd_block(tensor, ind, block, summation, scale)

    Generic implementation of dbcsr_t_put_block (arbitrary tensor rank and arbitrary datatype)

    Arguments

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

    block index

    type(block_nd), intent(in) :: block

    block to put

    logical, intent(in), optional :: summation

    whether block should be summed to existing block

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

    scaling factor

public interface dbcsr_t_get_block

  • private subroutine dbcsr_t_get_2d_block_r_dp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(2) :: sizes

    block size

    real(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_2d_block_r_dp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    real(kind=real_8), intent(out), DIMENSION(:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_3d_block_r_dp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(3) :: sizes

    block size

    real(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_3d_block_r_dp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    real(kind=real_8), intent(out), DIMENSION(:,:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_4d_block_r_dp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(4) :: sizes

    block size

    real(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_4d_block_r_dp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    real(kind=real_8), intent(out), DIMENSION(:,:,:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_2d_block_r_sp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(2) :: sizes

    block size

    real(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_2d_block_r_sp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    real(kind=real_4), intent(out), DIMENSION(:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_3d_block_r_sp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(3) :: sizes

    block size

    real(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_3d_block_r_sp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    real(kind=real_4), intent(out), DIMENSION(:,:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_4d_block_r_sp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(4) :: sizes

    block size

    real(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_4d_block_r_sp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    real(kind=real_4), intent(out), DIMENSION(:,:,:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_2d_block_c_dp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(2) :: sizes

    block size

    complex(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_2d_block_c_dp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    complex(kind=real_8), intent(out), DIMENSION(:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_3d_block_c_dp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(3) :: sizes

    block size

    complex(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_3d_block_c_dp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    complex(kind=real_8), intent(out), DIMENSION(:,:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_4d_block_c_dp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(4) :: sizes

    block size

    complex(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_4d_block_c_dp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    complex(kind=real_8), intent(out), DIMENSION(:,:,:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_2d_block_c_sp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(2) :: sizes

    block size

    complex(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_2d_block_c_sp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    complex(kind=real_4), intent(out), DIMENSION(:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_3d_block_c_sp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(3) :: sizes

    block size

    complex(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_3d_block_c_sp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    complex(kind=real_4), intent(out), DIMENSION(:,:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_4d_block_c_sp(tensor, ind, sizes, block, found)

    Template for dbcsr_t_get_block.

    Arguments

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

    block index

    integer, intent(in), DIMENSION(4) :: sizes

    block size

    complex(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_allocate_and_get_4d_block_c_sp(tensor, ind, block, found)

    allocate and get block

    Arguments

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

    block index

    complex(kind=real_4), intent(out), DIMENSION(:,:,:,:), ALLOCATABLE :: block

    block to get

    logical, intent(out) :: found

    whether block was found

  • private subroutine dbcsr_t_get_anyd_block(tensor, ind, block, found)

    Generic implementation of dbcsr_t_get_block (arbitrary tensor rank and arbitrary datatype)

    Arguments

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

    block index

    type(block_nd), intent(out) :: block

    block to get

    logical, intent(out) :: found

    whether block was found

public interface dbcsr_t_reserve_blocks

  • private subroutine dbcsr_t_reserve_blocks_index(tensor, blk_ind_1, blk_ind_2, blk_ind_3, blk_ind_4)

    reserve tensor blocks using block indices

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    integer, intent(in), optional, DIMENSION(:) :: blk_ind_1

    index of blocks to reserve in each dimension

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

    index of blocks to reserve in each dimension

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

    index of blocks to reserve in each dimension

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

    index of blocks to reserve in each dimension

  • private subroutine dbcsr_t_reserve_blocks_index_array(tensor, blk_ind)

    reserve blocks from indices as array object

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(inout) :: tensor
    integer, intent(in), DIMENSION(:, :) :: blk_ind
  • private subroutine dbcsr_t_reserve_blocks_template(tensor_in, tensor_out)

    reserve tensor blocks using template

    Arguments

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

    template tensor

    type(dbcsr_t_type), intent(inout) :: tensor_out
  • private subroutine dbcsr_t_reserve_blocks_tensor_to_matrix(tensor_in, matrix_out)

    reserve matrix blocks using tensor template

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_t_type), intent(in) :: tensor_in
    type(dbcsr_type), intent(inout) :: matrix_out
  • private subroutine dbcsr_t_reserve_blocks_matrix_to_tensor(matrix_in, tensor_out)

    reserve tensor blocks using matrix template

    Arguments

    Type IntentOptional Attributes Name
    type(dbcsr_type), intent(in), TARGET :: matrix_in
    type(dbcsr_t_type), intent(inout) :: tensor_out

Derived Types

type, public ::  dbcsr_t_iterator_type

Components

Type Visibility Attributes Name Initial
type(dbcsr_tas_iterator), public :: iter
type(nd_to_2d_mapping), public :: nd_index_blk
type(nd_to_2d_mapping), public :: nd_index
type(array_list), public :: blk_sizes
type(array_list), public :: blk_offsets

type, public ::  block_nd_r_dp

Components

Type Visibility Attributes Name Initial
integer, public, DIMENSION(:), ALLOCATABLE :: sizes
real(kind=real_8), public, DIMENSION(:), ALLOCATABLE :: blk

type, public ::  block_nd_r_sp

Components

Type Visibility Attributes Name Initial
integer, public, DIMENSION(:), ALLOCATABLE :: sizes
real(kind=real_4), public, DIMENSION(:), ALLOCATABLE :: blk

type, public ::  block_nd_c_dp

Components

Type Visibility Attributes Name Initial
integer, public, DIMENSION(:), ALLOCATABLE :: sizes
complex(kind=real_8), public, DIMENSION(:), ALLOCATABLE :: blk

type, public ::  block_nd_c_sp

Components

Type Visibility Attributes Name Initial
integer, public, DIMENSION(:), ALLOCATABLE :: sizes
complex(kind=real_4), public, DIMENSION(:), ALLOCATABLE :: blk

type, public ::  block_nd

Components

Type Visibility Attributes Name Initial
type(block_nd_r_dp), public :: r_dp
type(block_nd_r_sp), public :: r_sp
type(block_nd_c_dp), public :: c_dp
type(block_nd_c_sp), public :: c_sp
integer, public :: data_type = -1

Functions

private function block_size(block)

block size

Arguments

Type IntentOptional Attributes Name
type(block_nd), intent(in) :: block

Return Value integer, ALLOCATABLE, DIMENSION(:)

public pure function ndims_iterator(iterator)

Number of dimensions.

Read more…

Arguments

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

Return Value integer

public function dbcsr_t_iterator_blocks_left(iterator)

Generalization of dbcsr_iterator_blocks_left for tensors.

Arguments

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

Return Value logical


Subroutines

private subroutine create_block_nodata(block, sizes, data_type)

Create block without data

Arguments

Type IntentOptional Attributes Name
type(block_nd), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes
integer, intent(in) :: data_type

public subroutine destroy_block(block)

Destroy block

Arguments

Type IntentOptional Attributes Name
type(block_nd), intent(inout) :: block

public subroutine dbcsr_t_iterator_start(iterator, tensor)

Generalization of dbcsr_iterator_start for tensors.

Arguments

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

public subroutine dbcsr_t_iterator_stop(iterator)

Generalization of dbcsr_iterator_stop for tensors.

Arguments

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

public subroutine dbcsr_t_iterator_next_block(iterator, ind_nd, blk, blk_p, blk_size, blk_offset)

iterate over nd blocks of an nd rank tensor, index only (blocks must be retrieved by calling dbcsr_t_get_block on tensor).

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_iterator_type), intent(inout) :: iterator
integer, intent(out), DIMENSION(ndims_iterator(iterator)) :: ind_nd

nd index of block

integer, intent(out) :: blk

is this needed?

integer, intent(out), optional :: blk_p

is this needed?

integer, intent(out), optional, DIMENSION(ndims_iterator(iterator)) :: blk_size

blk size in each dimension blk offset in each dimension

integer, intent(out), optional, DIMENSION(ndims_iterator(iterator)) :: blk_offset

blk size in each dimension blk offset in each dimension

private subroutine dbcsr_t_reserve_blocks_index_array(tensor, blk_ind)

reserve blocks from indices as array object

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
integer, intent(in), DIMENSION(:, :) :: blk_ind

private subroutine dbcsr_t_reserve_blocks_index(tensor, blk_ind_1, blk_ind_2, blk_ind_3, blk_ind_4)

reserve tensor blocks using block indices

Arguments

Type IntentOptional Attributes Name
type(dbcsr_t_type), intent(inout) :: tensor
integer, intent(in), optional, DIMENSION(:) :: blk_ind_1

index of blocks to reserve in each dimension

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

index of blocks to reserve in each dimension

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

index of blocks to reserve in each dimension

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

index of blocks to reserve in each dimension

private subroutine dbcsr_t_reserve_blocks_template(tensor_in, tensor_out)

reserve tensor blocks using template

Arguments

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

template tensor

type(dbcsr_t_type), intent(inout) :: tensor_out

private subroutine dbcsr_t_reserve_blocks_matrix_to_tensor(matrix_in, tensor_out)

reserve tensor blocks using matrix template

Arguments

Type IntentOptional Attributes Name
type(dbcsr_type), intent(in), TARGET :: matrix_in
type(dbcsr_t_type), intent(inout) :: tensor_out

private subroutine dbcsr_t_reserve_blocks_tensor_to_matrix(tensor_in, matrix_out)

reserve matrix blocks using tensor template

Arguments

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

public subroutine dbcsr_t_reserved_block_indices(tensor, blk_ind)

indices of non-zero blocks

Arguments

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

private subroutine create_block_data_r_dp(block, sizes, array)

Create block from array, array can be n-dimensional.

Arguments

Type IntentOptional Attributes Name
type(block_nd), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes
real(kind=real_8), intent(in), DIMENSION(PRODUCT(sizes)) :: array

private subroutine create_block_data_r_sp(block, sizes, array)

Create block from array, array can be n-dimensional.

Arguments

Type IntentOptional Attributes Name
type(block_nd), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes
real(kind=real_4), intent(in), DIMENSION(PRODUCT(sizes)) :: array

private subroutine create_block_data_c_dp(block, sizes, array)

Create block from array, array can be n-dimensional.

Arguments

Type IntentOptional Attributes Name
type(block_nd), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes
complex(kind=real_8), intent(in), DIMENSION(PRODUCT(sizes)) :: array

private subroutine create_block_data_c_sp(block, sizes, array)

Create block from array, array can be n-dimensional.

Arguments

Type IntentOptional Attributes Name
type(block_nd), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes
complex(kind=real_4), intent(in), DIMENSION(PRODUCT(sizes)) :: array

private subroutine create_block_nodata_r_dp(block, sizes)

Create and allocate block, but no data.

Arguments

Type IntentOptional Attributes Name
type(block_nd_r_dp), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes

private subroutine create_block_nodata_r_sp(block, sizes)

Create and allocate block, but no data.

Arguments

Type IntentOptional Attributes Name
type(block_nd_r_sp), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes

private subroutine create_block_nodata_c_dp(block, sizes)

Create and allocate block, but no data.

Arguments

Type IntentOptional Attributes Name
type(block_nd_c_dp), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes

private subroutine create_block_nodata_c_sp(block, sizes)

Create and allocate block, but no data.

Arguments

Type IntentOptional Attributes Name
type(block_nd_c_sp), intent(out) :: block
integer, intent(in), DIMENSION(:) :: sizes

private subroutine destroy_block_r_dp(block)

Arguments

Type IntentOptional Attributes Name
type(block_nd_r_dp), intent(inout) :: block

private subroutine destroy_block_r_sp(block)

Arguments

Type IntentOptional Attributes Name
type(block_nd_r_sp), intent(inout) :: block

private subroutine destroy_block_c_dp(block)

Arguments

Type IntentOptional Attributes Name
type(block_nd_c_dp), intent(inout) :: block

private subroutine destroy_block_c_sp(block)

Arguments

Type IntentOptional Attributes Name
type(block_nd_c_sp), intent(inout) :: block

private subroutine dbcsr_t_get_anyd_block(tensor, ind, block, found)

Generic implementation of dbcsr_t_get_block (arbitrary tensor rank and arbitrary datatype)

Arguments

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

block index

type(block_nd), intent(out) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_put_anyd_block(tensor, ind, block, summation, scale)

Generic implementation of dbcsr_t_put_block (arbitrary tensor rank and arbitrary datatype)

Arguments

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

block index

type(block_nd), intent(in) :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

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

scaling factor

private subroutine dbcsr_t_put_anyd_block_r_dp(tensor, ind, block, summation, scale)

Generic implementation of dbcsr_t_put_block, template for datatype

Arguments

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

block index

type(block_nd_r_dp), intent(in) :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

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

scaling factor

private subroutine dbcsr_t_put_anyd_block_r_sp(tensor, ind, block, summation, scale)

Generic implementation of dbcsr_t_put_block, template for datatype

Arguments

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

block index

type(block_nd_r_sp), intent(in) :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

real(kind=real_4), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_anyd_block_c_dp(tensor, ind, block, summation, scale)

Generic implementation of dbcsr_t_put_block, template for datatype

Arguments

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

block index

type(block_nd_c_dp), intent(in) :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

complex(kind=real_8), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_anyd_block_c_sp(tensor, ind, block, summation, scale)

Generic implementation of dbcsr_t_put_block, template for datatype

Arguments

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

block index

type(block_nd_c_sp), intent(in) :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

complex(kind=real_4), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_get_anyd_block_r_dp(tensor, ind, block, found)

Generic implementation of dbcsr_t_get_block (arbitrary tensor rank)

Arguments

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

block index

type(block_nd), intent(out) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_anyd_block_r_sp(tensor, ind, block, found)

Generic implementation of dbcsr_t_get_block (arbitrary tensor rank)

Arguments

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

block index

type(block_nd), intent(out) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_anyd_block_c_dp(tensor, ind, block, found)

Generic implementation of dbcsr_t_get_block (arbitrary tensor rank)

Arguments

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

block index

type(block_nd), intent(out) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_anyd_block_c_sp(tensor, ind, block, found)

Generic implementation of dbcsr_t_get_block (arbitrary tensor rank)

Arguments

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

block index

type(block_nd), intent(out) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_put_2d_block_r_dp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(2) :: sizes

block size

real(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

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

scaling factor

private subroutine dbcsr_t_put_3d_block_r_dp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(3) :: sizes

block size

real(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

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

scaling factor

private subroutine dbcsr_t_put_4d_block_r_dp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(4) :: sizes

block size

real(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

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

scaling factor

private subroutine dbcsr_t_put_2d_block_r_sp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(2) :: sizes

block size

real(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

real(kind=real_4), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_3d_block_r_sp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(3) :: sizes

block size

real(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

real(kind=real_4), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_4d_block_r_sp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(4) :: sizes

block size

real(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

real(kind=real_4), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_2d_block_c_dp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(2) :: sizes

block size

complex(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

complex(kind=real_8), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_3d_block_c_dp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(3) :: sizes

block size

complex(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

complex(kind=real_8), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_4d_block_c_dp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(4) :: sizes

block size

complex(kind=real_8), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

complex(kind=real_8), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_2d_block_c_sp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(2) :: sizes

block size

complex(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

complex(kind=real_4), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_3d_block_c_sp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(3) :: sizes

block size

complex(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

complex(kind=real_4), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_put_4d_block_c_sp(tensor, ind, sizes, block, summation, scale)

Template for dbcsr_t_put_block.

Arguments

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

block index

integer, intent(in), DIMENSION(4) :: sizes

block size

complex(kind=real_4), intent(in), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)), TARGET :: block

block to put

logical, intent(in), optional :: summation

whether block should be summed to existing block

complex(kind=real_4), intent(in), optional :: scale

scaling factor

private subroutine dbcsr_t_allocate_and_get_2d_block_r_dp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

real(kind=real_8), intent(out), DIMENSION(:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_3d_block_r_dp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

real(kind=real_8), intent(out), DIMENSION(:,:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_4d_block_r_dp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

real(kind=real_8), intent(out), DIMENSION(:,:,:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_2d_block_r_sp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

real(kind=real_4), intent(out), DIMENSION(:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_3d_block_r_sp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

real(kind=real_4), intent(out), DIMENSION(:,:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_4d_block_r_sp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

real(kind=real_4), intent(out), DIMENSION(:,:,:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_2d_block_c_dp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

complex(kind=real_8), intent(out), DIMENSION(:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_3d_block_c_dp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

complex(kind=real_8), intent(out), DIMENSION(:,:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_4d_block_c_dp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

complex(kind=real_8), intent(out), DIMENSION(:,:,:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_2d_block_c_sp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

complex(kind=real_4), intent(out), DIMENSION(:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_3d_block_c_sp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

complex(kind=real_4), intent(out), DIMENSION(:,:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_allocate_and_get_4d_block_c_sp(tensor, ind, block, found)

allocate and get block

Arguments

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

block index

complex(kind=real_4), intent(out), DIMENSION(:,:,:,:), ALLOCATABLE :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_2d_block_r_dp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(2) :: sizes

block size

real(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_3d_block_r_dp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(3) :: sizes

block size

real(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_4d_block_r_dp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(4) :: sizes

block size

real(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_2d_block_r_sp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(2) :: sizes

block size

real(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_3d_block_r_sp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(3) :: sizes

block size

real(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_4d_block_r_sp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(4) :: sizes

block size

real(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_2d_block_c_dp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(2) :: sizes

block size

complex(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_3d_block_c_dp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(3) :: sizes

block size

complex(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_4d_block_c_dp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(4) :: sizes

block size

complex(kind=real_8), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_2d_block_c_sp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(2) :: sizes

block size

complex(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_3d_block_c_sp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(3) :: sizes

block size

complex(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3)) :: block

block to get

logical, intent(out) :: found

whether block was found

private subroutine dbcsr_t_get_4d_block_c_sp(tensor, ind, sizes, block, found)

Template for dbcsr_t_get_block.

Arguments

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

block index

integer, intent(in), DIMENSION(4) :: sizes

block size

complex(kind=real_4), intent(out), DIMENSION(sizes(1), sizes(2), sizes(3), sizes(4)) :: block

block to get

logical, intent(out) :: found

whether block was found