/[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.41 - (hide annotations) (download)
Thu Oct 30 18:44:26 2003 UTC (20 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint51q_post
Changes since 1.40: +4 -1 lines
modified pkg/cd_code
o moved cd_scheme.F -> cd_code_scheme.F
o separate read_checkpoint from cd_code_ini_vars.F
o separated cd_code part from write_checkpoint
o updated AD_SOURCE, generated .flow
o added CD_CODE_VARS.h to the_main_loop

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

  ViewVC Help
Powered by ViewVC 1.1.22