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

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

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


Revision 1.10 - (show annotations) (download)
Mon Jun 25 20:38:15 2001 UTC (22 years, 11 months ago) by ljmc
Branch: MAIN
CVS Tags: checkpoint40pre1
Changes since 1.9: +3 -3 lines
the default is now to call the filter after solve_for_pressure

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

  ViewVC Help
Powered by ViewVC 1.1.22