unres Adam's changes
[unres.git] / source / unres / src-HCD-5D / timing.F
1 C $Date: 1994/10/05 16:41:52 $
2 C $Revision: 2.2 $
3 C
4 C
5 C
6       subroutine set_timers
7 c
8       implicit none
9       double precision tcpu
10       include 'COMMON.TIME1'
11 #ifdef MP
12       include 'mpif.h'
13 #endif
14 C Diminish the assigned time limit a little so that there is some time to
15 C end a batch job
16 c     timlim=batime-150.0
17 C Calculate the initial time, if it is not zero (e.g. for the SUN).
18       stime=tcpu()
19 #ifdef MPI
20       walltime=MPI_WTIME()
21       time_reduce=0.0d0
22       time_allreduce=0.0d0
23       time_bcast=0.0d0
24       time_gather=0.0d0
25       time_sendrecv=0.0d0
26       time_scatter=0.0d0
27       time_scatter_fmat=0.0d0
28       time_scatter_ginv=0.0d0
29       time_scatter_fmatmult=0.0d0
30       time_scatter_ginvmult=0.0d0
31       time_barrier_e=0.0d0
32       time_barrier_g=0.0d0
33       time_enecalc=0.0d0
34       time_sumene=0.0d0
35       time_lagrangian=0.0d0
36       time_sumgradient=0.0d0
37       time_intcartderiv=0.0d0
38       time_inttocart=0.0d0
39       time_ginvmult=0.0d0
40       time_fricmatmult=0.0d0
41       time_cartgrad=0.0d0
42       time_bcastc=0.0d0
43       time_bcast7=0.0d0
44       time_bcastw=0.0d0
45       time_intfcart=0.0d0
46       time_vec=0.0d0
47       time_mat=0.0d0
48       time_fric=0.0d0
49       time_stoch=0.0d0
50       time_fricmatmult=0.0d0
51       time_fsample=0.0d0
52       time_SAXS=0.0d0
53       time_list=0.0d0
54       time_evdw=0.0d0
55       time_evdw_short=0.0d0
56       time_evdw_long=0.0d0
57       time_eelec=0.0d0
58       time_eelec_short=0.0d0
59       time_eelec_long=0.0d0
60       time_escp=0.0d0
61       time_escp_short=0.0d0
62       time_escp_long=0.0d0
63       time_escpsetup=0.0d0
64       time_escpcalc=0.0d0
65 #endif
66 cd    print *,' in SET_TIMERS stime=',stime
67       return 
68       end
69 C------------------------------------------------------------------------------
70       logical function stopx(nf)
71 C This function returns .true. if one of the following reasons to exit SUMSL
72 C occurs. The "reason" code is stored in WHATSUP passed thru a COMMON block:
73 C
74 C... WHATSUP = 0 - go on, no reason to stop. Stopx will return .false.
75 C...           1 - Time up in current node;
76 C...           2 - STOP signal was received from another node because the
77 C...               node's task was accomplished (parallel only);
78 C...          -1 - STOP signal was received from another node because of error;
79 C...          -2 - STOP signal was received from another node, because 
80 C...               the node's time was up.
81       implicit none
82       include 'DIMENSIONS'
83       integer nf
84       logical ovrtim
85 #ifdef MP
86       include 'mpif.h'
87       include 'COMMON.INFO'
88 #endif
89       include 'COMMON.IOUNITS'
90       include 'COMMON.TIME1'
91       integer Kwita
92
93 cd    print *,'Processor',MyID,' NF=',nf
94 #ifndef MPI
95       if (ovrtim()) then
96 C Finish if time is up.
97          stopx = .true.
98          WhatsUp=1
99 #ifdef MPL
100       else if (mod(nf,100).eq.0) then
101 C Other processors might have finished. Check this every 100th function 
102 C evaluation.
103 C Master checks if any other processor has sent accepted conformation(s) to it. 
104          if (MyID.ne.MasterID) call receive_mcm_info
105          if (MyID.eq.MasterID) call receive_conf
106 cd       print *,'Processor ',MyID,' is checking STOP: nf=',nf
107          call recv_stop_sig(Kwita)
108          if (Kwita.eq.-1) then
109            write (iout,'(a,i4,a,i5)') 'Processor',
110      &     MyID,' has received STOP signal in STOPX; NF=',nf
111            write (*,'(a,i4,a,i5)') 'Processor',
112      &     MyID,' has received STOP signal in STOPX; NF=',nf
113            stopx=.true.
114            WhatsUp=2
115          elseif (Kwita.eq.-2) then
116            write (iout,*)
117      &    'Processor',MyID,' received TIMEUP-STOP signal in SUMSL.'
118            write (*,*)
119      &    'Processor',MyID,' received TIMEUP-STOP signal in SUMSL.'
120            WhatsUp=-2
121            stopx=.true.  
122          else if (Kwita.eq.-3) then
123            write (iout,*)
124      &    'Processor',MyID,' received ERROR-STOP signal in SUMSL.'
125            write (*,*)
126      &    'Processor',MyID,' received ERROR-STOP signal in SUMSL.'
127            WhatsUp=-1
128            stopx=.true.
129          else
130            stopx=.false.
131            WhatsUp=0
132          endif
133 #endif
134       else
135          stopx = .false.
136          WhatsUp=0
137       endif
138 #else
139       stopx=.false.
140 #endif
141
142 #ifdef OSF
143 c Check for FOUND_NAN flag
144       if (FOUND_NAN) then
145         write(iout,*)"   ***   stopx : Found a NaN"
146         stopx=.true.
147       endif
148 #endif
149
150       return
151       end
152 C--------------------------------------------------------------------------
153       logical function ovrtim() 
154       implicit none
155       include 'DIMENSIONS'
156       include 'COMMON.IOUNITS'
157       include 'COMMON.TIME1'
158       real*8 tcpu,curtim
159 #ifdef MPI
160       include "mpif.h"
161       curtim = MPI_Wtime()-walltime
162 #else
163       curtim= tcpu()
164 #endif
165 C  curtim is the current time in seconds.
166 c      write (iout,*) "curtim",curtim," timlim",timlim," safety",safety
167       if (curtim .ge. timlim - safety) then
168         write (iout,'(a,f10.2,a,f10.2,a,f10.2,a)') 
169      &  "***************** Elapsed time (",curtim,
170      &  " s) is within the safety limit (",safety,
171      &  " s) of the allocated time (",timlim," s). Terminating."
172         ovrtim=.true.
173       else
174         ovrtim=.false.
175       endif
176       return                                               
177       end
178 **************************************************************************      
179       double precision function tcpu()
180       implicit none
181       include 'COMMON.TIME1'
182       double precision seconds
183 #ifdef ES9000 
184 ****************************
185 C Next definition for EAGLE (ibm-es9000)
186       real*8 micseconds
187       integer rcode
188       tcpu=cputime(micseconds,rcode)
189       tcpu=(micseconds/1.0E6) - stime
190 ****************************
191 #endif
192 #ifdef SUN
193 ****************************
194 C Next definitions for sun
195       REAL*8  ECPU,ETIME,ETCPU
196       dimension tarray(2)
197       tcpu=etime(tarray)
198       tcpu=tarray(1)
199 ****************************
200 #endif
201 #ifdef KSR
202 ****************************
203 C Next definitions for ksr
204 C this function uses the ksr timer ALL_SECONDS from the PMON library to
205 C return the elapsed time in seconds
206       tcpu= all_seconds() - stime
207 ****************************
208 #endif
209 #ifdef SGI
210 ****************************
211 C Next definitions for sgi
212       real timar(2), etime
213       seconds = etime(timar)
214 Cd    print *,'seconds=',seconds,' stime=',stime
215 C      usrsec = timar(1)
216 C      syssec = timar(2)
217       tcpu=seconds - stime
218 ****************************
219 #endif
220
221 #ifdef LINUX
222 ****************************
223 C Next definitions for sgi
224       real timar(2), etime
225       seconds = etime(timar)
226 Cd    print *,'seconds=',seconds,' stime=',stime
227 C      usrsec = timar(1)
228 C      syssec = timar(2)
229       tcpu=seconds - stime
230 ****************************
231 #endif
232
233
234 #ifdef CRAY
235 ****************************
236 C Next definitions for Cray
237 C     call date(curdat)
238 C     curdat=curdat(1:9)
239 C     call clock(curtim)
240 C     curtim=curtim(1:8)
241       cpusec = second()
242       tcpu=cpusec - stime
243 ****************************
244 #endif
245 #ifdef AIX
246 ****************************
247 C Next definitions for RS6000
248        integer*4 i1,mclock
249        i1 = mclock()
250        tcpu = (i1+0.0D0)/100.0D0
251 #endif
252 #ifdef WINPGI
253 ****************************
254 c next definitions for windows NT Digital fortran
255        real time_real
256        call cpu_time(time_real)
257        tcpu = time_real
258 #endif
259 #ifdef WINIFL
260 ****************************
261 c next definitions for windows NT Digital fortran
262        real time_real
263        call cpu_time(time_real)
264        tcpu = time_real
265 #endif
266
267       return     
268       end  
269 C---------------------------------------------------------------------------
270       subroutine dajczas(rntime,hrtime,mintime,sectime)
271       implicit none
272       include 'COMMON.IOUNITS'
273       real*8 rntime,hrtime,mintime,sectime 
274       integer ihr,imn,isc
275       hrtime=rntime/3600.0D0 
276       hrtime=dint(hrtime)
277       mintime=dint((rntime-3600.0D0*hrtime)/60.0D0)
278       sectime=dint((rntime-3600.0D0*hrtime-60.0D0*mintime)+0.5D0)
279       if (sectime.eq.60.0D0) then
280         sectime=0.0D0
281         mintime=mintime+1.0D0
282       endif
283       ihr=hrtime
284       imn=mintime
285       isc=sectime
286       write (iout,328) ihr,imn,isc
287   328 FORMAT(//'***** Computation time: ',I4  ,' hours ',I2  ,
288      1         ' minutes ', I2  ,' seconds *****')       
289       return
290       end
291 C---------------------------------------------------------------------------
292       subroutine print_detailed_timing
293       implicit none
294       include 'DIMENSIONS'
295 #ifdef MPI
296       include 'mpif.h'
297       double precision time1
298 #endif
299       include 'COMMON.IOUNITS'
300       include 'COMMON.TIME1'
301       include 'COMMON.SETUP'
302       include 'COMMON.MD'
303 #ifdef MPI
304       time1=MPI_WTIME()
305          write (iout,'(80(1h=)/a/(80(1h=)))') 
306      &    "Details of FG communication time"
307          write (*,'(7(a40,1pe15.5/),40(1h-)/a40,1pe15.5/80(1h=))') 
308      &    "BROADCAST:",time_bcast,"REDUCE:",time_reduce,
309      &    "GATHER:",time_gather,
310      &    "SCATTER:",time_scatter,"SENDRECV:",time_sendrecv,
311      &    "BARRIER ene",time_barrier_e,
312      &    "BARRIER grad",time_barrier_g,
313      &    "TOTAL:",
314      &    time_bcast+time_reduce+time_gather+time_scatter+time_sendrecv
315          write (*,*) fg_rank,myrank,
316      &     ': Total wall clock time',time1-walltime,' sec'
317          write (*,*) "Processor",fg_rank,myrank,
318      &     ": BROADCAST time",time_bcast," REDUCE time",
319      &      time_reduce," GATHER time",time_gather," SCATTER time",
320      &      time_scatter,
321      &     " SCATTER fmatmult",time_scatter_fmatmult,
322      &     " SCATTER ginvmult",time_scatter_ginvmult,
323      &     " SCATTER fmat",time_scatter_fmat,
324      &     " SCATTER ginv",time_scatter_ginv,
325      &      " SENDRECV",time_sendrecv,
326      &      " BARRIER ene",time_barrier_e,
327      &      " BARRIER GRAD",time_barrier_g,
328      &      " BCAST7",time_bcast7," BCASTC",time_bcastc,
329      &      " BCASTW",time_bcastw," ALLREDUCE",time_allreduce,
330      &      " TOTAL",
331      &      time_bcast+time_reduce+time_gather+time_scatter+
332      &      time_sendrecv+time_barrier_g+time_barrier_e+time_bcastc
333          write (*,*) "Processor",fg_rank,myrank," enecalc",time_enecalc
334 #ifdef TIMING_ENE
335          if (RESPA) then
336            write (*,*) "Processor",fg_rank,myrank," evdw_long",
337      &       time_evdw_long
338            write (*,*) "Processor",fg_rank,myrank," evdw_short",
339      &       time_evdw_short
340            write (*,*) "Processor",fg_rank,myrank," eelec_long",
341      &       time_eelec_long
342            write (*,*) "Processor",fg_rank,myrank," eelec_short",
343      &       time_eelec_short
344            write (*,*) "Processor",fg_rank,myrank," escp_long",
345      &       time_escp_long
346            write (*,*) "Processor",fg_rank,myrank," escp_short",
347      &       time_escp_short
348          else
349            write (*,*) "Processor",fg_rank,myrank," evdw",time_evdw
350            write (*,*) "Processor",fg_rank,myrank," eelec",time_eelec
351            write (*,*) "Processor",fg_rank,myrank," escp",time_escp
352            write (*,*) "Processor",fg_rank,myrank," escpsetup",
353      &      time_escpsetup
354            write (*,*) "Processor",fg_rank,myrank," escpcalc",
355      &      time_escpcalc
356          endif
357 #endif
358          write (*,*) "Processor",fg_rank,myrank," sumene",time_sumene
359          write (*,*) "Processor",fg_rank,myrank," intfromcart",
360      &     time_intfcart
361          write (*,*) "Processor",fg_rank,myrank," vecandderiv",
362      &     time_vec
363          write (*,*) "Processor",fg_rank,myrank," setmatrices",
364      &     time_mat
365          write (*,*) "Processor",fg_rank,myrank," ginvmult",
366      &     time_ginvmult
367          write (*,*) "Processor",fg_rank,myrank," fricmatmult",
368      &     time_fricmatmult
369          write (*,*) "Processor",fg_rank,myrank," inttocart",
370      &     time_inttocart
371          write (*,*) "Processor",fg_rank,myrank," sumgradient",
372      &     time_sumgradient
373          write (*,*) "Processor",fg_rank,myrank," intcartderiv",
374      &     time_intcartderiv
375          if (fg_rank.eq.0) then
376            write (*,*) "Processor",fg_rank,myrank," lagrangian",
377      &       time_lagrangian
378            write (*,*) "Processor",fg_rank,myrank," cartgrad",
379      &       time_cartgrad
380          endif
381          write (*,*) "Processor",fg_rank,myrank," SAXS",time_SAXS
382 #else
383          write (*,*) "enecalc",time_enecalc
384          write (*,*) "sumene",time_sumene
385          write (*,*) "intfromcart",time_intfcart
386          write (*,*) "vecandderiv",time_vec
387          write (*,*) "setmatrices",time_mat
388          write (*,*) "ginvmult",time_ginvmult
389          write (*,*) "fricmatmult",time_fricmatmult
390          write (*,*) "inttocart",time_inttocart
391          write (*,*) "sumgradient",time_sumgradient
392          write (*,*) "intcartderiv",time_intcartderiv
393          write (*,*) "lagrangian",time_lagrangian
394          write (*,*) "cartgrad",time_cartgrad
395          write (*,*) "SAXS",time_SAXS
396 #endif
397       return
398       end