/[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.12 - (hide annotations) (download)
Tue Mar 14 17:47:26 2000 UTC (24 years, 2 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint25, checkpoint27, checkpoint26
Changes since 1.11: +142 -11 lines
Various updates for OBCs and Non-hydrostatic routines.
 o OBCs now fits into time-stepping properly
 o div.G has been moved to solve_for_pressure()

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

  ViewVC Help
Powered by ViewVC 1.1.22