/[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.100 - (show annotations) (download)
Tue May 26 23:13:05 2009 UTC (14 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint61q, checkpoint61t, checkpoint61r, checkpoint61s, checkpoint61p
Changes since 1.99: +4 -2 lines
Adapt store directives to new pseudotimestep loop.

1 C $Header: /u/gcmpack/MITgcm/model/src/the_main_loop.F,v 1.99 2009/04/06 23:47:06 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).
29 C | For this purpose the initialization
30 C | of the model was split into two parts. Those parameters that do
31 C | not depend on a specific model run are set in INITIALISE_FIXED,
32 C | whereas those that do depend on the specific realization are
33 C | initialized in INITIALISE_VARIA.
34 C | This routine is to be used in conjuction with the MITgcmuv
35 C | checkpoint 37.
36 C *================================================================*
37 C \ev
38
39 C !USES:
40 IMPLICIT NONE
41 C == Global variables ==
42 #include "SIZE.h"
43 #include "EEPARAMS.h"
44 #include "PARAMS.h"
45
46 c**************************************
47 #ifdef ALLOW_AUTODIFF_TAMC
48 # ifndef ALLOW_AUTODIFF_OPENAD
49
50 c These includes are needed for
51 c AD-checkpointing.
52 c They provide the fields to be stored.
53
54 # include "GRID.h"
55 # include "DYNVARS.h"
56 # include "SURFACE.h"
57 # include "FFIELDS.h"
58 # include "EOS.h"
59 # include "AUTODIFF.h"
60
61 # ifdef ALLOW_GENERIC_ADVDIFF
62 # include "GAD.h"
63 # endif
64 # ifdef ALLOW_MOM_FLUXFORM
65 # include "MOM_FLUXFORM.h"
66 # endif
67 # ifdef ALLOW_CD_CODE
68 # include "CD_CODE_VARS.h"
69 # endif
70 # ifdef ALLOW_PTRACERS
71 # include "PTRACERS_SIZE.h"
72 # include "PTRACERS_FIELDS.h"
73 # endif
74 # ifdef ALLOW_GCHEM
75 # include "GCHEM_FIELDS.h"
76 # endif
77 # ifdef ALLOW_CFC
78 # include "CFC.h"
79 # endif
80 # ifdef ALLOW_DIC
81 # include "DIC_VARS.h"
82 # include "DIC_LOAD.h"
83 # include "DIC_ATMOS.h"
84 # endif
85 # ifdef ALLOW_OBCS
86 # include "OBCS.h"
87 # ifdef ALLOW_PTRACERS
88 # include "OBCS_PTRACERS.h"
89 # endif
90 # endif
91 # ifdef ALLOW_EXF
92 # include "EXF_FIELDS.h"
93 # ifdef ALLOW_BULKFORMULAE
94 # include "EXF_CONSTANTS.h"
95 # endif
96 # endif /* ALLOW_EXF */
97 # ifdef ALLOW_SEAICE
98 # include "SEAICE.h"
99 # include "SEAICE_PARAMS.h"
100 # include "SEAICE_COST.h"
101 # endif
102 # ifdef ALLOW_SALT_PLUME
103 # include "SALT_PLUME.h"
104 # endif
105 # ifdef ALLOW_THSICE
106 # include "THSICE_SIZE.h"
107 # include "THSICE_PARAMS.h"
108 # include "THSICE_VARS.h"
109 # endif
110 # ifdef ALLOW_EBM
111 # include "EBM.h"
112 # endif
113 # ifdef ALLOW_RBCS
114 # include "RBCS.h"
115 # endif
116 # ifdef ALLOW_DIVIDED_ADJOINT_MPI
117 # include "mpif.h"
118 # endif
119
120 # include "tamc.h"
121 # endif /* undef ALLOW_AUTODIFF_OPENAD */
122
123 # include "ctrl.h"
124 # include "ctrl_dummy.h"
125 # include "cost.h"
126
127 #endif /* ALLOW_AUTODIFF_TAMC */
128 c**************************************
129
130 C !INPUT/OUTPUT PARAMETERS:
131 C == Routine arguments ==
132 C note: under the multi-threaded model myiter and
133 C mytime are local variables passed around as routine
134 C arguments. Although this is fiddly it saves the need to
135 C impose additional synchronisation points when they are
136 C updated.
137 C myIter - iteration counter for this thread
138 C myTime - time counter for this thread
139 C myThid - thread number for this instance of the routine.
140 INTEGER myThid
141 INTEGER myIter
142 _RL myTime
143
144 C !FUNCTIONS:
145 C == Functions ==
146
147 C !LOCAL VARIABLES:
148 C == Local variables ==
149 integer iloop
150 #ifdef ALLOW_AUTODIFF_TAMC
151 # ifdef ALLOW_AUTODIFF_OPENAD
152 integer uCheckLev1, uCheckLev2, uCheckLev3,uCheckLev4
153 integer ilev_4
154 integer theCurrentStep
155 # endif
156 #endif
157
158 CEOP
159
160 #ifdef ALLOW_DEBUG
161 IF (debugMode) CALL DEBUG_ENTER('THE_MAIN_LOOP',myThid)
162 #endif
163
164 #ifdef ALLOW_AUTODIFF_TAMC
165 c-- Initialize storage for the cost function evaluation.
166 CADJ INIT dummytape = common, 1
167 c-- Initialize storage for the outermost loop.
168 CADJ INIT tapelev_ini_bibj_k = USER
169 CADJ INIT tapelev_init = USER
170 c
171 # if (defined (AUTODIFF_2_LEVEL_CHECKPOINT))
172 CADJ INIT tapelev2 = USER
173 # elif (defined (AUTODIFF_4_LEVEL_CHECKPOINT))
174 CADJ INIT tapelev4 = USER
175 # else
176 CADJ INIT tapelev3 = USER
177 # endif
178 #endif
179
180 #ifdef ALLOW_AUTODIFF
181 nIter0 = NINT( (startTime-baseTime)/deltaTClock )
182 ikey_dynamics = 1
183 #endif
184
185 #ifdef ALLOW_AUTODIFF_TAMC
186 # ifdef NONLIN_FRSURF
187 CADJ STORE hFacC = tapelev_init, key = 1
188 # endif
189 #endif
190
191 #ifdef ALLOW_AUTODIFF_OPENAD
192 # ifdef ALLOW_THETA0_CONTROL
193 c$openad INDEPENDENT(xx_theta)
194 # endif
195 # ifdef ALLOW_SALT0_CONTROL
196 c$openad INDEPENDENT(xx_salt)
197 # endif
198 # ifdef ALLOW_HFLUX0_CONTROL
199 c$openad INDEPENDENT(xx_hflux0)
200 # endif
201 # ifdef ALLOW_SFLUX0_CONTROL
202 c$openad INDEPENDENT(xx_sflux0)
203 # endif
204 # ifdef ALLOW_TAUU0_CONTROL
205 c$openad INDEPENDENT(xx_tauu0)
206 # endif
207 # ifdef ALLOW_TAUV0_CONTROL
208 c$openad INDEPENDENT(xx_tauv0)
209 # endif
210 # ifdef ALLOW_DIFFKR_CONTROL
211 c$openad INDEPENDENT(xx_diffkr)
212 # endif
213 # ifdef ALLOW_ KAPGM_CONTROL
214 c$openad INDEPENDENT(xx_kapgm)
215 # endif
216 #endif
217
218 #ifdef ALLOW_DEBUG
219 IF (debugMode) CALL DEBUG_CALL('INITIALISE_VARIA',myThid)
220 #endif
221
222 C-- Set initial conditions (variable arrays)
223 CALL TIMER_START('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
224 CALL INITIALISE_VARIA( mythid )
225 CALL TIMER_STOP ('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
226
227 #ifdef ALLOW_SHOWFLOPS
228 CALL TIMER_START('SHOWFLOPS_INIT [THE_MAIN_LOOP]', mythid)
229 CALL SHOWFLOPS_INIT( myThid )
230 CALL TIMER_STOP('SHOWFLOPS_INIT [THE_MAIN_LOOP]', mythid)
231 #endif
232
233 c-- Do the model integration.
234 CALL TIMER_START('MAIN LOOP [THE_MAIN_LOOP]', mythid)
235
236 c >>>>>>>>>>>>>>>>>>>>>>>>>>> LOOP <<<<<<<<<<<<<<<<<<<<<<<<<<<<
237 c >>>>>>>>>>>>>>>>>>>>>>>>>>> STARTS <<<<<<<<<<<<<<<<<<<<<<<<<<<<
238
239 c++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
240 #ifndef ALLOW_AUTODIFF_OPENAD
241 c++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
242 # ifdef ALLOW_AUTODIFF_TAMC
243 # ifdef ALLOW_TAMC_CHECKPOINTING
244
245 max_lev4=nTimeSteps/(nchklev_1*nchklev_2*nchklev_3)+1
246 max_lev3=nTimeSteps/(nchklev_1*nchklev_2)+1
247 max_lev2=nTimeSteps/nchklev_1+1
248
249 c**************************************
250 # ifdef ALLOW_DIVIDED_ADJOINT
251 CADJ loop = divided
252 # endif
253 c**************************************
254
255 # ifdef AUTODIFF_4_LEVEL_CHECKPOINT
256 do ilev_4 = 1,nchklev_4
257 if(ilev_4.le.max_lev4) then
258 c**************************************
259 CALL AUTODIFF_STORE( myThid )
260 #include "checkpoint_lev4_directives.h"
261 CALL AUTODIFF_RESTORE( myThid )
262 c**************************************
263 c-- Initialise storage for the middle loop.
264 CADJ INIT tapelev3 = USER
265 # endif /* AUTODIFF_4_LEVEL_CHECKPOINT */
266
267 # ifndef AUTODIFF_2_LEVEL_CHECKPOINT
268 do ilev_3 = 1,nchklev_3
269 if(ilev_3.le.max_lev3) then
270 c**************************************
271 CALL AUTODIFF_STORE( myThid )
272 #include "checkpoint_lev3_directives.h"
273 CALL AUTODIFF_RESTORE( myThid )
274 c**************************************
275 c-- Initialise storage for the middle loop.
276 CADJ INIT tapelev2 = USER
277 # endif /* AUTODIFF_2_LEVEL_CHECKPOINT */
278
279 do ilev_2 = 1,nchklev_2
280 if(ilev_2.le.max_lev2) then
281 c**************************************
282 CALL AUTODIFF_STORE( myThid )
283 #include "checkpoint_lev2_directives.h"
284 CALL AUTODIFF_RESTORE( myThid )
285 c**************************************
286
287 c**************************************
288 c--
289 c-- Initialize storage for the innermost loop.
290 c-- Always check common block sizes for the checkpointing!
291 c--
292 CADJ INIT comlev1 = COMMON,nchklev_1
293 CADJ INIT comlev1_bibj = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt
294 CADJ INIT comlev1_bibj_k = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt
295 c--
296 # ifdef ALLOW_KPP
297 CADJ INIT comlev1_kpp = COMMON,nchklev_1*nsx*nsy
298 CADJ INIT comlev1_kpp_k = COMMON,nchklev_1*nsx*nsy*nr
299 # endif /* ALLOW_KPP */
300 c--
301 # ifdef ALLOW_GMREDI
302 CADJ INIT comlev1_gmredi_k_gad
303 CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
304 # endif /* ALLOW_GMREDI */
305 c--
306 # ifdef ALLOW_PTRACERS
307 CADJ INIT comlev1_bibj_ptracers = COMMON,
308 CADJ & nchklev_1*nsx*nsy*nthreads_chkpt*PTRACERS_num
309 CADJ INIT comlev1_bibj_k_ptracers = COMMON,
310 CADJ & nchklev_1*nsx*nsy*nthreads_chkpt*PTRACERS_num*nr
311 # endif /* ALLOW_PTRACERS */
312 c--
313 # ifndef DISABLE_MULTIDIM_ADVECTION
314 CADJ INIT comlev1_bibj_k_gad = COMMON,
315 CADJ & nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
316 CADJ INIT comlev1_bibj_k_gad_pass = COMMON,
317 CADJ & nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass*maxpass
318 # endif /* DISABLE_MULTIDIM_ADVECTION */
319 c--
320 # ifndef AUTODIFF_DISABLE_LEITH
321 CADJ INIT comlev1_mom_ijk_loop
322 CADJ & = COMMON,nchklev_1*
323 CADJ & (snx+2*olx)*nsx*(sny+2*oly)*nsy*nr*nthreads_chkpt
324 # endif /* AUTODIFF_DISABLE_LEITH */
325 c--
326 # if (defined (ALLOW_EXF) && defined (ALLOW_BULKFORMULAE))
327 CADJ INIT comlev1_exf_1
328 CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
329 CADJ INIT comlev1_exf_2
330 CADJ & = COMMON,niter_bulk*nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
331 # endif /* ALLOW_BULKFORMULAE */
332 c--
333 # ifdef ALLOW_SEAICE
334 # ifdef SEAICE_ALLOW_DYNAMICS
335 cphCADJ INIT comlev1_lsr = COMMON,nchklev_1*2
336 CADJ INIT comlev1_dynsol = COMMON,nchklev_1*MPSEUDOTIMESTEPS
337 # endif
338 # ifdef SEAICE_ALLOW_EVP
339 CADJ INIT comlev1_evp = COMMON,nchklev_1
340 # endif
341 # endif /* ALLOW_SEAICE */
342 c--
343 # ifdef ALLOW_THSICE
344 CADJ INIT comlev1_thsice_1
345 CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
346 CADJ INIT comlev1_thsice_2
347 CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nlyr*nthreads_chkpt
348 CADJ INIT comlev1_thsice_3
349 CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*MaxTsf*nthreads_chkpt
350 CADJ INIT comlev1_thsice_4
351 CADJ & = COMMON,nchklev_1*nsx*nsy*maxpass*nthreads_chkpt
352 # endif /* ALLOW_THSICE */
353 c--
354 # ifdef ALLOW_DEPTH_CONTROL
355 CADJ INIT comlev1_cg2d
356 CADJ & = COMMON,nchklev_1*nthreads_chkpt
357 CADJ INIT comlev1_cg2d_iter
358 CADJ & = COMMON,nchklev_1*nthreads_chkpt*numItersMax
359 # endif
360 c--
361 c**************************************
362
363 do ilev_1 = 1,nchklev_1
364
365 c-- The if-statement below introduces a some flexibility in the
366 c-- choice of the 3-tupel ( nchklev_1, nchklev_2, nchklev_3 ).
367
368 iloop = (ilev_2 - 1)*nchklev_1 + ilev_1
369 # ifndef AUTODIFF_2_LEVEL_CHECKPOINT
370 & + (ilev_3 - 1)*nchklev_2*nchklev_1
371 # endif
372 # ifdef AUTODIFF_4_LEVEL_CHECKPOINT
373 & + (ilev_4 - 1)*nchklev_3*nchklev_2*nchklev_1
374 # endif
375
376 if ( iloop .le. nTimeSteps ) then
377
378 # else /* ALLOW_TAMC_CHECKPOINTING undefined */
379 c-- Initialise storage for reference trajectory without TAMC check-
380 c-- pointing.
381 CADJ INIT history = USER
382 CADJ INIT comlev1_bibj = COMMON,nchklev_0*nsx*nsy*nthreads_chkpt
383 CADJ INIT comlev1_bibj_k = COMMON,nchklev_0*nsx*nsy*nr*nthreads_chkpt
384 CADJ INIT comlev1_kpp = COMMON,nchklev_0*nsx*nsy
385
386 c-- Check the choice of the checkpointing parameters in relation
387 c-- to nTimeSteps: (nchklev_0 .ge. nTimeSteps)
388 if (nchklev_0 .lt. nTimeSteps) then
389 print*
390 print*, ' the_main_loop: TAMC checkpointing parameter ',
391 & 'nchklev_0 = ', nchklev_0
392 print*, ' not consistent with nTimeSteps = ',
393 & nTimeSteps
394 stop ' ... stopped in the_main_loop.'
395 endif
396
397 DO iloop = 1, nTimeSteps
398
399 # endif /* ALLOW_TAMC_CHECKPOINTING */
400 # endif /* ALLOW_AUTODIFF_TAMC */
401
402 #endif /* undef ALLOW_AUTODIFF_OPENAD */
403
404 #ifdef ALLOW_AUTODIFF_OPENAD
405 call openad_checkpointinit(uCheckLev1,
406 + uCheckLev2,
407 + uCheckLev3,
408 + uCheckLev4 )
409
410 theCurrentStep=0
411
412 if (uCheckLev4 .gt. 0 ) then
413 do ilev_4 = 1, uCheckLev4
414
415 #endif
416
417 #ifndef ALLOW_AUTODIFF
418
419 c-- Start the main loop of adjoint_Objfunc. Automatic differentiation
420 c-- NOT enabled.
421 DO iloop = 1, nTimeSteps
422
423 #endif /* ALLOW_AUTODIFF */
424
425 c-- >>> Loop body start <<<
426
427 #ifdef ALLOW_AUTODIFF_TAMC
428 nIter0 = NINT( (startTime-baseTime)/deltaTClock )
429 ikey_dynamics = ilev_1
430 #endif
431
432 #ifdef ALLOW_DEBUG
433 IF (debugMode) CALL DEBUG_CALL('FORWARD_STEP',myThid)
434 #endif
435
436 #ifdef ALLOW_ATM2D
437 CALL TIMER_START('FORWARD_STEP_ATM2D [THE_MAIN_LOOP]',mythid)
438 CALL FORWARD_STEP_ATM2D( iloop, mytime, myiter, mythid )
439 CALL TIMER_STOP ('FORWARD_STEP_ATM2D [THE_MAIN_LOOP]',mythid)
440 #else
441 CALL TIMER_START('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
442 # ifdef ALLOW_AUTODIFF_OPENAD
443 CALL THE_FOURTH_LEVEL_LOOP( ilev_4,
444 +uCheckLev1, uCheckLev2, uCheckLev3,uCheckLev4,
445 +theCurrentStep,
446 +myTime, myIter, myThid )
447 # else
448 CALL FORWARD_STEP( iloop, mytime, myiter, mythid )
449 # endif
450 CALL TIMER_STOP ('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
451 #endif
452
453 c-- >>> Loop body end <<<
454 #ifdef ALLOW_AUTODIFF
455 # ifndef ALLOW_AUTODIFF_OPENAD
456 # ifdef ALLOW_AUTODIFF_TAMC
457
458 # ifdef ALLOW_TAMC_CHECKPOINTING
459 endif
460 enddo
461 endif
462 enddo
463 # ifndef AUTODIFF_2_LEVEL_CHECKPOINT
464 endif
465 enddo
466 # endif
467 # ifdef AUTODIFF_4_LEVEL_CHECKPOINT
468 endif
469 enddo
470 # endif
471 # else /* ndef ALLOW_TAMC_CHECKPOINTING */
472 enddo
473 # endif /* ALLOW_TAMC_CHECKPOINTING */
474 # endif /* ALLOW_AUTODIFF_TAMC */
475 # else /* ALLOW_AUTODIFF_OPENAD */
476 end do
477 else
478 CALL THE_FOURTH_LEVEL_PLAIN(
479 +uCheckLev1, uCheckLev2, uCheckLev3,uCheckLev4,
480 +theCurrentStep,
481 +myTime, myIter, myThid )
482 end if
483 # endif /* ALLOW_AUTODIFF_OPENAD */
484 #else /* ALLOW_AUTODIFF */
485 enddo
486 #endif /* ALLOW_AUTODIFF */
487
488 #ifdef ALLOW_PROFILES
489 c-- Accumulate in-situ time averages of temperature, salinity, SSH.
490 CALL TIMER_START('PROFILES_INLOOP [THE_MAIN_LOOP]', mythid)
491 CALL PROFILES_INLOOP( mytime, mythid )
492 CALL TIMER_STOP ('PROFILES_INLOOP [THE_MAIN_LOOP]', mythid)
493 #endif
494
495 #ifdef ALLOW_COST
496 c-- Sum all cost function contributions.
497 CALL TIMER_START('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
498 CALL COST_FINAL ( mythid )
499 CALL TIMER_STOP ('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
500
501 # ifdef ALLOW_AUTODIFF_OPENAD
502 c$openad DEPENDENT(fc)
503 # endif /* ALLOW_AUTODIFF_OPENAD */
504
505 #endif /* ALLOW_COST */
506
507 _BARRIER
508 CALL TIMER_STOP ('MAIN LOOP [THE_MAIN_LOOP]', mythid)
509
510 #ifdef ALLOW_DEBUG
511 IF (debugMode) CALL DEBUG_LEAVE('THE_MAIN_LOOP',myThid)
512 #endif
513
514 END
515

  ViewVC Help
Powered by ViewVC 1.1.22