dbcsr_init_lib_hooks Subroutine

private subroutine dbcsr_init_lib_hooks(mp_comm, in_timeset_hook, in_timestop_hook, in_abort_hook, in_warn_hook, io_unit, accdrv_active_device_id)

Initialize the DBCSR library using external loggers and timer callbacks We do not need this routine within the library, so we keep the communicator as a handle and convert it here to a communicator type

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: mp_comm
procedure(timeset_interface), intent(in), POINTER :: in_timeset_hook
procedure(timestop_interface), intent(in), POINTER :: in_timestop_hook
procedure(dbcsr_abort_interface), intent(in), POINTER :: in_abort_hook
procedure(dbcsr_warn_interface), intent(in), POINTER :: in_warn_hook
integer, intent(in), optional :: io_unit
integer, intent(in), optional :: accdrv_active_device_id

Source Code

   SUBROUTINE dbcsr_init_lib_hooks(mp_comm, &
                                   in_timeset_hook, in_timestop_hook, &
                                   in_abort_hook, in_warn_hook, io_unit, &
                                   accdrv_active_device_id)
      !! Initialize the DBCSR library using external loggers and timer callbacks
      !! We do not need this routine within the library, so we keep the communicator as a handle
      !! and convert it here to a communicator type
      INTEGER, INTENT(IN)  :: mp_comm
      PROCEDURE(timeset_interface), INTENT(IN), POINTER :: in_timeset_hook
      PROCEDURE(timestop_interface), INTENT(IN), POINTER :: in_timestop_hook
      PROCEDURE(dbcsr_abort_interface), INTENT(IN), POINTER :: in_abort_hook
      PROCEDURE(dbcsr_warn_interface), INTENT(IN), POINTER :: in_warn_hook
      INTEGER, INTENT(IN), OPTIONAL :: io_unit, accdrv_active_device_id

      TYPE(mp_comm_type) :: my_mp_comm

      IF (is_initialized) THEN
         ! Update ext_io_unit
         IF (.NOT. ASSOCIATED(logger) .AND. PRESENT(io_unit)) ext_io_unit = io_unit
         RETURN
      END IF
      CALL my_mp_comm%set_handle(mp_comm)
      CALL dbcsr_init_lib_pre(my_mp_comm, io_unit, accdrv_active_device_id)
      ! abort/warn hooks
      dbcsr_abort_hook => in_abort_hook
      dbcsr_warn_hook => in_warn_hook
      ! timeset/timestop hooks
      timeset_hook => in_timeset_hook
      timestop_hook => in_timestop_hook
      ! timer environment is assumed
      !
      CALL dbcsr_init_lib_low()
   END SUBROUTINE dbcsr_init_lib_hooks