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

Annotation of /MITgcm_contrib/ksnow/press_release/code/calc_div_ghat.F

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


Revision 1.4 - (hide annotations) (download)
Sat Mar 4 11:57:16 2017 UTC (8 years, 9 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +5 -5 lines
further changes

1 dgoldberg 1.4 C $Header: /u/gcmpack/MITgcm_contrib/ksnow/press_release/code/calc_div_ghat.F,v 1.3 2017/02/04 18:55:11 dgoldberg Exp $
2 ksnow 1.1 C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: CALC_DIV_GHAT
8     C !INTERFACE:
9     SUBROUTINE CALC_DIV_GHAT(
10     I bi,bj,k,
11     U cg2d_b, cg3d_b,
12     I myThid)
13     C !DESCRIPTION: \bv
14     C *==========================================================*
15     C | S/R CALC_DIV_GHAT
16     C | o Form the right hand-side of the surface pressure eqn.
17     C *==========================================================*
18     C | Right hand side of pressure equation is divergence
19     C | of veclocity tendency (GHAT) term along with a relaxation
20     C | term equal to the barotropic flow field divergence.
21     C *==========================================================*
22     C \ev
23    
24     C !USES:
25     IMPLICIT NONE
26     C == Global variables ==
27     #include "SIZE.h"
28     #include "EEPARAMS.h"
29     #include "PARAMS.h"
30     #include "GRID.h"
31     #include "DYNVARS.h"
32     #ifdef ALLOW_ADDFLUID
33     # include "FFIELDS.h"
34     #endif
35    
36     C !INPUT/OUTPUT PARAMETERS:
37     C == Routine arguments ==
38     C bi, bj :: tile indices
39     C k :: Index of layer.
40     C cg2d_b :: Conjugate Gradient 2-D solver : Right-hand side vector
41     C cg3d_b :: Conjugate Gradient 3-D solver : Right-hand side vector
42     C myThid :: Instance number for this call of CALC_DIV_GHAT
43     INTEGER bi,bj
44     INTEGER k
45     _RL cg2d_b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
46     #ifdef ALLOW_NONHYDROSTATIC
47     _RL cg3d_b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
48     #else
49     _RL cg3d_b(1)
50     #endif
51     INTEGER myThid
52 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
53     _RL drag_fac
54     #endif
55 ksnow 1.1
56     C !LOCAL VARIABLES:
57     C == Local variables ==
58     C i,j :: Loop counters
59     C xA, yA :: Cell vertical face areas
60     C pf :: Intermediate array for building RHS source term.
61     INTEGER i,j
62     _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63     _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64     _RL pf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65     CEOP
66    
67     C Calculate vertical face areas
68     DO j=1,sNy+1
69     DO i=1,sNx+1
70     xA(i,j) = _dyG(i,j,bi,bj)*deepFacC(k)
71     & *drF(k)*_hFacW(i,j,k,bi,bj)*rhoFacC(k)
72     yA(i,j) = _dxG(i,j,bi,bj)*deepFacC(k)
73     & *drF(k)*_hFacS(i,j,k,bi,bj)*rhoFacC(k)
74     ENDDO
75     ENDDO
76    
77     C-- Pressure equation source term
78     C Term is the vertical integral of the divergence of the
79     C time tendency terms along with a relaxation term that
80     C pulls div(U) + dh/dt back toward zero.
81    
82     IF (implicDiv2Dflow.EQ.1.) THEN
83     C Fully Implicit treatment of the Barotropic Flow Divergence
84     DO j=1,sNy
85     DO i=1,sNx+1
86 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
87     IF (depthColW(i,j,bi,bj).lt.cg2dminColumnEps) THEN
88     drag_fac = _recip_hFacW(i,j,k,bi,bj)**2*recip_drF(k)**2*
89 dgoldberg 1.4 & pReleaseDamp * viscArNr(k) *
90 ksnow 1.2 & 1./(1+exp(-10./cg2dminColumnEps*
91     & (-1.)*(depthColW(i,j,bi,bj)-cg2dminColumnEps/2)))
92     ELSE
93     drag_fac = 0. _d 0
94     ENDIF
95     #endif
96 ksnow 1.1 pf(i,j) = xA(i,j)*gU(i,j,k,bi,bj) / deltaTMom
97 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
98     & / (1 + drag_fac*deltaTmom)
99 ksnow 1.1 #endif
100 ksnow 1.2
101 ksnow 1.1 ENDDO
102     ENDDO
103     ELSEIF (exactConserv) THEN
104     c ELSEIF (nonlinFreeSurf.GT.0) THEN
105     C Implicit treatment of the Barotropic Flow Divergence
106     DO j=1,sNy
107     DO i=1,sNx+1
108 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
109     IF (depthColW(i,j,bi,bj).lt.cg2dminColumnEps) THEN
110     drag_fac = _recip_hFacW(i,j,k,bi,bj)**2*recip_drF(k)**2*
111 dgoldberg 1.4 & pReleaseDamp * viscArNr(k) *
112 ksnow 1.2 & 1./(1+exp(-10./cg2dminColumnEps*
113     & (-1.)*(depthColW(i,j,bi,bj)-cg2dminColumnEps/2)))
114     ELSE
115     drag_fac = 0. _d 0
116     ENDIF
117     #endif
118 ksnow 1.1 pf(i,j) = implicDiv2Dflow
119     & *xA(i,j)*gU(i,j,k,bi,bj) / deltaTMom
120 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
121     & / (1 + drag_fac*deltaTmom)
122 ksnow 1.1 #endif
123 ksnow 1.2
124 ksnow 1.1 ENDDO
125     ENDDO
126     ELSE
127     C Explicit+Implicit part of the Barotropic Flow Divergence
128     C => Filtering of uVel,vVel is necessary
129     C-- Now the filter are applied in the_correction_step().
130     C We have left this code here to indicate where the filters used to be
131     C in the algorithm before JMC moved them to after the pressure solver.
132     c#ifdef ALLOW_ZONAL_FILT
133     c IF (zonal_filt_lat.LT.90.) THEN
134     c CALL ZONAL_FILTER(
135     c U uVel( 1-OLx,1-OLy,k,bi,bj),
136     c I hFacW(1-OLx,1-OLy,k,bi,bj),
137     c I 0, sNy+1, 1, bi, bj, 1, myThid )
138     c CALL ZONAL_FILTER(
139     c U vVel( 1-OLx,1-OLy,k,bi,bj),
140     c I hFacS(1-OLx,1-OLy,k,bi,bj),
141     c I 0, sNy+1, 1, bi, bj, 2, myThid )
142     c ENDIF
143     c#endif
144     DO j=1,sNy
145     DO i=1,sNx+1
146     pf(i,j) = ( implicDiv2Dflow * gU(i,j,k,bi,bj)
147     & + (1. _d 0-implicDiv2Dflow)* uVel(i,j,k,bi,bj)
148     & ) * xA(i,j) / deltaTMom
149     ENDDO
150     ENDDO
151     ENDIF
152     DO j=1,sNy
153     DO i=1,sNx
154     cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
155     & pf(i+1,j)-pf(i,j)
156     ENDDO
157     ENDDO
158    
159     #ifdef ALLOW_NONHYDROSTATIC
160     IF (use3Dsolver) THEN
161     DO j=1,sNy
162     DO i=1,sNx
163     cg3d_b(i,j,k,bi,bj) = ( pf(i+1,j)-pf(i,j) )
164     ENDDO
165     ENDDO
166     ENDIF
167     #endif
168    
169     IF (implicDiv2Dflow.EQ.1.) THEN
170     C Fully Implicit treatment of the Barotropic Flow Divergence
171     DO j=1,sNy+1
172     DO i=1,sNx
173 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
174     IF (depthColS(i,j,bi,bj).lt.cg2dminColumnEps) THEN
175     drag_fac = _recip_hFacS(i,j,k,bi,bj)**2*recip_drF(k)**2*
176 dgoldberg 1.4 & pReleaseDamp * viscArNr(k) *
177 ksnow 1.2 & 1./(1+exp(-10./cg2dminColumnEps*
178     & (-1.)*(depthColS(i,j,bi,bj)-cg2dminColumnEps/2)))
179     ELSE
180     drag_fac = 0. _d 0
181     ENDIF
182     #endif
183 ksnow 1.1 pf(i,j) = yA(i,j)*gV(i,j,k,bi,bj) / deltatmom
184 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
185     & / (1 + drag_fac*deltaTmom)
186 ksnow 1.1 #endif
187     ENDDO
188     ENDDO
189     ELSEIF (exactConserv) THEN
190     c ELSEIF (nonlinFreeSurf.GT.0) THEN
191     C Implicit treatment of the Barotropic Flow Divergence
192     DO j=1,sNy+1
193     DO i=1,sNx
194 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
195     IF (depthColS(i,j,bi,bj).lt.cg2dminColumnEps) THEN
196     drag_fac = _recip_hFacS(i,j,k,bi,bj)**2*recip_drF(k)**2*
197 dgoldberg 1.4 & pReleaseDamp * viscArNr(k) *
198 ksnow 1.2 & 1./(1+exp(-10./cg2dminColumnEps*
199     & (-1.)*(depthColS(i,j,bi,bj)-cg2dminColumnEps/2)))
200     ELSE
201     drag_fac = 0. _d 0
202     ENDIF
203     #endif
204 ksnow 1.1 pf(i,j) = implicDiv2Dflow
205     & *yA(i,j)*gV(i,j,k,bi,bj) / deltatmom
206 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
207     & / (1 + drag_fac*deltaTmom)
208 ksnow 1.1 #endif
209     ENDDO
210     ENDDO
211     ELSE
212     C Explicit+Implicit part of the Barotropic Flow Divergence
213     DO j=1,sNy+1
214     DO i=1,sNx
215     pf(i,j) = ( implicDiv2Dflow * gV(i,j,k,bi,bj)
216     & + (1. _d 0-implicDiv2Dflow)* vVel(i,j,k,bi,bj)
217     & ) * yA(i,j) / deltaTMom
218     ENDDO
219     ENDDO
220     ENDIF
221     DO j=1,sNy
222     DO i=1,sNx
223     cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
224     & pf(i,j+1)-pf(i,j)
225     ENDDO
226     ENDDO
227    
228     #ifdef ALLOW_NONHYDROSTATIC
229     IF (use3Dsolver) THEN
230     DO j=1,sNy
231     DO i=1,sNx
232     cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
233     & + ( pf(i,j+1)-pf(i,j) )
234     ENDDO
235     ENDDO
236     ENDIF
237     #endif
238    
239     #ifdef ALLOW_ADDFLUID
240     IF ( selectAddFluid.GE.1 ) THEN
241     DO j=1,sNy
242     DO i=1,sNx
243     cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
244     & - addMass(i,j,k,bi,bj)*mass2rUnit/deltaTMom
245     ENDDO
246     ENDDO
247     #ifdef ALLOW_NONHYDROSTATIC
248     IF (use3Dsolver) THEN
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     & - addMass(i,j,k,bi,bj)*mass2rUnit/deltaTMom
253     ENDDO
254     ENDDO
255     ENDIF
256     #endif
257     ENDIF
258     #endif /* ALLOW_ADDFLUID */
259    
260     RETURN
261     END

  ViewVC Help
Powered by ViewVC 1.1.22