/[MITgcm]/MITgcm_contrib/ksnow/press_release/code/integr_continuity.F
ViewVC logotype

Contents of /MITgcm_contrib/ksnow/press_release/code/integr_continuity.F

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


Revision 1.1 - (show annotations) (download)
Fri Dec 16 15:23:18 2016 UTC (8 years, 7 months ago) by ksnow
Branch: MAIN
Adding press_release core code files
C: ----------------------------------------------------------------------

1 C $Header: /u/gcmpack/MITgcm/model/src/integr_continuity.F,v 1.28 2011/12/22 19:00:58 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: INTEGR_CONTINUITY
9 C !INTERFACE:
10 SUBROUTINE INTEGR_CONTINUITY(
11 I uFld, vFld,
12 I myTime, myIter, myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | SUBROUTINE INTEGR_CONTINUITY
16 C | o Integrate the continuity Eq : compute vertical velocity
17 C | and free surface "r-anomaly" (etaN,etaH) to satisfy
18 C | exactly the conservation of the Total Volume
19 C *==========================================================*
20 C \ev
21
22 C !USES:
23 IMPLICIT NONE
24 C == Global variables
25 #include "SIZE.h"
26 #include "EEPARAMS.h"
27 #include "PARAMS.h"
28 #include "DYNVARS.h"
29 #include "GRID.h"
30 #include "SURFACE.h"
31 #include "FFIELDS.h"
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C == Routine arguments ==
35 C uFld :: Zonal velocity ( m/s )
36 C vFld :: Meridional velocity ( m/s )
37 C myTime :: Current time in simulation
38 C myIter :: Current iteration number in simulation
39 C myThid :: my Thread Id. number
40 _RL myTime
41 INTEGER myIter
42 INTEGER myThid
43 _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
44 _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
45 _RL depth, depth_fac
46
47 C !LOCAL VARIABLES:
48 C Local variables in common block
49
50 C Local variables
51 C bi,bj :: tile index
52 C i,j,k :: Loop counters
53 C uTrans :: Volume transports ( uVel.xA )
54 C vTrans :: Volume transports ( vVel.yA )
55 C hDivFlow :: Div. Barotropic Flow [transport unit m3/s]
56 INTEGER k,bi,bj
57 #ifdef EXACT_CONSERV
58 INTEGER i, j
59 INTEGER ks
60 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62 _RL hDivFlow(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63 _RL facEmP, facMass
64 #else /* EXACT_CONSERV */
65 # ifdef ALLOW_OBCS
66 INTEGER i, j
67 # endif
68 #endif /* EXACT_CONSERV */
69 #ifndef ALLOW_ADDFLUID
70 _RL addMass(1)
71 #endif /* ndef ALLOW_ADDFLUID */
72 #if (defined NONLIN_FRSURF) && !(defined DISABLE_RSTAR_CODE)
73 _RL rStarDhDt(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74 #else
75 _RL rStarDhDt(1)
76 #endif
77 CEOP
78
79 C-- Start bi,bj loops
80 DO bj=myByLo(myThid),myByHi(myThid)
81 DO bi=myBxLo(myThid),myBxHi(myThid)
82
83 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
84
85 #ifdef EXACT_CONSERV
86 IF (exactConserv) THEN
87
88 facEmP = 0.
89 IF ( fluidIsWater.AND.useRealFreshWaterFlux ) facEmP=mass2rUnit
90 facMass = 0.
91 IF ( selectAddFluid.GE.1 ) facMass = mass2rUnit
92
93 C-- Compute the Divergence of The Barotropic Flow :
94
95 C- Initialise
96 DO j=1-OLy,sNy+OLy
97 DO i=1-OLx,sNx+OLx
98 hDivFlow(i,j) = 0. _d 0
99 utrans(i,j) = 0. _d 0
100 vtrans(i,j) = 0. _d 0
101 ENDDO
102 ENDDO
103
104 DO k=1,Nr
105
106 C- Calculate velocity field "volume transports" through tracer cell faces
107 C anelastic: uTrans,vTrans are scaled by rhoFacC (~ mass transport).
108 DO j=1,sNy+1
109 DO i=1,sNx+1
110
111 uTrans(i,j) = uFld(i,j,k,bi,bj)*_dyG(i,j,bi,bj)
112 & *deepFacC(k)*rhoFacC(k)
113 & *drF(k)*_hFacW(i,j,k,bi,bj)
114
115 vTrans(i,j) = vFld(i,j,k,bi,bj)*_dxG(i,j,bi,bj)
116 & *deepFacC(k)*rhoFacC(k)
117 & *drF(k)*_hFacS(i,j,k,bi,bj)
118
119 ENDDO
120 ENDDO
121
122 C- Integrate vertically the Horizontal Divergence
123 DO j=1,sNy
124 DO i=1,sNx
125 hDivFlow(i,j) = hDivFlow(i,j)
126 & +maskC(i,j,k,bi,bj)*( uTrans(i+1,j)-uTrans(i,j)
127 & +vTrans(i,j+1)-vTrans(i,j) )
128 #ifdef ALLOW_ADDFLUID
129 & -facMass*addMass(i,j,k,bi,bj)
130 #endif /* ALLOW_ADDFLUID */
131 ENDDO
132 ENDDO
133
134 C- End DO k=1,Nr
135 ENDDO
136
137
138
139 #ifdef ALLOW_PRESSURE_RELEASE_CODE
140 DO j=1,sNy
141 DO i=1,sNx
142 hDivFlow(i,j) = hDivFlow(i,j)
143 & +maskinC(i,j,bi,bj)*_dyG(i,j,bi,bj)*
144 & (pReleaseTransX(i+1,j,bi,bj)-pReleaseTransX(i,j,bi,bj))
145 hDivFlow(i,j) = hDivFlow(i,j)
146 & +maskinC(i,j,bi,bj)*_dxG(i,j,bi,bj)*
147 & (pReleaseTransY(i,j+1,bi,bj)-pReleaseTransY(i,j,bi,bj))
148 ENDDO
149 ENDDO
150 #endif
151
152
153 C------------------------------------
154 C note: deep-model not implemented for P-coordinate + realFreshWaterFlux ;
155 C anelastic: always assumes that rhoFacF(1) = 1
156 IF ( myIter.EQ.nIter0 .AND. myIter.NE.0
157 & .AND. fluidIsWater .AND. useRealFreshWaterFlux ) THEN
158
159 C needs previous time-step value of E-P-R, that has not been loaded
160 C and was not in old pickup-file ; try to use etaN & etaH instead.
161 IF ( usePickupBeforeC54 ) THEN
162 DO j=1,sNy
163 DO i=1,sNx
164 dEtaHdt(i,j,bi,bj) = (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
165 & / (implicDiv2Dflow*deltaTfreesurf)
166 ENDDO
167 ENDDO
168 ENDIF
169
170 DO j=1,sNy
171 DO i=1,sNx
172 PmEpR(i,j,bi,bj) = dEtaHdt(i,j,bi,bj)
173 & + hDivFlow(i,j)*recip_rA(i,j,bi,bj)
174 & *recip_deepFac2F(1)
175 PmEpR(i,j,bi,bj) = PmEpR(i,j,bi,bj)*rUnit2mass
176 ENDDO
177 ENDDO
178 ELSEIF ( myIter.EQ.nIter0 ) THEN
179 DO j=1,sNy
180 DO i=1,sNx
181 ks = kSurfC(I,J,bi,bj)
182 PmEpR(i,j,bi,bj) = 0. _d 0
183 dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
184 & *recip_deepFac2F(ks)
185 ENDDO
186 ENDDO
187 ELSE
188 C-- Needs to get valid PmEpR (for T,S forcing) also in overlap regions
189 C (e.g., if using KPP) => set over full index range
190 DO j=1-OLy,sNy+OLy
191 DO i=1-OLx,sNx+OLx
192 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
193 ENDDO
194 ENDDO
195 DO j=1,sNy
196 DO i=1,sNx
197 ks = kSurfC(i,j,bi,bj)
198 dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
199 & *recip_deepFac2F(ks)
200 & -facEmP*EmPmR(i,j,bi,bj)
201 ENDDO
202 ENDDO
203 ENDIF
204 C------------------------------------
205
206 #ifdef ALLOW_OBCS
207 C-- reset dEtaHdt to zero outside the OB interior region
208 IF ( useOBCS ) THEN
209 DO j=1,sNy
210 DO i=1,sNx
211 dEtaHdt(i,j,bi,bj) = dEtaHdt(i,j,bi,bj)*maskInC(i,j,bi,bj)
212 ENDDO
213 ENDDO
214 ENDIF
215 #endif /* ALLOW_OBCS */
216
217 C-- end if exactConserv block
218 ENDIF
219
220 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
221
222 IF ( exactConserv .AND. myIter.NE.nIter0 ) THEN
223 C-- Update etaN at the end of the time step :
224 C Incorporate the Implicit part of -Divergence(Barotropic_Flow)
225
226 IF (implicDiv2Dflow.EQ. 0. _d 0) THEN
227 DO j=1-OLy,sNy+OLy
228 DO i=1-OLx,sNx+OLx
229 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
230 ENDDO
231 ENDDO
232 ELSE
233 DO j=1,sNy
234 DO i=1,sNx
235 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
236 & + implicDiv2Dflow*dEtaHdt(i,j,bi,bj)*deltaTfreesurf
237 ENDDO
238 ENDDO
239 ENDIF
240
241 #ifdef ALLOW_OBCS
242 C-- Was added on Dec 30, 2004 (to fix unrealistic etaN ?), but no longer
243 C needed with proper masking in solver (matrix+cg2d_b,x) and masking
244 C of dEtaHdt above. etaN next to OB does not enter present algorithm but
245 C leave it commented out in case we would implement an aternative scheme.
246 c IF ( useOBCS ) CALL OBCS_APPLY_ETA( bi, bj, etaN, myThid )
247 #endif /* ALLOW_OBCS */
248
249 C-- end if exactConserv and not myIter=nIter0 block
250 ENDIF
251
252 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
253
254 # ifdef NONLIN_FRSURF
255 IF (select_rStar .NE. 0) THEN
256 # ifndef DISABLE_RSTAR_CODE
257 C-- note: rStarDhDt is similar to rStarDhCDt from S/R CALC_R_STAR
258 C except for deep-factor and rho factor.
259 DO j=1,sNy
260 DO i=1,sNx
261 ks = kSurfC(i,j,bi,bj)
262 rStarDhDt(i,j) = dEtaHdt(i,j,bi,bj)
263 & *deepFac2F(ks)*rhoFacF(ks)
264 & *recip_Rcol(i,j,bi,bj)
265 ENDDO
266 ENDDO
267 # endif /* DISABLE_RSTAR_CODE */
268 ENDIF
269 # endif /* NONLIN_FRSURF */
270
271 #endif /* EXACT_CONSERV */
272
273 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
274
275 DO k=Nr,1,-1
276 C-- Integrate continuity vertically for vertical velocity
277
278 CALL INTEGRATE_FOR_W(
279 I bi, bj, k, uFld, vFld,
280 I addMass, rStarDhDt,
281 O wVel,
282 I myThid )
283
284 #ifdef EXACT_CONSERV
285 IF ( k.EQ.Nr .AND. myIter.NE.0 .AND. usingPCoords
286 & .AND. fluidIsWater .AND. useRealFreshWaterFlux ) THEN
287
288 DO j=1,sNy
289 DO i=1,sNx
290 wVel(i,j,k,bi,bj) = wVel(i,j,k,bi,bj)
291 & +mass2rUnit*PmEpR(i,j,bi,bj)*maskC(i,j,k,bi,bj)
292 ENDDO
293 ENDDO
294
295 ENDIF
296 #endif /* EXACT_CONSERV */
297
298 #ifdef ALLOW_OBCS
299 C-- reset W to zero outside the OB interior region
300 IF ( useOBCS ) THEN
301 DO j=1,sNy
302 DO i=1,sNx
303 wVel(i,j,k,bi,bj) = wVel(i,j,k,bi,bj)*maskInC(i,j,bi,bj)
304 ENDDO
305 ENDDO
306 ENDIF
307 C-- Apply OBC to W (non-hydrostatic):
308 IF ( useOBCS.AND.nonHydrostatic )
309 & CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )
310 #endif /* ALLOW_OBCS */
311
312 C- End DO k=Nr,1,-1
313 ENDDO
314
315 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
316
317 C-- End bi,bj loops
318 ENDDO
319 ENDDO
320
321 IF ( exactConserv .AND. myIter.NE.nIter0
322 & .AND. implicDiv2Dflow .NE. 0. _d 0 )
323 & _EXCH_XY_RL( etaN , myThid )
324 IF ( implicitIntGravWave .OR. myIter.EQ.nIter0 )
325 & _EXCH_XYZ_RL( wVel , myThid )
326
327 #ifdef EXACT_CONSERV
328 C-- Update etaH (from etaN and dEtaHdt):
329 IF (exactConserv) THEN
330 c IF ( useRealFreshWaterFlux .AND. myIter.EQ.nIter0 )
331 c & _EXCH_XY_RL( PmEpR, myThid )
332 #ifdef ALLOW_DEBUG
333 IF (debugMode) CALL DEBUG_CALL('UPDATE_ETAH',myThid)
334 #endif
335 CALL UPDATE_ETAH( myTime, myIter, myThid )
336 ENDIF
337
338 #ifdef NONLIN_FRSURF
339 # ifndef DISABLE_SIGMA_CODE
340 IF ( nonlinFreeSurf.GT.0 .AND. selectSigmaCoord.NE.0 ) THEN
341 CALL EXCH_XY_RL( dEtaHdt, myThid )
342 CALL UPDATE_ETAWS( myTime, myIter, myThid )
343 ENDIF
344 # endif /* DISABLE_SIGMA_CODE */
345 #endif /* NONLIN_FRSURF */
346
347 #endif /* EXACT_CONSERV */
348
349 RETURN
350 END

  ViewVC Help
Powered by ViewVC 1.1.22