/[MITgcm]/MITgcm_contrib/dgoldberg/depth_control_no_nsa/code/initialise_varia.F
ViewVC logotype

Annotation of /MITgcm_contrib/dgoldberg/depth_control_no_nsa/code/initialise_varia.F

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


Revision 1.1 - (hide annotations) (download)
Thu Dec 7 23:21:12 2017 UTC (7 years, 7 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
test case for depth control w/out cg2d_nsa

1 dgoldberg 1.1 C $Header: /u/gcmpack/MITgcm/model/src/initialise_varia.F,v 1.80 2016/08/12 14:48:33 heimbach Exp $
2     C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6     #ifdef ALLOW_AUTODIFF
7     # include "AUTODIFF_OPTIONS.h"
8     #endif
9     #ifdef ALLOW_CTRL
10     # include "CTRL_OPTIONS.h"
11     #endif
12    
13     CBOP
14     C !ROUTINE: INITIALISE_VARIA
15     C !INTERFACE:
16     SUBROUTINE INITIALISE_VARIA( myThid )
17     C !DESCRIPTION: \bv
18     C *==========================================================*
19     C | SUBROUTINE INITIALISE_VARIA
20     C | o Set the initial conditions for dynamics variables
21     C | and time dependent arrays
22     C *==========================================================*
23     C | This routine reads/writes data from an input file and
24     C | from various binary files.
25     C | Each thread invokes an instance of this routine as does
26     C | each process in a multi-process parallel environment like
27     C | MPI.
28     C *==========================================================*
29     C \ev
30    
31     C !CALLING SEQUENCE:
32     C INITIALISE_VARIA
33     C |
34     C #ifdef ALLOW_AUTODIFF
35     C |-- INI_DEPTHS \
36     C |-- CTRL_DEPTH_INI \
37     C |-- UPDATE_MASKS_ETC } ALLOW_DEPTH_CONTROL case
38     C |-- UPDATE_CG2D /
39     C #endif
40     C |-- INI_NLFS_VARS
41     C |-- INI_DYNVARS
42     C |-- INI_NH_VARS
43     C |-- INI_FFIELDS
44     C |
45     C |-- INI_FIELDS
46     C |
47     C |-- INI_MIXING
48     C |
49     C |-- TAUEDDY_INIT_VARIA
50     C |
51     C |-- INI_FORCING
52     C |
53     C |-- AUTODIFF_INIT_VARIA
54     C |
55     C |-- PACKAGES_INIT_VARIABLES
56     C |
57     C |-- COST_INIT_VARIA
58     C |
59     C |-- CONVECTIVE_ADJUSTMENT_INI
60     C |
61     C |-- CALC_R_STAR
62     C |-- UPDATE_R_STAR
63     C |-- UPDATE_SIGMA
64     C |-- CALC_SURF_DR
65     C |-- UPDATE_SURF_DR
66     C |
67     C |-- UPDATE_CG2D
68     C |
69     C |-- INTEGR_CONTINUITY
70     C |
71     C |-- CALC_R_STAR
72     C |-- CALC_SURF_DR
73     C |
74     C |-- STATE_SUMMARY
75     C |
76     C |-- MONITOR
77     C |
78     C |-- DO_STATEVARS_TAVE
79     C |
80     C |-- DO_THE_MODEL_IO
81    
82     C !USES:
83     IMPLICIT NONE
84     C == Global variables ==
85     #include "SIZE.h"
86     #include "EEPARAMS.h"
87     #include "PARAMS.h"
88     #include "DYNVARS.h"
89     #include "SURFACE.h"
90     #include "CG2D.h"
91     #ifdef ALLOW_AUTODIFF
92     # include "GRID.h"
93     # include "FFIELDS.h"
94     # include "CTRL_FIELDS.h"
95     #endif
96    
97     C !INPUT/OUTPUT PARAMETERS:
98     C == Routine arguments ==
99     INTEGER myThid
100    
101     C !LOCAL VARIABLES:
102     C == Local variables ==
103     INTEGER bi,bj
104     CEOP
105    
106     #ifdef ALLOW_DEBUG
107     IF (debugMode) CALL DEBUG_ENTER('INITIALISE_VARIA',myThid)
108     #endif
109    
110     #ifdef ALLOW_AUTODIFF
111     nIter0 = NINT( (startTime-baseTime)/deltaTClock )
112     #endif /* ALLOW_AUTODIFF */
113    
114     ! call write_fld_xy_rl('ro_surf1','',ro_surf,0,mythid)
115    
116     #ifdef ALLOW_CTRL
117     # ifdef ALLOW_DEPTH_CONTROL
118     C-- Intialize the depth for TAF/TAMC
119     CALL INI_DEPTHS( myThid )
120     C-- Get control parameter depth
121     CALL CTRL_DEPTH_INI( myThid )
122     #if defined(ALLOW_SHELFICE) && defined(ALLOW_DIFFERENTIATE_CG2D_MATRIX)
123     IF ( useShelfIce ) THEN
124     C-- Modify ocean upper boundary position according to ice-shelf topography
125     CALL SHELFICE_INIT_DEPTHS(
126     U R_low, Ro_surf,
127     I myThid )
128     ENDIF
129     #endif /* ALLOW_SHELFICE */
130     C-- Re-calculate hFacS/W and some other parameters from hFacC
131     CALL UPDATE_MASKS_ETC( myThid )
132     C-- Update laplace operators for use in 2D conjugate gradient solver.
133     CALL UPDATE_CG2D( startTime, nIter0, myThid )
134     # endif /* ALLOW_DEPTH_CONTROL */
135     #endif /* ALLOW_CTRL */
136     ! call write_fld_xy_rl('ro_surf2','',ro_surf,0,mythid)
137    
138     C-- Initialise Non-Lin FreeSurf variables:
139     CALL INI_NLFS_VARS( myThid )
140    
141     C-- Initialize DYNVARS arrays (state fields + G terms: Gu,Gv,...) to zero [always]
142     #ifdef ALLOW_DEBUG
143     IF (debugMode) CALL DEBUG_CALL('INI_DYNVARS',myThid)
144     #endif
145     CALL INI_DYNVARS( myThid )
146    
147     C-- Initialize NH_VARS arrays to zero [always]
148     #ifdef ALLOW_NONHYDROSTATIC
149     CALL INI_NH_VARS( myThid )
150     #endif
151    
152     C-- Initialize FFIELDS arrays to zero [always]
153     CALL INI_FFIELDS( myThid )
154    
155     C-- Initialise model fields.
156     C Starting values of U, V, W, temp., salt. and tendency terms
157     C are set here. Fields are either set to default or read from
158     C stored files.
159     #ifdef ALLOW_DEBUG
160     IF (debugMode) CALL DEBUG_CALL('INI_FIELDS',myThid)
161     #endif
162     CALL INI_FIELDS( myThid )
163    
164     C-- Initialise 3-dim. diffusivities
165     #ifdef ALLOW_DEBUG
166     IF (debugMode) CALL DEBUG_CALL('INI_MIXING',myThid)
167     #endif
168     CALL INI_MIXING( myThid )
169    
170     #ifdef ALLOW_EDDYPSI
171     C-- Initialise eddy diffusivities
172     CALL TAUEDDY_INIT_VARIA( myThid )
173     #endif
174    
175     C-- Initialise model forcing fields.
176     #ifdef ALLOW_DEBUG
177     IF (debugMode) CALL DEBUG_CALL('INI_FORCING',myThid)
178     #endif
179     CALL INI_FORCING( myThid )
180    
181     #ifdef ALLOW_AUTODIFF
182     C-- Initialise active fields to help TAMC
183     if (useAUTODIFF) CALL AUTODIFF_INIT_VARIA( myThid )
184     #endif
185    
186     C-- Initialize variable data for packages
187     #ifdef ALLOW_DEBUG
188     IF (debugMode) CALL DEBUG_CALL('PACKAGES_INIT_VARIABLES',myThid)
189     #endif
190     #ifdef ALLOW_AUTODIFF_TAMC
191     # ifdef NONLIN_FRSURF
192     CADJ STORE recip_hFacC = tapelev_init, key = 1
193     # endif
194     #endif
195     CALL PACKAGES_INIT_VARIABLES( myThid )
196    
197     #ifdef ALLOW_COST
198     C-- Initialise the cost function (moved out of packages_init_variables to
199     C here to prevent resetting cost-funct in adinitialise_varia recomput.)
200     CALL COST_INIT_VARIA( myThid )
201     #endif /* ALLOW_COST */
202    
203     c#ifndef ALLOW_AUTODIFF
204     c IF ( usePickupBeforeC35 .AND. startTime .NE. baseTime ) THEN
205     C-- IMPORTANT : Need to activate the following call to restart from a pickup
206     C file written by MITgcmUV_checkpoint34 (Feb-08, 2001) or earlier.
207     C- Disable this option on Jan-09, 2007.
208     c CALL THE_CORRECTION_STEP(startTime, nIter0, myThid)
209     c ENDIF
210     c#endif
211    
212     #ifndef ALLOW_AUTODIFF_WHTAPEIO
213     C-- Initial conditions are convectively adjusted (for historical reasons)
214     IF ( startTime .EQ. baseTime .AND. cAdjFreq .NE. 0. ) THEN
215     #ifdef ALLOW_DEBUG
216     IF (debugMode) CALL DEBUG_CALL('CONVECTIVE_ADJUSTMENT_INI',myThid)
217     #endif
218     CADJ loop = parallel
219     DO bj = myByLo(myThid), myByHi(myThid)
220     CADJ loop = parallel
221     DO bi = myBxLo(myThid), myBxHi(myThid)
222     CALL CONVECTIVE_ADJUSTMENT_INI(
223     I bi, bj, startTime, nIter0, myThid )
224     ENDDO
225     ENDDO
226     ENDIF
227     #endif /* ALLOW_AUTODIFF_WHTAPEIO */
228    
229     #ifdef NONLIN_FRSURF
230     C-- Compute the surface level thickness <-- function of etaH(n)
231     C and modify hFac(C,W,S) accordingly :
232     # ifndef DISABLE_RSTAR_CODE
233     IF ( select_rStar.NE.0 )
234     & CALL CALC_R_STAR(etaH, startTime, -1 , myThid )
235     # endif /* DISABLE_RSTAR_CODE */
236     IF ( nonlinFreeSurf.GT.0 ) THEN
237     IF ( select_rStar.GT.0 ) THEN
238     # ifndef DISABLE_RSTAR_CODE
239     CALL UPDATE_R_STAR( .TRUE., startTime, nIter0, myThid )
240     # endif /* DISABLE_RSTAR_CODE */
241     ELSEIF ( selectSigmaCoord.NE.0 ) THEN
242     # ifndef DISABLE_SIGMA_CODE
243     CALL UPDATE_SIGMA( etaH, startTime, nIter0, myThid )
244     # endif /* DISABLE_SIGMA_CODE */
245     ELSE
246     CALL CALC_SURF_DR(etaH, startTime, -1 , myThid )
247     CALL UPDATE_SURF_DR( .TRUE., startTime, nIter0, myThid )
248     ENDIF
249     ENDIF
250     C- update also CG2D matrix (and preconditioner)
251     IF ( nonlinFreeSurf.GT.2 ) THEN
252     CALL UPDATE_CG2D( startTime, nIter0, myThid )
253     ENDIF
254     #endif /* NONLIN_FRSURF */
255    
256     #ifdef ALLOW_DEBUG
257     IF (debugMode) CALL DEBUG_CALL('INTEGR_CONTINUITY',myThid)
258     #endif
259     C-- Integrate continuity vertically for vertical velocity
260     CALL INTEGR_CONTINUITY( uVel, vVel,
261     I startTime, nIter0, myThid )
262    
263     #ifdef NONLIN_FRSURF
264     IF ( select_rStar.NE.0 ) THEN
265     #ifndef DISABLE_RSTAR_CODE
266     C-- r* : compute the future level thickness according to etaH(n+1)
267     CALL CALC_R_STAR(etaH, startTime, nIter0, myThid )
268     #endif
269     ELSEIF ( nonlinFreeSurf.GT.0 .AND. selectSigmaCoord.EQ.0 ) THEN
270     C-- compute the future surface level thickness according to etaH(n+1)
271     CALL CALC_SURF_DR(etaH, startTime, nIter0, myThid )
272     ENDIF
273     #endif /* NONLIN_FRSURF */
274    
275     c IF ( nIter0.EQ.0 .AND. staggerTimeStep ) THEN
276     C-- Filter initial T & S fields if staggerTimeStep
277     C (only for backward compatibility ; to be removed later)
278     #ifdef ALLOW_SHAP_FILT
279     c IF ( useSHAP_FILT .AND. shap_filt_TrStagg ) THEN
280     c CALL SHAP_FILT_APPLY_TS(theta,salt,startTime,nIter0,myThid)
281     c ENDIF
282     #endif
283     #ifdef ALLOW_ZONAL_FILT
284     c IF ( useZONAL_FILT .AND. zonal_filt_TrStagg ) THEN
285     c CALL ZONAL_FILT_APPLY_TS( theta, salt, myThid )
286     c ENDIF
287     #endif
288     c ENDIF
289    
290     #ifdef ALLOW_GRIDALT
291     IF (useGRIDALT) THEN
292     CALL TIMER_START('GRIDALT_UPDATE [INITIALISE_VARIA]',myThid)
293     CALL GRIDALT_UPDATE(myThid)
294     CALL TIMER_STOP ('GRIDALT_UPDATE [INITIALISE_VARIA]',myThid)
295     ENDIF
296     #endif
297    
298     C-- Finally summarise the model state
299     #ifdef ALLOW_DEBUG
300     IF (debugMode) CALL DEBUG_CALL('STATE_SUMMARY',myThid)
301     #endif
302     CALL STATE_SUMMARY( myThid )
303    
304     #ifdef ALLOW_MONITOR
305     #ifdef ALLOW_DEBUG
306     IF (debugMode) CALL DEBUG_CALL('MONITOR',myThid)
307     #endif
308     C-- Check status of initial state (statistics, cfl, etc...)
309     CALL MONITOR( startTime, nIter0, myThid )
310     #endif /* ALLOW_MONITOR */
311    
312     #ifdef ALLOW_TIMEAVE
313     #ifdef ALLOW_DEBUG
314     IF (debugMode) CALL DEBUG_CALL('DO_STATEVARS_TAVE',myThid)
315     #endif
316     C-- Initialise time-average arrays with initial state values
317     CALL DO_STATEVARS_TAVE( startTime, nIter0, myThid )
318     #endif
319    
320     C-- Dump initial state to files
321     #ifdef ALLOW_DEBUG
322     IF (debugMode) CALL DEBUG_CALL('DO_THE_MODEL_IO',myThid)
323     #endif
324     CALL DO_THE_MODEL_IO( .FALSE., startTime, nIter0, myThid )
325    
326     #ifdef ALLOW_DEBUG
327     IF (debugMode) CALL DEBUG_LEAVE('INITIALISE_VARIA',myThid)
328     #endif
329    
330     C-- Check barrier synchronization:
331     CALL BAR_CHECK( 4, myThid )
332    
333     RETURN
334     END

  ViewVC Help
Powered by ViewVC 1.1.22