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

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

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


Revision 1.20 - (show annotations) (download)
Sun Mar 25 22:33:53 2001 UTC (23 years, 2 months ago) by heimbach
Branch: MAIN
CVS Tags: c37_adj
Changes since 1.19: +4 -2 lines
Modifications and additions to enable automatic differentiation.
Detailed info's in doc/notes_c37_adj.txt

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/solve_for_pressure.F,v 1.19 2001/03/09 20:45:09 adcroft Exp $
2 C $Name: checkpoint37 $
3
4 #include "CPP_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE SOLVE_FOR_PRESSURE( myThid )
8 C /==========================================================\
9 C | SUBROUTINE SOLVE_FOR_PRESSURE |
10 C | o Controls inversion of two and/or three-dimensional |
11 C | elliptic problems for the pressure field. |
12 C \==========================================================/
13 IMPLICIT NONE
14
15 C == Global variables
16 #include "SIZE.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "DYNVARS.h"
20 #include "GRID.h"
21 #include "SURFACE.h"
22 #ifdef ALLOW_NONHYDROSTATIC
23 #include "CG3D.h"
24 #include "GW.h"
25 #endif
26 #ifdef ALLOW_OBCS
27 #include "OBCS.h"
28 #endif
29
30 C == Routine arguments ==
31 C myThid - Number of this instance of SOLVE_FOR_PRESSURE
32 INTEGER myThid
33 CEndOfInterface
34
35 C Local variables
36 C cg2d_x - Conjugate Gradient 2-D solver : Solution vector
37 C cg2d_b - Conjugate Gradient 2-D solver : Right-hand side vector
38 INTEGER i,j,k,bi,bj
39 _RS uf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
40 _RS vf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
41 _RL cg2d_x(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
42 _RL cg2d_b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
43 _RL tolerance,residual
44 INTEGER numIters
45
46 C-- Save previous solution & Initialise Vector solution and source term :
47 DO bj=myByLo(myThid),myByHi(myThid)
48 DO bi=myBxLo(myThid),myBxHi(myThid)
49 DO j=1-OLy,sNy+OLy
50 DO i=1-OLx,sNx+OLx
51 #ifdef INCLUDE_CD_CODE
52 etaNm1(i,j,bi,bj) = etaN(i,j,bi,bj)
53 #endif
54 cg2d_x(i,j,bi,bj) = Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
55 cg2d_b(i,j,bi,bj) = 0.
56 #ifdef USE_NATURAL_BCS
57 & + freeSurfFac*_rA(i,j,bi,bj)*
58 & EmPmR(I,J,bi,bj)/deltaTMom
59 #endif
60 ENDDO
61 ENDDO
62 ENDDO
63 ENDDO
64
65 DO bj=myByLo(myThid),myByHi(myThid)
66 DO bi=myBxLo(myThid),myBxHi(myThid)
67 DO K=Nr,1,-1
68 DO j=1,sNy+1
69 DO i=1,sNx+1
70 uf(i,j) = _dyG(i,j,bi,bj)
71 & *drF(k)*_hFacW(i,j,k,bi,bj)
72 vf(i,j) = _dxG(i,j,bi,bj)
73 & *drF(k)*_hFacS(i,j,k,bi,bj)
74 ENDDO
75 ENDDO
76 CALL CALC_DIV_GHAT(
77 I bi,bj,1,sNx,1,sNy,K,
78 I uf,vf,
79 U cg2d_b,
80 I myThid)
81 ENDDO
82 ENDDO
83 ENDDO
84
85 C-- Add source term arising from w=d/dt (p_s + p_nh)
86 DO bj=myByLo(myThid),myByHi(myThid)
87 DO bi=myBxLo(myThid),myBxHi(myThid)
88 #ifdef ALLOW_NONHYDROSTATIC
89 DO j=1,sNy
90 DO i=1,sNx
91 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
92 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTMom
93 & *( etaN(i,j,bi,bj)
94 & +cg3d_x(i,j,1,bi,bj)*horiVertRatio/gravity )
95 cg3d_b(i,j,1,bi,bj) = cg3d_b(i,j,1,bi,bj)
96 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTMom
97 & *( etaN(i,j,bi,bj)
98 & +cg3d_x(i,j,1,bi,bj)*horiVertRatio/gravity )
99 C-jmc
100 c & -freeSurfFac*_rA(i,j,bi,bj)*recip_Bo(i,j,bi,bj)
101 c & *( cg2d_x(i,j,bi,bj) + cg3d_x(i,j,1,bi,bj) )
102 c & /deltaTMom/deltaTMom
103 C-jmc
104 ENDDO
105 ENDDO
106 #else
107 DO j=1,sNy
108 DO i=1,sNx
109 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
110 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTMom
111 & * etaN(i,j,bi,bj)
112 ENDDO
113 ENDDO
114 #endif
115
116 #ifdef ALLOW_OBCS
117 IF (useOBCS) THEN
118 DO i=1,sNx
119 C Northern boundary
120 IF (OB_Jn(I,bi,bj).NE.0) THEN
121 cg2d_b(I,OB_Jn(I,bi,bj),bi,bj)=0.
122 ENDIF
123 C Southern boundary
124 IF (OB_Js(I,bi,bj).NE.0) THEN
125 cg2d_b(I,OB_Js(I,bi,bj),bi,bj)=0.
126 ENDIF
127 ENDDO
128 DO j=1,sNy
129 C Eastern boundary
130 IF (OB_Ie(J,bi,bj).NE.0) THEN
131 cg2d_b(OB_Ie(J,bi,bj),J,bi,bj)=0.
132 ENDIF
133 C Western boundary
134 IF (OB_Iw(J,bi,bj).NE.0) THEN
135 cg2d_b(OB_Iw(J,bi,bj),J,bi,bj)=0.
136 ENDIF
137 ENDDO
138 ENDIF
139 #endif
140 ENDDO
141 ENDDO
142
143
144 C-- Find the surface pressure using a two-dimensional conjugate
145 C-- gradient solver.
146 C see CG2D_INTERNAL.h for the interface to this routine.
147 tolerance=cg2dTargetResidual
148 residual=0.
149 numIters=cg2dMaxIters
150 CALL CG2D(
151 I cg2d_b,
152 U cg2d_x,
153 U tolerance,
154 U residual,
155 U numIters,
156 I myThid )
157 _EXCH_XY_R8(cg2d_x, myThid )
158
159 _BEGIN_MASTER( myThid )
160 #ifndef ALLOW_AUTODIFF_TAMC
161 WRITE(0,'(A,I6,1PE30.14)') ' CG2D iters, err = ',
162 & 0, tolerance
163 WRITE(0,'(A,I6,1PE30.14)') ' CG2D iters, err = ',
164 & numIters, residual
165 #endif
166 _END_MASTER( )
167
168 C-- Transfert the 2D-solution to "etaN" :
169 DO bj=myByLo(myThid),myByHi(myThid)
170 DO bi=myBxLo(myThid),myBxHi(myThid)
171 DO j=1-OLy,sNy+OLy
172 DO i=1-OLx,sNx+OLx
173 etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)*cg2d_x(i,j,bi,bj)
174 ENDDO
175 ENDDO
176 ENDDO
177 ENDDO
178
179 #ifdef ALLOW_NONHYDROSTATIC
180 IF ( nonHydrostatic ) THEN
181
182 C-- Solve for a three-dimensional pressure term (NH or IGW or both ).
183 C see CG3D.h for the interface to this routine.
184 DO bj=myByLo(myThid),myByHi(myThid)
185 DO bi=myBxLo(myThid),myBxHi(myThid)
186 DO j=1,sNy+1
187 DO i=1,sNx+1
188 uf(i,j)=-_recip_dxC(i,j,bi,bj)*
189 & (cg2d_x(i,j,bi,bj)-cg2d_x(i-1,j,bi,bj))
190 vf(i,j)=-_recip_dyC(i,j,bi,bj)*
191 & (cg2d_x(i,j,bi,bj)-cg2d_x(i,j-1,bi,bj))
192 ENDDO
193 ENDDO
194
195 #ifdef ALLOW_OBCS
196 IF (useOBCS) THEN
197 DO i=1,sNx+1
198 C Northern boundary
199 IF (OB_Jn(I,bi,bj).NE.0) THEN
200 vf(I,OB_Jn(I,bi,bj))=0.
201 ENDIF
202 C Southern boundary
203 IF (OB_Js(I,bi,bj).NE.0) THEN
204 vf(I,OB_Js(I,bi,bj)+1)=0.
205 ENDIF
206 ENDDO
207 DO j=1,sNy+1
208 C Eastern boundary
209 IF (OB_Ie(J,bi,bj).NE.0) THEN
210 uf(OB_Ie(J,bi,bj),J)=0.
211 ENDIF
212 C Western boundary
213 IF (OB_Iw(J,bi,bj).NE.0) THEN
214 uf(OB_Iw(J,bi,bj)+1,J)=0.
215 ENDIF
216 ENDDO
217 ENDIF
218 #endif
219
220 K=1
221 DO j=1,sNy
222 DO i=1,sNx
223 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
224 & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
225 & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
226 & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
227 & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
228 & +( freeSurfFac*etaN(i,j,bi,bj)/deltaTMom
229 & -wVel(i,j,k+1,bi,bj)
230 & )*_rA(i,j,bi,bj)/deltaTmom
231 ENDDO
232 ENDDO
233 DO K=2,Nr-1
234 DO j=1,sNy
235 DO i=1,sNx
236 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
237 & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
238 & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
239 & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
240 & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
241 & +( wVel(i,j,k ,bi,bj)
242 & -wVel(i,j,k+1,bi,bj)
243 & )*_rA(i,j,bi,bj)/deltaTmom
244
245 ENDDO
246 ENDDO
247 ENDDO
248 K=Nr
249 DO j=1,sNy
250 DO i=1,sNx
251 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
252 & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
253 & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
254 & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
255 & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
256 & +( wVel(i,j,k ,bi,bj)
257 & )*_rA(i,j,bi,bj)/deltaTmom
258
259 ENDDO
260 ENDDO
261
262 #ifdef ALLOW_OBCS
263 IF (useOBCS) THEN
264 DO K=1,Nr
265 DO i=1,sNx
266 C Northern boundary
267 IF (OB_Jn(I,bi,bj).NE.0) THEN
268 cg3d_b(I,OB_Jn(I,bi,bj),K,bi,bj)=0.
269 ENDIF
270 C Southern boundary
271 IF (OB_Js(I,bi,bj).NE.0) THEN
272 cg3d_b(I,OB_Js(I,bi,bj),K,bi,bj)=0.
273 ENDIF
274 ENDDO
275 DO j=1,sNy
276 C Eastern boundary
277 IF (OB_Ie(J,bi,bj).NE.0) THEN
278 cg3d_b(OB_Ie(J,bi,bj),J,K,bi,bj)=0.
279 ENDIF
280 C Western boundary
281 IF (OB_Iw(J,bi,bj).NE.0) THEN
282 cg3d_b(OB_Iw(J,bi,bj),J,K,bi,bj)=0.
283 ENDIF
284 ENDDO
285 ENDDO
286 ENDIF
287 #endif
288
289 ENDDO ! bi
290 ENDDO ! bj
291
292 CALL CG3D( myThid )
293 _EXCH_XYZ_R8(cg3d_x, myThid )
294
295 ENDIF
296 #endif
297
298 RETURN
299 END

  ViewVC Help
Powered by ViewVC 1.1.22