acc_devmem_allocate_bytes Subroutine

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

Source Code

   SUBROUTINE acc_devmem_allocate_bytes(this, size_in_bytes)
      !! Allocates a given devmem.

      TYPE(acc_devmem_type), INTENT(INOUT)     :: this
      INTEGER, INTENT(IN)                      :: size_in_bytes

#if ! defined (__DBCSR_ACC)
      MARK_USED(this)
      MARK_USED(size_in_bytes)
      DBCSR_ABORT("__DBCSR_ACC not compiled in.")
#else
      INTEGER                                  :: istat

      IF (this%size_in_bytes >= 0) &
         DBCSR_ABORT("acc_devmem_alloc: already allocated")
      this%size_in_bytes = size_in_bytes
      IF (size_in_bytes > 0) THEN
         CALL dbcsr_acc_set_active_device(get_accdrv_active_device_id())
         istat = acc_interface_dev_mem_alloc(this%cptr, INT(this%size_in_bytes, KIND=C_SIZE_T))
         IF (istat /= 0) &
            DBCSR_ABORT("acc_devmem_allocate: failed")
      END IF
#endif
   END SUBROUTINE acc_devmem_allocate_bytes