/[MITgcm]/MITgcm/model/src/initialise_varia.F
ViewVC logotype

Diff of /MITgcm/model/src/initialise_varia.F

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

revision 1.17 by jmc, Mon Aug 27 18:50:41 2001 UTC revision 1.51 by jmc, Sat Jul 29 21:02:12 2006 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7  CStartOfInterface  CBOP
8    C     !ROUTINE: INITIALISE_VARIA
9    C     !INTERFACE:
10        SUBROUTINE INITIALISE_VARIA(myThid)        SUBROUTINE INITIALISE_VARIA(myThid)
11  C     /==========================================================\  C     !DESCRIPTION: \bv
12  C     | SUBROUTINE INITIALISE_VARIA                              |  C     *==========================================================*
13  C     | o Set the initial conditions for dynamics variables      |  C     | SUBROUTINE INITIALISE_VARIA                              
14  C     |   and time dependent arrays                              |  C     | o Set the initial conditions for dynamics variables      
15  C     |==========================================================|  C     |   and time dependent arrays                              
16  C     | This routine reads/writes  data from an input file and   |  C     *==========================================================*
17  C     | from various binary files.                               |  C     | This routine reads/writes  data from an input file and    
18  C     | Each thread invokes an instance of this routine as does  |  C     | from various binary files.                                
19  C     | each process in a multi-process parallel environment like|  C     | Each thread invokes an instance of this routine as does  
20  C     | MPI.                                                     |  C     | each process in a multi-process parallel environment like
21  C     \==========================================================/  C     | MPI.                                                      
22        IMPLICIT NONE  C     *==========================================================*
23    C     \ev
24    
25    C     !CALLING SEQUENCE:
26    C     INITIALISE_VARIA
27    C       |
28    C #ifdef ALLOW_AUTODIFF_TAMC
29    C       |-- INI_LINEAR_PHISURF
30    C       |
31    C       |-- INI_CORI
32    C       |
33    C       |-- INI_CG2D
34    C       |
35    C       |-- INI_CG3D
36    C #endif
37    C       |-- INI_MIXING
38    C       |
39    C       |-- INI_DYNVARS
40    C       |-- INI_NH_VARS
41    C       |
42    C       |-- INI_FIELDS
43    C       |
44    C       |-- INI_AUTODIFF
45    C       |
46    C       |-- PACKAGES_INIT_VARIABLES
47    C       |
48    C       |-- THE_CORRECTION_STEP (if restart from old pickup files)
49    C       |
50    C       |-- CALL CONVECTIVE_ADJUSTMENT_INI
51    C       |
52    C       |-- CALC_SURF_DR
53    C       |
54    C       |-- UPDATE_SURF_DR
55    C       |
56    C       |-- UPDATE_CG2D
57    C       |
58    C       |-- INTEGR_CONTINUITY
59    C       |
60    C       |-- TIMEAVE_STATVARS
61    C       |
62    C       |-- PTRACERS_STATVARS
63    C       |
64    C       |-- STATE_SUMMARY
65    
66    C     !USES:
67          IMPLICIT NONE
68  C     == Global variables ==  C     == Global variables ==
69  #include "SIZE.h"  #include "SIZE.h"
70  #include "EEPARAMS.h"  #include "EEPARAMS.h"
71  #include "PARAMS.h"  #include "PARAMS.h"
72  #include "DYNVARS.h"  #include "DYNVARS.h"
73    #include "SURFACE.h"
74    #ifdef ALLOW_SHAP_FILT
75    # include "SHAP_FILT.h"
76    #endif
77    #ifdef ALLOW_ZONAL_FILT
78    # include "ZONAL_FILT.h"
79    #endif
80    
81    C     !INPUT/OUTPUT PARAMETERS:
82  C     == Routine arguments ==  C     == Routine arguments ==
83        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
84    
85    C     !LOCAL VARIABLES:
86  C     == Local variables ==  C     == Local variables ==
87        INTEGER bi,bj,K,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
88    CEOP
89    
90  #ifdef ALLOW_TAMC_CHECKPOINTING  #ifdef ALLOW_DEBUG
91          IF (debugMode) CALL DEBUG_ENTER('INITIALISE_VARIA',myThid)
92    #endif
93    
94        nIter0 = INT( startTime/deltaTClock )  #ifdef ALLOW_AUTODIFF_TAMC
95    
96          nIter0 = NINT( (startTime-baseTime)/deltaTClock )
97    
98    C--   Intialize the hFacC for TAF/TAMC
99          CALL INI_HFAC( myThid )
100          CALL INI_DEPTHS( myThid )
101          CALL INI_MASKS_ETC( myThid )
102    
103  C--   Set Bo_surf => define the Linear Relation: Phi_surf(eta)  C--   Set Bo_surf => define the Linear Relation: Phi_surf(eta)
104    # ifdef ALLOW_DEBUG
105          IF (debugMode) CALL DEBUG_CALL('INI_LINEAR_PHISURF',myThid)
106    # endif
107        CALL INI_LINEAR_PHISURF( myThid )        CALL INI_LINEAR_PHISURF( myThid )
108    
109  C--   Set coriolis operators  C--   Set coriolis operators
110    # ifdef ALLOW_DEBUG
111          IF (debugMode) CALL DEBUG_CALL('INI_CORI',myThid)
112    # endif
113        CALL INI_CORI( myThid )        CALL INI_CORI( myThid )
114    
115  C--   Set laplace operators for use in 2D conjugate gradient solver.  C--   Set laplace operators for use in 2D conjugate gradient solver.
116    # ifdef ALLOW_DEBUG
117          IF (debugMode) CALL DEBUG_CALL('INI_CG2D',myThid)
118    # endif
119        CALL INI_CG2D( myThid )        CALL INI_CG2D( myThid )
120    
121  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_DEPTH_CONTROL
122    C--   get control parameter depth
123          CALL CTRL_DEPTH_INI( myThid )
124    C--   Re-calculate hFacS/W and some other parameters from hFacC
125          CALL UPDATE_MASKS_ETC( myThid )
126    C--   Update laplace operators for use in 2D conjugate gradient solver.
127          CALL UPDATE_CG2D( startTime, nIter0, myThid )
128    CML      CALL UPDATE_CG2D( myThid )
129    #endif /* ALLOW_DEPTH_CONTROL */
130    
131    # ifdef ALLOW_NONHYDROSTATIC
132  C--   Set laplace operators for use in 3D conjugate gradient solver.  C--   Set laplace operators for use in 3D conjugate gradient solver.
133    ceh3 should add an IF ( useNONHYDROSTATIC ) THEN
134    #  ifdef ALLOW_DEBUG
135          IF (debugMode) CALL DEBUG_CALL('INI_CG3D',myThid)
136    #  endif
137        CALL INI_CG3D( myThid )        CALL INI_CG3D( myThid )
138  #endif  # endif
139    
140  #endif /* ALLOW_TAMC_CHECKPOINTING */  #endif /* ALLOW_AUTODIFF_TAMC */
141        _BARRIER        _BARRIER
142    
143  C--   Initialise 3-dim. diffusivities  C--   Initialise 3-dim. diffusivities
144    #ifdef ALLOW_DEBUG
145          IF (debugMode) CALL DEBUG_CALL('INI_MIXING',myThid)
146    #endif
147        CALL INI_MIXING( myThid )        CALL INI_MIXING( myThid )
148        _BARRIER        _BARRIER
149    
150    #ifdef ALLOW_TAU_EDDY
151    C--  Initialise eddy diffusivities
152          CALL TAUEDDY_INIT_VARIA( myThid )
153    #endif
154    
155  C--   Initialize DYNVARS arrays (state fields + G terms: Gu,Gv,...) to zero [always]  C--   Initialize DYNVARS arrays (state fields + G terms: Gu,Gv,...) to zero [always]
156    #ifdef ALLOW_DEBUG
157          IF (debugMode) CALL DEBUG_CALL('INI_DYNVARS',myThid)
158    #endif
159        CALL INI_DYNVARS( myThid )        CALL INI_DYNVARS( myThid )
160    
161    C--   Initialize NH_VARS arrays to zero [always]
162    #ifdef ALLOW_NONHYDROSTATIC
163          CALL INI_NH_VARS( myThid )
164    #endif
165    
166  C--   Initialise model fields.  C--   Initialise model fields.
167  C     Starting values of U, V, W, temp., salt. and tendency terms  C     Starting values of U, V, W, temp., salt. and tendency terms
168  C     are set here. Fields are either set to default or read from  C     are set here. Fields are either set to default or read from
169  C     stored files.  C     stored files.
170    #ifdef ALLOW_DEBUG
171          IF (debugMode) CALL DEBUG_CALL('INI_FIELDS',myThid)
172    #endif
173        CALL INI_FIELDS( myThid )        CALL INI_FIELDS( myThid )
174        _BARRIER        _BARRIER
175    
176  #ifdef ALLOW_PASSIVE_TRACER  #ifdef ALLOW_AUTODIFF_TAMC
177  C--   Initialise passive tracer(s)  C--   Initialise active fields to help TAMC
178        CALL INI_TR1( myThid )        CALL INI_AUTODIFF( myThid )
179        _BARRIER        _BARRIER
180  #endif  #endif
181    
182    C--   Initialize variable data for packages
183    #ifdef ALLOW_DEBUG
184          IF (debugMode) CALL DEBUG_CALL('PACKAGES_INIT_VARIABLES',myThid)
185    #endif
186          CALL PACKAGES_INIT_VARIABLES( myThid )
187    
188    #ifndef ALLOW_AUTODIFF_TAMC
189        IF ( usePickupBeforeC35 ) THEN        IF ( usePickupBeforeC35 ) THEN
190  C-- IMPORTANT : Need to activate the following call to restart from  C-- IMPORTANT : Need to activate the following call to restart from
191  C     a pickup file written by MITgcmUV_checkpoint34 or earlier.  C     a pickup file written by MITgcmUV_checkpoint34 or earlier.
192        IF ( startTime .NE. 0. ) THEN        IF ( startTime .NE. baseTime ) THEN
193    #ifdef ALLOW_DEBUG
194          IF (debugMode) CALL DEBUG_CALL('THE_CORRECTION_STEP',myThid)
195    #endif
196         CALL THE_CORRECTION_STEP(startTime, nIter0, myThid)         CALL THE_CORRECTION_STEP(startTime, nIter0, myThid)
197        ENDIF        ENDIF
198        ENDIF        ENDIF
199    #endif
200    
201  C--   Initial conditions are convectively adjusted (for historical reasons)  C--   Initial conditions are convectively adjusted (for historical reasons)
202        IF ( startTime .EQ. 0. ) THEN        IF ( startTime .EQ. baseTime .AND. cAdjFreq .NE. 0. ) THEN
203    #ifdef ALLOW_DEBUG
204          IF (debugMode) CALL DEBUG_CALL('CONVECTIVE_ADJUSTMENT_INI',myThid)
205    #endif
206  CADJ loop = parallel  CADJ loop = parallel
207          DO bj = myByLo(myThid), myByHi(myThid)          DO bj = myByLo(myThid), myByHi(myThid)
208  CADJ loop = parallel  CADJ loop = parallel
# Line 96  CADJ loop = parallel Line 217  CADJ loop = parallel
217           ENDDO           ENDDO
218          ENDDO          ENDDO
219          _BARRIER          _BARRIER
220        END IF        ENDIF
   
 C--   Initialize variable data for packages  
       CALL PACKAGES_INIT_VARIABLES( myThid )  
221    
222  #ifdef NONLIN_FRSURF  #ifdef NONLIN_FRSURF
223  C--   Compute the surface level thickness, function of eta_n-1  C--   Compute the surface level thickness <-- function of etaH(n)
224  C     and modify hFac(C,W,S) accordingly :  C     and modify hFac(C,W,S) accordingly :
225          CALL INI_SURF_DR( myThid )
226          CALL INI_R_STAR( myThid )
227    # ifndef DISABLE_RSTAR_CODE
228          IF ( select_rStar.NE.0 )
229         &  CALL CALC_R_STAR(etaH, startTime, -1 , myThid )
230    # endif /* DISABLE_RSTAR_CODE */
231        IF (nonlinFreeSurf.GT.0) THEN        IF (nonlinFreeSurf.GT.0) THEN
232          CALL CALC_SURF_DR(etaNm1, startTime, nIter0, myThid )         IF ( select_rStar.GT.0 ) THEN
233    # ifndef DISABLE_RSTAR_CODE
234            CALL UPDATE_R_STAR( startTime, nIter0, myThid )
235    # endif /* DISABLE_RSTAR_CODE */
236           ELSE
237            CALL CALC_SURF_DR(etaH, startTime, -1 , myThid )
238          CALL UPDATE_SURF_DR( startTime, nIter0, myThid )          CALL UPDATE_SURF_DR( startTime, nIter0, myThid )
239           ENDIF
240        ENDIF        ENDIF
241  C-    update also CG2D matrix (and preconditioner)  C-    update also CG2D matrix (and preconditioner)
242        IF ( nonlinFreeSurf.GT.2) THEN        IF ( nonlinFreeSurf.GT.2) THEN
243          CALL UPDATE_CG2D( startTime, nIter0, myThid )          CALL UPDATE_CG2D( startTime, nIter0, myThid )
244        ENDIF        ENDIF
245    #endif /* NONLIN_FRSURF */
246    
247    #ifdef ALLOW_DEBUG
248          IF (debugMode) CALL DEBUG_CALL('INTEGR_CONTINUITY',myThid)
249  #endif  #endif
250          DO bj=myByLo(myThid),myByHi(myThid)
251           DO bi=myBxLo(myThid),myBxHi(myThid)
252    
253  C--   Finally summarise the model state  C--   Integrate continuity vertically for vertical velocity
254        CALL STATE_SUMMARY( myThid )          CALL INTEGR_CONTINUITY( bi, bj, uVel, vVel,
255         I                          startTime, nIter0, myThid )
256    
257           ENDDO
258          ENDDO
259    
260    #ifdef EXACT_CONSERV
261          IF ( exactConserv ) THEN
262    #ifdef ALLOW_DEBUG
263            IF (debugMode) CALL DEBUG_CALL('UPDATE_ETAH',myThid)
264    #endif
265    C--   Update etaH(n) :
266             CALL UPDATE_ETAH( startTime, nIter0, myThid )
267          ENDIF
268    #endif /* EXACT_CONSERV */
269    
270    #ifdef NONLIN_FRSURF
271          IF ( select_rStar.NE.0 ) THEN
272    #ifndef ALLOW_AUTODIFF_TAMC
273    C--   r* : compute the future level thickness according to etaH(n+1)
274              CALL CALC_R_STAR(etaH, startTime, nIter0, myThid )
275    #endif
276          ELSEIF ( nonlinFreeSurf.GT.0) THEN
277    C--   compute the future surface level thickness according to etaH(n+1)
278              CALL CALC_SURF_DR(etaH, startTime, nIter0, myThid )
279          ENDIF
280    #endif /* NONLIN_FRSURF */
281    
282    c     IF ( nIter0.EQ.0 .AND. staggerTimeStep ) THEN
283    C--    Filter initial T & S fields if staggerTimeStep
284    C       (only for backward compatibility ; to be removed later)
285    #ifdef ALLOW_SHAP_FILT
286    c      IF ( useSHAP_FILT .AND. shap_filt_TrStagg ) THEN
287    c       CALL SHAP_FILT_APPLY_TS(theta,salt,startTime,nIter0,myThid)
288    c      ENDIF
289    #endif
290    #ifdef ALLOW_ZONAL_FILT
291    c      IF ( useZONAL_FILT .AND. zonal_filt_TrStagg ) THEN
292    c       CALL ZONAL_FILT_APPLY_TS( theta, salt, myThid )
293    c      ENDIF
294    #endif
295    c     ENDIF
296    
297  #ifdef ALLOW_TIMEAVE  #ifdef ALLOW_TIMEAVE
298    #ifdef ALLOW_DEBUG
299          IF (debugMode) CALL DEBUG_CALL('TIMEAVE_STATVARS',myThid)
300    #endif
301          DO bj=myByLo(myThid),myByHi(myThid)
302           DO bi=myBxLo(myThid),myBxHi(myThid)
303    
304  C--   initialise time-average arrays with initial state values  C--   initialise time-average arrays with initial state values
305        IF (taveFreq.GT.0.) THEN          IF (taveFreq.GT.0.) THEN
         DO bj=myByLo(myThid),myByHi(myThid)  
          DO bi=myBxLo(myThid),myBxHi(myThid)  
306             CALL TIMEAVE_STATVARS(startTime, nIter0, bi, bj, myThid)             CALL TIMEAVE_STATVARS(startTime, nIter0, bi, bj, myThid)
307           ENDDO          ENDIF
308          ENDDO  
309        ENDIF  #ifdef ALLOW_PTRACERS
310            IF ( usePTRACERS ) THEN
311    #ifdef ALLOW_DEBUG
312              IF (debugMode) CALL DEBUG_CALL('PTRACERS_STATVARS',myThid)
313    #endif
314               CALL PTRACERS_STATVARS(startTime, nIter0, bi, bj, myThid)
315            ENDIF
316    #endif /* ALLOW_PTRACERS */
317    
318    C--   end bi,bj loop.
319           ENDDO
320          ENDDO
321  #endif /* ALLOW_TIMEAVE */  #endif /* ALLOW_TIMEAVE */
322    
323  #ifdef EXACT_CONSERV  #ifdef ALLOW_GRIDALT
324        IF (exactConserv) THEN          if (useGRIDALT) then
325  C--   Compute the initial Barotropic Flow Divergence :           CALL TIMER_START('GRIDALT_UPDATE  [INITIALISE_VARIA]',mythid)
326          DO bj=myByLo(myThid),myByHi(myThid)           CALL GRIDALT_UPDATE(myThid)
327           DO bi=myBxLo(myThid),myBxHi(myThid)           CALL TIMER_STOP ('GRIDALT_UPDATE  [INITIALISE_VARIA]',mythid)
328             CALL CALC_EXACT_ETA( bi,bj, uVel,vVel,          endif
329       I                          startTime, nIter0, myThid )  #endif
330           ENDDO  
331          ENDDO  C--   Fill in overlap regions for wVel :
332        ENDIF        _EXCH_XYZ_R8(wVel,myThid)
333  #endif /* EXACT_CONSERV */  
334          C--   Finally summarise the model state
335    #ifdef ALLOW_DEBUG
336          IF (debugMode) CALL DEBUG_CALL('STATE_SUMMARY',myThid)
337    #endif
338          CALL STATE_SUMMARY( myThid )
339    
340    #ifdef ALLOW_DEBUG
341          IF (debugMode) CALL DEBUG_LEAVE('INITIALISE_VARIA',myThid)
342    #endif
343    
344    C--   Check barrier synchronization:
345          CALL BAR_CHECK( 4, myThid )
346    
347        RETURN        RETURN
348        END        END

Legend:
Removed from v.1.17  
changed lines
  Added in v.1.51

  ViewVC Help
Powered by ViewVC 1.1.22