/[MITgcm]/MITgcm/pkg/gmredi/gmredi_calc_psi_bvp.F
ViewVC logotype

Contents of /MITgcm/pkg/gmredi/gmredi_calc_psi_bvp.F

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


Revision 1.2 - (show annotations) (download)
Thu Feb 10 23:22:28 2011 UTC (13 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62s, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.1: +25 -14 lines
- use partial cell factor in tridiagonal matrix coeff.
- use 2-D map & 1-D profile scaling factor with GM_background_K

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_calc_psi_bvp.F,v 1.1 2011/02/10 21:24:19 jmc Exp $
2 C $Name: $
3
4 #include "GMREDI_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: GMREDI_CALC_PSI_BVP
8 C !INTERFACE:
9 SUBROUTINE GMREDI_CALC_PSI_BVP(
10 I bi, bj, iMin, iMax, jMin, jMax,
11 I sigmaX, sigmaY, sigmaR,
12 I myThid )
13
14 C !DESCRIPTION: \bv
15 C *==========================================================*
16 C | SUBROUTINE GMREDI_CALC_PSI_BVP
17 C | o Calculate stream-functions for GM bolus velocity using
18 C | the BVP in Ferrari et al. (OM, 2010)
19 C *==========================================================*
20 C \ev
21
22 C !USES:
23 IMPLICIT NONE
24
25 C == Global variables ==
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "GRID.h"
30 #include "GMREDI.h"
31
32 C !INPUT/OUTPUT PARAMETERS:
33 C bi,bj :: Tile indices
34 C iMin,iMax :: computation domain 1rst index bounds
35 C jMin,jMax :: computation domain 2nd index bounds
36 C sigmaX :: Zonal gradient of density
37 C sigmaY :: Meridional gradient of density
38 C sigmaR :: Vertical gradient of Pot.density (locally referenced)
39 C myThid :: My Thread Id number
40 INTEGER bi,bj,iMin,iMax,jMin,jMax
41 _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
42 _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
43 _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
44 INTEGER myThid
45 CEOP
46
47 #ifdef ALLOW_GMREDI
48 #ifdef GM_BOLUS_BVP
49
50 C !LOCAL VARIABLES:
51 INTEGER i,j,k, km1
52 INTEGER errCode
53 _RL half_K
54 _RL sigmaX_W
55 _RL sigmaY_W
56 _RL dSigmaDrW
57 _RL dSigmaDrS
58 _RL wkb_cW(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
59 _RL wkb_cS(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
60 _RL rPI, c2
61 #ifdef ALLOW_DIAGNOSTICS
62 _RL tmpFac
63 #endif
64 CHARACTER*(MAX_LEN_MBUF) msgBuf
65
66 PARAMETER ( rPI = 0.318309886183791 _d 0 )
67
68 C- Matrix elements for tri-diagonal solver
69 _RL GM_a3d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
70 _RL GM_b3d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
71 _RL GM_c3d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
72
73 C- Initialization : <= done in S/R gmredi_init
74 IF (GM_UseBVP) THEN
75
76 C Initialize the WKB wave speeds to zero
77 C We use c = int_{-H}^0 N dz/(GM_BVP_ModeNumber*PI) and have absorbed
78 C a factor of g/rhoConst
79 DO j=1-Oly,sNy+Oly
80 DO i=1-Olx,sNx+Olx
81 wkb_cW(i,j) = 0. _d 0
82 wkb_cS(i,j) = 0. _d 0
83 ENDDO
84 ENDDO
85
86 C Surface BC : set to zero
87 DO j=1-Oly,sNy+Oly
88 DO i=1-Olx,sNx+Olx
89 GM_a3d(i,j,1) = 0. _d 0
90 GM_b3d(i,j,1) = 1. _d 0
91 GM_c3d(i,j,1) = 0. _d 0
92 GM_PsiX(i,j,1,bi,bj) = 0. _d 0
93 GM_PsiY(i,j,1,bi,bj) = 0. _d 0
94 ENDDO
95 ENDDO
96
97 DO k=2,Nr
98 km1 = k-1
99 half_K = GM_background_K
100 & *(GM_bolFac1d(km1)+GM_bolFac1d(k))*op25
101 C Gradient of Sigma below U and V points
102 DO j=1-Oly,sNy+Oly
103 DO i=1-Olx+1,sNx+Olx
104 sigmaX_W = op5*( sigmaX(i,j,km1)+sigmaX(i,j,k) )
105 & *maskW(i,j,k,bi,bj)
106 dSigmaDrW = op5*( sigmaR(i-1,j,k)+sigmaR(i,j,k) )
107 & *maskW(i,j,k,bi,bj)
108
109 wkb_cW(i,j) = wkb_cW(i,j)
110 & + SQRT(MAX( -dSigmaDrW, 0. _d 0 ))
111 & *drC(k)*GM_BVP_rModeNumber*rPI
112
113 C Part of main diagonal coming from zeroth order derivative
114 GM_b3d(i,j,k) = MAX( -dSigmaDrW, GM_Small_Number )
115
116 C This is initially the RHS
117 GM_PsiX(i,j,k,bi,bj) = half_K*sigmaX_W
118 & *(GM_bolFac2d(i-1,j,bi,bj)+GM_bolFac2d(i,j,bi,bj))
119 ENDDO
120 ENDDO
121 ENDDO
122
123 C Note: Use Dirichlet BC @ Surface & Bottom (whereas we use Neumann BC for
124 C implicit diffusion/advection Pb).
125 C Surface BC implementation: => keep non zero coeff @ k=2
126 C and set Psi=1 with Identity coeff @ k=1
127 C Same for bottom, except if kBottom=Nr (solver only process k=1:Nr)
128 C should substract c3d(k=Nr)*Psi(k=Nr+1) to RHS @ k=Nr ;
129 C However in our case this term is zero since Psi(k=Nr+1)=0
130 DO k=2,Nr
131 km1 = k-1
132 DO j=1-Oly,sNy+Oly
133 DO i=1-Olx+1,sNx+Olx
134 IF ( maskW(i,j,k,bi,bj).EQ.0. ) THEN
135 C- at Bottom and below, use identity matrix
136 GM_a3d(i,j,k) = 0. _d 0
137 GM_b3d(i,j,k) = 1. _d 0
138 GM_c3d(i,j,k) = 0. _d 0
139 ELSE
140 c2 = MAX( wkb_cW(i,j)*wkb_cW(i,j), GM_BVP_cHat2Min )
141 GM_a3d(i,j,k) = -c2*recip_drC(k)
142 & *recip_drF(km1)*recip_hFacW(i,j,km1,bi,bj)
143 GM_b3d(i,j,k) = GM_b3d(i,j,k)
144 & + c2*recip_drC(k)
145 & *(recip_drF(km1)*recip_hFacW(i,j,km1,bi,bj)
146 & +recip_drF(k)*recip_hFacW(i,j,k,bi,bj) )
147 GM_c3d(i,j,k) = -c2*recip_drC(k)
148 & *recip_drF(k)*recip_hFacW(i,j,k,bi,bj)
149 ENDIF
150 ENDDO
151 ENDDO
152 ENDDO
153
154 CALL SOLVE_TRIDIAGONAL( iMin+1,iMax,jMin,jMax,
155 & GM_a3d,GM_b3d,GM_c3d,
156 & GM_PsiX,
157 & errCode,bi,bj,myThid)
158
159 IF ( errCode .GT. 0 ) THEN
160 WRITE(msgBuf,'(A)')
161 & 'S/R GMREDI_CALC_PSI_BVP: matrix singular for PsiX'
162 CALL PRINT_ERROR( msgBuf, myThid )
163 STOP 'ABNORMAL END: S/R GMREDI_CALC_PSI_BVP'
164 ENDIF
165
166 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
167
168 DO k=2,Nr
169 km1 = k-1
170 half_K = GM_background_K
171 & *(GM_bolFac1d(km1)+GM_bolFac1d(k))*op25
172 DO j=1-Oly+1,sNy+Oly
173 DO i=1-Olx,sNx+Olx
174 sigmaY_W = op5*( sigmaY(i,j,km1)+sigmaY(i,j,k) )
175 & *maskS(i,j,k,bi,bj)
176 dSigmaDrS = op5*( sigmaR(i,j-1,k)+sigmaR(i,j,k) )
177 & *maskS(i,j,k,bi,bj)
178
179 wkb_cS(i,j) = wkb_cS(i,j)
180 & + SQRT(MAX( -dSigmaDrS, 0. _d 0 ))
181 & *drC(k)*GM_BVP_rModeNumber*rPI
182
183 C Part of main diagonal coming from zeroth order derivative
184 GM_b3d(i,j,k) = MAX( -dSigmaDrS, GM_Small_Number )
185
186 C This is initially the RHS
187 GM_PsiY(i,j,k,bi,bj) = half_K*sigmaY_W
188 & *(GM_bolFac2d(i,j-1,bi,bj)+GM_bolFac2d(i,j,bi,bj))
189 ENDDO
190 ENDDO
191 ENDDO
192
193 DO k=2,Nr
194 km1 = k-1
195 DO j=1-Oly+1,sNy+Oly
196 DO i=1-Olx,sNx+Olx
197 IF ( maskS(i,j,k,bi,bj).EQ.0. ) THEN
198 C- at Bottom and below, use identity matrix
199 GM_a3d(i,j,k) = 0. _d 0
200 GM_b3d(i,j,k) = 1. _d 0
201 GM_c3d(i,j,k) = 0. _d 0
202 ELSE
203 c2 = MAX( wkb_cS(i,j)*wkb_cS(i,j), GM_BVP_cHat2Min )
204 GM_a3d(i,j,k) = -c2*recip_drC(k)
205 & *recip_drF(km1)*recip_hFacS(i,j,km1,bi,bj)
206 GM_b3d(i,j,k) = GM_b3d(i,j,k)
207 & + c2*recip_drC(k)
208 & *(recip_drF(km1)*recip_hFacS(i,j,km1,bi,bj)
209 & +recip_drF(k)*recip_hFacS(i,j,k,bi,bj) )
210 GM_c3d(i,j,k) = -c2*recip_drC(k)
211 & *recip_drF(k)*recip_hFacS(i,j,k,bi,bj)
212 ENDIF
213 ENDDO
214 ENDDO
215 ENDDO
216
217 CALL SOLVE_TRIDIAGONAL( iMin,iMax,jMin+1,jMax,
218 & GM_a3d,GM_b3d,GM_c3d,
219 & GM_PsiY,
220 & errCode,bi,bj,myThid)
221
222 IF ( errCode .GT. 0 ) THEN
223 WRITE(msgBuf,'(A)')
224 & 'S/R GMREDI_CALC_PSI_BVP: matrix singular for PsiY'
225 CALL PRINT_ERROR( msgBuf, myThid )
226 STOP 'ABNORMAL END: S/R GMREDI_CALC_PSI_BVP'
227 ENDIF
228
229 #ifdef ALLOW_DIAGNOSTICS
230 C Write some diagnostics
231 IF ( useDiagnostics ) THEN
232 tmpFac = SQRT(gravity/rhoConst)
233 CALL DIAGNOSTICS_SCALE_FILL( wkb_cW, tmpFac, 1, 'GM_BVPcW',
234 & 0, 1, 2, bi, bj, myThid )
235 CALL DIAGNOSTICS_SCALE_FILL( wkb_cS, tmpFac, 1, 'GM_BVPcS',
236 & 0, 1, 2, bi, bj, myThid )
237 ENDIF
238 #endif
239
240 ENDIF
241 #endif /* GM_BOLUS_ADVEC */
242 #endif /* ALLOW_GMREDI */
243
244 RETURN
245 END

  ViewVC Help
Powered by ViewVC 1.1.22