27!||====================================================================
33#include "implicit_f.inc"
44 WRITE(procnam,
'(I4.4)')ispmd+1
45 filnam=rootnam(1:rootlen)//
'_'//chrun//
'_'//procnam//
'.int'
46 OPEN(unit=4999,file=filnam(1:rootlen+15),action=
'write',
47 . access=
'SEQUENTIAL',
48 . form=
'FORMATTED',status=
'UNKNOWN')
61#include "implicit_f.inc"
85#include "implicit_f.inc"
98 DOUBLE PRECISION :: tic
102 this%TIME(event,2)=tic
104 this%TIME(event,1:2)=0.0d0
114!||--- uses -----------------------------------------------------
125#include "implicit_f.inc"
138 DOUBLE PRECISION :: toc
142 this%TIME(event,1)=this%TIME(event,1) + (toc - this%TIME(event,2))
145 this%TIME(event,1)=this%TIME(event,1) + (toc - this%TIME(event,2))
149!||====================================================================
168#include "implicit_f.inc"
172#include "com01_c.inc"
173#include "com04_c.inc"
174#include "units_c.inc"
176#include "timerr_c.inc"
177#include "param_c.inc"
181 INTEGER,
INTENT(IN) :: NBINTC
182 INTEGER,
INTENT(IN) :: INTLIST(NBINTC),IPARI(,NINTER)
183 TYPE(intbuf_struct_),
DIMENSION(NINTER),
INTENT(IN) :: INTBUF_TAB
184 DOUBLE PRECISION :: TRESHOLD
188 DOUBLE PRECISION,
DIMENSION(:),
ALLOCATABLE :: SENDBUF
189 DOUBLE PRECISION,
DIMENSION(:,:),
ALLOCATABLE :: RECVBUF
191 DOUBLE PRECISION,
DIMENSION(:),
ALLOCATABLE :: RATIO
192 DOUBLE PRECISION,
DIMENSION(:,:,:),
ALLOCATABLE :: SUMMARY
193 DOUBLE PRECISION ::PMAX,TOTAL_TIME
194 INTEGER :: NB_PRINTED_INTERF
204 ALLOCATE(ratio(nbintc))
207 ALLOCATE(recvbuf(1,1))
209 ALLOCATE(summary(1,1,1))
219 sendbuf(j +
i_noint )=dble(intbuf_tab(n)%METRIC%NOINT )
220 sendbuf(j +
i_multimp )=dble(intbuf_tab(n)%METRIC%MULTIMP )
221 sendbuf(j +
i_nsn )=dble(intbuf_tab(n)%METRIC%NSN )
222 sendbuf(j +
i_nsnr )=dble(intbuf_tab(n)%METRIC%NSNR )
223 sendbuf(j +
i_ncont )=dble(intbuf_tab(n)%METRIC%NCONT )
234 nb_printed_interf = 0
235 ratio(1:nbintc) = 0.0d0
242 ratio(i) =
max(ratio(i),
264 IF(total_time > pmax)
THEN
272 IF(ratio(i) > treshold) nb_printed_interf = nb_printed_interf + 1
274 IF(nb_printed_interf > 0)
THEN
277 .
' ** INTERFACE SUMMARY **'
280 IF(ratio(i) > treshold)
THEN
284 .
'INTERFACE ID:',intbuf_tab(n)%METRIC%NOINT,
' TYPE: ',ipari(7,n)
285 WRITE(iout,
'(A,F12.3,A)')
286 .
'REMOTE SECONDARY:',summary(
i_nsnr,1,i)/summary(
i_nsn,1,i),
'%'
287 WRITE(iout,*)
'TIME (s) MAX AVG'
288 WRITE(iout,
'(A,2F12.2)')
290 WRITE(iout,
'(A,2F12.3)')
292 WRITE(iout,
'(A,2F12.3)')
294 WRITE(iout,
'(A,2F12.3)')
303 DEALLOCATE(ratio,sendbuf,recvbuf,summary)
double precision function mpi_wtime()
integer, parameter i_main_tri
integer, parameter size_metric
integer, parameter i_nsnr
integer, parameter i_ncont
integer, parameter i_main_opt_tri
integer, parameter i_main_forces
integer, parameter i_multimp
integer, parameter i_main_crit_tri
integer, parameter i_noint
integer, parameter file_id
subroutine spmd_dgather(sendbuf, length, recvbuf, rank)
subroutine close_interf_time()
subroutine open_interf_time(ispmd)
subroutine int_stoptime(this, event)
subroutine int_startime(this, event)
subroutine printime_interf(intbuf_tab, ipari, intlist, nbintc, treshold)