dbcsr_acc_devmem Module

Accelerator support



Interfaces

public interface acc_devmem_dev2host

  • private subroutine dev2host_i4_1D(this, hostmem, stream)

    Transfers GPU devmem to 1D fortran-array.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    integer(kind=int_4), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine dev2host_i8_1D(this, hostmem, stream)

    Transfers GPU devmem to 1D fortran-array.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    integer(kind=int_8), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine dev2host_r4_1D(this, hostmem, stream)

    Transfers GPU devmem to 1D fortran-array.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    real(kind=real_4), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine dev2host_r8_1D(this, hostmem, stream)

    Transfers GPU devmem to 1D fortran-array.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    real(kind=real_8), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine dev2host_c4_1D(this, hostmem, stream)

    Transfers GPU devmem to 1D fortran-array.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    complex(kind=real_4), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine dev2host_c8_1D(this, hostmem, stream)

    Transfers GPU devmem to 1D fortran-array.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    complex(kind=real_8), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream

public interface acc_devmem_host2dev

  • private subroutine host2dev_i4_1D(this, hostmem, stream)

    Transfers 1D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    integer(kind=int_4), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_i8_1D(this, hostmem, stream)

    Transfers 1D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    integer(kind=int_8), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_r4_1D(this, hostmem, stream)

    Transfers 1D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    real(kind=real_4), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_r8_1D(this, hostmem, stream)

    Transfers 1D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    real(kind=real_8), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_c4_1D(this, hostmem, stream)

    Transfers 1D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    complex(kind=real_4), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_c8_1D(this, hostmem, stream)

    Transfers 1D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    complex(kind=real_8), DIMENSION(:), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_i4_2D(this, hostmem, stream)

    Transfers 2D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    integer(kind=int_4), DIMENSION(:, :), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_i8_2D(this, hostmem, stream)

    Transfers 2D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    integer(kind=int_8), DIMENSION(:, :), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_r4_2D(this, hostmem, stream)

    Transfers 2D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    real(kind=real_4), DIMENSION(:, :), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_r8_2D(this, hostmem, stream)

    Transfers 2D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    real(kind=real_8), DIMENSION(:, :), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_c4_2D(this, hostmem, stream)

    Transfers 2D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    complex(kind=real_4), DIMENSION(:, :), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream
  • private subroutine host2dev_c8_2D(this, hostmem, stream)

    Transfers 2D fortran-array from host to GPU devmem.

    Arguments

    Type IntentOptional Attributes Name
    type(acc_devmem_type), intent(in) :: this
    complex(kind=real_8), DIMENSION(:, :), POINTER :: hostmem
    type(acc_stream_type), intent(in) :: stream

Derived Types

type, public ::  acc_devmem_type

Components

Type Visibility Attributes Name Initial
integer, private :: size_in_bytes = -1

Functions

public function acc_devmem_allocated(this) result(res)

Returns a logical, which indicates if the given devmem is allocated.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this

Return Value logical

true if device memory is allocated, false otherwise

public function acc_devmem_size_in_bytes(this) result(res)

Returns size of given devmem in terms of item count (not bytes!)

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this

Return Value integer

size of device memory (item count)

public function acc_devmem_cptr(this) result(res)

Returns C-pointer to data of given devmem.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: this

device memory

Return Value logical

false (accelerator support is not enabled)


Subroutines

public subroutine acc_devmem_ensure_size_bytes(this, stream, requested_size_in_bytes, nocopy, zero_pad)

Ensures that given devmem has at least the requested size.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(inout) :: this

device memory

type(acc_stream_type), intent(in) :: stream

on which zeroing and memcopying is performed

integer, intent(in) :: requested_size_in_bytes

requested size in bytes

logical, intent(in), optional :: nocopy

if after growin old content should NOT be copied over. Default: false. if after growing the new memory should be zeroed. Default: false.

logical, intent(in), optional :: zero_pad

if after growin old content should NOT be copied over. Default: false. if after growing the new memory should be zeroed. Default: false.

public subroutine acc_devmem_set_cptr(this, pointee, size_in_bytes, lb_in_bytes)

Allocates a given devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(inout) :: this
type(acc_devmem_type), intent(in) :: pointee
integer, intent(in) :: size_in_bytes
integer, intent(in) :: lb_in_bytes

public subroutine acc_devmem_info(free, total)

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), intent(out) :: free
integer(kind=int_8), intent(out) :: total

public subroutine acc_devmem_allocate_bytes(this, size_in_bytes)

Allocates a given devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(inout) :: this
integer, intent(in) :: size_in_bytes

public subroutine acc_devmem_deallocate(this)

Deallocates a given devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(inout) :: this

public subroutine acc_devmem_setzero_bytes(this, first_byte, last_byte, stream)

Sets entries in given devmem to zero, asynchronously.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(inout) :: this
integer, intent(in), optional :: first_byte

begin of region to zero, defaults to 1 if not given. end of region to zero, defaults to size if not given.

integer, intent(in), optional :: last_byte

begin of region to zero, defaults to 1 if not given. end of region to zero, defaults to size if not given.

type(acc_stream_type), intent(in) :: stream

stream on which zeroing is performed.

private subroutine host2dev_i4_1D(this, hostmem, stream)

Transfers 1D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
integer(kind=int_4), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_i4_2D(this, hostmem, stream)

Transfers 2D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
integer(kind=int_4), DIMENSION(:, :), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine dev2host_i4_1D(this, hostmem, stream)

Transfers GPU devmem to 1D fortran-array.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
integer(kind=int_4), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_i8_1D(this, hostmem, stream)

Transfers 1D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
integer(kind=int_8), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_i8_2D(this, hostmem, stream)

Transfers 2D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
integer(kind=int_8), DIMENSION(:, :), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine dev2host_i8_1D(this, hostmem, stream)

Transfers GPU devmem to 1D fortran-array.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
integer(kind=int_8), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_r4_1D(this, hostmem, stream)

Transfers 1D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
real(kind=real_4), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_r4_2D(this, hostmem, stream)

Transfers 2D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
real(kind=real_4), DIMENSION(:, :), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine dev2host_r4_1D(this, hostmem, stream)

Transfers GPU devmem to 1D fortran-array.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
real(kind=real_4), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_r8_1D(this, hostmem, stream)

Transfers 1D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
real(kind=real_8), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_r8_2D(this, hostmem, stream)

Transfers 2D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
real(kind=real_8), DIMENSION(:, :), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine dev2host_r8_1D(this, hostmem, stream)

Transfers GPU devmem to 1D fortran-array.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
real(kind=real_8), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_c4_1D(this, hostmem, stream)

Transfers 1D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
complex(kind=real_4), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_c4_2D(this, hostmem, stream)

Transfers 2D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
complex(kind=real_4), DIMENSION(:, :), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine dev2host_c4_1D(this, hostmem, stream)

Transfers GPU devmem to 1D fortran-array.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
complex(kind=real_4), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_c8_1D(this, hostmem, stream)

Transfers 1D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
complex(kind=real_8), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine host2dev_c8_2D(this, hostmem, stream)

Transfers 2D fortran-array from host to GPU devmem.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
complex(kind=real_8), DIMENSION(:, :), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream

private subroutine dev2host_c8_1D(this, hostmem, stream)

Transfers GPU devmem to 1D fortran-array.

Arguments

Type IntentOptional Attributes Name
type(acc_devmem_type), intent(in) :: this
complex(kind=real_8), DIMENSION(:), POINTER :: hostmem
type(acc_stream_type), intent(in) :: stream