OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
timer.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| initime ../starter/source/system/timer.F
25!||--- called by ------------------------------------------------------
26!|| starter0 ../starter/source/starter/starter0.F
27!||--- calls -----------------------------------------------------
28!||====================================================================
29 SUBROUTINE initime()
30C initialisation des timers
31C timer signification
32C
33C 1 translator
34C 2 lecture total (including ddsplit)
35c 3 ddsplit
36c 4 freeform
37c 5 IPARI_L_INI
38c 6 INTBUF_INI
39c 7 SPLIT_INTERFACES
40c 8 W_FI
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C G l o b a l P a r a m e t e r s
47C----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "scr05_c.inc"
51#include "timer_c.inc"
52 COMMON /iclock/clock0
53 INTEGER CLOCK0
54 COMMON /rclock/elapsed
55 DOUBLE PRECISION ELAPSED
56
57#ifdef _OPENMP
58 INTEGER OMP_GET_THREAD_NUM, OMP_GET_NUM_THREADS
59 EXTERNAL omp_get_thread_num, omp_get_num_threads
60 REAL(kind=8) omp_get_wtime
61 external OMP_get_wtime
62#endif
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 INTEGER I, J
67C-----------------------------------------------
68 DO i =1, nthmax
69 DO j = 1, ntimax
70 cputime(j,i) = zero
71 realtime(j,i) = zero
72 ENDDO
73 ENDDO
74 CALL system_clock(clock0) ! recuperation du temps de debut dans clock0
75 elapsed = zero ! initialisation a zero de l'elapsed time
76
77#ifdef _OPENMP
78 omp_starting_time = omp_get_wtime( )
79#endif
80
81 RETURN
82 END
83!||====================================================================
84!|| startime ../starter/source/system/timer.F
85!||--- called by ------------------------------------------------------
86!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
87!|| lectur ../starter/source/starter/lectur.F
88!|| starter0 ../starter/source/starter/starter0.F
89!||--- calls -----------------------------------------------------
90!|| my_etime ../starter/source/system/machine.F
91!||====================================================================
92 SUBROUTINE startime(EVENT,ITASK)
93C routine d'incrementation du timer event
94C-----------------------------------------------
95C I m p l i c i t T y p e s
96C-----------------------------------------------
97#include "implicit_f.inc"
98C-----------------------------------------------
99C G l o b a l P a r a m e t e r s
100C-----------------------------------------------
101C C o m m o n B l o c k s
102C-----------------------------------------------
103#include "scr05_c.inc"
104#include "timer_c.inc"
105C-----------------------------------------------
106C D u m m y A r g u m e n t s
107C-----------------------------------------------
108 INTEGER EVENT,ITASK
109C-----------------------------------------------
110C L o c a l V a r i a b l e s
111C-----------------------------------------------
112#ifdef _OPENMP
113 REAL(kind=8) omp_get_wtime
114 external OMP_GET_WTIME
115#endif
116C
117 CALL my_etime(timer(1,event,itask))
118#ifdef _OPENMP
119 omp_initime(event,itask) = omp_get_wtime( )
120#else
121 CALL system_clock(clockini(event,itask))
122#endif
123 RETURN
124 END
125!||====================================================================
126!|| stoptime ../starter/source/system/timer.F
127!||--- called by ------------------------------------------------------
128!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
129!|| lectur ../starter/source/starter/lectur.F
130!|| starter0 ../starter/source/starter/starter0.f
131!||--- calls -----------------------------------------------------
132!|| my_etime ../starter/source/system/machine.F
133!||====================================================================
134 SUBROUTINE stoptime(EVENT,ITASK)
135C routine incrementation du timer event
136C-----------------------------------------------
137C I m p l i c i t T y p e s
138C-----------------------------------------------
139#include "implicit_f.inc"
140C-----------------------------------------------
141C C o m m o n B l o c k s
142C-----------------------------------------------
143#include "scr05_c.inc"
144#include "timer_c.inc"
145C-----------------------------------------------
146C L o c a l V a r i a b l e s
147C-----------------------------------------------
148 INTEGER EVENT,ITASK
149
150 DOUBLE PRECISION SECS
151 INTEGER CLOCK1, CLOCKRATE, NBMAX
152 REAL(KIND=8) :: omp_ending_time
153#ifdef _OPENMP
154 REAL(kind=8) omp_get_wtime
155 external OMP_GET_WTIME
156#endif
157C-----------------------------------------------
158 CALL my_etime(timer(3,event,itask))
159 cputime(event,itask) = cputime(event,itask) +
160 . timer(3,event,itask)-timer(1,event,itask)
161
162#ifdef _OPENMP
163 omp_ending_time = omp_get_wtime( )
164 secs = omp_ending_time - omp_initime(event,itask)
165#else
166 CALL system_clock(count=clock1, count_rate=clockrate,
167 + count_max=nbmax )
168 secs = clock1-clockini(event,itask) ! diff temps courant - temps initial
169 IF(secs<zero) secs = secs + nbmax ! cas depassement nb de periode maximum
170 secs = secs/clockrate
171#endif
172 realtime(event,itask)=realtime(event,itask)+secs
173
174 RETURN
175 END
176!||====================================================================
177!|| printime ../starter/source/system/timer.F
178!||--- called by ------------------------------------------------------
179!|| starter0 ../starter/source/starter/starter0.F
180!||--- calls -----------------------------------------------------
181!|| elapstime ../starter/source/system/timer.F
182!||====================================================================
183 SUBROUTINE printime(ITASK,GOT_TIMER,STARTDATE,STARTTIME,ENDDATE,ENDTIME)
184C routine d'affichage des timers
185C-----------------------------------------------
186C I m p l i c i t T y p e s
187C-----------------------------------------------
188#include "implicit_f.inc"
189C-----------------------------------------------
190C G l o b a l P a r a m e t e r s
191C-----------------------------------------------
192C C o m m o n B l o c k s
193C-----------------------------------------------
194#include "scr05_c.inc"
195#include "timer_c.inc"
196#include "units_c.inc"
197 COMMON /iclock/clock0
198 INTEGER CLOCK0
199 COMMON /rclock/elapsed
200 DOUBLE PRECISION ELAPSED
201 CHARACTER(len=8), INTENT(IN) :: STARTDATE
202 CHARACTER(len=10), INTENT(IN) :: STARTTIME
203 CHARACTER(len=8), INTENT(OUT) :: ENDDATE
204 CHARACTER(len=10), INTENT(OUT) :: ENDTIME
205
206C-----------------------------------------------
207C D u m m y A r g u m e n t s
208C-----------------------------------------------
209 INTEGER ITASK,GOT_TIMER
210C-----------------------------------------------
211C L o c a l V a r i a b l e s
212C-----------------------------------------------
213 DOUBLE PRECISION SECS
214 CHARACTER(len=8) :: DATE
215 CHARACTER(len=10) :: TIME
216 INTEGER :: IH,IM,IS
217C-----------------------------------------------
218
219 CALL elapstime(secs)
220 ih=secs/3600
221 im=(secs-ih*3600)/60
222 is=secs-ih*3600-im*60
223
224 CALL date_and_time(date,time)
225 enddate = date
226 endtime = time
227
228 WRITE(iout,*) ' '
229 WRITE(istdo,*) ' '
230 WRITE(iout,6100)
231 WRITE(istdo,6100)
232 IF(got_timer>0) THEN
233 WRITE(iout,*)' '
234 WRITE(iout,*)'CPU USER TIME'
235 WRITE(iout,*)'-------------'
236
237 WRITE(iout,1000)
238 WRITE(iout,1100)
239 . cputime(1,itask),cputime(4,itask),cputime(2,itask)-
240 . cputime(3,itask),cputime(3,itask),
241 . cputime(5,itask),cputime(6,itask),cputime(7,itask),
242 . cputime(8,itask)
243
244 WRITE(istdo,*)' '
245 WRITE(istdo,*)'CPU USER TIME'
246 WRITE(istdo,*)'-------------'
247
248 WRITE(istdo,1000)
249 WRITE(istdo,1100)
250 . cputime(1,itask),cputime(4,itask),cputime(2,itask)-
251 . cputime(3,itask),cputime(3,itask),
252 . cputime(5,itask),cputime(6,itask),cputime(7,itask),
253 . cputime(8,itask)
254
255C---------------------------
256C Elapsed time & Estimated Speedup
257C---------------------------
258
259c---output file
260 WRITE(iout,*)' '
261 WRITE(iout,*)' '
262 WRITE(iout,*)'ELAPSED TIME'
263 WRITE(iout,*)'------------'
264
265 WRITE(IOUT,1000)
266 WRITE(IOUT,1100)
267 . REALTIME(1,1),REALTIME(4,1),REALTIME(2,1)-
268 . REALTIME(3,1),REALTIME(3,1),
269 . REALTIME(5,1),REALTIME(6,1),REALTIME(7,1),
270 . REALTIME(8,1)
271
272c---Standard output
273
274 WRITE(ISTDO,*)' '
275 WRITE(ISTDO,*)' '
276 WRITE(ISTDO,*)'elapsed time'
277 WRITE(ISTDO,*)'------------'
278
279 WRITE(ISTDO,1000)
280 WRITE(ISTDO,1100)
281 . REALTIME(1,1),REALTIME(4,1),REALTIME(2,1)-
282 . REALTIME(3,1),REALTIME(3,1),
283 . REALTIME(5,1),REALTIME(6,1),REALTIME(7,1),
284 . REALTIME(8,1)
285
286 WRITE(ISTDO,'(a)') ' '
287 WRITE(ISTDO,'(a,e9.4)') ' converter : ', REALTIME(15,1)
288 WRITE(ISTDO,'(a,e9.4)') ' rd input build : ', REALTIME(16,1)
289 WRITE(ISTDO,'(a)') ' '
290 WRITE(ISTDO,'(a,e9.4)') ' rd groups & surfaces : ', REALTIME(19,1)
291 WRITE(ISTDO,'(a)') ' '
292 WRITE(ISTDO,'(a,e9.4)') ' sets : ', REALTIME(17,1)
293 WRITE(ISTDO,'(a)') ' '
294 WRITE(ISTDO,'(a,e9.4)') 'iddlevel=0 - INTERFACE read : ', REALTIME(10,1)
295 WRITE(ISTDO,'(a,e9.4)') 'iddlevel=1 - INTERFACE read : ', REALTIME(11,1)
296 WRITE(ISTDO,'(a)') ' '
297 WRITE(ISTDO,'(a,e9.4)') 'iddlevel=0 - INTERFACE init : ', REALTIME(12,1)
298 WRITE(ISTDO,'(a,e9.4)') 'iddlevel=1 - INTERFACE init : ', REALTIME(13,1)
299 WRITE(ISTDO,'(a)') ' '
300 WRITE(ISTDO,'(a,e9.4)') 'iddlevel=1 - i7remnode : ', REALTIME(18,1)
301 WRITE(ISTDO,'(a)') ' '
302 WRITE(ISTDO,'(a,e9.4)') ' elbuf init : ', REALTIME(14,1)
303
304 ENDIF
305
306 WRITE(IOUT,*) ' '
307 WRITE(IOUT,*)
308 . ' ** compute time information **'
309 WRITE(IOUT,*)' '
310
311 WRITE(IOUT,6200)STARTDATE(1:4),STARTDATE(5:6),STARTDATE(7:8),
312 . STARTTIME(1:2),STARTTIME(3:4),STARTTIME(5:6)
313 WRITE(IOUT,6300)DATE(1:4),DATE(5:6),DATE(7:8),
314 . TIME(1:2),TIME(3:4),TIME(5:6)
315 WRITE(IOUT,*)' '
316
317 WRITE(ISTDO,*) ' '
318 WRITE(ISTDO,*)
319 . ' ** compute time information **'
320 WRITE(ISTDO,*)' '
321
322 WRITE(ISTDO,6200)STARTDATE(1:4),STARTDATE(5:6),STARTDATE(7:8),
323 . STARTTIME(1:2),STARTTIME(3:4),STARTTIME(5:6)
324 WRITE(ISTDO,6300)DATE(1:4),DATE(5:6),DATE(7:8),
325 . TIME(1:2),TIME(3:4),TIME(5:6)
326 WRITE(ISTDO,*)' '
327
328 WRITE(ISTDO,6000)SECS
329 WRITE(ISTDO,6050) IH,IM,IS
330 WRITE(ISTDO,*)' '
331
332 WRITE(IOUT,6000)SECS
333 WRITE(IOUT,6050)IH,IM,IS
334 WRITE(IOUT,*)' '
335
336 WRITE(IOUT,6100)
337 WRITE(ISTDO,6100)
338
339
340
341c---Format
342 1000 FORMAT(' translator ','FREEFORM ','LECTURE ',
343 .'DDSPLIT ','IPARI_L_INI ','INTBUF_INI ','SPL_INTS ',
344 .'W_FI ')
345 1100 FORMAT(e9.4,3x,e9.4,3x,e9.4,3x,e9.4,3x,e9.4,3x,e9.4
346 .,3x,e9.4,3x,e9.4)
347
348 6000 FORMAT(' ELAPSED TIME...........=',f14.2,' s')
349 6050 FORMAT(' ',i2.2,':',i2.2,':',i2.2)
350 6100 FORMAT('------------------------------------------------------------------------')
351 6200 FORMAT(' EXECUTION STARTED : ',
352 . a4,'/',a2,'/',a2,' ',a2,':',a2,':',a2)
353 6300 FORMAT(' EXECUTION COMPLETED : ',
354 . a4,'/',a2,'/',a2,' ',a2,':',a2,':',a2)
355
356
357 RETURN
358 END
359!||====================================================================
360!|| elapstime ../starter/source/system/timer.F
361!||--- called by ------------------------------------------------------
362!|| printime ../starter/source/system/timer.F
363!||--- calls -----------------------------------------------------
364!||====================================================================
365 SUBROUTINE elapstime(ETIME)
366C reset timer elapsed time et calcul du temps elapsed courant
367C-----------------------------------------------
368C I m p l i c i t T y p e s
369C-----------------------------------------------
370#include "implicit_f.inc"
371C-----------------------------------------------
372C G l o b a l P a r a m e t e r s
373C----------------------------------------------
374C C o m m o n B l o c k s
375C-----------------------------------------------
376#include "scr05_c.inc"
377#include "timer_c.inc"
378 COMMON /iclock/clock0
379 INTEGER CLOCK0
380 COMMON /rclock/elapsed
381 DOUBLE PRECISION ELAPSED
382C-----------------------------------------------
383C D u m m y A r g u m e n t s
384C-----------------------------------------------
385 DOUBLE PRECISION ETIME
386C-----------------------------------------------
387C L o c a l V a r i a b l e s
388C-----------------------------------------------
389 INTEGER CLOCK1, CLOCKRATE, NBMAX
390 DOUBLE PRECISION SECS
391 REAL(KIND=8) :: omp_ending_time
392#ifdef _OPENMP
393 REAL(kind=8) omp_get_wtime
394 external OMP_GET_WTIME
395#endif
396C-----------------------------------------------
397 CALL system_clock(count=clock1, count_rate=clockrate,
398 + count_max=nbmax )
399
400
401#if _OPENMP
402 omp_ending_time = omp_get_wtime( )
403 secs = omp_ending_time-omp_starting_time
404 elapsed = secs
405#else
406 secs = clock1-clock0 ! diff temps courant - temps initial (qui peut ne pas etre 0 !)
407 IF(secs<zero) secs = secs + nbmax ! cas depassement nb de periode maximum
408 secs = secs/clockrate
409 elapsed = elapsed + secs
410#endif
411
412 clock0 = clock1 ! recuperation du temps courant dans clock0
413 etime = elapsed
414
415 RETURN
416 END SUBROUTINE elapstime
417
418!||====================================================================
419!|| elapstime_omp ../starter/source/system/timer.F
420!||--- called by ------------------------------------------------------
421!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
422!||====================================================================
423 SUBROUTINE elapstime_omp(ETIME)
424! compute the current elapsed time
425C-----------------------------------------------
426C I m p l i c i t T y p e s
427C-----------------------------------------------
428#include "implicit_f.inc"
429C-----------------------------------------------
430C G l o b a l P a r a m e t e r s
431C----------------------------------------------
432C C o m m o n B l o c k s
433C-----------------------------------------------
434#include "scr05_c.inc"
435#include "timer_c.inc"
436C-----------------------------------------------
437C D u m m y A r g u m e n t s
438C-----------------------------------------------
439 real(kind=8) :: etime
440C-----------------------------------------------
441C L o c a l V a r i a b l e s
442C-----------------------------------------------
443 INTEGER CLOCK1, CLOCKRATE, NBMAX
444 real(kind=8) :: secs
445 real(kind=8) :: omp_ending_time
446 real(kind=8) :: omp_get_wtime
447#ifdef _OPENMP
448 external OMP_GET_WTIME
449C-----------------------------------------------
450 omp_ending_time = omp_get_wtime( )
451 secs = omp_ending_time-omp_starting_time
452
453 etime = secs
454#else
455 secs = 0
456 etime = secs
457#endif
458
459 RETURN
460 END SUBROUTINE elapstime_omp
subroutine i7remnode(iremnode, noint, titr, intbuf_tab, numnod, x, nrtm, irect, nsv, nsn, itab, gap_s, gap_m, gapmin, gapmax, gap_s_l, gap_m_l, igap, gap, drad, nremnode, nty, ipari, i_mem_rem, gapm_mx, gaps_mx, gapm_l_mx, gaps_l_mx, ilev, nbinflg, mbinflg, dgapload, npari)
Definition i7remnode.F:43
subroutine starter0
Definition starter0.F:79
subroutine my_etime(timer)
Definition machine.F:114
subroutine startime(event, itask)
Definition timer.F:93
subroutine elapstime(etime)
Definition timer.F:366
subroutine printime(itask, got_timer, startdate, starttime, enddate, endtime)
Definition timer.F:184
subroutine initime()
Definition timer.F:30
subroutine stoptime(event, itask)
Definition timer.F:135
subroutine elapstime_omp(etime)
Definition timer.F:424
program starter
Definition starter.F:39