/[MITgcm]/MITgcm_contrib/heimbach/ice_only_estimation/code/the_main_loop.F
ViewVC logotype

Annotation of /MITgcm_contrib/heimbach/ice_only_estimation/code/the_main_loop.F

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


Revision 1.1 - (hide annotations) (download)
Sat Sep 3 12:01:23 2005 UTC (19 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: HEAD
A seaice-only (no ocean) config. for 1x1 deg. Lab. Sea

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/the_main_loop.F,v 1.20 2005/07/28 13:51:36 heimbach Exp $
2     C $Name: $
3    
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     #ifdef ALLOW_GMREDI
14     # include "GMREDI_OPTIONS.h"
15     #endif
16    
17     subroutine the_main_loop( myTime, myIter, mythid )
18    
19     c ==================================================================
20     c SUBROUTINE the_main_loop
21     c ==================================================================
22     c
23     c o Run the ocean model and evaluate the specified cost function.
24     c
25     c *the_main_loop* is the top-level routine for the Tangent Linear and
26     c Adjoint Model Compiler (TAMC). For this purpose, the initialization
27     c of the model was split into two parts. Those parameters that do
28     c not depend on a specific model run are set in *initialise_fixed*,
29     c whereas those that do depend on the specific realization are
30     c initialized in *initialise_varia*. In order to do a so called
31     c checkpointing during the adjoint calculation and to account for the
32     c typical data involved in oceanographic applications a call tree
33     c that is divided into yearly, monthly, daily, and step parts can
34     c be used.
35     c
36     c This routine is to be used in conjuction with the MITgcmuv release
37     c checkpoint 24.
38     c
39     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
40     c
41     c changed: Christian Eckert eckert@mit.edu 14-Jul-1999
42     c
43     c - The call to mapping was moved to initialise_varia,
44     c since this routine has to be called before
45     c ini_predictor.
46     c
47     c Christian Eckert eckert@mit.edu 11-Feb-2000
48     c
49     c - Restructured the code in order to create a package
50     c for the MITgcmUV.
51     c
52     c Patrick Heimbach heimbach@mit.edu 3-Jun-2000
53     c - corrected computation of ikey_dynamics and
54     c added computation of ikey_dynamics for the case
55     c undef ALLOW_TAMC_CHECKPOINTING
56     c
57     c Patrick Heimbach heimbach@mit.edu 6-Jun-2000
58     c - corrected initialisation of comlev1 common blocks
59     c
60     c Dimitris Menemenlis menemenlis@jpl.nasa.gov 26-Feb-2003
61     c - modifications for pkg/seaice
62     c
63     c ==================================================================
64     c SUBROUTINE the_main_loop
65     c ==================================================================
66    
67     implicit none
68    
69     c == global variables ==
70    
71     #include "SIZE.h"
72     #include "EEPARAMS.h"
73     #include "PARAMS.h"
74    
75     c**************************************
76     #ifdef ALLOW_AUTODIFF_TAMC
77    
78     c These includes are needed for
79     c AD-checkpointing.
80     c They provide the fields to be stored.
81    
82     # include "GRID.h"
83     # include "DYNVARS.h"
84     # include "FFIELDS.h"
85     # include "EOS.h"
86     # include "GAD.h"
87    
88     # ifdef ALLOW_CD_CODE
89     # include "CD_CODE_VARS.h"
90     # endif
91     # ifdef ALLOW_PTRACERS
92     # include "PTRACERS_SIZE.h"
93     # include "PTRACERS.h"
94     # endif
95     # ifdef ALLOW_NONHYDROSTATIC
96     # include "CG3D.h"
97     # endif
98     # ifdef EXACT_CONSERV
99     # include "SURFACE.h"
100     # endif
101     # ifdef ALLOW_OBCS
102     # include "OBCS.h"
103     # endif
104     # ifdef ALLOW_EXF
105     # include "exf_fields.h"
106     # include "exf_clim_fields.h"
107     # ifdef ALLOW_BULKFORMULAE
108     # include "exf_constants.h"
109     # endif
110     # endif /* ALLOW_EXF */
111     # ifdef ALLOW_SEAICE
112     # include "SEAICE.h"
113     # endif
114     # ifdef ALLOW_KPP
115     # include "KPP.h"
116     # endif
117     # ifdef ALLOW_GMREDI
118     # include "GMREDI.h"
119     # endif
120     # ifdef ALLOW_DIVIDED_ADJOINT_MPI
121     # include "mpif.h"
122     # endif
123    
124     # include "tamc.h"
125     # include "ctrl.h"
126     # include "ctrl_dummy.h"
127     # include "cost.h"
128     # include "ecco_cost.h"
129    
130     #endif /* ALLOW_AUTODIFF_TAMC */
131     c**************************************
132    
133     c == routine arguments ==
134     c note: under the multi-threaded model myiter and
135     c mytime are local variables passed around as routine
136     c arguments. Although this is fiddly it saves the need to
137     c impose additional synchronisation points when they are
138     c updated.
139     c myiter - iteration counter for this thread
140     c mytime - time counter for this thread
141     c mythid - thread number for this instance of the routine.
142     integer mythid
143     integer myiter
144     _RL mytime
145    
146     c == local variables ==
147    
148     integer bi,bj
149     integer iloop
150     integer mydate(4)
151     #ifdef ALLOW_SNAPSHOTS
152     character yprefix*3
153     #endif
154    
155     #ifdef ALLOW_TAMC_CHECKPOINTING
156     integer ilev_1
157     integer ilev_2
158     integer ilev_3
159     integer max_lev2
160     integer max_lev3
161     #endif
162    
163     c-- == end of interface ==
164    
165     #ifndef DISABLE_DEBUGMODE
166     IF ( debugLevel .GE. debLevB )
167     & CALL DEBUG_ENTER('THE_MAIN_LOOP',myThid)
168     #endif
169    
170     #ifdef ALLOW_AUTODIFF_TAMC
171     c-- Initialize storage for the initialisations.
172     CADJ INIT tapelev_ini_bibj_k = USER
173     CADJ INIT tapelev_init = USER
174     #ifdef AUTODIFF_2_LEVEL_CHECKPOINT
175     CADJ INIT tapelev2 = USER
176     #else
177     CADJ INIT tapelev3 = USER
178     #endif
179     # ifdef ALLOW_DIVIDED_ADJOINT
180     CADJ INIT onetape = user
181     cphCADJ INIT onetape = common, 1
182     cph We want to avoid common blocks except in the inner loop.
183     cph Reason: the active write and consecutive read may occur
184     cph in separate model executions for which the info
185     cph in common blocks are lost.
186     cph Thus, we can only store real values (no integers)
187     cph because we only have active file handling to real available.
188     # endif
189     # ifdef ALLOW_TAMC_CHECKPOINTING
190     ikey_dynamics = 1
191     # endif
192     #endif /* ALLOW_AUTODIFF_TAMC */
193    
194     CALL TIMER_START('ECCO SPIN-UP', mythid)
195    
196     c-- Get the current date.
197     call CAL_TIMESTAMP( myiter, mytime, mydate, mythid )
198    
199     C-- Set initial conditions (variable arrays)
200     #ifndef DISABLE_DEBUGMODE
201     IF ( debugLevel .GE. debLevB )
202     & CALL DEBUG_CALL('INITIALISE_VARIA',myThid)
203     #endif
204     CALL TIMER_START('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
205     CALL INITIALISE_VARIA( mythid )
206     CALL TIMER_STOP ('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
207    
208     #ifdef ALLOW_MONITOR
209     #ifdef ALLOW_DEBUG
210     IF (debugMode) CALL DEBUG_CALL('MONITOR',myThid)
211     #endif
212     C-- Check status of solution (statistics, cfl, etc...)
213     CALL TIMER_START('MONITOR [THE_MAIN_LOOP]', mythid)
214     CALL MONITOR( myIter, myTime, myThid )
215     CALL TIMER_STOP ('MONITOR [THE_MAIN_LOOP]', mythid)
216     #endif /* ALLOW_MONITOR */
217    
218     C-- Do IO if needed (Dump for start state).
219     #ifdef ALLOW_DEBUG
220     IF (debugMode) CALL DEBUG_CALL('DO_THE_MODEL_IO',myThid)
221     #endif
222    
223     #ifdef ALLOW_OFFLINE
224     CALL TIMER_START('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
225     CALL OFFLINE_MODEL_IO( myTime, myIter, myThid )
226     CALL TIMER_STOP ('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
227     #else
228     CALL TIMER_START('DO_THE_MODEL_IO [THE_MAIN_LOOP]', mythid)
229     CALL DO_THE_MODEL_IO( myTime, myIter, mythid )
230     CALL TIMER_STOP ('DO_THE_MODEL_IO [THE_MAIN_LOOP]', mythid)
231     #endif
232    
233     call timer_stop ('ECCO SPIN-UP', mythid)
234     _BARRIER
235    
236     c-- Do the model integration.
237     call timer_start('ECCO MAIN LOOP',mythid)
238    
239     c >>>>>>>>>>>>>>>>>>>>>>>>>>> LOOP <<<<<<<<<<<<<<<<<<<<<<<<<<<<
240     c >>>>>>>>>>>>>>>>>>>>>>>>>>> STARTS <<<<<<<<<<<<<<<<<<<<<<<<<<<<
241    
242     #ifdef ALLOW_AUTODIFF_TAMC
243     #ifdef ALLOW_TAMC_CHECKPOINTING
244    
245     max_lev3=nTimeSteps/(nchklev_1*nchklev_2)+1
246     max_lev2=nTimeSteps/nchklev_1+1
247    
248     c**************************************
249     #ifdef ALLOW_DIVIDED_ADJOINT
250     CADJ loop = divided
251     #endif
252     c**************************************
253    
254     #ifndef AUTODIFF_2_LEVEL_CHECKPOINT
255    
256     do ilev_3 = 1,nchklev_3
257     if(ilev_3.le.max_lev3) then
258     c**************************************
259     #include "checkpoint_lev3_directives.h"
260     c**************************************
261    
262     c-- Initialise storage for the middle loop.
263     CADJ INIT tapelev2 = USER
264    
265     #endif /* AUTODIFF_2_LEVEL_CHECKPOINT */
266    
267     do ilev_2 = 1,nchklev_2
268     if(ilev_2.le.max_lev2) then
269     c**************************************
270     #include "checkpoint_lev2_directives.h"
271     c**************************************
272    
273     c**************************************
274     #ifdef ALLOW_AUTODIFF_TAMC
275     c-- Initialize storage for the innermost loop.
276     c-- Always check common block sizes for the checkpointing!
277     c--
278     CADJ INIT comlev1 = COMMON,nchklev_1
279     CADJ INIT comlev1_bibj = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt
280     CADJ INIT comlev1_bibj_k = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt
281     c--
282     # ifdef ALLOW_KPP
283     CADJ INIT comlev1_kpp = COMMON,nchklev_1*nsx*nsy
284     CADJ INIT comlev1_kpp_k = COMMON,nchklev_1*nsx*nsy*nr
285     # endif /* ALLOW_KPP */
286     c--
287     # ifdef ALLOW_GMREDI
288     CADJ INIT comlev1_gmredi_k_gad
289     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
290     # endif /* ALLOW_GMREDI */
291     c--
292     # ifdef ALLOW_PTRACERS
293     CADJ INIT comlev1_bibj_ptracers = COMMON,
294     CADJ & nchklev_1*nsx*nsy*nthreads_chkpt*PTRACERS_num
295     # endif /* ALLOW_PTRACERS */
296     c--
297     # ifndef DISABLE_MULTIDIM_ADVECTION
298     CADJ INIT comlev1_bibj_k_gad
299     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
300     CADJ INIT comlev1_bibj_k_gad_pass
301     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass*maxcube
302     # endif /* DISABLE_MULTIDIM_ADVECTION */
303     c--
304     # if (defined (ALLOW_EXF) && defined (ALLOW_BULKFORMULAE))
305     CADJ INIT comlev1_exf_1
306     CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
307     CADJ INIT comlev1_exf_2
308     CADJ & = COMMON,niter_bulk*nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
309     # endif
310     c--
311     # ifdef ALLOW_SEAICE
312     # ifdef SEAICE_ALLOW_DYNAMICS
313     CADJ INIT comlev1_lsr = COMMON,nchklev_1*2
314     # endif
315     # ifdef SEAICE_MULTILEVEL
316     CADJ INIT comlev1_multdim
317     CADJ & = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt*multdim
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     c--
329     c-- Requirement: nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps .
330    
331     iloop = (ilev_2 - 1)*nchklev_1 + ilev_1
332     #ifndef AUTODIFF_2_LEVEL_CHECKPOINT
333     & + (ilev_3 - 1)*nchklev_2*nchklev_1
334     #endif
335    
336     if ( iloop .le. nTimeSteps ) then
337    
338     #else /* ALLOW_TAMC_CHECKPOINTING undefined */
339     c-- Initialise storage for the reference trajectory without TAMC check-
340     c-- pointing.
341     CADJ INIT history = USER
342     CADJ INIT comlev1_bibj = COMMON,nchklev_0*nsx*nsy*nthreads_chkpt
343     CADJ INIT comlev1_bibj_k = COMMON,nchklev_0*nsx*nsy*nr*nthreads_chkpt
344     CADJ INIT comlev1_kpp = COMMON,nchklev_0*nsx*nsy
345    
346     c-- Check the choice of the checkpointing parameters in relation
347     c-- to nTimeSteps: (nchklev_0 .ge. nTimeSteps)
348     if (nchklev_0 .lt. nTimeSteps) then
349     print*
350     print*, ' the_main_loop: ',
351     & 'TAMC checkpointing parameter nchklev_0 = ',
352     & nchklev_0
353     print*, ' is 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     c-- Start the main loop of ecco_Objfunc. Automatic differentiation is
364     c-- NOT enabled.
365     do iloop = 1, nTimeSteps
366     #endif /* ALLOW_AUTODIFF_TAMC */
367    
368     #ifdef ALLOW_TAMC_CHECKPOINTING
369     nIter0 = NINT( (startTime-baseTime)/deltaTClock )
370     ikey_dynamics = ilev_1
371     #endif
372    
373     c-- Set the model iteration counter and the model time.
374     myiter = nIter0 + (iloop-1)
375     mytime = startTime + float(iloop-1)*deltaTclock
376    
377     #ifdef ALLOW_AUTODIFF_TAMC
378     CALL AUTODIFF_INADMODE_UNSET( myThid )
379     #endif
380    
381    
382     #ifdef ALLOW_COST
383    
384     c-- Accumulate time averages of temperature, salinity, and SSH.
385     call timer_start('COST_AVERAGESFIELDS [ECCO MAIN]', mythid)
386     call cost_averagesFields( mytime, mythid )
387     call timer_stop ('COST_AVERAGESFIELDS [ECCO MAIN]', mythid)
388     #ifdef ALLOW_COST_ATLANTIC
389     c-- Compute meridional heat transport
390     call timer_start('cost_atlantic [ECCO MAIN]', mythid)
391     call cost_atlantic( mytime, myiter,mythid )
392     call timer_stop ('cost_atlantic [ECCO MAIN]', mythid)
393     #endif
394     #endif /* ALLOW_COST */
395    
396     #ifdef ALLOW_AUTODIFF_TAMC
397     c**************************************
398     #include "checkpoint_lev1_directives.h"
399     c**************************************
400     #endif
401    
402     #ifndef DISABLE_DEBUGMODE
403     IF ( debugLevel .GE. debLevB )
404     & CALL DEBUG_CALL('EXF_GETFORCING',myThid)
405     #endif
406     CALL TIMER_START('EXF_GETFORCING [FORWARD_STEP]',mythid)
407     CALL EXF_GETFORCING( mytime, myiter, mythid )
408     CALL TIMER_STOP ('EXF_GETFORCING [FORWARD_STEP]',mythid)
409    
410     #ifdef ALLOW_AUTODIFF_TAMC
411     # if (defined (ALLOW_AUTODIFF_MONITOR))
412     CALL DUMMY_IN_STEPPING( myTime, myIter, myThid )
413     # endif
414     #endif
415    
416     #ifdef ALLOW_SEAICE
417     cph this simple runtime flag causes a lot of recomp.
418     IF ( useSEAICE ) THEN
419     #ifndef DISABLE_DEBUGMODE
420     IF ( debugLevel .GE. debLevB )
421     & CALL DEBUG_CALL('SEAICE_MODEL',myThid)
422     #endif
423     #ifdef ALLOW_AUTODIFF_TAMC
424     CADJ STORE area = comlev1, key = ikey_dynamics
425     #endif
426     CALL TIMER_START('SEAICE_MODEL [FORWARD_STEP]',myThid)
427     CALL SEAICE_MODEL( myTime, myIter, myThid )
428     CALL TIMER_STOP ('SEAICE_MODEL [FORWARD_STEP]',myThid)
429     #ifdef ALLOW_COST_ICE
430     CALL COST_ICE ( myTime, myIter, myThid )
431     #endif
432     ENDIF
433     #endif /* ALLOW_SEAICE */
434    
435     #ifdef ALLOW_AUTODIFF_TAMC
436     # ifdef ALLOW_PTRACERS
437     cph this replaces _bibj storing of ptracer within thermodynamics
438     CADJ STORE ptracer = comlev1, key = ikey_dynamics
439     # endif
440     #endif
441    
442     #ifndef ALLOW_OFFLINE
443     #ifdef ALLOW_DEBUG
444     IF ( debugLevel .GE. debLevB )
445     & CALL DEBUG_CALL('DO_OCEANIC_PHYS',myThid)
446     #endif
447     CALL TIMER_START('DO_OCEANIC_PHYS [FORWARD_STEP]',mythid)
448     CALL DO_OCEANIC_PHYS( myTime, myIter, myThid )
449     CALL TIMER_STOP ('DO_OCEANIC_PHYS [FORWARD_STEP]',mythid)
450     #endif
451    
452     C-- Update time-counter
453     myIter = nIter0 + iLoop
454     myTime = startTime + deltaTClock * float(iLoop)
455    
456     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
457    
458    
459     #ifdef ALLOW_AUTODIFF_TAMC
460     CALL AUTODIFF_INADMODE_SET( myThid )
461     #endif
462    
463     C-- State-variables statistics (time-aver, diagnostics ...)
464     CALL TIMER_START('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
465     CALL DO_STATEVARS_DIAGS( myTime, myIter, myThid )
466     CALL TIMER_STOP ('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
467    
468     #ifndef ALLOW_OFFLINE
469     #ifdef ALLOW_MONITOR
470     C-- Check status of solution (statistics, cfl, etc...)
471     CALL TIMER_START('MONITOR [FORWARD_STEP]',myThid)
472     CALL MONITOR( myIter, myTime, myThid )
473     CALL TIMER_STOP ('MONITOR [FORWARD_STEP]',myThid)
474     #endif /* ALLOW_MONITOR */
475     #endif
476    
477     C-- Do IO if needed.
478     #ifdef ALLOW_OFFLINE
479     CALL TIMER_START('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
480     CALL OFFLINE_MODEL_IO( myTime, myIter, myThid )
481     CALL TIMER_STOP ('OFFLINE_MODEL_IO [FORWARD_STEP]',myThid)
482     #else
483     CALL TIMER_START('DO_THE_MODEL_IO [FORWARD_STEP]',myThid)
484     CALL DO_THE_MODEL_IO( myTime, myIter, myThid )
485     CALL TIMER_STOP ('DO_THE_MODEL_IO [FORWARD_STEP]',myThid)
486     #endif
487    
488     #ifdef ALLOW_AUTODIFF_TAMC
489     #ifdef ALLOW_TAMC_CHECKPOINTING
490     endif
491     enddo
492     endif
493     enddo
494     #ifndef AUTODIFF_2_LEVEL_CHECKPOINT
495     endif
496     enddo
497     #endif
498     #else
499     enddo
500     #endif
501    
502     #else
503     enddo
504     #endif /* ALLOW_AUTODIFF_TAMC */
505    
506     _BARRIER
507     call timer_stop ('ECCO MAIN LOOP', mythid)
508    
509     call timer_start('ECCO SPIN-DOWN', mythid)
510    
511     #ifdef ALLOW_COST
512    
513     #ifdef ALLOW_DIVIDED_ADJOINT
514     CADJ STORE mytime = onetape
515     #endif
516     c-- Accumulate time averages of temperature, salinity, and SSH.
517     #ifndef DISABLE_DEBUGMODE
518     IF ( debugLevel .GE. debLevB )
519     & CALL DEBUG_CALL('cost_averagesfields',myThid)
520     #endif
521     call timer_start('cost_averagesfields [ECCO SPIN-DOWN]', mythid)
522     call cost_averagesfields( mytime, mythid )
523     call timer_stop ('cost_averagesfields [ECCO SPIN-DOWN]', mythid)
524     #ifdef ALLOW_DIVIDED_ADJOINT
525     c**************************************
526     #include "cost_averages_bar_directives.h"
527     c**************************************
528     #endif
529    
530     #ifdef ALLOW_COST_ATLANTIC
531     c-- Compute meridional heat transport
532     #ifndef DISABLE_DEBUGMODE
533     IF ( debugLevel .GE. debLevB )
534     & CALL DEBUG_CALL('cost_atlantic',myThid)
535     #endif
536     call timer_start('cost_atlantic [ECCO SPIN-DOWN]', mythid)
537     call cost_atlantic( mytime, myiter,mythid )
538     call timer_stop ('cost_atlantic [ECCO SPIN-DOWN]', mythid)
539     #endif
540    
541     c-- Compute the cost function contribution of the boundary forcing,
542     c-- i.e. heat flux, salt flux, zonal and meridional wind stress.
543     #ifndef DISABLE_DEBUGMODE
544     IF ( debugLevel .GE. debLevB )
545     & CALL DEBUG_CALL('cost_forcing',myThid)
546     #endif
547     call timer_start('cost_forcing [ECCO SPIN-DOWN]', mythid)
548     call cost_forcing( myiter, mytime, mythid )
549     call timer_stop ('cost_forcing [ECCO SPIN-DOWN]', mythid)
550    
551     c-- Compute cost function contribution of Temperature and Salinity.
552     #ifndef DISABLE_DEBUGMODE
553     IF ( debugLevel .GE. debLevB )
554     & CALL DEBUG_CALL('cost_hyd',myThid)
555     #endif
556     call timer_start('cost_hyd [ECCO SPIN-DOWN]', mythid)
557     call cost_hyd( myiter, mytime, mythid )
558     call timer_stop ('cost_hyd [ECCO SPIN-DOWN]', mythid)
559    
560     #ifdef ALLOW_OBCS_COST_CONTRIBUTION
561     #ifndef DISABLE_DEBUGMODE
562     IF ( debugLevel .GE. debLevB )
563     & CALL DEBUG_CALL('cost_obcs',myThid)
564     #endif
565     call timer_start('cost_obcs [ECCO SPIN-DOWN]', mythid)
566     call cost_obcs( myiter, mytime, mythid )
567     call timer_stop ('cost_obcs [ECCO SPIN-DOWN]', mythid)
568     #endif
569    
570     #ifdef ALLOW_CURMTR_COST_CONTRIBUTION
571     #ifndef DISABLE_DEBUGMODE
572     IF ( debugLevel .GE. debLevB )
573     & CALL DEBUG_CALL('cost_curmtr',myThid)
574     #endif
575     call timer_start('cost_curmtr [ECCO SPIN-DOWN]', mythid)
576     call cost_curmtr( myiter, mytime, mythid )
577     call timer_stop ('cost_curmtr [ECCO SPIN-DOWN]', mythid)
578     #endif
579    
580     c-- Compute cost function contribution of SSH.
581     #ifdef ALLOW_SSH_COST_CONTRIBUTION
582     #ifndef DISABLE_DEBUGMODE
583     IF ( debugLevel .GE. debLevB )
584     & CALL DEBUG_CALL('cost_ssh',myThid)
585     #endif
586     call timer_start('cost_ssh [ECCO SPIN-DOWN]', mythid)
587     call cost_ssh( myiter, mytime, mythid )
588     call timer_stop ('cost_ssh [ECCO SPIN-DOWN]', mythid)
589     #endif
590    
591     c-- Compute cost function contribution of drifter's velocities.
592     #ifdef ALLOW_DRIFTER_COST_CONTRIBUTION
593     #ifndef DISABLE_DEBUGMODE
594     IF ( debugLevel .GE. debLevB )
595     & CALL DEBUG_CALL('cost_drifter',myThid)
596     #endif
597     call timer_start('cost_drifter [ECCO SPIN-DOWN]', mythid)
598     call cost_drifter( myiter, mytime, mythid )
599     call timer_stop ('cost_drifter [ECCO SPIN-DOWN]', mythid)
600     #endif
601    
602     c-- Compute cost function contribution of wind stress observations.
603     #ifdef ALLOW_SCAT_COST_CONTRIBUTION
604     #ifndef DISABLE_DEBUGMODE
605     IF ( debugLevel .GE. debLevB )
606     & CALL DEBUG_CALL('cost_scat',myThid)
607     #endif
608     call timer_start('cost_scat [ECCO SPIN-DOWN]', mythid)
609     call cost_scat( myiter, mytime, mythid )
610     call timer_stop ('cost_scat [ECCO SPIN-DOWN]', mythid)
611     #endif
612    
613     c-- Compute cost function contribution of wind stress observations.
614     #ifdef ALLOW_MEAN_HFLUX_COST_CONTRIBUTION
615     call timer_start('cost_mean_heatflux [ECCO SPIN-DOWN]', mythid)
616     call cost_mean_heatflux( myiter, mytime, mythid )
617     call timer_stop ('cost_mean_heatflux [ECCO SPIN-DOWN]', mythid)
618     #endif
619    
620     c-- Compute cost function contribution of wind stress observations.
621     #ifdef ALLOW_MEAN_SFLUX_COST_CONTRIBUTION
622     call timer_start('cost_mean_saltflux [ECCO SPIN-DOWN]', mythid)
623     call cost_mean_saltflux( myiter, mytime, mythid )
624     call timer_stop ('cost_mean_saltflux [ECCO SPIN-DOWN]', mythid)
625     #endif
626    
627     c-- Compute cost function contribution of drift between the first
628     c and the last year.
629     #ifdef ALLOW_DRIFT_COST_CONTRIBUTION
630     #ifndef DISABLE_DEBUGMODE
631     IF ( debugLevel .GE. debLevB )
632     & CALL DEBUG_CALL('cost_drift',myThid)
633     #endif
634     call timer_start('cost_drift [ECCO SPIN-DOWN]', mythid)
635     call cost_drift( myiter, mytime, mythid )
636     call timer_stop ('cost_drift [ECCO SPIN-DOWN]', mythid)
637     #endif
638     #ifdef ALLOW_DRIFTW_COST_CONTRIBUTION
639     #ifndef DISABLE_DEBUGMODE
640     IF ( debugLevel .GE. debLevB )
641     & CALL DEBUG_CALL('cost_driftw',myThid)
642     #endif
643     call timer_start('cost_driftw [ECCO SPIN-DOWN]', mythid)
644     call cost_driftw( myiter, mytime, mythid )
645     call timer_stop ('cost_driftw [ECCO SPIN-DOWN]', mythid)
646     #endif
647     _BARRIER
648    
649     c-- Compute initial vs. final T/S deviation
650     #ifdef ALLOW_COST_INI_FIN
651     call timer_start('cost_ini_fin [ECCO SPIN-DOWN]', mythid)
652     call cost_theta_ini_fin( myiter, mytime, mythid )
653     call cost_salt_ini_fin( myiter, mytime, mythid )
654     call timer_stop ('cost_ini_fin [ECCO SPIN-DOWN]', mythid)
655     #endif
656     _BARRIER
657    
658     c-- Eddy stress penalty term
659     #ifdef ALLOW_COST_TAU_EDDY
660     call timer_start('cost_tau_eddy [ECCO SPIN-DOWN]', mythid)
661     call cost_tau_eddy( mythid )
662     call timer_stop ('cost_tau_eddy [ECCO SPIN-DOWN]', mythid)
663     #endif
664    
665     c-- Sum all cost function contributions.
666     #ifndef DISABLE_DEBUGMODE
667     IF ( debugLevel .GE. debLevB )
668     & CALL DEBUG_CALL('cost_final',myThid)
669     #endif
670     call timer_start('COST_FINAL [ECCO SPIN-DOWN]', mythid)
671     call cost_final( mythid )
672     call timer_stop ('COST_FINAL [ECCO SPIN-DOWN]', mythid)
673    
674     #endif /* ALLOW_COST */
675    
676     call timer_stop ('ECCO SPIN-DOWN', mythid)
677    
678     #ifndef DISABLE_DEBUGMODE
679     IF ( debugLevel .GE. debLevB )
680     & CALL DEBUG_LEAVE('THE_MAIN_LOOP',myThid)
681     #endif
682    
683     return
684     end
685    

  ViewVC Help
Powered by ViewVC 1.1.22