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

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

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


Revision 1.21 - (hide annotations) (download)
Tue Apr 10 22:35:25 2001 UTC (23 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint38, checkpoint39
Changes since 1.20: +4 -6 lines
See doc/tag-index and doc/notes_c37_adj.txt
Preparation for stand-alone autodifferentiability.

1 heimbach 1.21 C $Header: /u/gcmpack/models/MITgcmUV/model/src/solve_for_pressure.F,v 1.20 2001/03/25 22:33:53 heimbach Exp $
2     C $Name: $
3 cnh 1.1
4 adcroft 1.5 #include "CPP_OPTIONS.h"
5 cnh 1.1
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 adcroft 1.8 IMPLICIT NONE
14 cnh 1.1
15 cnh 1.4 C == Global variables
16     #include "SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #include "DYNVARS.h"
20 adcroft 1.12 #include "GRID.h"
21 jmc 1.17 #include "SURFACE.h"
22 adcroft 1.9 #ifdef ALLOW_NONHYDROSTATIC
23     #include "CG3D.h"
24     #include "GW.h"
25 adcroft 1.12 #endif
26 adcroft 1.11 #ifdef ALLOW_OBCS
27 adcroft 1.9 #include "OBCS.h"
28 adcroft 1.11 #endif
29 cnh 1.4
30 cnh 1.1 C == Routine arguments ==
31     C myThid - Number of this instance of SOLVE_FOR_PRESSURE
32     INTEGER myThid
33     CEndOfInterface
34 cnh 1.4
35     C Local variables
36 jmc 1.17 C cg2d_x - Conjugate Gradient 2-D solver : Solution vector
37     C cg2d_b - Conjugate Gradient 2-D solver : Right-hand side vector
38 cnh 1.6 INTEGER i,j,k,bi,bj
39 adcroft 1.9 _RS uf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
40     _RS vf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
41 jmc 1.17 _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 adcroft 1.19 _RL tolerance,residual
44     INTEGER numIters
45 jmc 1.17
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 jmc 1.18 cg2d_x(i,j,bi,bj) = Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
55 jmc 1.17 cg2d_b(i,j,bi,bj) = 0.
56     #ifdef USE_NATURAL_BCS
57 jmc 1.18 & + freeSurfFac*_rA(i,j,bi,bj)*
58 jmc 1.17 & EmPmR(I,J,bi,bj)/deltaTMom
59     #endif
60     ENDDO
61     ENDDO
62     ENDDO
63     ENDDO
64 adcroft 1.12
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 jmc 1.17 U cg2d_b,
80 adcroft 1.12 I myThid)
81     ENDDO
82     ENDDO
83     ENDDO
84 cnh 1.4
85 adcroft 1.12 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 adcroft 1.13 #ifdef ALLOW_NONHYDROSTATIC
89 adcroft 1.12 DO j=1,sNy
90     DO i=1,sNx
91     cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
92 jmc 1.18 & -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 adcroft 1.13 cg3d_b(i,j,1,bi,bj) = cg3d_b(i,j,1,bi,bj)
96 jmc 1.18 & -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 adcroft 1.12 ENDDO
105     ENDDO
106 adcroft 1.13 #else
107 adcroft 1.12 DO j=1,sNy
108     DO i=1,sNx
109 adcroft 1.13 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
110 jmc 1.18 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTMom
111     & * etaN(i,j,bi,bj)
112 adcroft 1.12 ENDDO
113     ENDDO
114     #endif
115    
116     #ifdef ALLOW_OBCS
117 adcroft 1.14 IF (useOBCS) THEN
118 adcroft 1.12 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 cnh 1.1 C-- Find the surface pressure using a two-dimensional conjugate
145     C-- gradient solver.
146 jmc 1.17 C see CG2D_INTERNAL.h for the interface to this routine.
147 adcroft 1.19 tolerance=cg2dTargetResidual
148     residual=0.
149     numIters=cg2dMaxIters
150 cnh 1.1 CALL CG2D(
151 cnh 1.6 I cg2d_b,
152     U cg2d_x,
153 adcroft 1.19 U tolerance,
154     U residual,
155     U numIters,
156 cnh 1.1 I myThid )
157 adcroft 1.19 _EXCH_XY_R8(cg2d_x, myThid )
158 cnh 1.1
159 adcroft 1.19 _BEGIN_MASTER( myThid )
160 heimbach 1.21 WRITE(*,'(A,I6,1PE30.14)') ' CG2D iters, err = ',
161 adcroft 1.19 & 0, tolerance
162 heimbach 1.21 WRITE(*,'(A,I6,1PE30.14)') ' CG2D iters, err = ',
163 adcroft 1.19 & numIters, residual
164     _END_MASTER( )
165 jmc 1.17
166     C-- Transfert the 2D-solution to "etaN" :
167     DO bj=myByLo(myThid),myByHi(myThid)
168     DO bi=myBxLo(myThid),myBxHi(myThid)
169     DO j=1-OLy,sNy+OLy
170     DO i=1-OLx,sNx+OLx
171 jmc 1.18 etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)*cg2d_x(i,j,bi,bj)
172 jmc 1.17 ENDDO
173     ENDDO
174     ENDDO
175     ENDDO
176 adcroft 1.10
177 adcroft 1.9 #ifdef ALLOW_NONHYDROSTATIC
178     IF ( nonHydrostatic ) THEN
179    
180     C-- Solve for a three-dimensional pressure term (NH or IGW or both ).
181     C see CG3D.h for the interface to this routine.
182     DO bj=myByLo(myThid),myByHi(myThid)
183     DO bi=myBxLo(myThid),myBxHi(myThid)
184     DO j=1,sNy+1
185     DO i=1,sNx+1
186 jmc 1.18 uf(i,j)=-_recip_dxC(i,j,bi,bj)*
187 adcroft 1.9 & (cg2d_x(i,j,bi,bj)-cg2d_x(i-1,j,bi,bj))
188 jmc 1.18 vf(i,j)=-_recip_dyC(i,j,bi,bj)*
189 adcroft 1.9 & (cg2d_x(i,j,bi,bj)-cg2d_x(i,j-1,bi,bj))
190     ENDDO
191     ENDDO
192    
193 adcroft 1.12 #ifdef ALLOW_OBCS
194 adcroft 1.14 IF (useOBCS) THEN
195 adcroft 1.9 DO i=1,sNx+1
196     C Northern boundary
197     IF (OB_Jn(I,bi,bj).NE.0) THEN
198     vf(I,OB_Jn(I,bi,bj))=0.
199     ENDIF
200     C Southern boundary
201     IF (OB_Js(I,bi,bj).NE.0) THEN
202     vf(I,OB_Js(I,bi,bj)+1)=0.
203     ENDIF
204     ENDDO
205     DO j=1,sNy+1
206     C Eastern boundary
207     IF (OB_Ie(J,bi,bj).NE.0) THEN
208     uf(OB_Ie(J,bi,bj),J)=0.
209     ENDIF
210     C Western boundary
211     IF (OB_Iw(J,bi,bj).NE.0) THEN
212     uf(OB_Iw(J,bi,bj)+1,J)=0.
213     ENDIF
214     ENDDO
215     ENDIF
216 adcroft 1.12 #endif
217 adcroft 1.9
218 adcroft 1.12 K=1
219     DO j=1,sNy
220     DO i=1,sNx
221     cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
222     & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
223     & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
224     & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
225     & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
226 jmc 1.18 & +( freeSurfFac*etaN(i,j,bi,bj)/deltaTMom
227     & -wVel(i,j,k+1,bi,bj)
228 adcroft 1.12 & )*_rA(i,j,bi,bj)/deltaTmom
229     ENDDO
230     ENDDO
231     DO K=2,Nr-1
232 adcroft 1.9 DO j=1,sNy
233     DO i=1,sNx
234     cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
235     & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
236     & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
237     & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
238     & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
239 adcroft 1.12 & +( wVel(i,j,k ,bi,bj)
240     & -wVel(i,j,k+1,bi,bj)
241     & )*_rA(i,j,bi,bj)/deltaTmom
242    
243 adcroft 1.9 ENDDO
244     ENDDO
245     ENDDO
246 adcroft 1.12 K=Nr
247     DO j=1,sNy
248     DO i=1,sNx
249     cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
250     & +dRF(K)*dYG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
251     & -dRF(K)*dYG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
252     & +dRF(K)*dXG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
253     & -dRF(K)*dXG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
254     & +( wVel(i,j,k ,bi,bj)
255     & )*_rA(i,j,bi,bj)/deltaTmom
256    
257     ENDDO
258     ENDDO
259    
260     #ifdef ALLOW_OBCS
261 adcroft 1.14 IF (useOBCS) THEN
262 adcroft 1.12 DO K=1,Nr
263     DO i=1,sNx
264     C Northern boundary
265     IF (OB_Jn(I,bi,bj).NE.0) THEN
266     cg3d_b(I,OB_Jn(I,bi,bj),K,bi,bj)=0.
267     ENDIF
268     C Southern boundary
269     IF (OB_Js(I,bi,bj).NE.0) THEN
270     cg3d_b(I,OB_Js(I,bi,bj),K,bi,bj)=0.
271     ENDIF
272     ENDDO
273     DO j=1,sNy
274     C Eastern boundary
275     IF (OB_Ie(J,bi,bj).NE.0) THEN
276     cg3d_b(OB_Ie(J,bi,bj),J,K,bi,bj)=0.
277     ENDIF
278     C Western boundary
279     IF (OB_Iw(J,bi,bj).NE.0) THEN
280     cg3d_b(OB_Iw(J,bi,bj),J,K,bi,bj)=0.
281     ENDIF
282     ENDDO
283     ENDDO
284     ENDIF
285     #endif
286 adcroft 1.9
287     ENDDO ! bi
288     ENDDO ! bj
289    
290     CALL CG3D( myThid )
291 adcroft 1.10 _EXCH_XYZ_R8(cg3d_x, myThid )
292 adcroft 1.9
293     ENDIF
294     #endif
295 cnh 1.1
296     RETURN
297     END

  ViewVC Help
Powered by ViewVC 1.1.22