dbcsr_ptr_util Module

DBCSR pointer and unmanaged array utilities



Variables

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

Interfaces

public interface ensure_array_size

  • private subroutine ensure_array_size_i(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

    Ensures that an array is appropriately large.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), DIMENSION(:), POINTER, CONTIGUOUS :: array

    array to verify and possibly resize

    integer(kind=int_4), optional, DIMENSION(:), POINTER :: array_resize
    integer, intent(in), optional :: lb

    desired array lower bound

    integer, intent(in) :: ub

    desired array upper bound

    real(kind=dp), intent(in), optional :: factor

    factor by which to exaggerate enlargements

    logical, intent(in), optional :: nocopy

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

    type(dbcsr_memtype_type), intent(in), optional :: memory_type

    use special memory

    logical, intent(in), optional :: zero_pad

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

  • private subroutine ensure_array_size_l(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

    Ensures that an array is appropriately large.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), DIMENSION(:), POINTER, CONTIGUOUS :: array

    array to verify and possibly resize

    integer(kind=int_8), optional, DIMENSION(:), POINTER :: array_resize
    integer, intent(in), optional :: lb

    desired array lower bound

    integer, intent(in) :: ub

    desired array upper bound

    real(kind=dp), intent(in), optional :: factor

    factor by which to exaggerate enlargements

    logical, intent(in), optional :: nocopy

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

    type(dbcsr_memtype_type), intent(in), optional :: memory_type

    use special memory

    logical, intent(in), optional :: zero_pad

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

  • private subroutine ensure_array_size_s(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

    Ensures that an array is appropriately large.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: array

    array to verify and possibly resize

    real(kind=real_4), optional, DIMENSION(:), POINTER :: array_resize
    integer, intent(in), optional :: lb

    desired array lower bound

    integer, intent(in) :: ub

    desired array upper bound

    real(kind=dp), intent(in), optional :: factor

    factor by which to exaggerate enlargements

    logical, intent(in), optional :: nocopy

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

    type(dbcsr_memtype_type), intent(in), optional :: memory_type

    use special memory

    logical, intent(in), optional :: zero_pad

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

  • private subroutine ensure_array_size_d(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

    Ensures that an array is appropriately large.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: array

    array to verify and possibly resize

    real(kind=real_8), optional, DIMENSION(:), POINTER :: array_resize
    integer, intent(in), optional :: lb

    desired array lower bound

    integer, intent(in) :: ub

    desired array upper bound

    real(kind=dp), intent(in), optional :: factor

    factor by which to exaggerate enlargements

    logical, intent(in), optional :: nocopy

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

    type(dbcsr_memtype_type), intent(in), optional :: memory_type

    use special memory

    logical, intent(in), optional :: zero_pad

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

  • private subroutine ensure_array_size_c(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

    Ensures that an array is appropriately large.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: array

    array to verify and possibly resize

    complex(kind=real_4), optional, DIMENSION(:), POINTER :: array_resize
    integer, intent(in), optional :: lb

    desired array lower bound

    integer, intent(in) :: ub

    desired array upper bound

    real(kind=dp), intent(in), optional :: factor

    factor by which to exaggerate enlargements

    logical, intent(in), optional :: nocopy

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

    type(dbcsr_memtype_type), intent(in), optional :: memory_type

    use special memory

    logical, intent(in), optional :: zero_pad

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

  • private subroutine ensure_array_size_z(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

    Ensures that an array is appropriately large.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: array

    array to verify and possibly resize

    complex(kind=real_8), optional, DIMENSION(:), POINTER :: array_resize
    integer, intent(in), optional :: lb

    desired array lower bound

    integer, intent(in) :: ub

    desired array upper bound

    real(kind=dp), intent(in), optional :: factor

    factor by which to exaggerate enlargements

    logical, intent(in), optional :: nocopy

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

    type(dbcsr_memtype_type), intent(in), optional :: memory_type

    use special memory

    logical, intent(in), optional :: zero_pad

    copy array on enlargement; default is to copy zero new allocations; default is to write nothing

public interface pointer_view

  • private function pointer_view_s(original, lb, ub) result(view)

    Returns a pointer with different bounds.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), DIMENSION(:), POINTER :: original

    original data pointer new pointer

    integer, intent(in) :: lb

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

    integer, intent(in) :: ub

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

    original data pointer new pointer

  • private function pointer_view_d(original, lb, ub) result(view)

    Returns a pointer with different bounds.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), DIMENSION(:), POINTER :: original

    original data pointer new pointer

    integer, intent(in) :: lb

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

    integer, intent(in) :: ub

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

    original data pointer new pointer

  • private function pointer_view_c(original, lb, ub) result(view)

    Returns a pointer with different bounds.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), DIMENSION(:), POINTER :: original

    original data pointer new pointer

    integer, intent(in) :: lb

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

    integer, intent(in) :: ub

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

    original data pointer new pointer

  • private function pointer_view_z(original, lb, ub) result(view)

    Returns a pointer with different bounds.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), DIMENSION(:), POINTER :: original

    original data pointer new pointer

    integer, intent(in) :: lb

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

    integer, intent(in) :: ub

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

    original data pointer new pointer

  • private function pointer_view_i(original, lb, ub) result(view)

    Returns a pointer with different bounds.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), DIMENSION(:), POINTER :: original

    original data pointer new pointer

    integer, intent(in) :: lb

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

    integer, intent(in) :: ub

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

    Return Value integer(kind=int_4), DIMENSION(:), POINTER

    original data pointer new pointer

  • private function pointer_view_l(original, lb, ub) result(view)

    Returns a pointer with different bounds.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), DIMENSION(:), POINTER :: original

    original data pointer new pointer

    integer, intent(in) :: lb

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

    integer, intent(in) :: ub

    lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

    original data pointer new pointer

  • private function pointer_view_a(new_area, area, offset, len) result(narea2)

    Repoints a pointer into a part of a data area

    Arguments

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

    repoints this encapsulated pointer

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

    area to point into

    integer, intent(in) :: offset

    point to this offset in area

    integer, intent(in), optional :: len

    length of data area to point to

    Return Value type(dbcsr_data_obj)

    copy of new_area

public interface pointer_rank_remap2

  • private subroutine pointer_s_rank_remap2(r2p, d1, d2, r1p)

    Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), DIMENSION(:, :), POINTER :: r2p
    integer, intent(in) :: d1
    integer, intent(in) :: d2
    real(kind=real_4), DIMENSION(:), POINTER :: r1p
  • private subroutine pointer_d_rank_remap2(r2p, d1, d2, r1p)

    Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), DIMENSION(:, :), POINTER :: r2p
    integer, intent(in) :: d1
    integer, intent(in) :: d2
    real(kind=real_8), DIMENSION(:), POINTER :: r1p
  • private subroutine pointer_c_rank_remap2(r2p, d1, d2, r1p)

    Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), DIMENSION(:, :), POINTER :: r2p
    integer, intent(in) :: d1
    integer, intent(in) :: d2
    complex(kind=real_4), DIMENSION(:), POINTER :: r1p
  • private subroutine pointer_z_rank_remap2(r2p, d1, d2, r1p)

    Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), DIMENSION(:, :), POINTER :: r2p
    integer, intent(in) :: d1
    integer, intent(in) :: d2
    complex(kind=real_8), DIMENSION(:), POINTER :: r1p
  • private subroutine pointer_l_rank_remap2(r2p, d1, d2, r1p)

    Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), DIMENSION(:, :), POINTER :: r2p
    integer, intent(in) :: d1
    integer, intent(in) :: d2
    integer(kind=int_8), DIMENSION(:), POINTER :: r1p
  • private subroutine pointer_i_rank_remap2(r2p, d1, d2, r1p)

    Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), DIMENSION(:, :), POINTER :: r2p
    integer, intent(in) :: d1
    integer, intent(in) :: d2
    integer(kind=int_4), DIMENSION(:), POINTER :: r1p

public interface memory_copy

  • private subroutine mem_copy_i(dst, src, n)

    Copies memory area

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), intent(out), DIMENSION(1:n) :: dst

    destination memory

    integer(kind=int_4), intent(in), DIMENSION(1:n) :: src

    source memory

    integer, intent(in) :: n

    length of copy

  • private subroutine mem_copy_l(dst, src, n)

    Copies memory area

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), intent(out), DIMENSION(1:n) :: dst

    destination memory

    integer(kind=int_8), intent(in), DIMENSION(1:n) :: src

    source memory

    integer, intent(in) :: n

    length of copy

  • private subroutine mem_copy_s(dst, src, n)

    Copies memory area

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(1:n) :: dst

    destination memory

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

    source memory

    integer, intent(in) :: n

    length of copy

  • private subroutine mem_copy_d(dst, src, n)

    Copies memory area

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(1:n) :: dst

    destination memory

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

    source memory

    integer, intent(in) :: n

    length of copy

  • private subroutine mem_copy_c(dst, src, n)

    Copies memory area

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(1:n) :: dst

    destination memory

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

    source memory

    integer, intent(in) :: n

    length of copy

  • private subroutine mem_copy_z(dst, src, n)

    Copies memory area

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(1:n) :: dst

    destination memory

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

    source memory

    integer, intent(in) :: n

    length of copy

public interface memory_zero

  • private subroutine mem_zero_i(dst, n)

    Zeros memory area

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), intent(out), DIMENSION(1:n) :: dst

    destination memory

    integer, intent(in) :: n

    length of elements to zero

  • private subroutine mem_zero_l(dst, n)

    Zeros memory area

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), intent(out), DIMENSION(1:n) :: dst

    destination memory

    integer, intent(in) :: n

    length of elements to zero

  • private subroutine mem_zero_s(dst, n)

    Zeros memory area

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), intent(out), DIMENSION(1:n) :: dst

    destination memory

    integer, intent(in) :: n

    length of elements to zero

  • private subroutine mem_zero_d(dst, n)

    Zeros memory area

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), intent(out), DIMENSION(1:n) :: dst

    destination memory

    integer, intent(in) :: n

    length of elements to zero

  • private subroutine mem_zero_c(dst, n)

    Zeros memory area

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), intent(out), DIMENSION(1:n) :: dst

    destination memory

    integer, intent(in) :: n

    length of elements to zero

  • private subroutine mem_zero_z(dst, n)

    Zeros memory area

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), intent(out), DIMENSION(1:n) :: dst

    destination memory

    integer, intent(in) :: n

    length of elements to zero

public interface memory_allocate

  • private subroutine mem_alloc_i(mem, n, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    integer, intent(in) :: n

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_l(mem, n, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    integer, intent(in) :: n

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_s(mem, n, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    integer, intent(in) :: n

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_d(mem, n, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    integer, intent(in) :: n

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_c(mem, n, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    integer, intent(in) :: n

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_z(mem, n, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    integer, intent(in) :: n

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_i_2d(mem, sizes, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), DIMENSION(:, :), POINTER :: mem

    memory to allocate

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

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_l_2d(mem, sizes, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), DIMENSION(:, :), POINTER :: mem

    memory to allocate

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

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_s_2d(mem, sizes, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), DIMENSION(:, :), POINTER :: mem

    memory to allocate

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

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_d_2d(mem, sizes, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), DIMENSION(:, :), POINTER :: mem

    memory to allocate

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

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_c_2d(mem, sizes, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), DIMENSION(:, :), POINTER :: mem

    memory to allocate

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

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_alloc_z_2d(mem, sizes, mem_type)

    Allocates memory

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), DIMENSION(:, :), POINTER :: mem

    memory to allocate

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

    length of elements to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

public interface memory_deallocate

  • private subroutine mem_dealloc_i(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_l(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_s(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_d(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_c(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_z(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_i_2d(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_4), DIMENSION(:, :), POINTER :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_l_2d(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int_8), DIMENSION(:, :), POINTER :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_s_2d(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_4), DIMENSION(:, :), POINTER :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_d_2d(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real_8), DIMENSION(:, :), POINTER :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_c_2d(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_4), DIMENSION(:, :), POINTER :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type

  • private subroutine mem_dealloc_z_2d(mem, mem_type)

    Deallocates memory

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=real_8), DIMENSION(:, :), POINTER :: mem

    memory to allocate

    type(dbcsr_memtype_type), intent(in) :: mem_type

    memory type


Functions

private function pointer_view_a(new_area, area, offset, len) result(narea2)

Repoints a pointer into a part of a data area

Arguments

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

repoints this encapsulated pointer

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

area to point into

integer, intent(in) :: offset

point to this offset in area

integer, intent(in), optional :: len

length of data area to point to

Return Value type(dbcsr_data_obj)

copy of new_area

private function pointer_view_d(original, lb, ub) result(view)

Returns a pointer with different bounds.

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), DIMENSION(:), POINTER :: original

original data pointer new pointer

integer, intent(in) :: lb

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

integer, intent(in) :: ub

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

original data pointer new pointer

private function pointer_view_s(original, lb, ub) result(view)

Returns a pointer with different bounds.

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), DIMENSION(:), POINTER :: original

original data pointer new pointer

integer, intent(in) :: lb

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

integer, intent(in) :: ub

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

original data pointer new pointer

private function pointer_view_z(original, lb, ub) result(view)

Returns a pointer with different bounds.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), DIMENSION(:), POINTER :: original

original data pointer new pointer

integer, intent(in) :: lb

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

integer, intent(in) :: ub

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

original data pointer new pointer

private function pointer_view_c(original, lb, ub) result(view)

Returns a pointer with different bounds.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), DIMENSION(:), POINTER :: original

original data pointer new pointer

integer, intent(in) :: lb

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

integer, intent(in) :: ub

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

original data pointer new pointer

private function pointer_view_i(original, lb, ub) result(view)

Returns a pointer with different bounds.

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), DIMENSION(:), POINTER :: original

original data pointer new pointer

integer, intent(in) :: lb

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

integer, intent(in) :: ub

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

Return Value integer(kind=int_4), DIMENSION(:), POINTER

original data pointer new pointer

private function pointer_view_l(original, lb, ub) result(view)

Returns a pointer with different bounds.

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), DIMENSION(:), POINTER :: original

original data pointer new pointer

integer, intent(in) :: lb

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

integer, intent(in) :: ub

lower and upper bound for the new pointer view lower and upper bound for the new pointer view

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

original data pointer new pointer


Subroutines

private subroutine ensure_array_size_d(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

Ensures that an array is appropriately large.

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: array

array to verify and possibly resize

real(kind=real_8), optional, DIMENSION(:), POINTER :: array_resize
integer, intent(in), optional :: lb

desired array lower bound

integer, intent(in) :: ub

desired array upper bound

real(kind=dp), intent(in), optional :: factor

factor by which to exaggerate enlargements

logical, intent(in), optional :: nocopy

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

type(dbcsr_memtype_type), intent(in), optional :: memory_type

use special memory

logical, intent(in), optional :: zero_pad

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

private subroutine mem_copy_d(dst, src, n)

Copies memory area

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(1:n) :: dst

destination memory

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

source memory

integer, intent(in) :: n

length of copy

private subroutine mem_zero_d(dst, n)

Zeros memory area

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), intent(out), DIMENSION(1:n) :: dst

destination memory

integer, intent(in) :: n

length of elements to zero

private subroutine mem_alloc_d(mem, n, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

integer, intent(in) :: n

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_alloc_d_2d(mem, sizes, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), DIMENSION(:, :), POINTER :: mem

memory to allocate

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

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_d(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_d_2d(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), DIMENSION(:, :), POINTER :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine pointer_d_rank_remap2(r2p, d1, d2, r1p)

Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

Arguments

Type IntentOptional Attributes Name
real(kind=real_8), DIMENSION(:, :), POINTER :: r2p
integer, intent(in) :: d1
integer, intent(in) :: d2
real(kind=real_8), DIMENSION(:), POINTER :: r1p

private subroutine ensure_array_size_s(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

Ensures that an array is appropriately large.

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: array

array to verify and possibly resize

real(kind=real_4), optional, DIMENSION(:), POINTER :: array_resize
integer, intent(in), optional :: lb

desired array lower bound

integer, intent(in) :: ub

desired array upper bound

real(kind=dp), intent(in), optional :: factor

factor by which to exaggerate enlargements

logical, intent(in), optional :: nocopy

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

type(dbcsr_memtype_type), intent(in), optional :: memory_type

use special memory

logical, intent(in), optional :: zero_pad

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

private subroutine mem_copy_s(dst, src, n)

Copies memory area

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(1:n) :: dst

destination memory

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

source memory

integer, intent(in) :: n

length of copy

private subroutine mem_zero_s(dst, n)

Zeros memory area

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(out), DIMENSION(1:n) :: dst

destination memory

integer, intent(in) :: n

length of elements to zero

private subroutine mem_alloc_s(mem, n, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

integer, intent(in) :: n

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_alloc_s_2d(mem, sizes, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), DIMENSION(:, :), POINTER :: mem

memory to allocate

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

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_s(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_s_2d(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), DIMENSION(:, :), POINTER :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine pointer_s_rank_remap2(r2p, d1, d2, r1p)

Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), DIMENSION(:, :), POINTER :: r2p
integer, intent(in) :: d1
integer, intent(in) :: d2
real(kind=real_4), DIMENSION(:), POINTER :: r1p

private subroutine ensure_array_size_z(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

Ensures that an array is appropriately large.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: array

array to verify and possibly resize

complex(kind=real_8), optional, DIMENSION(:), POINTER :: array_resize
integer, intent(in), optional :: lb

desired array lower bound

integer, intent(in) :: ub

desired array upper bound

real(kind=dp), intent(in), optional :: factor

factor by which to exaggerate enlargements

logical, intent(in), optional :: nocopy

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

type(dbcsr_memtype_type), intent(in), optional :: memory_type

use special memory

logical, intent(in), optional :: zero_pad

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

private subroutine mem_copy_z(dst, src, n)

Copies memory area

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(1:n) :: dst

destination memory

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

source memory

integer, intent(in) :: n

length of copy

private subroutine mem_zero_z(dst, n)

Zeros memory area

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), intent(out), DIMENSION(1:n) :: dst

destination memory

integer, intent(in) :: n

length of elements to zero

private subroutine mem_alloc_z(mem, n, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

integer, intent(in) :: n

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_alloc_z_2d(mem, sizes, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), DIMENSION(:, :), POINTER :: mem

memory to allocate

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

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_z(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_z_2d(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), DIMENSION(:, :), POINTER :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine pointer_z_rank_remap2(r2p, d1, d2, r1p)

Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_8), DIMENSION(:, :), POINTER :: r2p
integer, intent(in) :: d1
integer, intent(in) :: d2
complex(kind=real_8), DIMENSION(:), POINTER :: r1p

private subroutine ensure_array_size_c(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

Ensures that an array is appropriately large.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: array

array to verify and possibly resize

complex(kind=real_4), optional, DIMENSION(:), POINTER :: array_resize
integer, intent(in), optional :: lb

desired array lower bound

integer, intent(in) :: ub

desired array upper bound

real(kind=dp), intent(in), optional :: factor

factor by which to exaggerate enlargements

logical, intent(in), optional :: nocopy

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

type(dbcsr_memtype_type), intent(in), optional :: memory_type

use special memory

logical, intent(in), optional :: zero_pad

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

private subroutine mem_copy_c(dst, src, n)

Copies memory area

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(1:n) :: dst

destination memory

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

source memory

integer, intent(in) :: n

length of copy

private subroutine mem_zero_c(dst, n)

Zeros memory area

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), intent(out), DIMENSION(1:n) :: dst

destination memory

integer, intent(in) :: n

length of elements to zero

private subroutine mem_alloc_c(mem, n, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

integer, intent(in) :: n

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_alloc_c_2d(mem, sizes, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), DIMENSION(:, :), POINTER :: mem

memory to allocate

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

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_c(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_c_2d(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), DIMENSION(:, :), POINTER :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine pointer_c_rank_remap2(r2p, d1, d2, r1p)

Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

Arguments

Type IntentOptional Attributes Name
complex(kind=real_4), DIMENSION(:, :), POINTER :: r2p
integer, intent(in) :: d1
integer, intent(in) :: d2
complex(kind=real_4), DIMENSION(:), POINTER :: r1p

private subroutine ensure_array_size_i(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

Ensures that an array is appropriately large.

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), DIMENSION(:), POINTER, CONTIGUOUS :: array

array to verify and possibly resize

integer(kind=int_4), optional, DIMENSION(:), POINTER :: array_resize
integer, intent(in), optional :: lb

desired array lower bound

integer, intent(in) :: ub

desired array upper bound

real(kind=dp), intent(in), optional :: factor

factor by which to exaggerate enlargements

logical, intent(in), optional :: nocopy

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

type(dbcsr_memtype_type), intent(in), optional :: memory_type

use special memory

logical, intent(in), optional :: zero_pad

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

private subroutine mem_copy_i(dst, src, n)

Copies memory area

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), intent(out), DIMENSION(1:n) :: dst

destination memory

integer(kind=int_4), intent(in), DIMENSION(1:n) :: src

source memory

integer, intent(in) :: n

length of copy

private subroutine mem_zero_i(dst, n)

Zeros memory area

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), intent(out), DIMENSION(1:n) :: dst

destination memory

integer, intent(in) :: n

length of elements to zero

private subroutine mem_alloc_i(mem, n, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

integer, intent(in) :: n

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_alloc_i_2d(mem, sizes, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), DIMENSION(:, :), POINTER :: mem

memory to allocate

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

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_i(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_i_2d(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), DIMENSION(:, :), POINTER :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine pointer_i_rank_remap2(r2p, d1, d2, r1p)

Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

Arguments

Type IntentOptional Attributes Name
integer(kind=int_4), DIMENSION(:, :), POINTER :: r2p
integer, intent(in) :: d1
integer, intent(in) :: d2
integer(kind=int_4), DIMENSION(:), POINTER :: r1p

private subroutine ensure_array_size_l(array, array_resize, lb, ub, factor, nocopy, memory_type, zero_pad)

Ensures that an array is appropriately large.

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), DIMENSION(:), POINTER, CONTIGUOUS :: array

array to verify and possibly resize

integer(kind=int_8), optional, DIMENSION(:), POINTER :: array_resize
integer, intent(in), optional :: lb

desired array lower bound

integer, intent(in) :: ub

desired array upper bound

real(kind=dp), intent(in), optional :: factor

factor by which to exaggerate enlargements

logical, intent(in), optional :: nocopy

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

type(dbcsr_memtype_type), intent(in), optional :: memory_type

use special memory

logical, intent(in), optional :: zero_pad

copy array on enlargement; default is to copy zero new allocations; default is to write nothing

private subroutine mem_copy_l(dst, src, n)

Copies memory area

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), intent(out), DIMENSION(1:n) :: dst

destination memory

integer(kind=int_8), intent(in), DIMENSION(1:n) :: src

source memory

integer, intent(in) :: n

length of copy

private subroutine mem_zero_l(dst, n)

Zeros memory area

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), intent(out), DIMENSION(1:n) :: dst

destination memory

integer, intent(in) :: n

length of elements to zero

private subroutine mem_alloc_l(mem, n, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

integer, intent(in) :: n

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_alloc_l_2d(mem, sizes, mem_type)

Allocates memory

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), DIMENSION(:, :), POINTER :: mem

memory to allocate

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

length of elements to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_l(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), DIMENSION(:), POINTER, CONTIGUOUS :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine mem_dealloc_l_2d(mem, mem_type)

Deallocates memory

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), DIMENSION(:, :), POINTER :: mem

memory to allocate

type(dbcsr_memtype_type), intent(in) :: mem_type

memory type

private subroutine pointer_l_rank_remap2(r2p, d1, d2, r1p)

Sets a rank-2 pointer to rank-1 data using Fortran 2003 pointer rank remapping.

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), DIMENSION(:, :), POINTER :: r2p
integer, intent(in) :: d1
integer, intent(in) :: d2
integer(kind=int_8), DIMENSION(:), POINTER :: r1p