/[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.39 - (hide annotations) (download)
Thu Sep 25 03:01:59 2003 UTC (20 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint51f_post, checkpoint51j_post, checkpoint51h_pre, branchpoint-genmake2, checkpoint51i_pre, checkpoint51g_post
Branch point for: branch-genmake2
Changes since 1.38: +1 -4 lines
o Mods and bug fixes to pkg/cal, pkg/exf, etc., needed for computation
  of tracer Green's fucntions for ocean inversion project.

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

  ViewVC Help
Powered by ViewVC 1.1.22