/[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.22 - (hide annotations) (download)
Thu Nov 8 20:57:51 2001 UTC (22 years, 7 months ago) by heimbach
Branch: MAIN
Changes since 1.21: +14 -3 lines
Preparing adjoint of Held-Suarez:
- bugfix for storing in absence of CD code
- adding EXACT_CONSERV to AD list
- new routine ini_autodiff to add TAMC-specific initialisations
- adding Shapiro filter to AD list

1 heimbach 1.22 C $Header: /u/gcmpack/models/MITgcmUV/model/src/the_main_loop.F,v 1.21 2001/09/28 02:26:57 adcroft 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.7 #ifdef ALLOW_TAMC_CHECKPOINTING
84 heimbach 1.13 nIter0 = INT( startTime/deltaTClock )
85 heimbach 1.7 ikey_dynamics = 1
86     #endif
87 adcroft 1.10 CALL TIMER_START('ADJOINT SPIN-UP', mythid)
88 heimbach 1.6 #endif
89    
90 adcroft 1.1 C-- Set initial conditions (variable arrays)
91 adcroft 1.10 CALL TIMER_START('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
92 heimbach 1.6 CALL INITIALISE_VARIA( mythid )
93 adcroft 1.10 CALL TIMER_STOP ('INITIALISE_VARIA [THE_MAIN_LOOP]', mythid)
94 heimbach 1.6
95     #ifndef ALLOW_AUTODIFF_TAMC
96     c-- Dump for start state.
97 adcroft 1.10 CALL TIMER_START('WRITE_STATE [THE_MAIN_LOOP]', mythid)
98 heimbach 1.6 CALL WRITE_STATE( mytime, myiter, mythid )
99 adcroft 1.10 CALL TIMER_STOP ('WRITE_STATE [THE_MAIN_LOOP]', mythid)
100 heimbach 1.6 #endif
101 adcroft 1.9
102     #ifndef EXCLUDE_MONITOR
103     C-- Check status of solution (statistics, cfl, etc...)
104 adcroft 1.10 CALL TIMER_START('MONITOR [THE_MAIN_LOOP]', mythid)
105 adcroft 1.9 CALL MONITOR( myIter, myTime, myThid )
106 adcroft 1.10 CALL TIMER_STOP ('MONITOR [THE_MAIN_LOOP]', mythid)
107 adcroft 1.9 #endif /* EXCLUDE_MONITOR */
108 heimbach 1.6
109 heimbach 1.12 #ifdef ALLOW_ADJOINT_RUN
110 heimbach 1.6 c-- Add control vector for forcing and parameter fields
111     CALL CTRL_MAP_FORCING (mythid)
112     #endif
113    
114 adcroft 1.10 #ifdef ALLOW_AUTODIFF_TAMC
115 heimbach 1.6 CALL TIMER_STOP ('ADJOINT SPIN-UP', mythid)
116     _BARRIER
117 adcroft 1.10 #endif
118 heimbach 1.6
119     c-- Do the model integration.
120 adcroft 1.10 CALL TIMER_START('MAIN LOOP [THE_MAIN_LOOP]', mythid)
121 heimbach 1.6
122     c >>>>>>>>>>>>>>>>>>>>>>>>>>> LOOP <<<<<<<<<<<<<<<<<<<<<<<<<<<<
123     c >>>>>>>>>>>>>>>>>>>>>>>>>>> STARTS <<<<<<<<<<<<<<<<<<<<<<<<<<<<
124    
125     #ifdef ALLOW_AUTODIFF_TAMC
126     #ifdef ALLOW_TAMC_CHECKPOINTING
127     c-- Implement a three level checkpointing. For a two level
128     c-- checkpointing delete the middle loop; for n levels (n > 3)
129     c-- insert more loops.
130    
131     c-- Check the choice of the checkpointing parameters in relation
132     c-- to nTimeSteps: (nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps)
133     if (nchklev_1*nchklev_2*nchklev_3 .lt. nTimeSteps) then
134     print*
135     print*, ' the_main_loop: TAMC checkpointing parameters'
136     print*, ' nchklev_1*nchklev_2*nchklev_3 = ',
137     & nchklev_1*nchklev_2*nchklev_3
138     print*, ' are not consistent with nTimeSteps = ',
139     & nTimeSteps
140     stop ' ... stopped in the_main_loop.'
141     endif
142     max_lev3=nTimeSteps/(nchklev_1*nchklev_2)+1
143     max_lev2=nTimeSteps/nchklev_1+1
144    
145     do ilev_3 = 1,nchklev_3
146     if(ilev_3.le.max_lev3) then
147     CADJ STORE gsnm1 = tapelev3, key = ilev_3
148     CADJ STORE gtnm1 = tapelev3, key = ilev_3
149     CADJ STORE gunm1 = tapelev3, key = ilev_3
150     CADJ STORE gvnm1 = tapelev3, key = ilev_3
151     CADJ STORE theta = tapelev3, key = ilev_3
152     CADJ STORE salt = tapelev3, key = ilev_3
153     CADJ STORE uvel = tapelev3, key = ilev_3
154     CADJ STORE vvel = tapelev3, key = ilev_3
155     CADJ STORE wvel = tapelev3, key = ilev_3
156     CADJ STORE etan = tapelev3, key = ilev_3
157 heimbach 1.17 CADJ STORE gu = tapelev3, key = ilev_3
158     CADJ STORE gv = tapelev3, key = ilev_3
159 heimbach 1.6 #ifdef INCLUDE_CD_CODE
160 heimbach 1.22 CADJ STORE etanm1 = tapelev3, key = ilev_3
161 heimbach 1.6 CADJ STORE uveld = tapelev3, key = ilev_3
162     CADJ STORE vveld = tapelev3, key = ilev_3
163     CADJ STORE unm1 = tapelev3, key = ilev_3
164     CADJ STORE vnm1 = tapelev3, key = ilev_3
165 heimbach 1.17 CADJ STORE gucd = tapelev3, key = ilev_3
166     CADJ STORE gvcd = tapelev3, key = ilev_3
167 heimbach 1.6 #endif
168 heimbach 1.12 #ifdef ALLOW_COST_TRACER
169     CADJ STORE tr1 = tapelev3, key = ilev_3
170     CADJ STORE gtr1nm1 = tapelev3, key = ilev_3
171     #endif
172 heimbach 1.22 #ifdef EXACT_CONSERV
173     CADJ STORE etaH = tapelev3, key = ilev_3
174     CADJ STORE hDivFlow = tapelev3, key = ilev_3
175     #endif
176 heimbach 1.6
177     c-- Initialise storage for the middle loop.
178     CADJ INIT tapelev2 = USER
179    
180     do ilev_2 = 1,nchklev_2
181     if(ilev_2.le.max_lev2) then
182     CADJ STORE gsnm1 = tapelev2, key = ilev_2
183     CADJ STORE gtnm1 = tapelev2, key = ilev_2
184     CADJ STORE gunm1 = tapelev2, key = ilev_2
185     CADJ STORE gvnm1 = tapelev2, key = ilev_2
186     CADJ STORE theta = tapelev2, key = ilev_2
187     CADJ STORE salt = tapelev2, key = ilev_2
188     CADJ STORE uvel = tapelev2, key = ilev_2
189     CADJ STORE vvel = tapelev2, key = ilev_2
190     CADJ STORE wvel = tapelev2, key = ilev_2
191     CADJ STORE etan = tapelev2, key = ilev_2
192 heimbach 1.17 CADJ STORE gu = tapelev2, key = ilev_2
193     CADJ STORE gv = tapelev2, key = ilev_2
194 heimbach 1.6 #ifdef INCLUDE_CD_CODE
195 heimbach 1.22 CADJ STORE etanm1 = tapelev2, key = ilev_2
196 heimbach 1.6 CADJ STORE uveld = tapelev2, key = ilev_2
197     CADJ STORE vveld = tapelev2, key = ilev_2
198     CADJ STORE unm1 = tapelev2, key = ilev_2
199     CADJ STORE vnm1 = tapelev2, key = ilev_2
200 heimbach 1.17 CADJ STORE gucd = tapelev2, key = ilev_2
201     CADJ STORE gvcd = tapelev2, key = ilev_2
202 heimbach 1.6 #endif
203 heimbach 1.12 #ifdef ALLOW_COST_TRACER
204     CADJ STORE tr1 = tapelev2, key = ilev_2
205     CADJ STORE gtr1nm1 = tapelev2, key = ilev_2
206 heimbach 1.22 #endif
207     #ifdef EXACT_CONSERV
208     CADJ STORE etaH = tapelev2, key = ilev_2
209     CADJ STORE hDivFlow = tapelev2, key = ilev_2
210 heimbach 1.12 #endif
211 heimbach 1.6
212     c-- Initialize storage for the innermost loop.
213     c-- Always check common block sizes for the checkpointing!
214     CADJ INIT comlev1 = COMMON,nchklev_1
215     CADJ INIT comlev1_bibj = COMMON,nchklev_1*nsx*nsy*nthreads_chkpt
216     CADJ INIT comlev1_bibj_k = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt
217     CADJ INIT comlev1_kpp = COMMON,nchklev_1*nsx*nsy
218 adcroft 1.21 #ifndef DISABLE_MULTIDIM_ADVECTION
219 heimbach 1.20 CADJ INIT comlev1_bibj_pass
220     CADJ & = COMMON,nchklev_1*nsx*nsy*nr*nthreads_chkpt*maxpass
221 adcroft 1.21 #endif /* DISABLE_MULTIDIM_ADVECTION */
222 heimbach 1.20 #ifdef ALLOW_BULKFORMULAE
223     CADJ INIT comlev1_exf_1
224     CADJ & = COMMON,nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
225     CADJ INIT comlev1_exf_2
226     CADJ & = COMMON,niter_bulk*nchklev_1*snx*nsx*sny*nsy*nthreads_chkpt
227     #endif
228 heimbach 1.6
229     do ilev_1 = 1,nchklev_1
230    
231     c-- The if-statement below introduces a some flexibility in the
232     c-- choice of the 3-tupel ( nchklev_1, nchklev_2, nchklev_3 ).
233     c--
234     c-- Requirement: nchklev_1*nchklev_2*nchklev_3 .ge. nTimeSteps .
235    
236     iloop = (ilev_3 - 1)*nchklev_2*nchklev_1 +
237     & (ilev_2 - 1)*nchklev_1 + ilev_1
238    
239     if ( iloop .le. nTimeSteps ) then
240    
241     #else /* ALLOW_TAMC_CHECKPOINTING undefined */
242     c-- Initialise storage for reference trajectory without TAMC check-
243     c-- pointing.
244     CADJ INIT history = USER
245     CADJ INIT comlev1_bibj = COMMON,nchklev_0*nsx*nsy*nthreads_chkpt
246     CADJ INIT comlev1_bibj_k = COMMON,nchklev_0*nsx*nsy*nr*nthreads_chkpt
247     CADJ INIT comlev1_kpp = COMMON,nchklev_0*nsx*nsy
248    
249     C-- RG replace 2 by max of num_v_smooth_Ri
250     CADJ INIT comlev1_kpp_sm = COMMON,nchklev_0*nsx*nsy*2
251    
252     c-- Check the choice of the checkpointing parameters in relation
253     c-- to nTimeSteps: (nchklev_0 .ge. nTimeSteps)
254     if (nchklev_0 .lt. nTimeSteps) then
255     print*
256     print*, ' the_main_loop: TAMC checkpointing parameter ',
257 adcroft 1.19 & 'nchklev_0 = ', nchklev_0
258 heimbach 1.6 print*, ' not consistent with nTimeSteps = ',
259     & nTimeSteps
260     stop ' ... stopped in the_main_loop.'
261     endif
262    
263 adcroft 1.10 DO iloop = 1, nTimeSteps
264 heimbach 1.6
265     #endif /* ALLOW_TAMC_CHECKPOINTING */
266    
267     #else /* ALLOW_AUTODIFF_TAMC undefined */
268    
269     c-- Start the main loop of adjoint_Objfunc. Automatic differentiation
270     c-- NOT enabled.
271 adcroft 1.10 DO iloop = 1, nTimeSteps
272 heimbach 1.6
273     #endif /* ALLOW_AUTODIFF_TAMC */
274    
275 adcroft 1.10 c-- >>> Loop body start <<<
276 heimbach 1.6
277     #ifdef ALLOW_TAMC_CHECKPOINTING
278 heimbach 1.14 nIter0 = INT( startTime/deltaTClock )
279 heimbach 1.13 ikey_dynamics = ilev_1
280 heimbach 1.6 #endif
281 heimbach 1.14
282    
283 heimbach 1.13 CALL TIMER_START('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
284     CALL FORWARD_STEP( iloop, mytime, myiter, mythid )
285     CALL TIMER_STOP ('FORWARD_STEP [THE_MAIN_LOOP]',mythid)
286 adcroft 1.8
287 heimbach 1.12 #ifdef ALLOW_COST
288 heimbach 1.13 C-- compare model with data and compute cost function
289     C-- this is done after exchanges to allow interpolation
290     CALL TIMER_START('COST_TILE [THE_MAIN_LOOP]',myThid)
291     CALL COST_TILE ( myThid )
292     CALL TIMER_STOP ('COST_TILE [THE_MAIN_LOOP]',myThid)
293 heimbach 1.12 #endif
294    
295 heimbach 1.13 c-- >>> Loop body end <<<
296 heimbach 1.6
297     #ifdef ALLOW_AUTODIFF_TAMC
298     #ifdef ALLOW_TAMC_CHECKPOINTING
299     endif
300     enddo
301     endif
302     enddo
303     endif
304     enddo
305     #else
306     enddo
307     #endif
308    
309     #else
310     enddo
311     #endif
312    
313 heimbach 1.12 #ifdef ALLOW_COST
314     c-- Sum all cost function contributions.
315     call TIMER_START('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
316     call COST_FINAL ( mythid )
317     call TIMER_STOP ('COST_FINAL [ADJOINT SPIN-DOWN]', mythid)
318     #endif
319    
320 heimbach 1.6 _BARRIER
321 adcroft 1.10 CALL TIMER_STOP ('MAIN LOOP [THE_MAIN_LOOP]', mythid)
322 adcroft 1.1
323 adcroft 1.10 END

  ViewVC Help
Powered by ViewVC 1.1.22