47 logical,
public :: info
48 logical,
public :: trace
49 logical,
public :: trace_term
50 logical,
public :: trace_file
51 logical :: extra_checks
52 logical,
public :: interaction_graph
53 logical,
public :: interaction_graph_full
54 logical,
public :: propagation_graph
58 type(debug_t),
save :: debug
61 integer,
parameter :: unit_offset = 1000
66 type(debug_t),
intent(out) :: this
67 type(namespace_t),
intent(in) :: namespace
69 character(len=256) :: node_hook
70 logical :: file_exists, mpi_debug_hook
106 call parse_variable(namespace,
'Debug', option__debug__no, this%bits)
130 if (mpi_debug_hook)
then
133 write(stdout,
'(a,i6,a,i6.6,20x,a)')
'* I ',sec,
'.',usec,
' | MPI debug hook'
135 write(stdout,
'(a,i3,a)')
'node:',
mpi_world%rank,
' In debug hook'
137 file_exists = .false.
139 do while (.not. file_exists)
140 inquire(file=
'node_hook.'//node_hook, exist=file_exists)
143 ' - still sleeping. To release me touch: node_hook.'//trim(node_hook)
146 write(stdout,
'(a,i3,a)')
'node:',
mpi_world%rank,
' Leaving debug hook'
152 write(stdout,
'(a,i6,a,i6.6,20x,a)')
'* O ', sec,
'.', usec,
' | MPI debug hook'
161 type(
debug_t),
intent(inout) :: this
165 this%trace_term = .
true.
166 this%trace_file = .
true.
167 this%interaction_graph = .
true.
168 this%interaction_graph_full = .
true.
169 this%propagation_graph = .
true.
176 type(
debug_t),
intent(inout) :: this
187 character(len=6) :: filenum
190 write(filenum,
'(i6.6)') iunit - unit_offset
192 call loct_rm(
'debug/debug_trace.node.'//filenum)
199 integer,
intent(out) :: iunit
201 character(len=6) :: filenum
204 write(filenum,
'(i6.6)') iunit - unit_offset
206 open(iunit, file =
'debug/debug_trace.node.'//filenum, &
207 action=
'write', status=
'unknown', position=
'append')
214 type(
debug_t),
intent(inout) :: this
216 this%info = (
bitand(this%bits, option__debug__info) /= 0)
217 this%trace_term = (
bitand(this%bits, option__debug__trace_term) /= 0)
218 this%trace_file = (
bitand(this%bits, option__debug__trace_file) /= 0)
219 this%trace = (
bitand(this%bits, option__debug__trace) /= 0) .or. this%trace_term .or. this%trace_file
220 this%extra_checks = (
bitand(this%bits, option__debug__extra_checks) /= 0) .or. this%trace_term .or. this%trace_file
221 this%interaction_graph = (
bitand(this%bits, option__debug__interaction_graph) /= 0)
222 this%interaction_graph_full = (
bitand(this%bits, option__debug__interaction_graph_full) /= 0)
223 this%propagation_graph = (
bitand(this%bits, option__debug__propagation_graph) /= 0)
230 integer,
intent(inout) :: sec
231 integer,
intent(inout) :: usec
242 subroutine time_diff(sec1, usec1, sec2, usec2)
243 integer,
intent(in) :: sec1
244 integer,
intent(in) :: usec1
245 integer,
intent(inout) :: sec2
246 integer,
intent(inout) :: usec2
251 if (usec2 - usec1 < 0)
then
252 usec2 = 1000000 + usec2
253 if (sec2 >= sec1)
then
259 if (sec2 >= sec1)
then
262 usec2 = usec2 - usec1
271 character(len=*),
intent(in) :: sub_name
273 integer,
parameter :: max_recursion_level = 50
274 integer iunit, sec, usec
276 if (.not. debug%trace)
return
283 sub_stack(max_recursion_level) =
'debug_push_sub'
284 write(stderr,
'(a,i3,a)')
'Too many recursion levels in debug trace (max=', max_recursion_level,
')'
292 if (debug%trace_file)
then
307 integer,
intent(in) :: iunit_out
310 character(len=1000) :: tmpstr
312 write(tmpstr,
'(a,i6,a,i6.6,f20.6,i8,a)')
"* I ", &
317 write(tmpstr,
'(2a)') trim(tmpstr),
"..|"
320 write(iunit_out,
'(a)') trim(tmpstr)
329 character(len=*),
intent(in) :: sub_name
331 character(len=80) :: sub_name_short
332 integer iunit, sec, usec
334 if (.not. debug%trace)
return
342 write(stderr,
'(a)')
'Too few recursion levels in debug trace'
352 write(stderr,
'(a)')
'Wrong sub name on pop_sub :'
353 write(stderr,
'(2a)')
' got : ', sub_name_short
359 if (debug%trace_file)
then
376 integer,
intent(in) :: iunit_out
379 character(len=1000) :: tmpstr
381 write(tmpstr,
'(a,i6,a,i6.6,f20.6,i8, a)')
"* O ", &
386 write(tmpstr,
'(2a)') trim(tmpstr),
"..|"
390 write(iunit_out,
'(a)') trim(tmpstr)
400 character(len=*),
intent(in) :: filename
404 pos = index(filename,
'src/', back = .
true.)
407 clean_path = filename
410 clean_path = filename(pos+4:)
subroutine pop_sub_write(iunit_out)
subroutine push_sub_write(iunit_out)
character(len=max_path_len) function, public debug_clean_path(filename)
Prune a filename path to only include subdirectories of the "src" directory.
subroutine, public debug_enable(this)
type(debug_t), save, public debug
subroutine, public debug_pop_sub(sub_name)
Pop a routine from the debug trace.
subroutine, public debug_open_trace(iunit)
subroutine, public epoch_time_diff(sec, usec)
subroutine from_bits(this)
subroutine, public debug_init(this, namespace)
subroutine, public debug_disable(this)
subroutine time_diff(sec1, usec1, sec2, usec2)
Computes t2 <- t2-t1. sec1,2 and usec1,2 are seconds,microseconds of t1,2.
subroutine, public debug_push_sub(sub_name)
Push a routine to the debug trace.
subroutine, public debug_delete_trace()
integer, public s_epoch_sec
global epoch time (time at startup)
integer, public no_sub_stack
real(real64), dimension(50), public time_stack
character(len=80), dimension(50), public sub_stack
The stack.
integer, public s_epoch_usec
subroutine, public mpi_debug_init(rank, info)
logical function mpi_grp_is_root(grp)
type(mpi_grp_t), public mpi_world
type(namespace_t), public global_namespace