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

Annotation of /MITgcm/model/src/the_correction_step.F

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


Revision 1.17 - (hide annotations) (download)
Fri Feb 8 22:06:52 2002 UTC (22 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: chkpt44d_post, checkpoint44e_pre, chkpt44c_post, checkpoint44e_post, release1_final_v1, checkpoint44f_pre
Branch point for: release1_final
Changes since 1.16: +1 -32 lines
remove some store directives

1 jmc 1.17 C $Header: /u/gcmpack/MITgcm/model/src/the_correction_step.F,v 1.16 2001/12/11 14:58:46 jmc Exp $
2 jmc 1.13 C Tag $Name: $
3 adcroft 1.2
4     #include "CPP_OPTIONS.h"
5    
6 cnh 1.14 CBOP
7     C !ROUTINE: THE_CORRECTION_STEP
8     C !INTERFACE:
9 adcroft 1.2 SUBROUTINE THE_CORRECTION_STEP(myTime, myIter, myThid)
10 cnh 1.14 C !DESCRIPTION: \bv
11     C *==========================================================*
12     C | SUBROUTINE THE_CORRECTION_STEP
13     C *==========================================================*
14     C |1rst Part : Update U,V,T,S.
15     C |
16     C | The arrays used for time stepping are cycled.
17     C | Tracers:
18     C | T(n) = Gt(n-1)
19     C | Gt(n-1) = Gt(n)
20     C | Momentum:
21     C | V(n) = Gv(n-1) - dt * grad Eta
22     C | Gv(n-1) = Gv(n)
23     C |
24     C |part1: update U,V,T,S
25     C | U*,V* (contained in gUnm1,gVnm1) have the surface
26     C | pressure gradient term added and the result stored
27     C | in U,V (contained in uVel, vVel)
28     C | T* (contained in gTnm1) is copied to T (theta)
29     C | S* (contained in gSnm1) is copied to S (salt)
30     C |
31     C |part2: Adjustments.
32     C | o Filter U,V,T,S (Shapiro Filter, Zonal_Filter)
33     C | o Convective Adjustment
34     C | o Compute again Eta (exact volume conservation)
35     C | o Diagmnostic of state variables (Time average)
36     C *==========================================================*
37     C \ev
38    
39     C !USES:
40 adcroft 1.2 IMPLICIT NONE
41     C == Global variables ===
42     #include "SIZE.h"
43     #include "EEPARAMS.h"
44     #include "PARAMS.h"
45     #include "DYNVARS.h"
46 heimbach 1.12 #ifdef ALLOW_PASSIVE_TRACER
47 heimbach 1.11 #include "TR1.h"
48 heimbach 1.12 #endif
49 jmc 1.16
50     #ifdef ALLOW_SHAP_FILT
51     #include "SHAP_FILT.h"
52     #endif
53     #ifdef ALLOW_ZONAL_FILT
54     #include "ZONAL_FILT.h"
55     #endif
56    
57 cnh 1.14 C !INPUT/OUTPUT PARAMETERS:
58 adcroft 1.2 C == Routine arguments ==
59     C myTime - Current time in simulation
60     C myIter - Current iteration number in simulation
61     C myThid - Thread number for this instance of the routine.
62     _RL myTime
63     INTEGER myIter
64     INTEGER myThid
65    
66 cnh 1.14 C !LOCAL VARIABLES:
67 adcroft 1.2 C == Local variables
68 jmc 1.6 _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69     _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70 adcroft 1.2 INTEGER iMin,iMax
71     INTEGER jMin,jMax
72     INTEGER bi,bj
73     INTEGER k,i,j
74    
75 cnh 1.14 CEOP
76 adcroft 1.9
77 adcroft 1.2 DO bj=myByLo(myThid),myByHi(myThid)
78     DO bi=myBxLo(myThid),myBxHi(myThid)
79 heimbach 1.7
80 adcroft 1.2 C-- Set up work arrays that need valid initial values
81     DO j=1-OLy,sNy+OLy
82     DO i=1-OLx,sNx+OLx
83 jmc 1.6 phiSurfX(i,j)=0.
84     phiSurfY(i,j)=0.
85 adcroft 1.2 ENDDO
86     ENDDO
87    
88     C Loop range: Gradients of Eta are evaluated so valid
89     C range is all but first row and column in overlaps.
90     iMin = 1-OLx+1
91     iMax = sNx+OLx
92     jMin = 1-OLy+1
93     jMax = sNy+OLy
94    
95 jmc 1.6 C- Calculate gradient of surface Potentiel
96     CALL CALC_GRAD_PHI_SURF(
97 adcroft 1.2 I bi,bj,iMin,iMax,jMin,jMax,
98 jmc 1.5 I etaN,
99 jmc 1.6 O phiSurfX,phiSurfY,
100 adcroft 1.2 I myThid )
101    
102     C-- Loop over all layers, top to bottom
103     DO K=1,Nr
104    
105     C- Update velocity fields: V(n) = V** - dt * grad Eta
106 adcroft 1.3 IF (momStepping)
107     & CALL CORRECTION_STEP(
108 adcroft 1.2 I bi,bj,iMin,iMax,jMin,jMax,K,
109 jmc 1.6 I phiSurfX,phiSurfY,myTime,myThid )
110 adcroft 1.2
111     C- Update tracer fields: T(n) = T**, Gt(n-1) = Gt(n)
112     IF (tempStepping)
113     & CALL CYCLE_TRACER(
114     I bi,bj,iMin,iMax,jMin,jMax,K,
115     U theta,gT,gTNm1,
116     I myTime,myThid )
117     IF (saltStepping)
118     & CALL CYCLE_TRACER(
119     I bi,bj,iMin,iMax,jMin,jMax,K,
120     U salt,gS,gSNm1,
121 heimbach 1.11 I myTime,myThid )
122 heimbach 1.12 #ifdef ALLOW_PASSIVE_TRACER
123 heimbach 1.11 IF (tr1Stepping)
124     & CALL CYCLE_TRACER(
125     I bi,bj,iMin,iMax,jMin,jMax,K,
126     U Tr1,gTr1,gTr1Nm1,
127 adcroft 1.2 I myTime,myThid )
128 heimbach 1.12 #endif
129 adcroft 1.2
130     #ifdef ALLOW_OBCS
131     IF (useOBCS) THEN
132     CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid)
133     ENDIF
134     #endif /* ALLOW_OBCS */
135    
136     C-- End DO K=1,Nr
137     ENDDO
138    
139 adcroft 1.9 C-- End of 1rst bi,bj loop
140     ENDDO
141     ENDDO
142    
143     C--- 2nd Part : Adjustment.
144     C
145     C Static stability is calculated and the tracers are
146     C convective adjusted where statically unstable.
147    
148 jmc 1.16 C-- Filter (and exchange)
149 adcroft 1.9 #ifdef ALLOW_SHAP_FILT
150     IF (useSHAP_FILT) THEN
151 jmc 1.16 IF ( .NOT.shap_filt_uvStar )
152     & CALL SHAP_FILT_APPLY_UV( uVel, vVel, myTime, myIter, myThid )
153    
154     IF ( .NOT.(staggerTimeStep .AND. shap_filt_TrStagg) )
155     & CALL SHAP_FILT_APPLY_TS( theta,salt, myTime, myIter, myThid )
156 adcroft 1.9 ENDIF
157     #endif
158 jmc 1.16 #ifdef ALLOW_ZONAL_FILT
159     IF (useZONAL_FILT) THEN
160     IF ( .NOT.zonal_filt_uvStar )
161     & CALL ZONAL_FILT_APPLY_UV( uVel, vVel, myThid )
162    
163     IF ( .NOT.(staggerTimeStep .AND. zonal_filt_TrStagg) )
164     & CALL ZONAL_FILT_APPLY_TS( theta, salt, myThid )
165 adcroft 1.9
166     ENDIF
167     #endif
168    
169     DO bj=myByLo(myThid),myByHi(myThid)
170     DO bi=myBxLo(myThid),myBxHi(myThid)
171    
172 adcroft 1.2 C-- Convectively adjust new fields to be statically stable
173 adcroft 1.9 iMin = 1-OLx+1
174     iMax = sNx+OLx
175     jMin = 1-OLy+1
176     jMax = sNy+OLy
177 adcroft 1.2 CALL CONVECTIVE_ADJUSTMENT(
178     I bi, bj, iMin, iMax, jMin, jMax,
179     I myTime, myIter, myThid )
180 jmc 1.4
181 adcroft 1.9 #ifdef EXACT_CONSERV
182     IF (exactConserv) THEN
183     C-- Compute again "eta" to satisfy exactly the total Volume Conservation :
184 jmc 1.13 CALL CALC_EXACT_ETA( .TRUE., bi,bj, uVel,vVel,
185 adcroft 1.9 I myTime, myIter, myThid )
186     ENDIF
187     #endif /* EXACT_CONSERV */
188    
189 jmc 1.5 #ifdef ALLOW_TIMEAVE
190 jmc 1.4 IF (taveFreq.GT.0.) THEN
191 jmc 1.5 CALL TIMEAVE_STATVARS(myTime, myIter, bi, bj, myThid)
192 jmc 1.4 ENDIF
193 jmc 1.5 #endif /* ALLOW_TIMEAVE */
194 adcroft 1.2
195 adcroft 1.9 C-- End of 2nd bi,bj loop
196 adcroft 1.2 ENDDO
197     ENDDO
198 adcroft 1.9
199     #ifdef EXACT_CONSERV
200 jmc 1.13 IF (exactConserv .AND. implicDiv2Dflow .NE. 0. _d 0)
201     & _EXCH_XY_R8(etaN, myThid )
202 adcroft 1.9 #endif /* EXACT_CONSERV */
203 adcroft 1.2
204     RETURN
205     END

  ViewVC Help
Powered by ViewVC 1.1.22