/[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.36 - (hide annotations) (download)
Fri Mar 7 23:48:41 2003 UTC (21 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint50c_post, checkpoint50c_pre, checkpoint50d_pre, checkpoint50, checkpoint50d_post, checkpoint50b_pre, checkpoint50a_post, checkpoint50b_post
Changes since 1.35: +7 -6 lines
cleanup.

1 heimbach 1.36 C $Header: /u/gcmpack/MITgcm/model/src/the_main_loop.F,v 1.35 2003/03/05 23:39:53 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     # ifdef ALLOW_NONHYDROSTATIC
50     # include "CG3D.h"
51     # endif
52 heimbach 1.22 # ifdef EXACT_CONSERV
53     # include "SURFACE.h"
54     # endif
55 heimbach 1.35 # ifdef INCLUDE_EXTERNAL_FORCING_PACKAGE
56     # include "exf_fields.h"
57     # include "exf_clim_fields.h"
58     # ifdef ALLOW_BULKFORMULAE
59     # include "exf_constants.h"
60     # endif
61     # endif /* INCLUDE_EXTERNAL_FORCING_PACKAGE */
62     # ifdef ALLOW_SEAICE
63     # include "SEAICE.h"
64     # endif
65     # ifdef ALLOW_DIVIDED_ADJOINT_MPI
66     # include "mpif.h"
67     # endif
68    
69     # include "tamc.h"
70     # include "ctrl.h"
71     # include "ctrl_dummy.h"
72     # include "cost.h"
73    
74     #endif /* ALLOW_AUTODIFF_TAMC */
75     c**************************************
76 heimbach 1.6
77 cnh 1.18 C !INPUT/OUTPUT PARAMETERS:
78     C == Routine arguments ==
79     C note: under the multi-threaded model myiter and
80     C mytime are local variables passed around as routine
81     C arguments. Although this is fiddly it saves the need to
82     C impose additional synchronisation points when they are
83     C updated.
84     C myIter - iteration counter for this thread
85     C myTime - time counter for this thread
86     C myThid - thread number for this instance of the routine.
87     INTEGER myThid
88     INTEGER myIter
89     _RL myTime
90 heimbach 1.6
91 cnh 1.18 C !LOCAL VARIABLES:
92     C == Local variables ==
93 heimbach 1.6 integer iloop
94     #ifdef ALLOW_TAMC_CHECKPOINTING
95     integer ilev_1
96     integer ilev_2
97     integer ilev_3
98     integer max_lev2
99     integer max_lev3
100     #endif
101 cnh 1.18 CEOP
102 adcroft 1.1
103 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
104     c-- Initialize storage for the cost function evaluation.
105     CADJ INIT dummytape = common, 1
106     c-- Initialize storage for the outermost loop.
107     CADJ INIT tapelev3 = USER
108 heimbach 1.27 CADJ INIT tapelev_ini_bibj_k = USER
109 heimbach 1.7 #ifdef ALLOW_TAMC_CHECKPOINTING
110 heimbach 1.13 nIter0 = INT( startTime/deltaTClock )
111 heimbach 1.7 ikey_dynamics = 1
112     #endif
113 adcroft 1.10 CALL TIMER_START('ADJOINT SPIN-UP', mythid)
114 heimbach 1.6 #endif
115    
116 adcroft 1.1 C-- Set initial conditions (variable arrays)
117 adcroft 1.10 CALL TIMER_START('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
118 heimbach 1.6 CALL INITIALISE_VARIA( mythid )
119 adcroft 1.10 CALL TIMER_STOP ('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
120 heimbach 1.6
121     c-- Dump for start state.
122 adcroft 1.10 CALL TIMER_START('WRITE_STATE [THE_MAIN_LOOP]', mythid)
123 heimbach 1.6 CALL WRITE_STATE( mytime, myiter, mythid )
124 adcroft 1.10 CALL TIMER_STOP ('WRITE_STATE [THE_MAIN_LOOP]', mythid)
125 adcroft 1.9
126     #ifndef EXCLUDE_MONITOR
127     C-- Check status of solution (statistics, cfl, etc...)
128 adcroft 1.10 CALL TIMER_START('MONITOR [THE_MAIN_LOOP]', mythid)
129 adcroft 1.9 CALL MONITOR( myIter, myTime, myThid )
130 adcroft 1.10 CALL TIMER_STOP ('MONITOR [THE_MAIN_LOOP]', mythid)
131 adcroft 1.9 #endif /* EXCLUDE_MONITOR */
132 heimbach 1.6
133 adcroft 1.10 #ifdef ALLOW_AUTODIFF_TAMC
134 heimbach 1.6 CALL TIMER_STOP ('ADJOINT SPIN-UP', mythid)
135     _BARRIER
136 adcroft 1.10 #endif
137 heimbach 1.6
138     c-- Do the model integration.
139 adcroft 1.10 CALL TIMER_START('MAIN LOOP [THE_MAIN_LOOP]', mythid)
140 heimbach 1.6
141     c >>>>>>>>>>>>>>>>>>>>>>>>>>> LOOP <<<<<<<<<<<<<<<<<<<<<<<<<<<<
142     c >>>>>>>>>>>>>>>>>>>>>>>>>>> STARTS <<<<<<<<<<<<<<<<<<<<<<<<<<<<
143    
144     #ifdef ALLOW_AUTODIFF_TAMC
145     #ifdef ALLOW_TAMC_CHECKPOINTING
146     c-- Implement a three level checkpointing. For a two level
147     c-- checkpointing delete the middle loop; for n levels (n > 3)
148     c-- insert more loops.
149    
150     c-- Check the choice of the checkpointing parameters in relation
151     c-- to nTimeSteps: (nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps)
152     if (nchklev_1*nchklev_2*nchklev_3 .lt. nTimeSteps) then
153     print*
154     print*, ' the_main_loop: TAMC checkpointing parameters'
155     print*, ' nchklev_1*nchklev_2*nchklev_3 = ',
156     & nchklev_1*nchklev_2*nchklev_3
157     print*, ' are not consistent with nTimeSteps = ',
158     & nTimeSteps
159     stop ' ... stopped in the_main_loop.'
160     endif
161     max_lev3=nTimeSteps/(nchklev_1*nchklev_2)+1
162     max_lev2=nTimeSteps/nchklev_1+1
163 heimbach 1.26
164     c**************************************
165     #ifdef ALLOW_DIVIDED_ADJOINT
166     CADJ loop = divided
167     #endif
168     c**************************************
169 heimbach 1.6
170     do ilev_3 = 1,nchklev_3
171     if(ilev_3.le.max_lev3) then
172 heimbach 1.24 c**************************************
173     #include "checkpoint_lev3_directives.h"
174     c**************************************
175 heimbach 1.6
176     c-- Initialise storage for the middle loop.
177     CADJ INIT tapelev2 = USER
178    
179     do ilev_2 = 1,nchklev_2
180     if(ilev_2.le.max_lev2) then
181 heimbach 1.24 c**************************************
182     #include "checkpoint_lev2_directives.h"
183     c**************************************
184 heimbach 1.6
185 heimbach 1.36 c**************************************
186     #ifdef ALLOW_AUTODIFF_TAMC
187 heimbach 1.6 c-- Initialize storage for the innermost loop.
188     c-- Always check common block sizes for the checkpointing!
189 heimbach 1.36 c--
190 heimbach 1.6 CADJ INIT comlev1 = COMMON,nchklev_1
191     CADJ INIT comlev1_bibj = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt
192     CADJ INIT comlev1_bibj_k = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt
193 heimbach 1.28 c--
194     #ifdef ALLOW_KPP
195 heimbach 1.6 CADJ INIT comlev1_kpp = COMMON,nchklev_1*nsx*nsy
196 heimbach 1.28 #endif /* ALLOW_KPP */
197     c--
198     #ifdef ALLOW_GMREDI
199     CADJ INIT comlev1_gmredi_k_gad
200     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
201     #endif /* ALLOW_GMREDI */
202     c--
203 adcroft 1.21 #ifndef DISABLE_MULTIDIM_ADVECTION
204 heimbach 1.28 CADJ INIT comlev1_bibj_k_gad
205 heimbach 1.20 CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
206 heimbach 1.28 CADJ INIT comlev1_bibj_k_gad_pass
207     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass*maxcube
208 adcroft 1.21 #endif /* DISABLE_MULTIDIM_ADVECTION */
209 heimbach 1.28 c--
210 cheisey 1.30 #ifdef ALLOW_BULK_FORCE
211 heimbach 1.20 CADJ INIT comlev1_exf_1
212     CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
213     CADJ INIT comlev1_exf_2
214     CADJ & = COMMON,niter_bulk*nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
215 cheisey 1.30 #endif /* ALLOW_BULK_FORCE */
216 dimitri 1.31 #ifdef ALLOW_BULKFORMULAE
217     CADJ INIT comlev1_exf_1
218     CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
219     CADJ INIT comlev1_exf_2
220     CADJ & = COMMON,niter_bulk*nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
221     #endif /* ALLOW_BULKFORMULAE */
222 heimbach 1.36 c--
223     #endif /* ALLOW_AUTODIFF_TAMC */
224     c**************************************
225 heimbach 1.6
226     do ilev_1 = 1,nchklev_1
227    
228     c-- The if-statement below introduces a some flexibility in the
229     c-- choice of the 3-tupel ( nchklev_1, nchklev_2, nchklev_3 ).
230     c--
231     c-- Requirement: nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps .
232    
233     iloop = (ilev_3 - 1)*nchklev_2*nchklev_1 +
234     & (ilev_2 - 1)*nchklev_1 + ilev_1
235    
236     if ( iloop .le. nTimeSteps ) then
237    
238     #else /* ALLOW_TAMC_CHECKPOINTING undefined */
239     c-- Initialise storage for reference trajectory without TAMC check-
240     c-- pointing.
241     CADJ INIT history = USER
242     CADJ INIT comlev1_bibj = COMMON,nchklev_0*nsx*nsy*nthreads_chkpt
243     CADJ INIT comlev1_bibj_k = COMMON,nchklev_0*nsx*nsy*nr*nthreads_chkpt
244     CADJ INIT comlev1_kpp = COMMON,nchklev_0*nsx*nsy
245    
246     c-- Check the choice of the checkpointing parameters in relation
247     c-- to nTimeSteps: (nchklev_0 .ge. nTimeSteps)
248     if (nchklev_0 .lt. nTimeSteps) then
249     print*
250     print*, ' the_main_loop: TAMC checkpointing parameter ',
251 adcroft 1.19 & 'nchklev_0 = ', nchklev_0
252 heimbach 1.6 print*, ' not consistent with nTimeSteps = ',
253     & nTimeSteps
254     stop ' ... stopped in the_main_loop.'
255     endif
256    
257 adcroft 1.10 DO iloop = 1, nTimeSteps
258 heimbach 1.6
259     #endif /* ALLOW_TAMC_CHECKPOINTING */
260    
261     #else /* ALLOW_AUTODIFF_TAMC undefined */
262    
263     c-- Start the main loop of adjoint_Objfunc. Automatic differentiation
264     c-- NOT enabled.
265 adcroft 1.10 DO iloop = 1, nTimeSteps
266 heimbach 1.6
267     #endif /* ALLOW_AUTODIFF_TAMC */
268    
269 adcroft 1.10 c-- >>> Loop body start <<<
270 heimbach 1.6
271     #ifdef ALLOW_TAMC_CHECKPOINTING
272 heimbach 1.14 nIter0 = INT( startTime/deltaTClock )
273 heimbach 1.13 ikey_dynamics = ilev_1
274 heimbach 1.6 #endif
275 dimitri 1.31
276 heimbach 1.14
277 heimbach 1.13 CALL TIMER_START('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
278     CALL FORWARD_STEP( iloop, mytime, myiter, mythid )
279     CALL TIMER_STOP ('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
280 adcroft 1.8
281 heimbach 1.12 #ifdef ALLOW_COST
282 heimbach 1.13 C-- compare model with data and compute cost function
283     C-- this is done after exchanges to allow interpolation
284     CALL TIMER_START('COST_TILE [THE_MAIN_LOOP]',myThid)
285     CALL COST_TILE ( myThid )
286     CALL TIMER_STOP ('COST_TILE [THE_MAIN_LOOP]',myThid)
287 heimbach 1.12 #endif
288    
289 heimbach 1.13 c-- >>> Loop body end <<<
290 heimbach 1.6
291     #ifdef ALLOW_AUTODIFF_TAMC
292     #ifdef ALLOW_TAMC_CHECKPOINTING
293     endif
294     enddo
295     endif
296     enddo
297     endif
298     enddo
299     #else
300     enddo
301     #endif
302    
303     #else
304     enddo
305     #endif
306    
307 heimbach 1.12 #ifdef ALLOW_COST
308     c-- Sum all cost function contributions.
309     call TIMER_START('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
310     call COST_FINAL ( mythid )
311     call TIMER_STOP ('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
312     #endif
313    
314 heimbach 1.6 _BARRIER
315 adcroft 1.10 CALL TIMER_STOP ('MAIN LOOP [THE_MAIN_LOOP]', mythid)
316 adcroft 1.1
317 adcroft 1.10 END

  ViewVC Help
Powered by ViewVC 1.1.22