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

Contents of /MITgcm_contrib/ksnow/press_release/code/adjust_ghat_press_release.F

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


Revision 1.3 - (show 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.2: +2 -7 lines
further changes

1 C $Header: /u/gcmpack/MITgcm_contrib/ksnow/press_release/code/adjust_ghat_press_release.F,v 1.2 2017/02/05 19:08:18 dgoldberg Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5 #ifdef ALLOW_PRESSURE_RELEASE_CODE
6 # include "SHELFICE_OPTIONS.h"
7 #endif
8
9
10 CBOP
11 C !ROUTINE: CALC_DIV_GHAT
12 C !INTERFACE:
13 SUBROUTINE ADJUST_GHAT_PRESS_RELEASE(
14 U cg2d_b,bi,bj,
15 I myThid)
16 C !DESCRIPTION: \bv
17 C *==========================================================*
18 C | S/R CALC_DIV_GHAT
19 C | o Form the right hand-side of the surface pressure eqn.
20 C *==========================================================*
21 C | Right hand side of pressure equation is divergence
22 C | of veclocity tendency (GHAT) term along with a relaxation
23 C | term equal to the barotropic flow field divergence.
24 C *==========================================================*
25 C \ev
26
27 C !USES:
28 IMPLICIT NONE
29 C == Global variables ==
30 #include "SIZE.h"
31 #include "EEPARAMS.h"
32 #include "PARAMS.h"
33 #include "GRID.h"
34 #include "DYNVARS.h"
35 #include "SURFACE.h"
36 #ifdef ALLOW_ADDFLUID
37 # include "FFIELDS.h"
38 #endif
39 #ifdef ALLOW_PRESSURE_RELEASE_CODE
40 # include "SHELFICE.h"
41 #endif
42
43 C !INPUT/OUTPUT PARAMETERS:
44 C == Routine arguments ==
45 C bi, bj :: tile indices
46 C k :: Index of layer.
47 C cg2d_b :: Conjugate Gradient 2-D solver : Right-hand side vector
48 C cg3d_b :: Conjugate Gradient 3-D solver : Right-hand side vector
49 C myThid :: Instance number for this call of CALC_DIV_GHAT
50 INTEGER bi,bj
51 _RL cg2d_b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
52 INTEGER myThid
53
54 C !LOCAL VARIABLES:
55 C == Local variables ==
56 C i,j :: Loop counters
57 C xA, yA :: Cell vertical face areas
58 C pf :: Intermediate array for building RHS source term.
59 INTEGER i,j, k, km1
60 _RL pf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61 #ifdef ALLOW_PRESSURE_RELEASE_CODE
62 _RL curPrelVisc, avgGrd
63 _RL depth, eff_depth, pinit, phiLow, phiLowM1
64 #endif
65 CEOP
66
67 #ifdef ALLOW_PRESSURE_RELEASE_CODE
68 #ifndef ALLOW_NONHYDROSTATIC
69
70 IF (implicDiv2Dflow.EQ.1) THEN
71
72 C Calculate vertical face areas
73 ! xA(i,j) = _dyG(i,j,bi,bj)*depthColW(i,j,bi,bj)*rhoFacC(k)
74 ! yA(i,j) = _dxG(i,j,bi,bj)*depthColS(i,j,bi,bj)*rhoFacC(k)
75
76 C-- Pressure equation source term
77 C Term is the vertical integral of the divergence of the
78 C time tendency terms along with a relaxation term that
79 C pulls div(U) + dh/dt back toward zero.
80
81 _EXCH_XY_RL (phi0surf,mythid)
82
83 DO j=1,sNy+1
84 DO i=1,sNx+1
85 pf(i,j)=0.0
86 ENDDO
87 ENDDO
88 DO j=1,sNy
89 DO i=1,sNx+1
90 IF (maskInC(i,j,bi,bj)*maskInC(i-1,j,bi,bj).eq.1.) THEN
91 ! pf(i,j) = xA(i,j)*gU(i,j,k,bi,bj) / deltaTMom
92 depth = depthColW(i,j,bi,bj)
93 IF (depth.lt.cg2dminColumnEps) THEN
94
95 phiLow = phiHydLowC (i,j,bi,bj)
96 phiLowM1 = phiHydLowC (i-1,j,bi,bj)
97
98 avgGrd = min (grdFactor(i,j,bi,bj),grdFactor(i-1,j,bi,bj))
99 curPrelVisc = max((0.55+avgGrd*0.45),0. _d 0)*pReleaseVisc
100
101 eff_depth = cg2dminColumnEps -
102 & 2. * cg2dminColumnEps / PI *
103 & COS (PI * depth / (2.*cg2dminColumnEps))
104
105 pinit = -1. * curPrelVisc *
106 & _recip_dxC(i,j,bi,bj) * _dyG(i,j,bi,bj)
107 & *(phi0surf(i,j,bi,bj)-phi0surf(i-1,j,bi,bj)+
108 & phiLow-phiLowM1)
109 & /deltaTmom
110
111
112
113 ! pinit = -1. * pReleaseVisc *
114 ! & _recip_dxC(i,j,bi,bj) * _dyG(i,j,bi,bj)
115 ! & *(phiLow-phiLowM1)
116 ! & /deltaTmom
117
118 pf(i,j) = pinit * (eff_depth - depth)
119
120 ENDIF
121 ENDIF
122 ENDDO
123 ENDDO
124 DO j=1,sNy
125 DO i=1,sNx
126 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
127 & pf(i+1,j)-pf(i,j)
128 ENDDO
129 ENDDO
130
131 ! call write_fld_xy_rl('cg2db_1a','',cg2d_b,0,mythid)
132
133 DO j=1,sNy+1
134 DO i=1,sNx+1
135 pf(i,j)=0.0
136 ENDDO
137 ENDDO
138
139 DO j=1,sNy+1
140 DO i=1,sNx
141 IF (maskInC(i,j,bi,bj)*maskInC(i,j-1,bi,bj).eq.1.) THEN
142 ! pf(i,j) = xA(i,j)*gU(i,j,k,bi,bj) / deltaTMom
143 depth = depthColS(i,j,bi,bj)
144 IF (depth.lt.cg2dminColumnEps) THEN
145
146 phiLow = phiHydLowC (i,j,bi,bj)
147 phiLowM1 = phiHydLowC (i,j-1,bi,bj)
148
149 avgGrd = min (grdFactor(i,j,bi,bj),grdFactor(i,j-1,bi,bj))
150 curPrelVisc = max((0.55+avgGrd*0.45),0. _d 0)*pReleaseVisc
151
152 eff_depth = cg2dminColumnEps -
153 & 2. * cg2dminColumnEps / PI *
154 & COS (PI * depth / (2.*cg2dminColumnEps))
155
156 pinit = -1. * curPrelVisc *
157 & _recip_dyC(i,j,bi,bj) * _dxG(i,j,bi,bj)
158 & *(phi0surf(i,j,bi,bj)-phi0surf(i,j-1,bi,bj)+
159 & phiLow-phiLowM1)
160 & /deltaTmom
161
162
163 pf(i,j) = pinit * (eff_depth - depth)
164
165
166 ENDIF
167 ENDIF
168 ENDDO
169 ENDDO
170 DO j=1,sNy
171 DO i=1,sNx
172 cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj) +
173 & pf(i,j+1)-pf(i,j)
174 ENDDO
175 ENDDO
176
177 ENDIF
178
179 #endif
180 #endif
181
182 RETURN
183 END

  ViewVC Help
Powered by ViewVC 1.1.22