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

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

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


Revision 1.52 - (hide annotations) (download)
Tue Jul 13 16:48:48 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint54d_post, checkpoint54c_post
Changes since 1.51: +3 -5 lines
max number of passive tracers is now defined in PTRACERS_SIZE.h

1 jmc 1.52 C $Header: /u/gcmpack/MITgcm/model/src/the_main_loop.F,v 1.51 2004/05/21 21:45:35 heimbach Exp $
2 edhill 1.40 C $Name: $
3 adcroft 1.1
4 edhill 1.40 #include "PACKAGES_CONFIG.h"
5 adcroft 1.1 #include "CPP_OPTIONS.h"
6 heimbach 1.50 #ifdef ALLOW_OBCS
7     # include "OBCS_OPTIONS.h"
8 heimbach 1.46 #endif
9 adcroft 1.1
10 cnh 1.18 CBOP
11     C !ROUTINE: THE_MAIN_LOOP
12     C !INTERFACE:
13 jmc 1.47 SUBROUTINE THE_MAIN_LOOP( myTime, myIter, myThid )
14 cnh 1.18
15     C !DESCRIPTION: \bv
16     C *================================================================*
17     C | SUBROUTINE the_main_loop
18     C | o Run the ocean model and evaluate the specified cost function.
19     C *================================================================*
20     C |
21     C | THE_MAIN_LOOP is the toplevel routine for the Tangent Linear and
22     C | Adjoint Model Compiler (TAMC). For this purpose the initialization
23     C | of the model was split into two parts. Those parameters that do
24     C | not depend on a specific model run are set in INITIALISE_FIXED,
25     C | whereas those that do depend on the specific realization are
26     C | initialized in INITIALISE_VARIA.
27     C | This routine is to be used in conjuction with the MITgcmuv
28     C | checkpoint 37.
29     C *================================================================*
30     C \ev
31    
32     C !USES:
33     IMPLICIT NONE
34     C == Global variables ==
35 adcroft 1.1 #include "SIZE.h"
36     #include "EEPARAMS.h"
37     #include "PARAMS.h"
38 heimbach 1.35
39     c**************************************
40 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
41 heimbach 1.35
42     c These includes are needed for
43     c AD-checkpointing.
44     c They provide the fields to be stored.
45    
46 heimbach 1.32 # include "GRID.h"
47 heimbach 1.16 # include "DYNVARS.h"
48     # include "FFIELDS.h"
49 heimbach 1.29 # include "EOS.h"
50 adcroft 1.21 # include "GAD.h"
51 heimbach 1.41 # ifdef ALLOW_CD_CODE
52     # include "CD_CODE_VARS.h"
53     # endif
54 heimbach 1.16 # ifdef ALLOW_PASSIVE_TRACER
55     # include "TR1.h"
56     # endif
57 heimbach 1.38 # ifdef ALLOW_PTRACERS
58 jmc 1.52 # include "PTRACERS_SIZE.h"
59 heimbach 1.38 # include "PTRACERS.h"
60     # endif
61 heimbach 1.16 # ifdef ALLOW_NONHYDROSTATIC
62     # include "CG3D.h"
63     # endif
64 heimbach 1.22 # ifdef EXACT_CONSERV
65     # include "SURFACE.h"
66     # endif
67 heimbach 1.45 # ifdef ALLOW_OBCS
68     # include "OBCS.h"
69     # endif
70 edhill 1.42 # ifdef ALLOW_EXF
71 heimbach 1.35 # include "exf_fields.h"
72     # include "exf_clim_fields.h"
73     # ifdef ALLOW_BULKFORMULAE
74     # include "exf_constants.h"
75     # endif
76 edhill 1.42 # endif /* ALLOW_EXF */
77 heimbach 1.35 # ifdef ALLOW_SEAICE
78     # include "SEAICE.h"
79     # endif
80 heimbach 1.51 # ifdef ALLOW_EBM
81     # include "EBM.h"
82     # endif
83 heimbach 1.35 # 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 heimbach 1.6
95 cnh 1.18 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 heimbach 1.6
109 cnh 1.18 C !LOCAL VARIABLES:
110     C == Local variables ==
111 heimbach 1.6 integer iloop
112     #ifdef ALLOW_TAMC_CHECKPOINTING
113     integer ilev_1
114     integer ilev_2
115     integer ilev_3
116     integer max_lev2
117     integer max_lev3
118     #endif
119 cnh 1.18 CEOP
120 adcroft 1.1
121 edhill 1.44 #ifdef ALLOW_DEBUG
122 adcroft 1.37 IF (debugMode) CALL DEBUG_ENTER('THE_MAIN_LOOP',myThid)
123     #endif
124    
125 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
126     c-- Initialize storage for the cost function evaluation.
127     CADJ INIT dummytape = common, 1
128     c-- Initialize storage for the outermost loop.
129     CADJ INIT tapelev3 = USER
130 heimbach 1.27 CADJ INIT tapelev_ini_bibj_k = USER
131 heimbach 1.7 #ifdef ALLOW_TAMC_CHECKPOINTING
132 heimbach 1.13 nIter0 = INT( startTime/deltaTClock )
133 heimbach 1.7 ikey_dynamics = 1
134     #endif
135 adcroft 1.10 CALL TIMER_START('ADJOINT SPIN-UP', mythid)
136 heimbach 1.6 #endif
137    
138 edhill 1.44 #ifdef ALLOW_DEBUG
139 adcroft 1.37 IF (debugMode) CALL DEBUG_CALL('INITIALISE_VARIA',myThid)
140     #endif
141    
142 adcroft 1.1 C-- Set initial conditions (variable arrays)
143 adcroft 1.10 CALL TIMER_START('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
144 heimbach 1.6 CALL INITIALISE_VARIA( mythid )
145 adcroft 1.10 CALL TIMER_STOP ('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
146 heimbach 1.6
147 edhill 1.43 #ifdef ALLOW_MONITOR
148 edhill 1.44 #ifdef ALLOW_DEBUG
149 adcroft 1.37 IF (debugMode) CALL DEBUG_CALL('MONITOR',myThid)
150     #endif
151 adcroft 1.9 C-- Check status of solution (statistics, cfl, etc...)
152 adcroft 1.10 CALL TIMER_START('MONITOR [THE_MAIN_LOOP]', mythid)
153 heimbach 1.49 CALL MONITOR( myIter, myTime, myThid )
154 adcroft 1.10 CALL TIMER_STOP ('MONITOR [THE_MAIN_LOOP]', mythid)
155 edhill 1.43 #endif /* ALLOW_MONITOR */
156 jmc 1.47
157     C-- Do IO if needed (Dump for start state).
158     #ifdef ALLOW_DEBUG
159     IF (debugMode) CALL DEBUG_CALL('DO_THE_MODEL_IO',myThid)
160     #endif
161     CALL TIMER_START('DO_THE_MODEL_IO [THE_MAIN_LOOP]', mythid)
162 heimbach 1.49 CALL DO_THE_MODEL_IO( myTime, myIter, mythid )
163 jmc 1.47 CALL TIMER_STOP ('DO_THE_MODEL_IO [THE_MAIN_LOOP]', mythid)
164 heimbach 1.6
165 adcroft 1.10 #ifdef ALLOW_AUTODIFF_TAMC
166 heimbach 1.6 CALL TIMER_STOP ('ADJOINT SPIN-UP', mythid)
167     _BARRIER
168 adcroft 1.10 #endif
169 heimbach 1.6
170     c-- Do the model integration.
171 adcroft 1.10 CALL TIMER_START('MAIN LOOP [THE_MAIN_LOOP]', mythid)
172 heimbach 1.6
173     c >>>>>>>>>>>>>>>>>>>>>>>>>>> LOOP <<<<<<<<<<<<<<<<<<<<<<<<<<<<
174     c >>>>>>>>>>>>>>>>>>>>>>>>>>> STARTS <<<<<<<<<<<<<<<<<<<<<<<<<<<<
175    
176     #ifdef ALLOW_AUTODIFF_TAMC
177     #ifdef ALLOW_TAMC_CHECKPOINTING
178     c-- Implement a three level checkpointing. For a two level
179     c-- checkpointing delete the middle loop; for n levels (n > 3)
180     c-- insert more loops.
181    
182     c-- Check the choice of the checkpointing parameters in relation
183     c-- to nTimeSteps: (nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps)
184     if (nchklev_1*nchklev_2*nchklev_3 .lt. nTimeSteps) then
185     print*
186     print*, ' the_main_loop: TAMC checkpointing parameters'
187     print*, ' nchklev_1*nchklev_2*nchklev_3 = ',
188     & nchklev_1*nchklev_2*nchklev_3
189     print*, ' are not consistent with nTimeSteps = ',
190     & nTimeSteps
191     stop ' ... stopped in the_main_loop.'
192     endif
193     max_lev3=nTimeSteps/(nchklev_1*nchklev_2)+1
194     max_lev2=nTimeSteps/nchklev_1+1
195 heimbach 1.26
196     c**************************************
197     #ifdef ALLOW_DIVIDED_ADJOINT
198     CADJ loop = divided
199     #endif
200     c**************************************
201 heimbach 1.6
202     do ilev_3 = 1,nchklev_3
203     if(ilev_3.le.max_lev3) then
204 heimbach 1.24 c**************************************
205     #include "checkpoint_lev3_directives.h"
206     c**************************************
207 heimbach 1.6
208     c-- Initialise storage for the middle loop.
209     CADJ INIT tapelev2 = USER
210    
211     do ilev_2 = 1,nchklev_2
212     if(ilev_2.le.max_lev2) then
213 heimbach 1.24 c**************************************
214     #include "checkpoint_lev2_directives.h"
215     c**************************************
216 heimbach 1.6
217 heimbach 1.36 c**************************************
218     #ifdef ALLOW_AUTODIFF_TAMC
219 heimbach 1.6 c-- Initialize storage for the innermost loop.
220     c-- Always check common block sizes for the checkpointing!
221 heimbach 1.36 c--
222 heimbach 1.6 CADJ INIT comlev1 = COMMON,nchklev_1
223     CADJ INIT comlev1_bibj = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt
224     CADJ INIT comlev1_bibj_k = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt
225 heimbach 1.28 c--
226     #ifdef ALLOW_KPP
227 heimbach 1.6 CADJ INIT comlev1_kpp = COMMON,nchklev_1*nsx*nsy
228 heimbach 1.51 CADJ INIT comlev1_kpp_k = COMMON,nchklev_1*nsx*nsy*nr
229 heimbach 1.28 #endif /* ALLOW_KPP */
230     c--
231     #ifdef ALLOW_GMREDI
232     CADJ INIT comlev1_gmredi_k_gad
233     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
234     #endif /* ALLOW_GMREDI */
235 heimbach 1.45 c--
236 heimbach 1.38 #ifdef ALLOW_PTRACERS
237     CADJ INIT comlev1_bibj_ptracers = COMMON,
238 jmc 1.52 CADJ & nchklev_1*nsx*nsy*nthreads_chkpt*PTRACERS_num
239 heimbach 1.38 #endif /* ALLOW_PTRACERS */
240 heimbach 1.28 c--
241 adcroft 1.21 #ifndef DISABLE_MULTIDIM_ADVECTION
242 heimbach 1.28 CADJ INIT comlev1_bibj_k_gad
243 heimbach 1.20 CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
244 heimbach 1.28 CADJ INIT comlev1_bibj_k_gad_pass
245     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass*maxcube
246 adcroft 1.21 #endif /* DISABLE_MULTIDIM_ADVECTION */
247 heimbach 1.28 c--
248 heimbach 1.45 #if (defined (ALLOW_EXF) && defined (ALLOW_BULKFORMULAE))
249 dimitri 1.31 CADJ INIT comlev1_exf_1
250     CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
251     CADJ INIT comlev1_exf_2
252     CADJ & = COMMON,niter_bulk*nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
253     #endif /* ALLOW_BULKFORMULAE */
254 heimbach 1.45 c--
255     #ifdef ALLOW_SEAICE
256     # ifdef SEAICE_ALLOW_DYNAMICS
257     CADJ INIT comlev1_lsr = COMMON,nchklev_1*2
258     # endif
259     #endif /* ALLOW_SEAICE */
260 heimbach 1.36 c--
261     #endif /* ALLOW_AUTODIFF_TAMC */
262     c**************************************
263 heimbach 1.6
264     do ilev_1 = 1,nchklev_1
265    
266     c-- The if-statement below introduces a some flexibility in the
267     c-- choice of the 3-tupel ( nchklev_1, nchklev_2, nchklev_3 ).
268     c--
269     c-- Requirement: nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps .
270    
271     iloop = (ilev_3 - 1)*nchklev_2*nchklev_1 +
272     & (ilev_2 - 1)*nchklev_1 + ilev_1
273    
274     if ( iloop .le. nTimeSteps ) then
275    
276     #else /* ALLOW_TAMC_CHECKPOINTING undefined */
277     c-- Initialise storage for reference trajectory without TAMC check-
278     c-- pointing.
279     CADJ INIT history = USER
280     CADJ INIT comlev1_bibj = COMMON,nchklev_0*nsx*nsy*nthreads_chkpt
281     CADJ INIT comlev1_bibj_k = COMMON,nchklev_0*nsx*nsy*nr*nthreads_chkpt
282     CADJ INIT comlev1_kpp = COMMON,nchklev_0*nsx*nsy
283    
284     c-- Check the choice of the checkpointing parameters in relation
285     c-- to nTimeSteps: (nchklev_0 .ge. nTimeSteps)
286     if (nchklev_0 .lt. nTimeSteps) then
287     print*
288     print*, ' the_main_loop: TAMC checkpointing parameter ',
289 adcroft 1.19 & 'nchklev_0 = ', nchklev_0
290 heimbach 1.6 print*, ' not consistent with nTimeSteps = ',
291     & nTimeSteps
292     stop ' ... stopped in the_main_loop.'
293     endif
294    
295 adcroft 1.10 DO iloop = 1, nTimeSteps
296 heimbach 1.6
297     #endif /* ALLOW_TAMC_CHECKPOINTING */
298    
299     #else /* ALLOW_AUTODIFF_TAMC undefined */
300    
301     c-- Start the main loop of adjoint_Objfunc. Automatic differentiation
302     c-- NOT enabled.
303 adcroft 1.10 DO iloop = 1, nTimeSteps
304 heimbach 1.6
305     #endif /* ALLOW_AUTODIFF_TAMC */
306    
307 adcroft 1.10 c-- >>> Loop body start <<<
308 heimbach 1.6
309     #ifdef ALLOW_TAMC_CHECKPOINTING
310 heimbach 1.14 nIter0 = INT( startTime/deltaTClock )
311 heimbach 1.13 ikey_dynamics = ilev_1
312 heimbach 1.6 #endif
313 dimitri 1.31
314 edhill 1.44 #ifdef ALLOW_DEBUG
315 adcroft 1.37 IF (debugMode) CALL DEBUG_CALL('FORWARD_STEP',myThid)
316     #endif
317 heimbach 1.14
318 heimbach 1.13 CALL TIMER_START('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
319     CALL FORWARD_STEP( iloop, mytime, myiter, mythid )
320     CALL TIMER_STOP ('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
321 adcroft 1.8
322 heimbach 1.12 #ifdef ALLOW_COST
323 heimbach 1.13 C-- compare model with data and compute cost function
324     C-- this is done after exchanges to allow interpolation
325 edhill 1.40 ceh3 perhaps needs an IF ( useCOST ) THEN
326 heimbach 1.13 CALL TIMER_START('COST_TILE [THE_MAIN_LOOP]',myThid)
327     CALL COST_TILE ( myThid )
328     CALL TIMER_STOP ('COST_TILE [THE_MAIN_LOOP]',myThid)
329 heimbach 1.12 #endif
330    
331 heimbach 1.13 c-- >>> Loop body end <<<
332 heimbach 1.6
333     #ifdef ALLOW_AUTODIFF_TAMC
334     #ifdef ALLOW_TAMC_CHECKPOINTING
335     endif
336     enddo
337     endif
338     enddo
339     endif
340     enddo
341     #else
342     enddo
343     #endif
344    
345     #else
346     enddo
347     #endif
348    
349 heimbach 1.12 #ifdef ALLOW_COST
350     c-- Sum all cost function contributions.
351     call TIMER_START('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
352     call COST_FINAL ( mythid )
353     call TIMER_STOP ('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
354     #endif
355    
356 heimbach 1.6 _BARRIER
357 adcroft 1.10 CALL TIMER_STOP ('MAIN LOOP [THE_MAIN_LOOP]', mythid)
358 adcroft 1.37
359 edhill 1.44 #ifdef ALLOW_DEBUG
360 adcroft 1.37 IF (debugMode) CALL DEBUG_LEAVE('THE_MAIN_LOOP',myThid)
361     #endif
362 adcroft 1.1
363 adcroft 1.10 END

  ViewVC Help
Powered by ViewVC 1.1.22