/[MITgcm]/MITgcm/pkg/ecco/the_main_loop.F
ViewVC logotype

Annotation of /MITgcm/pkg/ecco/the_main_loop.F

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


Revision 1.8 - (hide annotations) (download)
Fri Sep 17 23:02:01 2004 UTC (19 years, 9 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint55d_pre, checkpoint55b_post, checkpoint55, checkpoint55a_post
Changes since 1.7: +150 -147 lines
o bringing adjoint up to date for sheduled c55

1 heimbach 1.8 C $Header: /u/gcmpack/MITgcm/pkg/ecco/the_main_loop.F,v 1.7 2004/07/13 18:06:48 jmc Exp $
2 jmc 1.7 C $Name: $
3 heimbach 1.1
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     #ifdef ALLOW_OBCS
8     # include "OBCS_OPTIONS.h"
9     #endif
10     #ifdef ALLOW_SEAICE
11     # include "SEAICE_OPTIONS.h"
12     #endif
13    
14     subroutine the_main_loop( myTime, myIter, mythid )
15    
16     c ==================================================================
17     c SUBROUTINE the_main_loop
18     c ==================================================================
19     c
20     c o Run the ocean model and evaluate the specified cost function.
21     c
22     c *the_main_loop* is the top-level routine for the Tangent Linear and
23     c Adjoint Model Compiler (TAMC). For this purpose, the initialization
24     c of the model was split into two parts. Those parameters that do
25     c not depend on a specific model run are set in *initialise_fixed*,
26     c whereas those that do depend on the specific realization are
27     c initialized in *initialise_varia*. In order to do a so called
28     c checkpointing during the adjoint calculation and to account for the
29     c typical data involved in oceanographic applications a call tree
30     c that is divided into yearly, monthly, daily, and step parts can
31     c be used.
32     c
33     c This routine is to be used in conjuction with the MITgcmuv release
34     c checkpoint 24.
35     c
36     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
37     c
38     c changed: Christian Eckert eckert@mit.edu 14-Jul-1999
39     c
40     c - The call to mapping was moved to initialise_varia,
41     c since this routine has to be called before
42     c ini_predictor.
43     c
44     c Christian Eckert eckert@mit.edu 11-Feb-2000
45     c
46     c - Restructured the code in order to create a package
47     c for the MITgcmUV.
48     c
49     c Patrick Heimbach heimbach@mit.edu 3-Jun-2000
50     c - corrected computation of ikey_dynamics and
51     c added computation of ikey_dynamics for the case
52     c undef ALLOW_TAMC_CHECKPOINTING
53     c
54     c Patrick Heimbach heimbach@mit.edu 6-Jun-2000
55     c - corrected initialisation of comlev1 common blocks
56     c
57     c Dimitris Menemenlis menemenlis@jpl.nasa.gov 26-Feb-2003
58     c - modifications for pkg/seaice
59     c
60     c ==================================================================
61     c SUBROUTINE the_main_loop
62     c ==================================================================
63    
64     implicit none
65    
66     c == global variables ==
67    
68     #include "SIZE.h"
69     #include "EEPARAMS.h"
70     #include "PARAMS.h"
71    
72     c**************************************
73     #ifdef ALLOW_AUTODIFF_TAMC
74    
75     c These includes are needed for
76     c AD-checkpointing.
77     c They provide the fields to be stored.
78    
79     # include "GRID.h"
80     # include "DYNVARS.h"
81     # include "FFIELDS.h"
82     # include "EOS.h"
83     # include "GAD.h"
84    
85     # ifdef ALLOW_CD_CODE
86     # include "CD_CODE_VARS.h"
87     # endif
88     # ifdef ALLOW_PTRACERS
89 jmc 1.7 # include "PTRACERS_SIZE.h"
90 heimbach 1.1 # include "PTRACERS.h"
91     # endif
92     # ifdef ALLOW_NONHYDROSTATIC
93     # include "CG3D.h"
94     # endif
95     # ifdef EXACT_CONSERV
96     # include "SURFACE.h"
97     # endif
98     # ifdef ALLOW_OBCS
99     # include "OBCS.h"
100     # endif
101     # ifdef ALLOW_EXF
102     # include "exf_fields.h"
103     # include "exf_clim_fields.h"
104     # ifdef ALLOW_BULKFORMULAE
105     # include "exf_constants.h"
106     # endif
107     # endif /* ALLOW_EXF */
108     # ifdef ALLOW_SEAICE
109     # include "SEAICE.h"
110     # endif
111     # ifdef ALLOW_DIVIDED_ADJOINT_MPI
112     # include "mpif.h"
113     # endif
114    
115     # include "tamc.h"
116     # include "ctrl.h"
117     # include "ctrl_dummy.h"
118     # include "cost.h"
119 heimbach 1.3 # include "ecco_cost.h"
120 heimbach 1.1
121     #endif /* ALLOW_AUTODIFF_TAMC */
122     c**************************************
123    
124     c == routine arguments ==
125     c note: under the multi-threaded model myiter and
126     c mytime are local variables passed around as routine
127     c arguments. Although this is fiddly it saves the need to
128     c impose additional synchronisation points when they are
129     c updated.
130     c myiter - iteration counter for this thread
131     c mytime - time counter for this thread
132     c mythid - thread number for this instance of the routine.
133     integer mythid
134     integer myiter
135     _RL mytime
136    
137     c == local variables ==
138    
139     integer bi,bj
140     integer iloop
141     integer mydate(4)
142     #ifdef ALLOW_SNAPSHOTS
143     character yprefix*3
144     #endif
145    
146     #ifdef ALLOW_TAMC_CHECKPOINTING
147     integer ilev_1
148     integer ilev_2
149     integer ilev_3
150     integer max_lev2
151     integer max_lev3
152     #endif
153    
154     c-- == end of interface ==
155    
156     #ifndef DISABLE_DEBUGMODE
157     IF ( debugLevel .GE. debLevB )
158     & CALL DEBUG_ENTER('THE_MAIN_LOOP',myThid)
159     #endif
160    
161     #ifdef ALLOW_AUTODIFF_TAMC
162     c-- Initialize storage for the initialisations.
163     CADJ INIT tapelev3 = USER
164     c-- Some more initialisations to please TAMC
165     CADJ INIT tapelev_ini_bibj_k = USER
166     # ifdef ALLOW_DIVIDED_ADJOINT
167     CADJ INIT onetape = user
168     cphCADJ INIT onetape = common, 1
169     cph We want to avoid common blocks except in the inner loop.
170     cph Reason: the active write and consecutive read may occur
171     cph in separate model executions for which the info
172     cph in common blocks are lost.
173     cph Thus, we can only store real values (no integers)
174     cph because we only have active file handling to real available.
175     # endif
176     # ifdef ALLOW_TAMC_CHECKPOINTING
177     ikey_dynamics = 1
178     # endif
179     #endif /* ALLOW_AUTODIFF_TAMC */
180    
181     CALL TIMER_START('ECCO SPIN-UP', mythid)
182    
183     c-- Get the current date.
184     call CAL_TIMESTAMP( myiter, mytime, mydate, mythid )
185    
186     C-- Set initial conditions (variable arrays)
187     #ifndef DISABLE_DEBUGMODE
188     IF ( debugLevel .GE. debLevB )
189     & CALL DEBUG_CALL('INITIALISE_VARIA',myThid)
190     #endif
191     CALL TIMER_START('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
192     CALL INITIALISE_VARIA( mythid )
193     CALL TIMER_STOP ('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
194    
195 heimbach 1.8 #ifdef ALLOW_MONITOR
196     #ifdef ALLOW_DEBUG
197     IF (debugMode) CALL DEBUG_CALL('MONITOR',myThid)
198 heimbach 1.1 #endif
199     C-- Check status of solution (statistics, cfl, etc...)
200     CALL TIMER_START('MONITOR [THE_MAIN_LOOP]', mythid)
201     CALL MONITOR( myIter, myTime, myThid )
202     CALL TIMER_STOP ('MONITOR [THE_MAIN_LOOP]', mythid)
203     #endif /* ALLOW_MONITOR */
204 heimbach 1.4
205 heimbach 1.8 C-- Do IO if needed (Dump for start state).
206 heimbach 1.4 #ifdef ALLOW_DEBUG
207     IF (debugMode) CALL DEBUG_CALL('DO_THE_MODEL_IO',myThid)
208     #endif
209 heimbach 1.8
210     #ifdef ALLOW_OFFLINE
211     CALL TIMER_START('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
212     CALL OFFLINE_MODEL_IO( myTime, myIter, myThid )
213     CALL TIMER_STOP ('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
214     #else
215 heimbach 1.4 CALL TIMER_START('DO_THE_MODEL_IO [THE_MAIN_LOOP]', mythid)
216     CALL DO_THE_MODEL_IO( myTime, myIter, mythid )
217     CALL TIMER_STOP ('DO_THE_MODEL_IO [THE_MAIN_LOOP]', mythid)
218 heimbach 1.8 #endif
219 heimbach 1.1
220     call timer_stop ('ECCO SPIN-UP', mythid)
221     _BARRIER
222    
223     c-- Do the model integration.
224     call timer_start('ECCO MAIN LOOP',mythid)
225    
226     c >>>>>>>>>>>>>>>>>>>>>>>>>>> LOOP <<<<<<<<<<<<<<<<<<<<<<<<<<<<
227     c >>>>>>>>>>>>>>>>>>>>>>>>>>> STARTS <<<<<<<<<<<<<<<<<<<<<<<<<<<<
228    
229     #ifdef ALLOW_AUTODIFF_TAMC
230     #ifdef ALLOW_TAMC_CHECKPOINTING
231     c-- Implement a three level checkpointing. For a two level
232     c-- checkpointing delete the middle loop; for n levels (n > 3)
233     c-- insert more loops.
234    
235     c-- Check the choice of the checkpointing parameters in relation
236     c-- to nTimeSteps: (nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps)
237     if (nchklev_1*nchklev_2*nchklev_3 .lt. nTimeSteps) then
238     print*
239     print*, ' the_main_loop: TAMC checkpointing parameters'
240     print*, ' nchklev_1*nchklev_2*nchklev_3 = ',
241     & nchklev_1*nchklev_2*nchklev_3
242     print*, ' are not consistent with nTimeSteps = ',
243     & nTimeSteps
244     stop ' ... stopped in the_main_loop.'
245     endif
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     do ilev_3 = 1,nchklev_3
256     if(ilev_3.le.max_lev3) then
257     c**************************************
258     #include "checkpoint_lev3_directives.h"
259     c**************************************
260    
261     c-- Initialise storage for the middle loop.
262     CADJ INIT tapelev2 = USER
263    
264     do ilev_2 = 1,nchklev_2
265     if(ilev_2.le.max_lev2) then
266     c**************************************
267     #include "checkpoint_lev2_directives.h"
268     c**************************************
269    
270    
271     c**************************************
272     #ifdef ALLOW_AUTODIFF_TAMC
273     c-- Initialize storage for the innermost loop.
274     c-- Always check common block sizes for the checkpointing!
275     c--
276     CADJ INIT comlev1 = COMMON,nchklev_1
277     CADJ INIT comlev1_bibj = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt
278     CADJ INIT comlev1_bibj_k = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt
279     c--
280     # ifdef ALLOW_KPP
281     CADJ INIT comlev1_kpp = COMMON,nchklev_1*nsx*nsy
282 heimbach 1.6 CADJ INIT comlev1_kpp_k = COMMON,nchklev_1*nsx*nsy*nr
283 heimbach 1.1 # endif /* ALLOW_KPP */
284     c--
285     # ifdef ALLOW_GMREDI
286     CADJ INIT comlev1_gmredi_k_gad
287     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
288     # endif /* ALLOW_GMREDI */
289     c--
290     # ifdef ALLOW_PTRACERS
291     CADJ INIT comlev1_bibj_ptracers = COMMON,
292 jmc 1.7 CADJ & nchklev_1*nsx*nsy*nthreads_chkpt*PTRACERS_num
293 heimbach 1.1 # endif /* ALLOW_PTRACERS */
294     c--
295     # ifndef DISABLE_MULTIDIM_ADVECTION
296     CADJ INIT comlev1_bibj_k_gad
297     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
298     CADJ INIT comlev1_bibj_k_gad_pass
299     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass*maxcube
300     # endif /* DISABLE_MULTIDIM_ADVECTION */
301     c--
302     # if (defined (ALLOW_EXF) && defined (ALLOW_BULKFORMULAE))
303     CADJ INIT comlev1_exf_1
304     CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
305     CADJ INIT comlev1_exf_2
306     CADJ & = COMMON,niter_bulk*nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
307     # endif
308     c--
309     # ifdef ALLOW_SEAICE
310     # ifdef SEAICE_ALLOW_DYNAMICS
311     CADJ INIT comlev1_lsr = COMMON,nchklev_1*2
312     # endif
313     # ifdef SEAICE_MULTILEVEL
314     CADJ INIT comlev1_multdim
315     CADJ & = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt*multdim
316     # endif
317     # endif /* ALLOW_SEAICE */
318     c--
319     #endif /* ALLOW_AUTODIFF_TAMC */
320     c**************************************
321    
322     do ilev_1 = 1,nchklev_1
323    
324     c-- The if-statement below introduces a some flexibility in the
325     c-- choice of the 3-tupel ( nchklev_1, nchklev_2, nchklev_3 ).
326     c--
327     c-- Requirement: nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps .
328    
329     iloop = (ilev_3 - 1)*nchklev_2*nchklev_1 +
330     & (ilev_2 - 1)*nchklev_1 + ilev_1
331    
332     if ( iloop .le. nTimeSteps ) then
333    
334     #else /* ALLOW_TAMC_CHECKPOINTING undefined */
335     c-- Initialise storage for the reference trajectory without TAMC check-
336     c-- pointing.
337     CADJ INIT history = USER
338     CADJ INIT comlev1_bibj = COMMON,nchklev_0*nsx*nsy*nthreads_chkpt
339     CADJ INIT comlev1_bibj_k = COMMON,nchklev_0*nsx*nsy*nr*nthreads_chkpt
340     CADJ INIT comlev1_kpp = COMMON,nchklev_0*nsx*nsy
341    
342     c-- Check the choice of the checkpointing parameters in relation
343     c-- to nTimeSteps: (nchklev_0 .ge. nTimeSteps)
344     if (nchklev_0 .lt. nTimeSteps) then
345     print*
346     print*, ' the_main_loop: ',
347     & 'TAMC checkpointing parameter nchklev_0 = ',
348     & nchklev_0
349     print*, ' is not consistent with nTimeSteps = ',
350     & nTimeSteps
351     stop ' ... stopped in the_main_loop.'
352     endif
353    
354     do iloop = 1, nTimeSteps
355    
356     #endif /* ALLOW_TAMC_CHECKPOINTING */
357    
358     #else /* ALLOW_AUTODIFF_TAMC undefined */
359     c-- Start the main loop of ecco_Objfunc. Automatic differentiation is
360     c-- NOT enabled.
361     do iloop = 1, nTimeSteps
362     #endif /* ALLOW_AUTODIFF_TAMC */
363    
364     #ifdef ALLOW_TAMC_CHECKPOINTING
365     nIter0 = INT( startTime/deltaTClock )
366     ikey_dynamics = ilev_1
367     #endif
368    
369     c-- Set the model iteration counter and the model time.
370     myiter = nIter0 + (iloop-1)
371     mytime = startTime + float(iloop-1)*deltaTclock
372    
373     #ifdef ALLOW_COST
374    
375     c-- Accumulate time averages of temperature, salinity, and SSH.
376     call timer_start('COST_AVERAGESFIELDS [ECCO MAIN]', mythid)
377     call cost_averagesFields( mytime, mythid )
378     call timer_stop ('COST_AVERAGESFIELDS [ECCO MAIN]', mythid)
379     #ifdef ALLOW_COST_ATLANTIC
380     c-- Compute meridional heat transport
381     call timer_start('cost_atlantic [ECCO MAIN]', mythid)
382     call cost_atlantic( mytime, myiter,mythid )
383     call timer_stop ('cost_atlantic [ECCO MAIN]', mythid)
384     #endif
385     #endif /* ALLOW_COST */
386    
387     #ifdef ALLOW_AUTODIFF_TAMC
388     c**************************************
389     #include "checkpoint_lev1_directives.h"
390     c**************************************
391     #endif
392    
393     #ifndef DISABLE_DEBUGMODE
394     IF ( debugLevel .GE. debLevB )
395     & CALL DEBUG_CALL('EXF_GETFORCING',myThid)
396     #endif
397     CALL TIMER_START('EXF_GETFORCING [FORWARD_STEP]',mythid)
398     CALL EXF_GETFORCING( mytime, myiter, mythid )
399     CALL TIMER_STOP ('EXF_GETFORCING [FORWARD_STEP]',mythid)
400    
401     #ifdef ALLOW_SEAICE
402     cph this simple runtime flag causes a lot of recomp.
403     cph IF ( useSEAICE ) THEN
404     #ifndef DISABLE_DEBUGMODE
405     IF ( debugLevel .GE. debLevB )
406     & CALL DEBUG_CALL('SEAICE_MODEL',myThid)
407     #endif
408     CALL TIMER_START('SEAICE_MODEL [FORWARD_STEP]',myThid)
409     CALL SEAICE_MODEL( myTime, myIter, myThid )
410     CALL TIMER_STOP ('SEAICE_MODEL [FORWARD_STEP]',myThid)
411     #ifdef ALLOW_COST_ICE
412     CALL COST_ICE ( myTime, myIter, myThid )
413     #endif
414     cph ENDIF
415     #endif /* ALLOW_SEAICE */
416    
417     #if (defined (ALLOW_AUTODIFF_TAMC) && \
418     defined (ALLOW_AUTODIFF_MONITOR))
419     C Include call to a dummy routine. Its adjoint will be
420     C called at the proper place in the adjoint code.
421     C The adjoint routine will print out adjoint values
422     C if requested. The location of the call is important,
423     C it has to be after the adjoint of the exchanges
424     C (DO_GTERM_BLOCKING_EXCHANGES).
425     CALL DUMMY_IN_STEPPING( myTime, myIter, myThid )
426     #endif
427    
428 heimbach 1.8 #ifdef ALLOW_EBM
429     IF ( useEBM ) THEN
430     # ifdef ALLOW_DEBUG
431     IF ( debugLevel .GE. debLevB )
432     & CALL DEBUG_CALL('EBM',myThid)
433     # endif
434     CALL TIMER_START('EBM [FORWARD_STEP]',mythid)
435     CALL EBM_DRIVER ( myTime, myIter, myThid )
436     CALL TIMER_STOP ('EBM [FORWARD_STEP]',mythid)
437     ENDIF
438 heimbach 1.1 #endif
439    
440     C-- Step forward fields and calculate time tendency terms.
441    
442 heimbach 1.8 #ifdef ALLOW_DEBUG
443     IF ( debugLevel .GE. debLevB )
444     & CALL DEBUG_CALL('DO_ATMOSPHERIC_PHYS',myThid)
445 heimbach 1.1 #endif
446 heimbach 1.8 CALL TIMER_START('DO_ATMOSPHERIC_PHYS [FORWARD_STEP]',mythid)
447     CALL DO_ATMOSPHERIC_PHYS( myTime, myIter, myThid )
448     CALL TIMER_STOP ('DO_ATMOSPHERIC_PHYS [FORWARD_STEP]',mythid)
449 heimbach 1.1
450 heimbach 1.8 #ifndef ALLOW_OFFLINE
451     #ifdef ALLOW_DEBUG
452     IF ( debugLevel .GE. debLevB )
453     & CALL DEBUG_CALL('DO_OCEANIC_PHYS',myThid)
454 heimbach 1.1 #endif
455 heimbach 1.8 CALL TIMER_START('DO_OCEANIC_PHYS [FORWARD_STEP]',mythid)
456     CALL DO_OCEANIC_PHYS( myTime, myIter, myThid )
457     CALL TIMER_STOP ('DO_OCEANIC_PHYS [FORWARD_STEP]',mythid)
458 heimbach 1.1 #endif
459    
460 heimbach 1.8 IF ( .NOT.staggerTimeStep ) THEN
461     #ifdef ALLOW_DEBUG
462 heimbach 1.1 IF ( debugLevel .GE. debLevB )
463 heimbach 1.8 & CALL DEBUG_CALL('THERMODYNAMICS',myThid)
464 heimbach 1.1 #endif
465 heimbach 1.8 CALL TIMER_START('THERMODYNAMICS [FORWARD_STEP]',mythid)
466     CALL THERMODYNAMICS( myTime, myIter, myThid )
467     CALL TIMER_STOP ('THERMODYNAMICS [FORWARD_STEP]',mythid)
468     C-- if not staggerTimeStep: end
469 heimbach 1.1 ENDIF
470    
471     C-- Step forward fields and calculate time tendency terms.
472 heimbach 1.8 #ifndef ALLOW_OFFLINE
473 heimbach 1.1 #ifndef ALLOW_AUTODIFF_TAMC
474     IF ( momStepping ) THEN
475     #endif
476 heimbach 1.8 #ifdef ALLOW_DEBUG
477 heimbach 1.1 IF ( debugLevel .GE. debLevB )
478     & CALL DEBUG_CALL('DYNAMICS',myThid)
479     #endif
480     CALL TIMER_START('DYNAMICS [FORWARD_STEP]',mythid)
481     CALL DYNAMICS( myTime, myIter, myThid )
482     CALL TIMER_STOP ('DYNAMICS [FORWARD_STEP]',mythid)
483     #ifndef ALLOW_AUTODIFF_TAMC
484     ENDIF
485     #endif
486 heimbach 1.8 #endif
487 heimbach 1.1
488     #ifdef ALLOW_NONHYDROSTATIC
489     C-- Step forward W field in N-H algorithm
490     IF ( momStepping .AND. nonHydrostatic ) THEN
491 heimbach 1.8 #ifdef ALLOW_DEBUG
492     IF ( debugLevel .GE. debLevB )
493     & CALL DEBUG_CALL('CALC_GW',myThid)
494 heimbach 1.1 #endif
495     CALL TIMER_START('CALC_GW [FORWARD_STEP]',myThid)
496     CALL CALC_GW(myThid)
497     CALL TIMER_STOP ('CALC_GW [FORWARD_STEP]',myThid)
498     ENDIF
499     #endif
500    
501 heimbach 1.8 C-- Update time-counter
502     myIter = nIter0 + iLoop
503     myTime = startTime + deltaTClock * float(iLoop)
504    
505     C-- Update geometric factors:
506 heimbach 1.1 #ifdef NONLIN_FRSURF
507 heimbach 1.8 C- update hfacC,W,S and recip_hFac according to etaH(n+1) :
508 heimbach 1.1 IF ( nonlinFreeSurf.GT.0) THEN
509     IF ( select_rStar.GT.0 ) THEN
510     CALL TIMER_START('UPDATE_R_STAR [FORWARD_STEP]',myThid)
511     CALL UPDATE_R_STAR( myTime, myIter, myThid )
512     CALL TIMER_STOP ('UPDATE_R_STAR [FORWARD_STEP]',myThid)
513     ELSE
514     CALL TIMER_START('UPDATE_SURF_DR [FORWARD_STEP]',myThid)
515     CALL UPDATE_SURF_DR( myTime, myIter, myThid )
516     CALL TIMER_STOP ('UPDATE_SURF_DR [FORWARD_STEP]',myThid)
517     ENDIF
518     ENDIF
519     C- update also CG2D matrix (and preconditioner)
520     IF ( momStepping .AND. nonlinFreeSurf.GT.2 ) THEN
521     CALL TIMER_START('UPDATE_CG2D [FORWARD_STEP]',myThid)
522     CALL UPDATE_CG2D( myTime, myIter, myThid )
523     CALL TIMER_STOP ('UPDATE_CG2D [FORWARD_STEP]',myThid)
524     ENDIF
525     #endif
526    
527     C-- Apply Filters to u*,v* before SOLVE_FOR_PRESSURE
528     #ifdef ALLOW_SHAP_FILT
529     IF (useSHAP_FILT .AND. shap_filt_uvStar) THEN
530     CALL TIMER_START('SHAP_FILT [FORWARD_STEP]',myThid)
531     IF (implicDiv2Dflow.LT.1.) THEN
532     C-- Explicit+Implicit part of the Barotropic Flow Divergence
533     C => Filtering of uVel,vVel is necessary
534     CALL SHAP_FILT_APPLY_UV( uVel,vVel,
535 heimbach 1.8 & myTime, myIter, myThid )
536 heimbach 1.1 ENDIF
537 heimbach 1.8 CALL SHAP_FILT_APPLY_UV( gU,gV,myTime,myIter,myThid)
538 heimbach 1.1 CALL TIMER_STOP ('SHAP_FILT [FORWARD_STEP]',myThid)
539     ENDIF
540     #endif
541     #ifdef ALLOW_ZONAL_FILT
542     IF (useZONAL_FILT .AND. zonal_filt_uvStar) THEN
543     CALL TIMER_START('ZONAL_FILT_APPLY [FORWARD_STEP]',myThid)
544     IF (implicDiv2Dflow.LT.1.) THEN
545     C-- Explicit+Implicit part of the Barotropic Flow Divergence
546     C => Filtering of uVel,vVel is necessary
547     CALL ZONAL_FILT_APPLY_UV( uVel, vVel, myThid )
548     ENDIF
549     CALL ZONAL_FILT_APPLY_UV( gU, gV, myThid )
550     CALL TIMER_STOP ('ZONAL_FILT_APPLY [FORWARD_STEP]',myThid)
551     ENDIF
552     #endif
553    
554     C-- Solve elliptic equation(s).
555     C Two-dimensional only for conventional hydrostatic or
556     C three-dimensional for non-hydrostatic and/or IGW scheme.
557 heimbach 1.8 #ifndef ALLOW_OFFLINE
558 heimbach 1.1 IF ( momStepping ) THEN
559 heimbach 1.8 CALL TIMER_START('SOLVE_FOR_PRESSURE [FORWARD_STEP]',myThid)
560     CALL SOLVE_FOR_PRESSURE(myTime, myIter, myThid)
561     CALL TIMER_STOP ('SOLVE_FOR_PRESSURE [FORWARD_STEP]',myThid)
562 heimbach 1.1 ENDIF
563 heimbach 1.8 #endif
564    
565     C-- Correct divergence in flow field and cycle time-stepping momentum
566     c IF ( momStepping ) THEN
567     #ifndef ALLOW_OFFLINE
568     CALL TIMER_START('UV_CORRECTION_STEP [FORWARD_STEP]',myThid)
569     CALL MOMENTUM_CORRECTION_STEP(myTime, myIter, myThid)
570     CALL TIMER_STOP ('UV_CORRECTION_STEP [FORWARD_STEP]',myThid)
571     #endif
572     c ENDIF
573    
574     #ifdef EXACT_CONSERV
575     IF (exactConserv) THEN
576     C-- Update etaH(n+1) :
577     CALL TIMER_START('UPDATE_ETAH [FORWARD_STEP]',mythid)
578     CALL UPDATE_ETAH( myTime, myIter, myThid )
579     CALL TIMER_STOP ('UPDATE_ETAH [FORWARD_STEP]',mythid)
580     ENDIF
581     #endif /* EXACT_CONSERV */
582    
583     #ifdef NONLIN_FRSURF
584     IF ( select_rStar.NE.0 ) THEN
585     C-- r* : compute the future level thickness according to etaH(n+1)
586     CALL TIMER_START('CALC_R_STAR [FORWARD_STEP]',mythid)
587     CALL CALC_R_STAR(etaH, myTime, myIter, myThid )
588     CALL TIMER_STOP ('CALC_R_STAR [FORWARD_STEP]',mythid)
589     ELSEIF ( nonlinFreeSurf.GT.0) THEN
590     C-- compute the future surface level thickness according to etaH(n+1)
591     CALL TIMER_START('CALC_SURF_DR [FORWARD_STEP]',mythid)
592     CALL CALC_SURF_DR(etaH, myTime, myIter, myThid )
593     CALL TIMER_STOP ('CALC_SURF_DR [FORWARD_STEP]',mythid)
594     ENDIF
595     #endif /* NONLIN_FRSURF */
596    
597     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
598     IF ( staggerTimeStep ) THEN
599     C-- do exchanges of U,V (needed for multiDim) when using stagger time-step :
600     #ifdef ALLOW_DEBUG
601     IF ( debugLevel .GE. debLevB )
602     & CALL DEBUG_CALL('DO_STAGGER_FIELDS_EXCH.',myThid)
603     #endif
604     CALL TIMER_START('BLOCKING_EXCHANGES [FORWARD_STEP]',myThid)
605     CALL DO_STAGGER_FIELDS_EXCHANGES( myTime, myIter, myThid )
606     CALL TIMER_STOP ('BLOCKING_EXCHANGES [FORWARD_STEP]',myThid)
607    
608     #ifdef ALLOW_DEBUG
609     IF ( debugLevel .GE. debLevB )
610     & CALL DEBUG_CALL('THERMODYNAMICS',myThid)
611     #endif
612     CALL TIMER_START('THERMODYNAMICS [FORWARD_STEP]',mythid)
613     CALL THERMODYNAMICS( myTime, myIter, myThid )
614     CALL TIMER_STOP ('THERMODYNAMICS [FORWARD_STEP]',mythid)
615    
616     C-- if staggerTimeStep: end
617     ENDIF
618     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
619 heimbach 1.1
620     #ifdef ALLOW_AUTODIFF_TAMC
621     cph This is needed because convective_adjustment calls
622     cph find_rho which may use pressure()
623     CADJ STORE totphihyd = comlev1, key = ikey_dynamics
624     #endif
625 heimbach 1.8 C-- Cycle time-stepping Tracers arrays (T,S,+pTracers)
626     CALL TIMER_START('TS_CORRECTION_STEP [FORWARD_STEP]',myThid)
627     CALL TRACERS_CORRECTION_STEP(myTime, myIter, myThid)
628     CALL TIMER_STOP ('TS_CORRECTION_STEP [FORWARD_STEP]',myThid)
629 heimbach 1.1
630     C-- Do "blocking" sends and receives for tendency "overlap" terms
631     c CALL TIMER_START('BLOCKING_EXCHANGES [FORWARD_STEP]',myThid)
632     c CALL DO_GTERM_BLOCKING_EXCHANGES( myThid )
633     c CALL TIMER_STOP ('BLOCKING_EXCHANGES [FORWARD_STEP]',myThid)
634    
635     C-- Do "blocking" sends and receives for field "overlap" terms
636     CALL TIMER_START('BLOCKING_EXCHANGES [FORWARD_STEP]',myThid)
637     CALL DO_FIELDS_BLOCKING_EXCHANGES( myThid )
638     CALL TIMER_STOP ('BLOCKING_EXCHANGES [FORWARD_STEP]',myThid)
639    
640     #ifdef ALLOW_FLT
641     C-- Calculate float trajectories
642     IF (useFLT) THEN
643     CALL TIMER_START('FLOATS [FORWARD_STEP]',myThid)
644     CALL FLT_MAIN(myIter,myTime, myThid)
645     CALL TIMER_STOP ('FLOATS [FORWARD_STEP]',myThid)
646     ENDIF
647     #endif
648    
649 heimbach 1.8 C-- State-variables statistics (time-aver, diagnostics ...)
650     CALL TIMER_START('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
651     CALL DO_STATEVARS_DIAGS( myTime, myIter, myThid )
652     CALL TIMER_STOP ('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
653    
654     #ifndef ALLOW_OFFLINE
655 heimbach 1.1 #ifdef ALLOW_MONITOR
656     C-- Check status of solution (statistics, cfl, etc...)
657     CALL TIMER_START('MONITOR [FORWARD_STEP]',myThid)
658     CALL MONITOR( myIter, myTime, myThid )
659     CALL TIMER_STOP ('MONITOR [FORWARD_STEP]',myThid)
660     #endif /* ALLOW_MONITOR */
661 heimbach 1.8 #endif
662 heimbach 1.1
663     C-- Do IO if needed.
664 heimbach 1.8 #ifdef ALLOW_OFFLINE
665     CALL TIMER_START('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
666     CALL OFFLINE_MODEL_IO( myTime, myIter, myThid )
667     CALL TIMER_STOP ('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
668     #else
669 heimbach 1.1 CALL TIMER_START('DO_THE_MODEL_IO [FORWARD_STEP]',myThid)
670     CALL DO_THE_MODEL_IO( myTime, myIter, myThid )
671     CALL TIMER_STOP ('DO_THE_MODEL_IO [FORWARD_STEP]',myThid)
672 heimbach 1.8 #endif
673 heimbach 1.1
674     C-- Save state for restarts
675     CALL TIMER_START('WRITE_CHECKPOINT [FORWARD_STEP]',myThid)
676 heimbach 1.5 CALL PACKAGES_WRITE_PICKUP(
677 heimbach 1.8 I .FALSE., myTime, myIter, myThid )
678     #ifndef ALLOW_OFFLINE
679 heimbach 1.1 CALL WRITE_CHECKPOINT(
680 heimbach 1.8 I .FALSE., myTime, myIter, myThid )
681     #endif
682     CALL TIMER_STOP ('WRITE_CHECKPOINT [FORWARD_STEP]',myThid)
683 heimbach 1.1
684     #ifdef ALLOW_AUTODIFF_TAMC
685     #ifdef ALLOW_TAMC_CHECKPOINTING
686     endif
687     enddo
688     endif
689     enddo
690     endif
691     enddo
692     #else
693     enddo
694     #endif
695    
696     #else
697     enddo
698     #endif /* ALLOW_AUTODIFF_TAMC */
699    
700     _BARRIER
701     call timer_stop ('ECCO MAIN LOOP', mythid)
702    
703     call timer_start('ECCO SPIN-DOWN', mythid)
704    
705     #ifdef ALLOW_COST
706    
707     #ifdef ALLOW_DIVIDED_ADJOINT
708     CADJ STORE mytime = onetape
709     #endif
710     c-- Accumulate time averages of temperature, salinity, and SSH.
711     #ifndef DISABLE_DEBUGMODE
712     IF ( debugLevel .GE. debLevB )
713     & CALL DEBUG_CALL('cost_averagesfields',myThid)
714     #endif
715     call timer_start('cost_averagesfields [ECCO SPIN-DOWN]', mythid)
716     call cost_averagesfields( mytime, mythid )
717     call timer_stop ('cost_averagesfields [ECCO SPIN-DOWN]', mythid)
718     #ifdef ALLOW_DIVIDED_ADJOINT
719     c**************************************
720 heimbach 1.2 #include "cost_averages_bar_directives.h"
721 heimbach 1.1 c**************************************
722     #endif
723    
724     #ifdef ALLOW_COST_ATLANTIC
725     c-- Compute meridional heat transport
726     #ifndef DISABLE_DEBUGMODE
727     IF ( debugLevel .GE. debLevB )
728     & CALL DEBUG_CALL('cost_atlantic',myThid)
729     #endif
730     call timer_start('cost_atlantic [ECCO SPIN-DOWN]', mythid)
731     call cost_atlantic( mytime, myiter,mythid )
732     call timer_stop ('cost_atlantic [ECCO SPIN-DOWN]', mythid)
733     #endif
734    
735 heimbach 1.8 c-- Compute the cost function contribution of the boundary forcing,
736     c-- i.e. heat flux, salt flux, zonal and meridional wind stress.
737     call timer_start('COST_FORCING [ECCO SPIN-UP]', mythid)
738     call cost_forcing( myiter, mytime, mythid )
739     call timer_stop ('COST_FORCING [ECCO SPIN-UP]', mythid)
740    
741     #ifdef ALLOW_OBCS_COST_CONTRIBUTION
742     call timer_start('cost_obcs [ECCO SPIN-UP]', mythid)
743     call cost_obcs( myiter, mytime, mythid )
744     call timer_stop ('cost_obcs [ECCO SPIN-UP]', mythid)
745     #endif
746    
747 heimbach 1.1 c-- Compute cost function contribution of Temperature and Salinity.
748     #ifndef DISABLE_DEBUGMODE
749     IF ( debugLevel .GE. debLevB )
750     & CALL DEBUG_CALL('cost_hyd',myThid)
751     #endif
752     call timer_start('cost_hyd [ECCO SPIN-DOWN]', mythid)
753     call cost_hyd( myiter, mytime, mythid )
754     call timer_stop ('cost_hyd [ECCO SPIN-DOWN]', mythid)
755    
756     #ifdef ALLOW_CURMTR_COST_CONTRIBUTION
757     #ifndef DISABLE_DEBUGMODE
758     IF ( debugLevel .GE. debLevB )
759     & CALL DEBUG_CALL('cost_curmtr',myThid)
760     #endif
761     call timer_start('cost_curmtr [ECCO SPIN-DOWN]', mythid)
762     call cost_curmtr( myiter, mytime, mythid )
763     call timer_stop ('cost_curmtr [ECCO SPIN-DOWN]', mythid)
764     #endif
765    
766     c-- Compute cost function contribution of SSH.
767     #ifdef ALLOW_SSH_COST_CONTRIBUTION
768     #ifndef DISABLE_DEBUGMODE
769     IF ( debugLevel .GE. debLevB )
770     & CALL DEBUG_CALL('cost_ssh',myThid)
771     #endif
772     call timer_start('cost_ssh [ECCO SPIN-DOWN]', mythid)
773     call cost_ssh( myiter, mytime, mythid )
774     call timer_stop ('cost_ssh [ECCO SPIN-DOWN]', mythid)
775     #endif
776    
777     c-- Compute cost function contribution of SSS.
778     #ifdef ALLOW_SST_COST_CONTRIBUTION
779     #ifndef DISABLE_DEBUGMODE
780     IF ( debugLevel .GE. debLevB )
781     & CALL DEBUG_CALL('cost_sst',myThid)
782     #endif
783     call timer_start('cost_sst [ECCO SPIN-DOWN]', mythid)
784     call cost_sst( myiter, mytime, mythid )
785     call timer_stop ('cost_sst [ECCO SPIN-DOWN]', mythid)
786     #endif
787    
788     c-- Compute cost function contribution of SSS.
789     #ifdef ALLOW_SSS_COST_CONTRIBUTION
790     #ifndef DISABLE_DEBUGMODE
791     IF ( debugLevel .GE. debLevB )
792     & CALL DEBUG_CALL('cost_sss',myThid)
793     #endif
794     call timer_start('cost_sss [ECCO SPIN-DOWN]', mythid)
795     call cost_sss( myiter, mytime, mythid )
796     call timer_stop ('cost_sss [ECCO SPIN-DOWN]', mythid)
797     #endif
798    
799     c-- Compute cost function contribution of drifter's velocities.
800     #ifdef ALLOW_DRIFTER_COST_CONTRIBUTION
801     #ifndef DISABLE_DEBUGMODE
802     IF ( debugLevel .GE. debLevB )
803     & CALL DEBUG_CALL('cost_drifter',myThid)
804     #endif
805     call timer_start('cost_drifter [ECCO SPIN-DOWN]', mythid)
806     call cost_drifter( myiter, mytime, mythid )
807     call timer_stop ('cost_drifter [ECCO SPIN-DOWN]', mythid)
808     #endif
809    
810     c-- Compute cost function contribution of wind stress observations.
811     #ifdef ALLOW_SCAT_COST_CONTRIBUTION
812     #ifndef DISABLE_DEBUGMODE
813     IF ( debugLevel .GE. debLevB )
814     & CALL DEBUG_CALL('cost_scat',myThid)
815     #endif
816     call timer_start('cost_scat [ECCO SPIN-DOWN]', mythid)
817     call cost_scat( myiter, mytime, mythid )
818     call timer_stop ('cost_scat [ECCO SPIN-DOWN]', mythid)
819     #endif
820    
821     c-- Compute cost function contribution of wind stress observations.
822     #ifdef ALLOW_MEAN_HFLUX_COST_CONTRIBUTION
823     call timer_start('cost_mean_heatflux [ECCO SPIN-DOWN]', mythid)
824     call cost_mean_heatflux( myiter, mytime, mythid )
825     call timer_stop ('cost_mean_heatflux [ECCO SPIN-DOWN]', mythid)
826     #endif
827    
828     c-- Compute cost function contribution of wind stress observations.
829     #ifdef ALLOW_MEAN_SFLUX_COST_CONTRIBUTION
830     call timer_start('cost_mean_saltflux [ECCO SPIN-DOWN]', mythid)
831     call cost_mean_saltflux( myiter, mytime, mythid )
832     call timer_stop ('cost_mean_saltflux [ECCO SPIN-DOWN]', mythid)
833     #endif
834    
835     c-- Compute cost function contribution of drift between the first
836     c and the last year.
837     #ifdef ALLOW_DRIFT_COST_CONTRIBUTION
838     #ifndef DISABLE_DEBUGMODE
839     IF ( debugLevel .GE. debLevB )
840     & CALL DEBUG_CALL('cost_drift',myThid)
841     #endif
842     call timer_start('cost_drift [ECCO SPIN-DOWN]', mythid)
843     call cost_drift( myiter, mytime, mythid )
844     call timer_stop ('cost_drift [ECCO SPIN-DOWN]', mythid)
845     #endif
846     #ifdef ALLOW_DRIFTW_COST_CONTRIBUTION
847     #ifndef DISABLE_DEBUGMODE
848     IF ( debugLevel .GE. debLevB )
849     & CALL DEBUG_CALL('cost_driftw',myThid)
850     #endif
851     call timer_start('cost_driftw [ECCO SPIN-DOWN]', mythid)
852     call cost_driftw( myiter, mytime, mythid )
853     call timer_stop ('cost_driftw [ECCO SPIN-DOWN]', mythid)
854     #endif
855     _BARRIER
856    
857     c-- Compute initial vs. final T/S deviation
858     #ifdef ALLOW_COST_INI_FIN
859     call timer_start('cost_ini_fin [ECCO SPIN-DOWN]', mythid)
860     call cost_theta_ini_fin( myiter, mytime, mythid )
861     call cost_salt_ini_fin( myiter, mytime, mythid )
862     call timer_stop ('cost_ini_fin [ECCO SPIN-DOWN]', mythid)
863     #endif
864     _BARRIER
865    
866     c-- Sum all cost function contributions.
867     #ifndef DISABLE_DEBUGMODE
868     IF ( debugLevel .GE. debLevB )
869     & CALL DEBUG_CALL('cost_final',myThid)
870     #endif
871     call timer_start('COST_FINAL [ECCO SPIN-DOWN]', mythid)
872     call cost_final( mythid )
873     call timer_stop ('COST_FINAL [ECCO SPIN-DOWN]', mythid)
874    
875     #endif /* ALLOW_COST */
876    
877     call timer_stop ('ECCO SPIN-DOWN', mythid)
878    
879     #ifndef DISABLE_DEBUGMODE
880     IF ( debugLevel .GE. debLevB )
881     & CALL DEBUG_LEAVE('THE_MAIN_LOOP',myThid)
882     #endif
883    
884     return
885     end
886    

  ViewVC Help
Powered by ViewVC 1.1.22