/[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.31 - (hide annotations) (download)
Sat Dec 28 10:11:10 2002 UTC (21 years, 6 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint47g_post, checkpoint47f_post
Changes since 1.30: +10 -1 lines
checkpoint47f_post
Merging from release1_p10:
o modifications for using pkg/exf with pkg/seaice
  - pkg/seaice CPP options SEAICE_EXTERNAL_FORCING
    and SEAICE_EXTERNAL_FLUXES
  - pkg/exf CPP options EXF_READ_EVAP and
    EXF_NO_BULK_COMPUTATIONS
  - usage examples are Experiments 8 and 9 in
    verification/lab_sea/README
  - verification/lab_sea default experiment now uses
    pkg/gmredi, pkg/kpp, pkg/seaice, and pkg/exf

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

  ViewVC Help
Powered by ViewVC 1.1.22