/[MITgcm]/MITgcm/model/src/the_main_loop.F
ViewVC logotype

Contents of /MITgcm/model/src/the_main_loop.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.67 - (show annotations) (download)
Thu Dec 22 01:08:57 2005 UTC (18 years, 5 months ago) by ce107
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint58, checkpoint58a_post, checkpoint57z_post, checkpoint58c_post
Changes since 1.66: +55 -1 lines
Updated code to provide timing information per timestep to include cases
where there is no pressure solve by moving the code to the main loop.
Modified the timing in the pressure solver for the case where TAF needs
to be fooled. Added support for PAPI summary MFlop/s information per
timestep along side the simple (user/system/wallclock) timing. To use
PAPI one currently needs to have declared PAPIINC and PAPILIB in the
optfile for the include and library linking stings.

1 C $Header: /u/gcmpack/MITgcm/model/src/the_main_loop.F,v 1.66 2005/12/08 15:44:34 heimbach Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6 #ifdef ALLOW_OBCS
7 # include "OBCS_OPTIONS.h"
8 #endif
9 #ifdef ALLOW_SEAICE
10 # include "SEAICE_OPTIONS.h"
11 #endif
12 #ifdef ALLOW_GMREDI
13 # include "GMREDI_OPTIONS.h"
14 #endif
15
16 CBOP
17 C !ROUTINE: THE_MAIN_LOOP
18 C !INTERFACE:
19 SUBROUTINE THE_MAIN_LOOP( myTime, myIter, myThid )
20
21 C !DESCRIPTION: \bv
22 C *================================================================*
23 C | SUBROUTINE the_main_loop
24 C | o Run the ocean model and evaluate the specified cost function.
25 C *================================================================*
26 C |
27 C | THE_MAIN_LOOP is the toplevel routine for the Tangent Linear and
28 C | Adjoint Model Compiler (TAMC). For this purpose the initialization
29 C | of the model was split into two parts. Those parameters that do
30 C | not depend on a specific model run are set in INITIALISE_FIXED,
31 C | whereas those that do depend on the specific realization are
32 C | initialized in INITIALISE_VARIA.
33 C | This routine is to be used in conjuction with the MITgcmuv
34 C | checkpoint 37.
35 C *================================================================*
36 C \ev
37
38 C !USES:
39 IMPLICIT NONE
40 C == Global variables ==
41 #include "SIZE.h"
42 #include "EEPARAMS.h"
43 #include "PARAMS.h"
44
45 c**************************************
46 #ifdef ALLOW_AUTODIFF_TAMC
47
48 c These includes are needed for
49 c AD-checkpointing.
50 c They provide the fields to be stored.
51
52 # include "GRID.h"
53 # include "DYNVARS.h"
54 # include "FFIELDS.h"
55 # include "EOS.h"
56 # include "GAD.h"
57 # ifdef ALLOW_CD_CODE
58 # include "CD_CODE_VARS.h"
59 # endif
60 # ifdef ALLOW_PTRACERS
61 # include "PTRACERS_SIZE.h"
62 # include "PTRACERS.h"
63 # endif
64 # if (defined (EXACT_CONSERV) || defined (NONLIN_FRSURF))
65 # include "SURFACE.h"
66 # endif
67 # ifdef ALLOW_OBCS
68 # include "OBCS.h"
69 # endif
70 # ifdef ALLOW_EXF
71 # include "exf_fields.h"
72 # include "exf_clim_fields.h"
73 # ifdef ALLOW_BULKFORMULAE
74 # include "exf_constants.h"
75 # endif
76 # endif /* ALLOW_EXF */
77 # ifdef ALLOW_SEAICE
78 # include "SEAICE.h"
79 # endif
80 # ifdef ALLOW_EBM
81 # include "EBM.h"
82 # endif
83 # ifdef ALLOW_DIVIDED_ADJOINT_MPI
84 # include "mpif.h"
85 # endif
86
87 # include "tamc.h"
88 # include "ctrl.h"
89 # include "ctrl_dummy.h"
90 # include "cost.h"
91
92 #endif /* ALLOW_AUTODIFF_TAMC */
93 c**************************************
94
95 C !INPUT/OUTPUT PARAMETERS:
96 C == Routine arguments ==
97 C note: under the multi-threaded model myiter and
98 C mytime are local variables passed around as routine
99 C arguments. Although this is fiddly it saves the need to
100 C impose additional synchronisation points when they are
101 C updated.
102 C myIter - iteration counter for this thread
103 C myTime - time counter for this thread
104 C myThid - thread number for this instance of the routine.
105 INTEGER myThid
106 INTEGER myIter
107 _RL myTime
108
109 C !FUNCTIONS:
110 C == Functions ==
111 #ifdef ALLOW_RUNCLOCK
112 LOGICAL RUNCLOCK_CONTINUE
113 LOGICAL RC_CONT
114 #endif
115
116 C !LOCAL VARIABLES:
117 C == Local variables ==
118 integer iloop
119 #ifdef ALLOW_AUTODIFF_TAMC
120 integer ilev_1
121 integer ilev_2
122 integer ilev_3
123 integer ilev_4
124 integer max_lev2
125 integer max_lev3
126 integer max_lev4
127 #endif
128 CEOP
129 #if defined(TIME_PER_TIMESTEP) || defined(USE_PAPI_FLOPS)
130 CHARACTER*(MAX_LEN_MBUF) msgBuf
131 #ifdef TIME_PER_TIMESTEP
132 CCE107 common block for per timestep timing
133 C !TIMING VARIABLES
134 C == Timing variables ==
135 REAL*8 utnew, utold, stnew, stold, wtnew, wtold
136 DATA utnew, utold, stnew, stold, wtnew, wtold /6*0.0D0/
137 #endif
138 #ifdef USE_PAPI_FLOPS
139 CCE107 common block for PAPI summary performance
140 #include <fpapi.h>
141 INTEGER*8 flpops
142 DATA flpops /0/
143 INTEGER check
144 REAL real_time, proc_time, mflops
145 DATA real_time, proc_time, mflops /3*0.0D0/
146 #endif
147 #endif
148
149 #ifdef ALLOW_DEBUG
150 IF (debugMode) CALL DEBUG_ENTER('THE_MAIN_LOOP',myThid)
151 #endif
152
153 #ifdef ALLOW_AUTODIFF_TAMC
154 c-- Initialize storage for the cost function evaluation.
155 CADJ INIT dummytape = common, 1
156 c-- Initialize storage for the outermost loop.
157 CADJ INIT tapelev_ini_bibj_k = USER
158 CADJ INIT tapelev_init = USER
159 c
160 #if (defined (AUTODIFF_2_LEVEL_CHECKPOINT))
161 CADJ INIT tapelev2 = USER
162 #elif (defined (AUTODIFF_4_LEVEL_CHECKPOINT))
163 CADJ INIT tapelev4 = USER
164 #else
165 CADJ INIT tapelev3 = USER
166 #endif
167
168 nIter0 = NINT( (startTime-baseTime)/deltaTClock )
169 ikey_dynamics = 1
170
171 CALL TIMER_START('ADJOINT SPIN-UP', mythid)
172 #endif
173
174 #ifdef ALLOW_AUTODIFF_TAMC
175 # ifdef NONLIN_FRSURF
176 CADJ STORE hFacC = tapelev_init, key = 1
177 # endif
178 #endif
179
180 #ifdef ALLOW_DEBUG
181 IF (debugMode) CALL DEBUG_CALL('INITIALISE_VARIA',myThid)
182 #endif
183 C-- Set initial conditions (variable arrays)
184 CALL TIMER_START('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
185 CALL INITIALISE_VARIA( mythid )
186 CALL TIMER_STOP ('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
187
188 #ifdef ALLOW_MONITOR
189 #ifdef ALLOW_DEBUG
190 IF (debugMode) CALL DEBUG_CALL('MONITOR',myThid)
191 #endif
192 C-- Check status of solution (statistics, cfl, etc...)
193 CALL TIMER_START('MONITOR [THE_MAIN_LOOP]', mythid)
194 CALL MONITOR( myIter, myTime, myThid )
195 CALL TIMER_STOP ('MONITOR [THE_MAIN_LOOP]', mythid)
196 #endif /* ALLOW_MONITOR */
197
198 C-- Do IO if needed (Dump for start state).
199 #ifdef ALLOW_DEBUG
200 IF (debugMode) CALL DEBUG_CALL('DO_THE_MODEL_IO',myThid)
201 #endif
202
203 #ifdef ALLOW_OFFLINE
204 CALL TIMER_START('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
205 CALL OFFLINE_MODEL_IO( myTime, myIter, myThid )
206 CALL TIMER_STOP ('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
207 #else
208 CALL TIMER_START('DO_THE_MODEL_IO [THE_MAIN_LOOP]', mythid)
209 CALL DO_THE_MODEL_IO( myTime, myIter, mythid )
210 CALL TIMER_STOP ('DO_THE_MODEL_IO [THE_MAIN_LOOP]', mythid)
211 #endif
212
213
214 #ifdef ALLOW_AUTODIFF_TAMC
215 CALL TIMER_STOP ('ADJOINT SPIN-UP', mythid)
216 _BARRIER
217 #endif
218
219 #ifdef TIME_PER_TIMESTEP
220 CCE107 Initial call for timers
221 _BEGIN_MASTER( myThid )
222 CALL TIMER_GET_TIME( utold, stold, wtold )
223 _END_MASTER( myThid )
224 #endif
225 #ifdef USE_PAPI_FLOPS
226 CCE107 Initial call for PAPI
227 _BEGIN_MASTER( myThid )
228 call PAPIF_flops(real_time, proc_time, flpops, mflops, check)
229 _END_MASTER( myThid )
230 #endif
231
232 c-- Do the model integration.
233 CALL TIMER_START('MAIN LOOP [THE_MAIN_LOOP]', mythid)
234
235 c >>>>>>>>>>>>>>>>>>>>>>>>>>> LOOP <<<<<<<<<<<<<<<<<<<<<<<<<<<<
236 c >>>>>>>>>>>>>>>>>>>>>>>>>>> STARTS <<<<<<<<<<<<<<<<<<<<<<<<<<<<
237
238 #ifdef ALLOW_AUTODIFF_TAMC
239 #ifdef ALLOW_TAMC_CHECKPOINTING
240
241 max_lev4=nTimeSteps/(nchklev_1*nchklev_2*nchklev_3)+1
242 max_lev3=nTimeSteps/(nchklev_1*nchklev_2)+1
243 max_lev2=nTimeSteps/nchklev_1+1
244
245 c**************************************
246 #ifdef ALLOW_DIVIDED_ADJOINT
247 CADJ loop = divided
248 #endif
249 c**************************************
250
251 #ifdef AUTODIFF_4_LEVEL_CHECKPOINT
252 do ilev_4 = 1,nchklev_4
253 if(ilev_4.le.max_lev4) then
254 c**************************************
255 #include "checkpoint_lev4_directives.h"
256 c**************************************
257 c-- Initialise storage for the middle loop.
258 CADJ INIT tapelev3 = USER
259 #endif /* AUTODIFF_4_LEVEL_CHECKPOINT */
260
261 #ifndef AUTODIFF_2_LEVEL_CHECKPOINT
262 do ilev_3 = 1,nchklev_3
263 if(ilev_3.le.max_lev3) then
264 c**************************************
265 #include "checkpoint_lev3_directives.h"
266 c**************************************
267 c-- Initialise storage for the middle loop.
268 CADJ INIT tapelev2 = USER
269 #endif /* AUTODIFF_2_LEVEL_CHECKPOINT */
270
271 do ilev_2 = 1,nchklev_2
272 if(ilev_2.le.max_lev2) then
273 c**************************************
274 #include "checkpoint_lev2_directives.h"
275 c**************************************
276
277 c**************************************
278 #ifdef ALLOW_AUTODIFF_TAMC
279 c-- Initialize storage for the innermost loop.
280 c-- Always check common block sizes for the checkpointing!
281 c--
282 CADJ INIT comlev1 = COMMON,nchklev_1
283 CADJ INIT comlev1_bibj = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt
284 CADJ INIT comlev1_bibj_k = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt
285 c--
286 #ifdef ALLOW_KPP
287 CADJ INIT comlev1_kpp = COMMON,nchklev_1*nsx*nsy
288 CADJ INIT comlev1_kpp_k = COMMON,nchklev_1*nsx*nsy*nr
289 #endif /* ALLOW_KPP */
290 c--
291 #ifdef ALLOW_GMREDI
292 CADJ INIT comlev1_gmredi_k_gad
293 CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
294 #endif /* ALLOW_GMREDI */
295 c--
296 #ifdef ALLOW_PTRACERS
297 CADJ INIT comlev1_bibj_ptracers = COMMON,
298 CADJ & nchklev_1*nsx*nsy*nthreads_chkpt*PTRACERS_num
299 #endif /* ALLOW_PTRACERS */
300 c--
301 #ifndef DISABLE_MULTIDIM_ADVECTION
302 CADJ INIT comlev1_bibj_k_gad
303 CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
304 CADJ INIT comlev1_bibj_k_gad_pass
305 CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass*maxcube
306 #endif /* DISABLE_MULTIDIM_ADVECTION */
307 c--
308 #if (defined (ALLOW_EXF) && defined (ALLOW_BULKFORMULAE))
309 CADJ INIT comlev1_exf_1
310 CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
311 CADJ INIT comlev1_exf_2
312 CADJ & = COMMON,niter_bulk*nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
313 #endif /* ALLOW_BULKFORMULAE */
314 c--
315 #ifdef ALLOW_SEAICE
316 # ifdef SEAICE_ALLOW_DYNAMICS
317 CADJ INIT comlev1_lsr = COMMON,nchklev_1*2
318 # endif
319 #endif /* ALLOW_SEAICE */
320 c--
321 #endif /* ALLOW_AUTODIFF_TAMC */
322 c**************************************
323
324 do ilev_1 = 1,nchklev_1
325
326 c-- The if-statement below introduces a some flexibility in the
327 c-- choice of the 3-tupel ( nchklev_1, nchklev_2, nchklev_3 ).
328
329 iloop = (ilev_2 - 1)*nchklev_1 + ilev_1
330 #ifndef AUTODIFF_2_LEVEL_CHECKPOINT
331 & + (ilev_3 - 1)*nchklev_2*nchklev_1
332 #endif
333 #ifdef AUTODIFF_4_LEVEL_CHECKPOINT
334 & + (ilev_4 - 1)*nchklev_3*nchklev_2*nchklev_1
335 #endif
336
337 if ( iloop .le. nTimeSteps ) then
338
339 #else /* ALLOW_TAMC_CHECKPOINTING undefined */
340 c-- Initialise storage for reference trajectory without TAMC check-
341 c-- pointing.
342 CADJ INIT history = USER
343 CADJ INIT comlev1_bibj = COMMON,nchklev_0*nsx*nsy*nthreads_chkpt
344 CADJ INIT comlev1_bibj_k = COMMON,nchklev_0*nsx*nsy*nr*nthreads_chkpt
345 CADJ INIT comlev1_kpp = COMMON,nchklev_0*nsx*nsy
346
347 c-- Check the choice of the checkpointing parameters in relation
348 c-- to nTimeSteps: (nchklev_0 .ge. nTimeSteps)
349 if (nchklev_0 .lt. nTimeSteps) then
350 print*
351 print*, ' the_main_loop: TAMC checkpointing parameter ',
352 & 'nchklev_0 = ', nchklev_0
353 print*, ' not consistent with nTimeSteps = ',
354 & nTimeSteps
355 stop ' ... stopped in the_main_loop.'
356 endif
357
358 DO iloop = 1, nTimeSteps
359
360 #endif /* ALLOW_TAMC_CHECKPOINTING */
361
362 #else /* ALLOW_AUTODIFF_TAMC undefined */
363
364 c-- Start the main loop of adjoint_Objfunc. Automatic differentiation
365 c-- NOT enabled.
366 DO iloop = 1, nTimeSteps
367
368 #endif /* ALLOW_AUTODIFF_TAMC */
369
370 c-- >>> Loop body start <<<
371
372 #ifdef ALLOW_AUTODIFF_TAMC
373 nIter0 = NINT( (startTime-baseTime)/deltaTClock )
374 ikey_dynamics = ilev_1
375 CALL AUTODIFF_INADMODE_UNSET( myThid )
376 #endif
377
378 #ifdef ALLOW_AUTODIFF_TAMC
379 CALL AUTODIFF_INADMODE_UNSET( myThid )
380 #endif
381
382 #ifdef ALLOW_DEBUG
383 IF (debugMode) CALL DEBUG_CALL('FORWARD_STEP',myThid)
384 #endif
385 CALL TIMER_START('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
386 CALL FORWARD_STEP( iloop, mytime, myiter, mythid )
387 CALL TIMER_STOP ('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
388
389 #ifdef ALLOW_AUTODIFF_TAMC
390 CALL AUTODIFF_INADMODE_SET( myThid )
391 #endif
392
393 #ifdef ALLOW_RUNCLOCK
394 IF (useRunClock) THEN
395 RC_CONT=RUNCLOCK_CONTINUE( myThid )
396 IF (.NOT.RC_CONT) RETURN
397 ENDIF
398 #endif /* ALLOW_RUNCLOCK */
399 #ifdef TIME_PER_TIMESTEP
400 CCE107 Time per timestep information
401 _BEGIN_MASTER( myThid )
402 CALL TIMER_GET_TIME( utnew, stnew, wtnew )
403 WRITE(msgBuf,'(A34,3F10.6,I8)')
404 $ 'User, system and wallclock time:', utnew - utold,
405 $ stnew - stold, wtnew - wtold, iloop
406 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
407 utold = utnew
408 stold = stnew
409 wtold = wtnew
410 _END_MASTER( myThid )
411 #endif
412 #ifdef USE_PAPI_FLOPS
413 CCE107 PAPI summary performance
414 _BEGIN_MASTER( myThid )
415 call PAPIF_flops(real_time, proc_time, flpops, mflops, check)
416 WRITE(msgBuf,'(F10.6,A34,I8)')
417 $ mflops, 'Mflop/s during timestep ', iloop
418 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
419 _END_MASTER( myThid )
420 #endif
421
422 c-- >>> Loop body end <<<
423
424 #ifdef ALLOW_AUTODIFF_TAMC
425 CALL AUTODIFF_INADMODE_SET( myThid )
426 #ifdef ALLOW_TAMC_CHECKPOINTING
427 endif
428 enddo
429 endif
430 enddo
431 #ifndef AUTODIFF_2_LEVEL_CHECKPOINT
432 endif
433 enddo
434 #endif
435 #ifdef AUTODIFF_4_LEVEL_CHECKPOINT
436 endif
437 enddo
438 #endif
439 #else /* ndef ALLOW_TAMC_CHECKPOINTING */
440 enddo
441 #endif /* ALLOW_TAMC_CHECKPOINTING */
442
443 #else /* ndef ALLOW_AUTODIFF_TAMC */
444 enddo
445 #endif /* ALLOW_AUTODIFF_TAMC */
446
447 #ifdef ALLOW_COST
448 c-- Sum all cost function contributions.
449 call TIMER_START('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
450 call COST_FINAL ( mythid )
451 call TIMER_STOP ('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
452 #endif
453
454 _BARRIER
455 CALL TIMER_STOP ('MAIN LOOP [THE_MAIN_LOOP]', mythid)
456
457 #ifdef ALLOW_DEBUG
458 IF (debugMode) CALL DEBUG_LEAVE('THE_MAIN_LOOP',myThid)
459 #endif
460
461 END

  ViewVC Help
Powered by ViewVC 1.1.22