make cp src-HCD-5D
[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 #endif
54 cd    print *,' in SET_TIMERS stime=',stime
55       return 
56       end
57 C------------------------------------------------------------------------------
58       logical function stopx(nf)
59 C This function returns .true. if one of the following reasons to exit SUMSL
60 C occurs. The "reason" code is stored in WHATSUP passed thru a COMMON block:
61 C
62 C... WHATSUP = 0 - go on, no reason to stop. Stopx will return .false.
63 C...           1 - Time up in current node;
64 C...           2 - STOP signal was received from another node because the
65 C...               node's task was accomplished (parallel only);
66 C...          -1 - STOP signal was received from another node because of error;
67 C...          -2 - STOP signal was received from another node, because 
68 C...               the node's time was up.
69       implicit none
70       include 'DIMENSIONS'
71       integer nf
72       logical ovrtim
73 #ifdef MP
74       include 'mpif.h'
75       include 'COMMON.INFO'
76 #endif
77       include 'COMMON.IOUNITS'
78       include 'COMMON.TIME1'
79       integer Kwita
80
81 cd    print *,'Processor',MyID,' NF=',nf
82 #ifndef MPI
83       if (ovrtim()) then
84 C Finish if time is up.
85          stopx = .true.
86          WhatsUp=1
87 #ifdef MPL
88       else if (mod(nf,100).eq.0) then
89 C Other processors might have finished. Check this every 100th function 
90 C evaluation.
91 C Master checks if any other processor has sent accepted conformation(s) to it. 
92          if (MyID.ne.MasterID) call receive_mcm_info
93          if (MyID.eq.MasterID) call receive_conf
94 cd       print *,'Processor ',MyID,' is checking STOP: nf=',nf
95          call recv_stop_sig(Kwita)
96          if (Kwita.eq.-1) then
97            write (iout,'(a,i4,a,i5)') 'Processor',
98      &     MyID,' has received STOP signal in STOPX; NF=',nf
99            write (*,'(a,i4,a,i5)') 'Processor',
100      &     MyID,' has received STOP signal in STOPX; NF=',nf
101            stopx=.true.
102            WhatsUp=2
103          elseif (Kwita.eq.-2) then
104            write (iout,*)
105      &    'Processor',MyID,' received TIMEUP-STOP signal in SUMSL.'
106            write (*,*)
107      &    'Processor',MyID,' received TIMEUP-STOP signal in SUMSL.'
108            WhatsUp=-2
109            stopx=.true.  
110          else if (Kwita.eq.-3) then
111            write (iout,*)
112      &    'Processor',MyID,' received ERROR-STOP signal in SUMSL.'
113            write (*,*)
114      &    'Processor',MyID,' received ERROR-STOP signal in SUMSL.'
115            WhatsUp=-1
116            stopx=.true.
117          else
118            stopx=.false.
119            WhatsUp=0
120          endif
121 #endif
122       else
123          stopx = .false.
124          WhatsUp=0
125       endif
126 #else
127       stopx=.false.
128 #endif
129
130 #ifdef OSF
131 c Check for FOUND_NAN flag
132       if (FOUND_NAN) then
133         write(iout,*)"   ***   stopx : Found a NaN"
134         stopx=.true.
135       endif
136 #endif
137
138       return
139       end
140 C--------------------------------------------------------------------------
141       logical function ovrtim() 
142       implicit none
143       include 'DIMENSIONS'
144       include 'COMMON.IOUNITS'
145       include 'COMMON.TIME1'
146       real*8 tcpu,curtim
147 #ifdef MPI
148       include "mpif.h"
149       curtim = MPI_Wtime()-walltime
150 #else
151       curtim= tcpu()
152 #endif
153 C  curtim is the current time in seconds.
154 c      write (iout,*) "curtim",curtim," timlim",timlim," safety",safety
155       if (curtim .ge. timlim - safety) then
156         write (iout,'(a,f10.2,a,f10.2,a,f10.2,a)') 
157      &  "***************** Elapsed time (",curtim,
158      &  " s) is within the safety limit (",safety,
159      &  " s) of the allocated time (",timlim," s). Terminating."
160         ovrtim=.true.
161       else
162         ovrtim=.false.
163       endif
164       return                                               
165       end
166 **************************************************************************      
167       double precision function tcpu()
168       implicit none
169       include 'COMMON.TIME1'
170       double precision seconds
171 #ifdef ES9000 
172 ****************************
173 C Next definition for EAGLE (ibm-es9000)
174       real*8 micseconds
175       integer rcode
176       tcpu=cputime(micseconds,rcode)
177       tcpu=(micseconds/1.0E6) - stime
178 ****************************
179 #endif
180 #ifdef SUN
181 ****************************
182 C Next definitions for sun
183       REAL*8  ECPU,ETIME,ETCPU
184       dimension tarray(2)
185       tcpu=etime(tarray)
186       tcpu=tarray(1)
187 ****************************
188 #endif
189 #ifdef KSR
190 ****************************
191 C Next definitions for ksr
192 C this function uses the ksr timer ALL_SECONDS from the PMON library to
193 C return the elapsed time in seconds
194       tcpu= all_seconds() - stime
195 ****************************
196 #endif
197 #ifdef SGI
198 ****************************
199 C Next definitions for sgi
200       real timar(2), etime
201       seconds = etime(timar)
202 Cd    print *,'seconds=',seconds,' stime=',stime
203 C      usrsec = timar(1)
204 C      syssec = timar(2)
205       tcpu=seconds - stime
206 ****************************
207 #endif
208
209 #ifdef LINUX
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
222 #ifdef CRAY
223 ****************************
224 C Next definitions for Cray
225 C     call date(curdat)
226 C     curdat=curdat(1:9)
227 C     call clock(curtim)
228 C     curtim=curtim(1:8)
229       cpusec = second()
230       tcpu=cpusec - stime
231 ****************************
232 #endif
233 #ifdef AIX
234 ****************************
235 C Next definitions for RS6000
236        integer*4 i1,mclock
237        i1 = mclock()
238        tcpu = (i1+0.0D0)/100.0D0
239 #endif
240 #ifdef WINPGI
241 ****************************
242 c next definitions for windows NT Digital fortran
243        real time_real
244        call cpu_time(time_real)
245        tcpu = time_real
246 #endif
247 #ifdef WINIFL
248 ****************************
249 c next definitions for windows NT Digital fortran
250        real time_real
251        call cpu_time(time_real)
252        tcpu = time_real
253 #endif
254
255       return     
256       end  
257 C---------------------------------------------------------------------------
258       subroutine dajczas(rntime,hrtime,mintime,sectime)
259       implicit none
260       include 'COMMON.IOUNITS'
261       real*8 rntime,hrtime,mintime,sectime 
262       integer ihr,imn,isc
263       hrtime=rntime/3600.0D0 
264       hrtime=dint(hrtime)
265       mintime=dint((rntime-3600.0D0*hrtime)/60.0D0)
266       sectime=dint((rntime-3600.0D0*hrtime-60.0D0*mintime)+0.5D0)
267       if (sectime.eq.60.0D0) then
268         sectime=0.0D0
269         mintime=mintime+1.0D0
270       endif
271       ihr=hrtime
272       imn=mintime
273       isc=sectime
274       write (iout,328) ihr,imn,isc
275   328 FORMAT(//'***** Computation time: ',I4  ,' hours ',I2  ,
276      1         ' minutes ', I2  ,' seconds *****')       
277       return
278       end
279 C---------------------------------------------------------------------------
280       subroutine print_detailed_timing
281       implicit none
282       include 'DIMENSIONS'
283 #ifdef MPI
284       include 'mpif.h'
285       double precision time1
286 #endif
287       include 'COMMON.IOUNITS'
288       include 'COMMON.TIME1'
289       include 'COMMON.SETUP'
290 #ifdef MPI
291       time1=MPI_WTIME()
292          write (iout,'(80(1h=)/a/(80(1h=)))') 
293      &    "Details of FG communication time"
294          write (*,'(7(a40,1pe15.5/),40(1h-)/a40,1pe15.5/80(1h=))') 
295      &    "BROADCAST:",time_bcast,"REDUCE:",time_reduce,
296      &    "GATHER:",time_gather,
297      &    "SCATTER:",time_scatter,"SENDRECV:",time_sendrecv,
298      &    "BARRIER ene",time_barrier_e,
299      &    "BARRIER grad",time_barrier_g,
300      &    "TOTAL:",
301      &    time_bcast+time_reduce+time_gather+time_scatter+time_sendrecv
302          write (*,*) fg_rank,myrank,
303      &     ': Total wall clock time',time1-walltime,' sec'
304          write (*,*) "Processor",fg_rank,myrank,
305      &     ": BROADCAST time",time_bcast," REDUCE time",
306      &      time_reduce," GATHER time",time_gather," SCATTER time",
307      &      time_scatter,
308      &     " SCATTER fmatmult",time_scatter_fmatmult,
309      &     " SCATTER ginvmult",time_scatter_ginvmult,
310      &     " SCATTER fmat",time_scatter_fmat,
311      &     " SCATTER ginv",time_scatter_ginv,
312      &      " SENDRECV",time_sendrecv,
313      &      " BARRIER ene",time_barrier_e,
314      &      " BARRIER GRAD",time_barrier_g,
315      &      " BCAST7",time_bcast7," BCASTC",time_bcastc,
316      &      " BCASTW",time_bcastw," ALLREDUCE",time_allreduce,
317      &      " TOTAL",
318      &      time_bcast+time_reduce+time_gather+time_scatter+
319      &      time_sendrecv+time_barrier_g+time_barrier_e+time_bcastc
320          write (*,*) "Processor",fg_rank,myrank," enecalc",time_enecalc
321          write (*,*) "Processor",fg_rank,myrank," sumene",time_sumene
322          write (*,*) "Processor",fg_rank,myrank," intfromcart",
323      &     time_intfcart
324          write (*,*) "Processor",fg_rank,myrank," vecandderiv",
325      &     time_vec
326          write (*,*) "Processor",fg_rank,myrank," setmatrices",
327      &     time_mat
328          write (*,*) "Processor",fg_rank,myrank," ginvmult",
329      &     time_ginvmult
330          write (*,*) "Processor",fg_rank,myrank," fricmatmult",
331      &     time_fricmatmult
332          write (*,*) "Processor",fg_rank,myrank," inttocart",
333      &     time_inttocart
334          write (*,*) "Processor",fg_rank,myrank," sumgradient",
335      &     time_sumgradient
336          write (*,*) "Processor",fg_rank,myrank," intcartderiv",
337      &     time_intcartderiv
338          if (fg_rank.eq.0) then
339            write (*,*) "Processor",fg_rank,myrank," lagrangian",
340      &       time_lagrangian
341            write (*,*) "Processor",fg_rank,myrank," cartgrad",
342      &       time_cartgrad
343          endif
344          write (*,*) "Processor",fg_rank,myrank," SAXS",time_SAXS
345 #else
346          write (*,*) "enecalc",time_enecalc
347          write (*,*) "sumene",time_sumene
348          write (*,*) "intfromcart",time_intfcart
349          write (*,*) "vecandderiv",time_vec
350          write (*,*) "setmatrices",time_mat
351          write (*,*) "ginvmult",time_ginvmult
352          write (*,*) "fricmatmult",time_fricmatmult
353          write (*,*) "inttocart",time_inttocart
354          write (*,*) "sumgradient",time_sumgradient
355          write (*,*) "intcartderiv",time_intcartderiv
356          write (*,*) "lagrangian",time_lagrangian
357          write (*,*) "cartgrad",time_cartgrad
358          write (*,*) "SAXS",time_SAXS
359 #endif
360       return
361       end