4 ! use mpi, only : mpi_character
7 use da_control
, only
: num_procs
, documentation_url
, use_html
, ierr
, &
8 trace_pe
, trace_memory
, trace_unit
, trace_csv_unit
, &
9 trace_csv
, myproc
, comm
, rootproc
, trace_max_depth
, &
10 trace_repeat_head
, trace_repeat_body
, trace_start_points
, trace_all_pes
11 use da_par_util1
, only
: da_proc_sum_ints
, da_proc_sum_real
, da_proc_sum_int
12 use da_reporting
, only
: da_error
19 subroutine da_memory(memory_used
)
20 integer, intent(out
) :: memory_used
21 end subroutine da_memory
24 integer, parameter :: TraceIndentAmount
= 2 ! default indent
25 integer, parameter :: MaxNoRoutines
= 440 ! maxium number of subroutines
26 integer, parameter :: TraceNameLen
= 31 ! Length of trace name
28 character (LEN
=*), parameter :: &
34 integer :: TraceDepth
! Current depth of trace
35 integer :: NoRoutines
! Number of routines so far
36 integer :: NoCalls(MaxNoRoutines
) ! Number of calls to each routine
37 integer :: NoCallsBody(MaxNoRoutines
) ! Number of calls in body of each routine
38 integer :: CalledBy(MaxNoRoutines
)
39 integer :: MaxHeap(MaxNoRoutines
)
40 integer :: EntryHeap(MaxNoRoutines
)
41 integer :: Pointer ! pointer to routine arrays in TIMER.
42 integer :: BaseElapsedTime
46 ! All CPU times in seconds
48 real :: CPUTimeStart(MaxNoRoutines
)
49 real :: CPUTimeLocalStart
50 real :: CPUTime(MaxNoRoutines
)
51 real :: CPUTimeLocal(MaxNoRoutines
)
52 real :: CPUTimeThisCall(MaxNoRoutines
)
54 ! All Elapsed times based on wall clock in seconds
56 real :: ElapsedTimeStart(MaxNoRoutines
)
57 real :: ElapsedTimeLocalStart
58 real :: ElapsedTime(MaxNoRoutines
)
59 real :: ElapsedTimeLocal(MaxNoRoutines
)
60 real :: ElapsedTimeThisCall(MaxNoRoutines
)
62 logical :: TraceActive
= .false
. ! Is it active in this routine?
64 character (LEN
=TraceNameLen
) :: TraceStartedBy
! Subroutine name
65 ! that activated trace
66 character (LEN
=TraceNameLen
) :: TimerNames(MaxNoRoutines
) ! Subroutine names
67 character (LEN
=TraceNameLen
) :: TraceNames(MaxNoRoutines
) ! for timing and tracing
69 logical :: trace_write
= .false
.
74 #
include "da_trace_init.inc"
75 #
include "da_trace_entry.inc"
76 #
include "da_trace.inc"
77 #
include "da_trace_exit.inc"
78 #
include "da_trace_int_sort.inc"
79 #
include "da_trace_real_sort.inc"
80 #
include "da_trace_report.inc"