LMDZ
yomgstats.F90
Go to the documentation of this file.
1 MODULE yomgstats
2 
3 USE parkind1 ,ONLY : jpim ,jprb
4 
5 IMPLICIT NONE
6 
7 SAVE
8 
9 ! ------------------------------------------------------------------
10 ! Module for timing statistics. Module is internal to the GSTATS package -
11 ! routines GSTATS, SUSTATS and STATS_OUTPUT. The logical switches are
12 ! re-initialized in SUMPINI
13 
14 ! LSTATS - TRUE for gathering timing statistics
15 ! LSTATSCPU - TRUE for gathering CPU timing statistics
16 ! LSYNCSTATS - TRUE for syncronization (call to barrier) at the
17 ! start of timing event
18 ! LDETAILED_STATS - TRUE for more detail in output
19 ! LSTATS_OMP - TRUE for gathering timing statistics on OpenMP regions
20 ! 1001-1999
21 ! LSTATS_COMMS - TRUE for gathering detailed timing of Message passing
22 ! 501-1000
23 ! NTRACE_STATS - max number of entries in trace
24 ! LTRACE_STATS - True for trace of all calls to gstats
25 ! LGSTATS_LABEL - True after GSTATS-labels have been set
26 ! JPMAXSTAT - max number of separate timers in gstats
27 ! JPOBCOUNT_BASE - first counter for obs types
28 ! NCALLS - number of times a timer has been switched on
29 ! TIMESUM - total time spent with timer on
30 ! TIMESQSUM - sum of the squares of times
31 ! TIMEMAX - max time of all calls
32 ! TIMESUMB - sum of times between previous timer was invoked and this
33 ! timer was switched on ( to be used for finding out which parts
34 ! of the code that is not being timed)
35 ! TIMELCALL - time when event was switched on or resumed
36 ! TTCPUSUM - total cpu time
37 ! TVCPUSUM - total vector cpu time
38 ! THISTIME - total accumulated time for this call to timing event (necessary
39 ! to be able to suspend and resume timer and still have it counted
40 ! as one timing event)
41 ! THISTCPU - as THISTIME but for CPU time
42 ! THISVCPU - as THISTIME but for vector CPU time
43 ! TTCPULCALL - as TIMELCALL but for CPU time
44 ! TVCPULCALL - as TIMELCALL but for vector CPU time
45 ! TIME_LAST_CALL - last time GSTATS was called
46 ! TIME_START - used for recording parallel startup time
47 
48 
49 LOGICAL :: lstats = .true.
50 LOGICAL :: lstats_omp = .false.
51 LOGICAL :: lstats_comms = .false.
52 LOGICAL :: lstats_mem = .false.
53 LOGICAL :: lstats_alloc = .false.
54 LOGICAL :: lstatscpu = .true.
55 LOGICAL :: lsyncstats = .false.
56 LOGICAL :: ldetailed_stats = .true.
57 LOGICAL :: lbarrier_stats = .false.
58 LOGICAL :: ltrace_stats = .false.
59 LOGICAL :: lgstats_label = .false.
60 
61 INTEGER(KIND=JPIM),PARAMETER :: jpmaxstat=2500
62 
63 INTEGER(KIND=JPIM),PARAMETER :: jpobcount_base=201
64 INTEGER(KIND=JPIM) :: ntrace_stats=0
65 INTEGER(KIND=JPIM) :: ncalls(0:jpmaxstat)
66 INTEGER(KIND=JPIM) :: ncalls_total=0
67 INTEGER(KIND=JPIM),ALLOCATABLE :: ncall_trace(:)
68 
69 REAL(KIND=JPRB) :: timesum(0:jpmaxstat)
70 REAL(KIND=JPRB) :: timesqsum(0:jpmaxstat)
71 REAL(KIND=JPRB) :: timemax(0:jpmaxstat)
72 REAL(KIND=JPRB) :: timesumb(0:jpmaxstat)
73 REAL(KIND=JPRB) :: timelcall(0:jpmaxstat)
74 REAL(KIND=JPRB) :: ttcpusum(0:jpmaxstat)
75 REAL(KIND=JPRB) :: tvcpusum(0:jpmaxstat)
76 REAL(KIND=JPRB) :: thistime(0:jpmaxstat)
77 REAL(KIND=JPRB) :: thistcpu(0:jpmaxstat)
78 REAL(KIND=JPRB) :: thisvcpu(0:jpmaxstat)
79 REAL(KIND=JPRB) :: ttcpulcall(0:jpmaxstat)
80 REAL(KIND=JPRB) :: tvcpulcall(0:jpmaxstat)
81 REAL(KIND=JPRB) :: time_last_call
82 
83 REAL(KIND=JPRB),ALLOCATABLE :: time_start(:)
84 REAL(KIND=JPRB),ALLOCATABLE :: time_trace(:)
85 INTEGER(KIND=JPIM),PARAMETER :: jperr=0
86 INTEGER(KIND=JPIM),PARAMETER :: jptagstat=20555
87 
88 CHARACTER*50 :: ccdesc(0:jpmaxstat) = ""
89 CHARACTER*3 :: cctype(0:jpmaxstat) = ""
90 
91 INTEGER(KIND=JPIM) :: nproc_stats = 1
92 INTEGER(KIND=JPIM) :: myproc_stats = 1
93 INTEGER(KIND=JPIM),ALLOCATABLE :: nprcids_stats(:)
94 
95 INTEGER(KIND=JPIM) :: ntmem(0:jpmaxstat,5)
96 INTEGER(KIND=JPIM) :: nstats_mem=0
97 
98 INTEGER(KIND=JPIM) :: nprnt_stats=3
99 
100 !$OMP THREADPRIVATE(ccdesc,cctype,lbarrier_stats,ldetailed_stats,lgstats_label,lstats,lstats_alloc)
101 !$OMP THREADPRIVATE(lstats_comms,lstats_mem,lstats_omp,lstatscpu,lsyncstats,ltrace_stats,myproc_stats)
102 !$OMP THREADPRIVATE(ncalls,ncalls_total,nprnt_stats,nproc_stats,nstats_mem,ntmem,ntrace_stats,thistcpu)
103 !$OMP THREADPRIVATE(thistime,thisvcpu,time_last_call,timelcall,timemax,timesqsum,timesum,timesumb)
104 !$OMP THREADPRIVATE(ttcpulcall,ttcpusum,tvcpulcall,tvcpusum)
105 !$OMP THREADPRIVATE(ncall_trace,nprcids_stats,time_start,time_trace)
106 END MODULE yomgstats
107 
108 
109 
110 
real(kind=jprb), dimension(0:jpmaxstat) thisvcpu
Definition: yomgstats.F90:78
real(kind=jprb), dimension(0:jpmaxstat) ttcpulcall
Definition: yomgstats.F90:79
integer(kind=jpim), dimension(0:jpmaxstat, 5) ntmem
Definition: yomgstats.F90:95
integer(kind=jpim) myproc_stats
Definition: yomgstats.F90:92
real(kind=jprb), dimension(0:jpmaxstat) ttcpusum
Definition: yomgstats.F90:74
integer(kind=jpim), parameter jptagstat
Definition: yomgstats.F90:86
real(kind=jprb), dimension(0:jpmaxstat) tvcpulcall
Definition: yomgstats.F90:80
real(kind=jprb) time_last_call
Definition: yomgstats.F90:81
real(kind=jprb), dimension(0:jpmaxstat) timesum
Definition: yomgstats.F90:69
real(kind=jprb), dimension(0:jpmaxstat) timemax
Definition: yomgstats.F90:71
real(kind=jprb), dimension(0:jpmaxstat) tvcpusum
Definition: yomgstats.F90:75
integer(kind=jpim) nproc_stats
Definition: yomgstats.F90:91
integer(kind=jpim) nstats_mem
Definition: yomgstats.F90:96
real(kind=jprb), dimension(:), allocatable time_start
Definition: yomgstats.F90:83
integer(kind=jpim), parameter jpmaxstat
Definition: yomgstats.F90:61
real(kind=jprb), dimension(:), allocatable time_trace
Definition: yomgstats.F90:84
integer(kind=jpim) ntrace_stats
Definition: yomgstats.F90:64
integer(kind=jpim), dimension(:), allocatable ncall_trace
Definition: yomgstats.F90:67
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
logical lstats_alloc
Definition: yomgstats.F90:53
real(kind=jprb), dimension(0:jpmaxstat) timesqsum
Definition: yomgstats.F90:70
integer, parameter jprb
Definition: parkind1.F90:31
real(kind=jprb), dimension(0:jpmaxstat) timesumb
Definition: yomgstats.F90:72
logical ltrace_stats
Definition: yomgstats.F90:58
character *3, dimension(0:jpmaxstat) cctype
Definition: yomgstats.F90:89
logical lsyncstats
Definition: yomgstats.F90:55
logical lstatscpu
Definition: yomgstats.F90:54
character *50, dimension(0:jpmaxstat) ccdesc
Definition: yomgstats.F90:88
integer(kind=jpim), dimension(:), allocatable nprcids_stats
Definition: yomgstats.F90:93
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
integer(kind=jpim), parameter jperr
Definition: yomgstats.F90:85
integer(kind=jpim) nprnt_stats
Definition: yomgstats.F90:98
logical lstats_comms
Definition: yomgstats.F90:51
real(kind=jprb), dimension(0:jpmaxstat) thistcpu
Definition: yomgstats.F90:77
integer(kind=jpim) ncalls_total
Definition: yomgstats.F90:66
logical lbarrier_stats
Definition: yomgstats.F90:57
integer, parameter jpim
Definition: parkind1.F90:13
logical lgstats_label
Definition: yomgstats.F90:59
logical ldetailed_stats
Definition: yomgstats.F90:56
integer(kind=jpim), dimension(0:jpmaxstat) ncalls
Definition: yomgstats.F90:65
logical lstats_omp
Definition: yomgstats.F90:50
logical lstats
Definition: yomgstats.F90:49
real(kind=jprb), dimension(0:jpmaxstat) thistime
Definition: yomgstats.F90:76
logical lstats_mem
Definition: yomgstats.F90:52
integer(kind=jpim), parameter jpobcount_base
Definition: yomgstats.F90:63
real(kind=jprb), dimension(0:jpmaxstat) timelcall
Definition: yomgstats.F90:73