1 |
czaja |
1.1 |
C $Header: /u/u0/gcmpack/models/MITgcmUV/model/src/the_correction_step.F,v 1.15 2001/09/27 20:12:10 heimbach Exp $ |
2 |
|
|
C Tag $Name: release1_beta1 $ |
3 |
|
|
|
4 |
|
|
#include "CPP_OPTIONS.h" |
5 |
|
|
|
6 |
|
|
CBOP |
7 |
|
|
C !ROUTINE: THE_CORRECTION_STEP |
8 |
|
|
C !INTERFACE: |
9 |
|
|
SUBROUTINE THE_CORRECTION_STEP(myTime, myIter, myThid) |
10 |
|
|
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 |
|
|
IMPLICIT NONE |
41 |
|
|
C == Global variables === |
42 |
|
|
#include "SIZE.h" |
43 |
|
|
#include "EEPARAMS.h" |
44 |
|
|
#include "PARAMS.h" |
45 |
|
|
#include "DYNVARS.h" |
46 |
|
|
#ifdef ALLOW_PASSIVE_TRACER |
47 |
|
|
#include "TR1.h" |
48 |
|
|
#endif |
49 |
|
|
#ifdef ALLOW_AUTODIFF_TAMC |
50 |
|
|
#include "tamc.h" |
51 |
|
|
#include "tamc_keys.h" |
52 |
|
|
#endif /* ALLOW_AUTODIFF_TAMC */ |
53 |
|
|
|
54 |
|
|
#ifdef ALLOW_SHAP_FILT |
55 |
|
|
#include "SHAP_FILT.h" |
56 |
|
|
#endif |
57 |
|
|
|
58 |
|
|
|
59 |
|
|
C !INPUT/OUTPUT PARAMETERS: |
60 |
|
|
C == Routine arguments == |
61 |
|
|
C myTime - Current time in simulation |
62 |
|
|
C myIter - Current iteration number in simulation |
63 |
|
|
C myThid - Thread number for this instance of the routine. |
64 |
|
|
_RL myTime |
65 |
|
|
INTEGER myIter |
66 |
|
|
INTEGER myThid |
67 |
|
|
|
68 |
|
|
C !LOCAL VARIABLES: |
69 |
|
|
C == Local variables |
70 |
|
|
_RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
71 |
|
|
_RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
72 |
|
|
INTEGER iMin,iMax |
73 |
|
|
INTEGER jMin,jMax |
74 |
|
|
INTEGER bi,bj |
75 |
|
|
INTEGER k,i,j |
76 |
|
|
|
77 |
|
|
CEOP |
78 |
|
|
|
79 |
|
|
DO bj=myByLo(myThid),myByHi(myThid) |
80 |
|
|
DO bi=myBxLo(myThid),myBxHi(myThid) |
81 |
|
|
|
82 |
|
|
#ifdef ALLOW_AUTODIFF_TAMC |
83 |
|
|
act1 = bi - myBxLo(myThid) |
84 |
|
|
max1 = myBxHi(myThid) - myBxLo(myThid) + 1 |
85 |
|
|
act2 = bj - myByLo(myThid) |
86 |
|
|
max2 = myByHi(myThid) - myByLo(myThid) + 1 |
87 |
|
|
act3 = myThid - 1 |
88 |
|
|
max3 = nTx*nTy |
89 |
|
|
act4 = ikey_dynamics - 1 |
90 |
|
|
ikey = (act1 + 1) + act2*max1 |
91 |
|
|
& + act3*max1*max2 |
92 |
|
|
& + act4*max1*max2*max3 |
93 |
|
|
#endif /* ALLOW_AUTODIFF_TAMC */ |
94 |
|
|
|
95 |
|
|
C-- Set up work arrays that need valid initial values |
96 |
|
|
DO j=1-OLy,sNy+OLy |
97 |
|
|
DO i=1-OLx,sNx+OLx |
98 |
|
|
phiSurfX(i,j)=0. |
99 |
|
|
phiSurfY(i,j)=0. |
100 |
|
|
ENDDO |
101 |
|
|
ENDDO |
102 |
|
|
|
103 |
|
|
C Loop range: Gradients of Eta are evaluated so valid |
104 |
|
|
C range is all but first row and column in overlaps. |
105 |
|
|
iMin = 1-OLx+1 |
106 |
|
|
iMax = sNx+OLx |
107 |
|
|
jMin = 1-OLy+1 |
108 |
|
|
jMax = sNy+OLy |
109 |
|
|
|
110 |
|
|
C- Calculate gradient of surface Potentiel |
111 |
|
|
CALL CALC_GRAD_PHI_SURF( |
112 |
|
|
I bi,bj,iMin,iMax,jMin,jMax, |
113 |
|
|
I etaN, |
114 |
|
|
O phiSurfX,phiSurfY, |
115 |
|
|
I myThid ) |
116 |
|
|
|
117 |
|
|
C-- Loop over all layers, top to bottom |
118 |
|
|
DO K=1,Nr |
119 |
|
|
|
120 |
|
|
#ifdef ALLOW_AUTODIFF_TAMC |
121 |
|
|
kkey = (ikey-1)*Nr + k |
122 |
|
|
#endif |
123 |
|
|
|
124 |
|
|
C- Update velocity fields: V(n) = V** - dt * grad Eta |
125 |
|
|
IF (momStepping) |
126 |
|
|
& CALL CORRECTION_STEP( |
127 |
|
|
I bi,bj,iMin,iMax,jMin,jMax,K, |
128 |
|
|
I phiSurfX,phiSurfY,myTime,myThid ) |
129 |
|
|
|
130 |
|
|
C- Update tracer fields: T(n) = T**, Gt(n-1) = Gt(n) |
131 |
|
|
IF (tempStepping) |
132 |
|
|
& CALL CYCLE_TRACER( |
133 |
|
|
I bi,bj,iMin,iMax,jMin,jMax,K, |
134 |
|
|
U theta,gT,gTNm1, |
135 |
|
|
I myTime,myThid ) |
136 |
|
|
IF (saltStepping) |
137 |
|
|
& CALL CYCLE_TRACER( |
138 |
|
|
I bi,bj,iMin,iMax,jMin,jMax,K, |
139 |
|
|
U salt,gS,gSNm1, |
140 |
|
|
I myTime,myThid ) |
141 |
|
|
#ifdef ALLOW_PASSIVE_TRACER |
142 |
|
|
IF (tr1Stepping) |
143 |
|
|
& CALL CYCLE_TRACER( |
144 |
|
|
I bi,bj,iMin,iMax,jMin,jMax,K, |
145 |
|
|
U Tr1,gTr1,gTr1Nm1, |
146 |
|
|
I myTime,myThid ) |
147 |
|
|
#endif |
148 |
|
|
|
149 |
|
|
#ifdef ALLOW_OBCS |
150 |
|
|
#ifdef ALLOW_AUTODIFF_TAMC |
151 |
|
|
CADJ STORE uvel (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte |
152 |
|
|
CADJ STORE vvel (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte |
153 |
|
|
CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte |
154 |
|
|
CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte |
155 |
|
|
#ifdef ALLOW_PASSIVE_TRACER |
156 |
|
|
CADJ STORE tr1 (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte |
157 |
|
|
#endif |
158 |
|
|
#endif /* ALLOW_AUTODIFF_TAMC */ |
159 |
|
|
IF (useOBCS) THEN |
160 |
|
|
CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid) |
161 |
|
|
ENDIF |
162 |
|
|
#endif /* ALLOW_OBCS */ |
163 |
|
|
|
164 |
|
|
C-- End DO K=1,Nr |
165 |
|
|
ENDDO |
166 |
|
|
|
167 |
|
|
C-- End of 1rst bi,bj loop |
168 |
|
|
ENDDO |
169 |
|
|
ENDDO |
170 |
|
|
|
171 |
|
|
C--- 2nd Part : Adjustment. |
172 |
|
|
C |
173 |
|
|
C Static stability is calculated and the tracers are |
174 |
|
|
C convective adjusted where statically unstable. |
175 |
|
|
|
176 |
|
|
|
177 |
|
|
C modif omp: shapiro filter before elliptic solver --> comment out here |
178 |
|
|
#ifdef ALLOW_SHAP_FILT |
179 |
|
|
IF (useSHAP_FILT) THEN |
180 |
|
|
IF ( .NOT.shap_filt_uvStar ) |
181 |
|
|
& CALL SHAP_FILT_APPLY_UV( uVel, vVel, myTime, myIter, myThid ) |
182 |
|
|
|
183 |
|
|
IF ( .NOT.(staggerTimeStep .AND. shap_filt_TrStagg) ) |
184 |
|
|
& CALL SHAP_FILT_APPLY_TS( theta,salt, myTime, myIter, myThid ) |
185 |
|
|
ENDIF |
186 |
|
|
#endif |
187 |
|
|
|
188 |
|
|
|
189 |
|
|
C modif omp: zonal filter before elliptic solver --> comment out here |
190 |
|
|
C#ifdef ALLOW_ZONAL_FILT |
191 |
|
|
C IF (zonal_filt_lat.LT.90.) THEN |
192 |
|
|
C CALL ZONAL_FILT_APPLY( |
193 |
|
|
C U uVel, vVel, theta, salt, |
194 |
|
|
C I myThid ) |
195 |
|
|
C write(*,*) 'Zonally filtered' |
196 |
|
|
C ENDIF |
197 |
|
|
C#endif |
198 |
|
|
|
199 |
|
|
DO bj=myByLo(myThid),myByHi(myThid) |
200 |
|
|
DO bi=myBxLo(myThid),myBxHi(myThid) |
201 |
|
|
|
202 |
|
|
C-- Convectively adjust new fields to be statically stable |
203 |
|
|
iMin = 1-OLx+1 |
204 |
|
|
iMax = sNx+OLx |
205 |
|
|
jMin = 1-OLy+1 |
206 |
|
|
jMax = sNy+OLy |
207 |
|
|
CALL CONVECTIVE_ADJUSTMENT( |
208 |
|
|
I bi, bj, iMin, iMax, jMin, jMax, |
209 |
|
|
I myTime, myIter, myThid ) |
210 |
|
|
|
211 |
|
|
#ifdef EXACT_CONSERV |
212 |
|
|
IF (exactConserv) THEN |
213 |
|
|
C-- Compute again "eta" to satisfy exactly the total Volume Conservation : |
214 |
|
|
CALL CALC_EXACT_ETA( .TRUE., bi,bj, uVel,vVel, |
215 |
|
|
I myTime, myIter, myThid ) |
216 |
|
|
ENDIF |
217 |
|
|
#endif /* EXACT_CONSERV */ |
218 |
|
|
|
219 |
|
|
#ifdef ALLOW_TIMEAVE |
220 |
|
|
IF (taveFreq.GT.0.) THEN |
221 |
|
|
CALL TIMEAVE_STATVARS(myTime, myIter, bi, bj, myThid) |
222 |
|
|
ENDIF |
223 |
|
|
#endif /* ALLOW_TIMEAVE */ |
224 |
|
|
|
225 |
|
|
C-- End of 2nd bi,bj loop |
226 |
|
|
ENDDO |
227 |
|
|
ENDDO |
228 |
|
|
|
229 |
|
|
#ifdef EXACT_CONSERV |
230 |
|
|
IF (exactConserv .AND. implicDiv2Dflow .NE. 0. _d 0) |
231 |
|
|
& _EXCH_XY_R8(etaN, myThid ) |
232 |
|
|
#endif /* EXACT_CONSERV */ |
233 |
|
|
|
234 |
|
|
RETURN |
235 |
|
|
END |
236 |
|
|
|
237 |
|
|
|