timings_setup_tracing Subroutine

public subroutine timings_setup_tracing(trace_max, unit_nr, trace_str, routine_names)

Set routine tracer

Arguments

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

maximum number of calls reported per routine. Setting this to zero disables tracing. output unit used for printing the trace-messages

integer, intent(in) :: unit_nr

maximum number of calls reported per routine. Setting this to zero disables tracing. output unit used for printing the trace-messages

character(len=13), intent(in) :: trace_str

short info-string which is printed along with every message

character(len=default_string_length), intent(in), optional, DIMENSION(:) :: routine_names

List of routine-names. If provided only these routines will be traced. If not present all routines will traced.


Source Code

   SUBROUTINE timings_setup_tracing(trace_max, unit_nr, trace_str, routine_names)
      !! Set routine tracer

      INTEGER, INTENT(IN)                                :: trace_max, unit_nr
         !! maximum number of calls reported per routine. Setting this to zero disables tracing.
         !! output unit used for printing the trace-messages
      CHARACTER(len=13), INTENT(IN)                      :: trace_str
         !! short info-string which is printed along with every message
      CHARACTER(len=default_string_length), &
         DIMENSION(:), INTENT(IN), OPTIONAL              :: routine_names
         !! List of routine-names. If provided only these routines will be traced. If not present all routines will traced.

      INTEGER                                            :: i, routine_id
      TYPE(routine_stat_type), POINTER                   :: r_stat
      TYPE(timer_env_type), POINTER                      :: timer_env

      timer_env => list_peek(timers_stack)
      timer_env%trace_max = trace_max
      timer_env%trace_unit = unit_nr
      timer_env%trace_str = trace_str
      timer_env%trace_all = .TRUE.
      IF (.NOT. PRESENT(routine_names)) RETURN

      ! setup routine-specific tracing
      timer_env%trace_all = .FALSE.
      DO i = 1, SIZE(routine_names)
         routine_id = routine_name2id(routine_names(i))
         r_stat => list_get(timer_env%routine_stats, routine_id)
         r_stat%trace = .TRUE.
      END DO

   END SUBROUTINE timings_setup_tracing