/[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.28 - (hide annotations) (download)
Tue Nov 12 20:42:24 2002 UTC (21 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint46n_post
Changes since 1.27: +15 -3 lines
Merging from release1_p8 branch:
o GAD:
  - generated new common blocks to account for call of
    same gad routines with differing traceridentities
    (needed to modify tracerIdentity indices in GAD.h)
  - generated separate common blocks for case useCubedSphereExchange
    (Department of Futurology)
  - parameter lists to gmredi_?transport: added tracerIdentity
  - added new key indices to tamc.h

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

  ViewVC Help
Powered by ViewVC 1.1.22