/[MITgcm]/MITgcm_contrib/ESMF/global_ocean.128x60x15/code/forward_step_setup.F
ViewVC logotype

Annotation of /MITgcm_contrib/ESMF/global_ocean.128x60x15/code/forward_step_setup.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Tue Mar 30 03:58:56 2004 UTC (21 years, 4 months ago) by cnh
Branch: MAIN
CVS Tags: adoption_1_0_pre_A, HEAD
New test with different size

1 cnh 1.1 C $Header: /u/gcmpack/MITgcm_contrib/ESMF/global_ocean.128x64x15/code/forward_step_setup.F,v 1.1.1.1 2004/02/15 22:28:18 cnh Exp $
2     C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     cswdptr -- add --
8     #ifdef ALLOW_GCHEM
9     # include "GCHEM_OPTIONS.h"
10     #endif
11     cswdptr -- end add ---
12    
13     CBOP
14     C !ROUTINE: FORWARD_STEP_SETUP
15     C !INTERFACE:
16     SUBROUTINE FORWARD_STEP_SETUP( iloop, myTime, myIter, myThid )
17    
18     C !DESCRIPTION: \bv
19     C *==================================================================
20     C | SUBROUTINE forward_step
21     C | o Run the ocean model and, optionally, evaluate a cost function.
22     C *==================================================================
23     C |
24     C | THE_MAIN_LOOP is the toplevel routine for the Tangent Linear and
25     C | Adjoint Model Compiler (TAMC). For this purpose the initialization
26     C | of the model was split into two parts. Those parameters that do
27     C | not depend on a specific model run are set in INITIALISE_FIXED,
28     C | whereas those that do depend on the specific realization are
29     C | initialized in INITIALISE_VARIA.
30     C |
31     C *==================================================================
32     C \ev
33    
34     C !USES:
35     IMPLICIT NONE
36     C == Global variables ==
37     #include "SIZE.h"
38     #include "EEPARAMS.h"
39     #include "PARAMS.h"
40     #include "DYNVARS.h"
41     #include "FFIELDS.h"
42    
43     #ifdef ALLOW_NONHYDROSTATIC
44     #include "CG3D.h"
45     #endif
46    
47     #ifdef ALLOW_SHAP_FILT
48     #include "SHAP_FILT.h"
49     #endif
50     #ifdef ALLOW_ZONAL_FILT
51     #include "ZONAL_FILT.h"
52     #endif
53    
54     #ifdef ALLOW_AUTODIFF_TAMC
55     # include "tamc.h"
56     # include "ctrl.h"
57     # include "ctrl_dummy.h"
58     # include "cost.h"
59     # include "EOS.h"
60     # ifdef ALLOW_EXF
61     # include "exf_fields.h"
62     # ifdef ALLOW_BULKFORMULAE
63     # include "exf_constants.h"
64     # endif
65     # endif
66     # ifdef ALLOW_OBCS
67     # include "OBCS.h"
68     # endif
69     # ifdef ALLOW_PTRACERS
70     # include "PTRACERS.h"
71     # endif
72     #endif /* ALLOW_AUTODIFF_TAMC */
73    
74     C !LOCAL VARIABLES:
75     C == Routine arguments ==
76     C note: under the multi-threaded model myiter and
77     C mytime are local variables passed around as routine
78     C arguments. Although this is fiddly it saves the need to
79     C impose additional synchronisation points when they are
80     C updated.
81     C myiter - iteration counter for this thread
82     C mytime - time counter for this thread
83     C mythid - thread number for this instance of the routine.
84     integer iloop
85     integer mythid
86     integer myiter
87     _RL mytime
88     integer i,L
89     CEOP
90    
91     #ifdef ALLOW_DEBUG
92     IF ( debugLevel .GE. debLevB )
93     & CALL DEBUG_ENTER('FORWARD_STEP',myThid)
94     #endif
95    
96     #ifdef ALLOW_AUTODIFF_TAMC
97     C-- Reset the model iteration counter and the model time.
98     myiter = nIter0 + (iloop-1)
99     mytime = startTime + float(iloop-1)*deltaTclock
100     #endif
101    
102     #if (defined (ALLOW_AUTODIFF_TAMC) && defined (ALLOW_AUTODIFF_MONITOR))
103     C Include call to a dummy routine. Its adjoint will be
104     C called at the proper place in the adjoint code.
105     C The adjoint routine will print out adjoint values
106     C if requested. The location of the call is important,
107     C it has to be after the adjoint of the exchanges
108     C (DO_GTERM_BLOCKING_EXCHANGES).
109     CALL DUMMY_IN_STEPPING( myTime, myIter, myThid )
110     cph I've commented this line since it may conflict with MITgcm's adjoint
111     cph However, need to check whether that's still consistent
112     cph with the ecco-branch (it should).
113     cph CALL DO_FIELDS_BLOCKING_EXCHANGES( myThid )
114     #endif
115    
116     #ifdef EXACT_CONSERV
117     IF (exactConserv) THEN
118     C-- Update etaH(n+1) :
119     CALL TIMER_START('UPDATE_ETAH [FORWARD_STEP]',mythid)
120     CALL UPDATE_ETAH( myTime, myIter, myThid )
121     CALL TIMER_STOP ('UPDATE_ETAH [FORWARD_STEP]',mythid)
122     ENDIF
123     #endif /* EXACT_CONSERV */
124    
125     #ifdef NONLIN_FRSURF
126     IF ( select_rStar.NE.0 ) THEN
127     C-- r* : compute the future level thickness according to etaH(n+1)
128     CALL TIMER_START('CALC_R_STAR [FORWARD_STEP]',mythid)
129     CALL CALC_R_STAR(etaH, myTime, myIter, myThid )
130     CALL TIMER_STOP ('CALC_R_STAR [FORWARD_STEP]',mythid)
131     ELSEIF ( nonlinFreeSurf.GT.0) THEN
132     C-- compute the future surface level thickness according to etaH(n+1)
133     CALL TIMER_START('CALC_SURF_DR [FORWARD_STEP]',mythid)
134     CALL CALC_SURF_DR(etaH, myTime, myIter, myThid )
135     CALL TIMER_STOP ('CALC_SURF_DR [FORWARD_STEP]',mythid)
136     ENDIF
137     #endif /* NONLIN_FRSURF */
138    
139     #ifdef ALLOW_AUTODIFF_TAMC
140     c**************************************
141     #include "checkpoint_lev1_directives.h"
142     c**************************************
143     #endif
144    
145     C-- Call external forcing package
146     #ifdef ALLOW_BULK_FORCE
147     IF ( useBulkForce ) THEN
148     #ifdef ALLOW_DEBUG
149     IF ( debugLevel .GE. debLevB )
150     & CALL DEBUG_CALL('BULKF_FIELDS_LOAD',myThid)
151     #endif
152     CALL TIMER_START('BULKF_FORCING [FORWARD_STEP]',mythid)
153     C- load all forcing fields at current time
154     CALL BULKF_FIELDS_LOAD( myTime, myIter, myThid )
155     C- calculate qnet and empmr (and wind stress)
156     CALL BULKF_FORCING( myTime, myIter, myThid )
157     CALL TIMER_STOP ('BULKF_FORCING [FORWARD_STEP]',mythid)
158     ELSE
159     #endif /* ALLOW_BULK_FORCE */
160    
161     # ifdef ALLOW_EXF
162     # ifdef ALLOW_DEBUG
163     IF ( debugLevel .GE. debLevB )
164     & CALL DEBUG_CALL('EXF_GETFORCING',myThid)
165     # endif
166     CALL TIMER_START('EXF_GETFORCING [FORWARD_STEP]',mythid)
167     CALL EXF_GETFORCING( mytime, myiter, mythid )
168     CALL TIMER_STOP ('EXF_GETFORCING [FORWARD_STEP]',mythid)
169     # else /* ALLOW_EXF undef */
170     cph The following IF-statement creates an additional dependency
171     cph for the forcing fields requiring additional storing.
172     cph Therefore, the IF-statement will be put between CPP-OPTIONS,
173     cph assuming that ALLOW_SEAICE has not yet been differentiated.
174     # ifdef ALLOW_SEAICE
175     IF ( .NOT. useSEAICE ) THEN
176     # endif
177     #ifdef ALLOW_DEBUG
178     IF ( debugLevel .GE. debLevB )
179     & CALL DEBUG_CALL('EXTERNAL_FIELDS_LOAD',myThid)
180     #endif
181     CALL TIMER_START('EXTERNAL_FIELDS_LOAD[FORWARD_STEP]',mythid)
182     CALL EXTERNAL_FIELDS_LOAD( mytime, myiter, mythid )
183     CALL TIMER_STOP ('EXTERNAL_FIELDS_LOAD[FORWARD_STEP]',mythid)
184     # ifdef ALLOW_SEAICE
185     ENDIF
186     # endif
187     # endif /* ALLOW_EXF */
188     #ifdef ALLOW_BULK_FORCE
189     C-- end of if/else block useBulfforce --
190     ENDIF
191     #endif /* ALLOW_BULK_FORCE */
192    
193     #ifdef ALLOW_AUTODIFF
194     c-- Add control vector for forcing and parameter fields
195     if ( myiter .EQ. nIter0 )
196     & CALL CTRL_MAP_FORCING (mythid)
197     #endif
198    
199     #ifdef ALLOW_THSICE
200     IF (useThSIce) THEN
201     #ifdef ALLOW_DEBUG
202     IF ( debugLevel .GE. debLevB )
203     & CALL DEBUG_CALL('THSICE_MAIN',myThid)
204     #endif
205     C-- Step forward Therm.Sea-Ice variables
206     C and modify forcing terms including effects from ice
207     CALL TIMER_START('THSICE_MAIN [FORWARD_STEP]', myThid)
208     CALL THSICE_MAIN( myTime, myIter, myThid )
209     CALL TIMER_STOP( 'THSICE_MAIN [FORWARD_STEP]', myThid)
210     ENDIF
211     #endif /* ALLOW_THSICE */
212    
213     # ifdef ALLOW_SEAICE
214     C-- Call sea ice model to compute forcing/external data fields. In
215     C addition to computing prognostic sea-ice variables and diagnosing the
216     C forcing/external data fields that drive the ocean model, SEAICE_MODEL
217     C also sets theta to the freezing point under sea-ice. The implied
218     C surface heat flux is then stored in variable surfaceTendencyTice,
219     C which is needed by KPP package (kpp_calc.F and kpp_transport_t.F)
220     C to diagnose surface buoyancy fluxes and for the non-local transport
221     C term. Because this call precedes model thermodynamics, temperature
222     C under sea-ice may not be "exactly" at the freezing point by the time
223     C theta is dumped or time-averaged.
224     IF ( useSEAICE ) THEN
225     #ifdef ALLOW_DEBUG
226     IF ( debugLevel .GE. debLevB )
227     & CALL DEBUG_CALL('SEAICE_MODEL',myThid)
228     #endif
229     CALL TIMER_START('SEAICE_MODEL [FORWARD_STEP]',myThid)
230     CALL SEAICE_MODEL( myTime, myIter, myThid )
231     CALL TIMER_STOP ('SEAICE_MODEL [FORWARD_STEP]',myThid)
232     ENDIF
233     # endif /* ALLOW_SEAICE */
234    
235     C-- Freeze water at the surface
236     #ifdef ALLOW_AUTODIFF_TAMC
237     CADJ STORE theta = comlev1, key = ikey_dynamics
238     #endif
239     IF ( allowFreezing .AND. .NOT. useSEAICE
240     & .AND. .NOT. useThSIce ) THEN
241     CALL FREEZE_SURFACE( myTime, myIter, myThid )
242     ENDIF
243    
244     #ifdef ALLOW_AUTODIFF_TAMC
245     # ifdef ALLOW_PTRACERS
246     cph this replaces _bibj storing of ptracer within thermodynamics
247     CADJ STORE ptracer = comlev1, key = ikey_dynamics
248     # endif
249     #endif
250    
251     #ifdef ALLOW_PTRACERS
252     # ifdef ALLOW_GCHEM
253     CALL GCHEM_FIELDS_LOAD( mytime, myiter, mythid )
254     # endif
255     #endif
256    
257     #ifdef COMPONENT_MODULE
258     IF ( useCoupler ) THEN
259     C Post coupling data that I export.
260     C Read in coupling data that I import.
261     CALL TIMER_START('CPL_EXPORT-IMPORT [FORWARD_STEP]',myThid)
262     CALL CPL_EXPORT_MY_DATA( myIter, myTime, myThid )
263     CALL CPL_IMPORT_EXTERNAL_DATA( myIter, myTime, myThid )
264     CALL TIMER_STOP ('CPL_EXPORT-IMPORT [FORWARD_STEP]',myThid)
265     ENDIF
266     #endif /* COMPONENT_MODULE */
267    
268     #ifdef COMPONENT_MODULE
269     # ifndef ALLOW_AIM
270     C jmc: don't know precisely where to put this call. leave it here for now.
271     IF ( useCoupler ) THEN
272     CALL OCN_APPLY_IMPORT( myTime, myIter, myThid )
273     ENDIF
274     # endif
275     #endif /* COMPONENT_MODULE */
276    
277     RETURN
278     END

  ViewVC Help
Powered by ViewVC 1.1.22