acc_event_record Subroutine

public subroutine acc_event_record(this, stream)

Fortran-wrapper for recording a CUDA/HIP event.

Arguments

Type IntentOptional Attributes Name
type(acc_event_type), intent(in) :: this
type(acc_stream_type), intent(in) :: stream

Source Code

   SUBROUTINE acc_event_record(this, stream)
      !! Fortran-wrapper for recording a CUDA/HIP event.

      TYPE(acc_event_type), INTENT(IN)  :: this
      TYPE(acc_stream_type), INTENT(IN) :: stream

#if ! defined (__DBCSR_ACC)
      MARK_USED(this)
      MARK_USED(stream)
      DBCSR_ABORT("__DBCSR_ACC not compiled in.")
#else
      INTEGER                                  :: istat
      TYPE(C_PTR)                              :: stream_cptr

      stream_cptr = acc_stream_cptr(stream)
      IF (.NOT. C_ASSOCIATED(this%cptr)) &
         DBCSR_ABORT("acc_event_record: event not allocated")
      IF (.NOT. C_ASSOCIATED(stream_cptr)) &
         DBCSR_ABORT("acc_event_record: stream not allocated")
      CALL dbcsr_acc_set_active_device(get_accdrv_active_device_id())
      istat = acc_interface_event_record(this%cptr, stream_cptr)
      IF (istat /= 0) &
         DBCSR_ABORT("acc_event_record failed")
#endif
   END SUBROUTINE acc_event_record