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

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

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


Revision 1.10 - (show annotations) (download)
Thu Dec 30 18:30:54 2004 UTC (19 years, 6 months ago) by adcroft
Branch: MAIN
Changes since 1.9: +4 -1 lines
This fixes the problems with discontinuous SSH near open boundaries. It makes a difference for OBCs with a non-linear freesurface (and z*).

1 C $Header: /u/gcmpack/MITgcm/model/src/integr_continuity.F,v 1.9 2004/10/19 02:39: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 bi, bj, 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) to satisfy
18 C | exactly the convervation 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 bi,bj :: tile index
38 C myTime :: Current time in simulation
39 C myIter :: Current iteration number in simulation
40 C myThid :: Thread number for this instance of the routine.
41 _RL myTime
42 INTEGER myIter
43 INTEGER myThid
44 INTEGER bi,bj
45 LOGICAL UpdateEtaN_EtaH
46 _RL uFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
47 _RL vFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
48
49 C !LOCAL VARIABLES:
50 C Local variables in common block
51
52 C Local variables
53 C i,j,k :: Loop counters
54 C uTrans :: Volume transports ( uVel.xA )
55 C vTrans :: Volume transports ( vVel.yA )
56 C hDivFlow :: Div. Barotropic Flow [transport unit m3/s]
57 INTEGER i,j,k
58 _RL uTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
59 _RL vTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
60 _RL hDivFlow(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
61 _RL wSurf, facEmP
62 CEOP
63
64 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
65
66 #ifdef EXACT_CONSERV
67 IF (exactConserv) THEN
68
69 C-- Compute the Divergence of The Barotropic Flow :
70
71 C- Initialise
72 DO j=1-Oly,sNy+Oly
73 DO i=1-Olx,sNx+Olx
74 hDivFlow(i,j) = 0. _d 0
75 utrans(i,j) = 0. _d 0
76 vtrans(i,j) = 0. _d 0
77 ENDDO
78 ENDDO
79
80 DO k=1,Nr
81
82 C- Calculate velocity field "volume transports" through tracer cell faces
83 DO j=1,sNy+1
84 DO i=1,sNx+1
85 uTrans(i,j) = uFld(i,j,k,bi,bj)*_dyG(i,j,bi,bj)
86 & *drF(k)*_hFacW(i,j,k,bi,bj)
87 vTrans(i,j) = vFld(i,j,k,bi,bj)*_dxG(i,j,bi,bj)
88 & *drF(k)*_hFacS(i,j,k,bi,bj)
89 ENDDO
90 ENDDO
91
92 C- Integrate vertically the Horizontal Divergence
93 DO j=1,sNy
94 DO i=1,sNx
95 hDivFlow(i,j) = hDivFlow(i,j)
96 & +maskC(i,j,k,bi,bj)*( uTrans(i+1,j)-uTrans(i,j)
97 & +vTrans(i,j+1)-vTrans(i,j) )
98 ENDDO
99 ENDDO
100
101 C- End DO k=1,Nr
102 ENDDO
103
104 C------------------------------------
105 facEmP = 0.
106 IF (useRealFreshWaterFlux) facEmP = convertEmP2rUnit
107 IF ( myTime.EQ.startTime .AND. myTime.NE. 0. _d 0
108 & .AND. useRealFreshWaterFlux) THEN
109
110 C needs previous time-step value of E-P-R, that has not been loaded
111 C and was not in old pickup-file ; try to use etaN & etaH instead.
112 IF ( usePickupBeforeC54 ) THEN
113 DO j=1,sNy
114 DO i=1,sNx
115 dEtaHdt(i,j,bi,bj) = (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
116 & / (implicDiv2Dflow*deltaTfreesurf)
117 ENDDO
118 ENDDO
119 ENDIF
120
121 DO j=1,sNy
122 DO i=1,sNx
123 PmEpR(i,j,bi,bj) = dEtaHdt(i,j,bi,bj)
124 & + hDivFlow(i,j)*recip_rA(i,j,bi,bj)
125 PmEpR(i,j,bi,bj) = PmEpR(i,j,bi,bj)/convertEmP2rUnit
126 ENDDO
127 ENDDO
128 ELSEIF ( myTime.EQ.startTime ) THEN
129 DO j=1,sNy
130 DO i=1,sNx
131 PmEpR(i,j,bi,bj) = 0. _d 0
132 dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
133 ENDDO
134 ENDDO
135 ELSE
136 DO j=1,sNy
137 DO i=1,sNx
138 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
139 dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
140 & -facEmP*EmPmR(i,j,bi,bj)
141 ENDDO
142 ENDDO
143 ENDIF
144 C------------------------------------
145
146 ENDIF
147
148 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
149
150 IF (exactConserv .AND. myTime.NE.startTime) THEN
151 C-- Update etaN at the end of the time step :
152 C Incorporate the Implicit part of -Divergence(Barotropic_Flow)
153
154 IF (implicDiv2Dflow.EQ. 0. _d 0) THEN
155 DO j=1-Oly,sNy+Oly
156 DO i=1-Olx,sNx+Olx
157 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
158 ENDDO
159 ENDDO
160 ELSE
161 DO j=1,sNy
162 DO i=1,sNx
163 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
164 & + implicDiv2Dflow*dEtaHdt(i,j,bi,bj)*deltaTfreesurf
165 ENDDO
166 ENDDO
167 ENDIF
168
169 IF ( useOBCS )
170 & CALL OBCS_APPLY_ETA( bi, bj, etaN, myThid )
171
172 ENDIF
173
174 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
175
176 #ifdef NONLIN_FRSURF
177 IF (select_rStar .NE. 0) THEN
178 DO j=1,sNy
179 DO i=1,sNx
180 rStarDhCDt(i,j,bi,bj) =
181 & dEtaHdt(i,j,bi,bj)*recip_Rcol(i,j,bi,bj)
182 ENDDO
183 ENDDO
184 ENDIF
185 #endif /* NONLIN_FRSURF */
186 #endif /* EXACT_CONSERV */
187
188 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
189
190 DO k=Nr,1,-1
191 C-- Integrate continuity vertically for vertical velocity
192
193 CALL INTEGRATE_FOR_W(
194 I bi, bj, k, uFld, vFld,
195 O wVel,
196 I myThid )
197
198 #ifdef EXACT_CONSERV
199 IF ( k.EQ.Nr .AND. myTime.NE. 0. _d 0 .AND.
200 & useRealFreshWaterFlux .AND. usingPCoords ) THEN
201
202 DO j=1,sNy
203 DO i=1,sNx
204 wVel(i,j,k,bi,bj) = wVel(i,j,k,bi,bj)
205 & +convertEmP2rUnit*PmEpR(i,j,bi,bj)*maskC(i,j,k,bi,bj)
206 ENDDO
207 ENDDO
208
209 ENDIF
210 #endif /* EXACT_CONSERV */
211
212 #ifdef ALLOW_OBCS
213 #ifdef ALLOW_NONHYDROSTATIC
214 C-- Apply OBC to W if in N-H mode
215 IF (useOBCS.AND.nonHydrostatic) THEN
216 CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )
217 ENDIF
218 #endif /* ALLOW_NONHYDROSTATIC */
219 #endif /* ALLOW_OBCS */
220
221 C- End DO k=Nr,1,-1
222 ENDDO
223
224 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
225
226 RETURN
227 END

  ViewVC Help
Powered by ViewVC 1.1.22