acc_stream_create Subroutine

public subroutine acc_stream_create(this, name, priority)

Fortran-wrapper for creation of a CUDA/HIP stream.

Arguments

Type IntentOptional Attributes Name
type(acc_stream_type), intent(out) :: this
character(len=*), intent(in) :: name
integer, intent(in), optional :: priority

Source Code

   SUBROUTINE acc_stream_create(this, name, priority)
      !! Fortran-wrapper for creation of a CUDA/HIP stream.

      TYPE(acc_stream_type), INTENT(OUT) :: this
      CHARACTER(LEN=*), INTENT(IN)             :: name
      INTEGER, INTENT(IN), OPTIONAL            :: priority

#if ! defined (__DBCSR_ACC)
      MARK_USED(this)
      MARK_USED(name)
      MARK_USED(priority)
      DBCSR_ABORT("__DBCSR_ACC not compiled in.")
#else
      INTEGER                                  :: istat, my_priority

      my_priority = -1
      IF (PRESENT(priority)) &
         my_priority = priority

      IF (C_ASSOCIATED(this%cptr)) &
         DBCSR_ABORT("acc_stream_create: stream already allocated")

      CALL dbcsr_acc_set_active_device(get_accdrv_active_device_id())
      istat = acc_interface_stream_create(this%cptr, name//c_null_char, my_priority)

      IF (istat /= 0 .OR. .NOT. C_ASSOCIATED(this%cptr)) &
         DBCSR_ABORT("acc_stream_create failed")
#endif
   END SUBROUTINE acc_stream_create