/[MITgcm]/MITgcm/pkg/diagnostics/diagnostics_calc_phivel.F
ViewVC logotype

Contents of /MITgcm/pkg/diagnostics/diagnostics_calc_phivel.F

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


Revision 1.11 - (show annotations) (download)
Tue Nov 25 01:12:11 2014 UTC (9 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, HEAD
Changes since 1.10: +26 -46 lines
- remove recently added code (under #ifdef DIAG_PHIVEL_AS_IF_CLOSED_OB)
  (can be recovered by setting connected Id to zero)
- fix RHS norm (case with OBCS); add some comments regarding OBCS treatment.

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_calc_phivel.F,v 1.10 2014/11/21 20:59:06 jmc Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 0
8 C !ROUTINE: DIAGNOSTICS_CALC_PHIVEL
9
10 C !INTERFACE:
11 SUBROUTINE DIAGNOSTICS_CALC_PHIVEL(
12 I listId, md, ndId, ip, im, lm,
13 I NrMax,
14 U qtmp1, qtmp2,
15 I myTime, myIter, myThid )
16
17 C !DESCRIPTION:
18 C Compute Velocity Potential and Velocity Stream-Function
19
20 C !USES:
21 IMPLICIT NONE
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "GRID.h"
26 #include "DIAGNOSTICS_SIZE.h"
27 #include "DIAGNOSTICS.h"
28 #include "DIAGNOSTICS_CALC.h"
29
30 C !INPUT PARAMETERS:
31 C listId :: Diagnostics list number being written
32 C md :: field number in the list "listId".
33 C ndId :: diagnostics Id number (in available diagnostics list)
34 C ip :: diagnostics pointer to storage array
35 C im :: counter-mate pointer to storage array
36 C lm :: index in the averageCycle
37 C NrMax :: 3rd dimension of input/output arrays
38 C qtmp1 :: horizontal velocity input diag., u-component
39 C qtmp2 :: horizontal velocity input diag., v-component
40 C myTime :: current time of simulation (s)
41 C myIter :: current iteration number
42 C myThid :: my Thread Id number
43 INTEGER listId, md, ndId, ip, im, lm
44 INTEGER NrMax
45 _RL qtmp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,NrMax,nSx,nSy)
46 _RL qtmp2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,NrMax,nSx,nSy)
47 _RL myTime
48 INTEGER myIter, myThid
49
50 C !OUTPUT PARAMETERS:
51 C qtmp1 :: horizontal-velocity potential
52 C qtmp2 :: horizontal-velocity stream-function
53 CEOP
54
55 C !FUNCTIONS:
56 INTEGER ILNBLNK
57 EXTERNAL ILNBLNK
58
59 C !LOCAL VARIABLES:
60 C bi, bj :: tile indices
61 C i,j,k :: loop indices
62 C uTrans :: horizontal transport, u-component
63 C vTrans :: horizontal transport, u-component
64 C psiVel :: horizontal stream-function
65 C psiLoc :: horizontal stream-function at special location
66 INTEGER bi, bj
67 INTEGER i, j, k
68
69 INTEGER ks
70 INTEGER numIters, nIterMin
71 LOGICAL normaliseMatrice, diagNormaliseRHS
72 _RL residCriter, firstResidual, minResidual, lastResidual
73 _RL a2dMax, a2dNorm
74 _RL rhsMax, b2dNorm, x2dNorm
75 _RS aW2d(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
76 _RS aS2d(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
77 _RL b2d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
78 _RL x2d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
79 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
80 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
81 _RL psiVel(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
82 _RL psiLoc(2)
83 INTEGER iL
84 CHARACTER*(MAX_LEN_FNAM) dataFName
85 CHARACTER*(MAX_LEN_MBUF) msgBuf
86
87 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
88
89 #ifdef ALLOW_DEBUG
90 IF (debugMode) CALL DEBUG_ENTER('DIAGNOSTICS_CALC_PHIVEL',myThid)
91 #endif
92
93 DO ks = 1,nlevels(listId)
94 k = NINT(levs(ks,listId))
95 C-- Solve for velocity potential for each level:
96
97 a2dMax = 0. _d 0
98 rhsMax = 0. _d 0
99 DO bj = myByLo(myThid), myByHi(myThid)
100 DO bi = myBxLo(myThid), myBxHi(myThid)
101 C- Initialise fist guess & RHS
102 DO j = 1-OLy,sNy+OLy
103 DO i = 1-OLx,sNx+OLx
104 b2d(i,j,bi,bj) = 0.
105 x2d(i,j,bi,bj) = 0.
106 ENDDO
107 ENDDO
108 C- calculate cg2d matrix:
109 C Note: Here, at Open-Boundary location, we keep non-zero aW & aS (using
110 C maskInW & maskInS) whereas in S/R CG2D they are zero (product of maskInC)
111 DO j = 1,sNy+1
112 DO i = 1,sNx+1
113 aW2d(i,j,bi,bj) = dyG(i,j,bi,bj)*recip_dxC(i,j,bi,bj)
114 & *drF(k)*hFacW(i,j,k,bi,bj)
115 & *maskInW(i,j,bi,bj)
116 aS2d(i,j,bi,bj) = dxG(i,j,bi,bj)*recip_dyC(i,j,bi,bj)
117 & *drF(k)*hFacS(i,j,k,bi,bj)
118 & *maskInS(i,j,bi,bj)
119 a2dMax = MAX(a2dMax,aW2d(i,j,bi,bj))
120 a2dMax = MAX(a2dMax,aS2d(i,j,bi,bj))
121 ENDDO
122 ENDDO
123
124 C- calculate horizontal transport
125 DO j = 1,sNy+1
126 DO i = 1,sNx+1
127 uTrans(i,j,bi,bj) = dyG(i,j,bi,bj)*drF(k)
128 & *qtmp1(i,j,ks,bi,bj)*maskInW(i,j,bi,bj)
129 vTrans(i,j,bi,bj) = dxG(i,j,bi,bj)*drF(k)
130 & *qtmp2(i,j,ks,bi,bj)*maskInS(i,j,bi,bj)
131 ENDDO
132 ENDDO
133 C- end bi,bj loops
134 ENDDO
135 ENDDO
136
137 C- calculate RHS = rAc*Div(uVel,vVel):
138 DO bj = myByLo(myThid), myByHi(myThid)
139 DO bi = myBxLo(myThid), myBxHi(myThid)
140 DO j = 1,sNy
141 DO i = 1,sNx
142 b2d(i,j,bi,bj) = (
143 & ( uTrans(i+1,j,bi,bj) - uTrans(i,j,bi,bj) )
144 & + ( vTrans(i,j+1,bi,bj) - vTrans(i,j,bi,bj) )
145 & )*maskInC(i,j,bi,bj)
146 ENDDO
147 ENDDO
148 ENDDO
149 ENDDO
150
151 #ifdef ALLOW_OBCS
152 C There is ambiguity in splitting OB cross flow into divergent (grad.Phi)
153 C contribution and rotational (rot.Psi) contribution:
154 C a) In most cases, will interpret most of the OB cross flow (except
155 C the net inflow which has to come from grad.Phi) as non divergent
156 C and only keep the divergence associated with the net inflow
157 C (assuming here uniform distribution along the OB section;
158 C This processing must be done for each domain-connected section
159 C of the OB (using pkg/obcs OB[N,S,E,W]_connect Id) otherwise the
160 C solver will not converge.
161 C b) When setting a null domain-connected Id for some OB section,
162 C we can recover the other extreme where the OB cross flow is
163 C interpreted as a pure divergent (grad.Phi) contribution (-> constant
164 C Psi along this section). This is done by keeping the full RHS just
165 C outside OB (i.e., where tracer OBCS are applied.
166 IF ( useOBCS ) THEN
167 CALL OBCS_DIAG_BALANCE(
168 U b2d,
169 I uTrans, vTrans, k,
170 I myTime, myIter, myThid )
171 ENDIF
172 #endif /* ALLOW_OBCS */
173
174 C- Normalise Matrice & RHS :
175 diagNormaliseRHS = diagCG_resTarget.GT.0.
176 normaliseMatrice = .TRUE.
177 diagNormaliseRHS = .TRUE.
178 IF ( diagNormaliseRHS ) THEN
179 DO bj = myByLo(myThid), myByHi(myThid)
180 DO bi = myBxLo(myThid), myBxHi(myThid)
181 DO j = 1,sNy
182 DO i = 1,sNx
183 rhsMax = MAX(ABS(b2d(I,J,bi,bj)),rhsMax)
184 ENDDO
185 ENDDO
186 ENDDO
187 ENDDO
188 ENDIF
189 a2dNorm = 1. _d 0
190 b2dNorm = 1. _d 0
191 x2dNorm = 1. _d 0
192 IF ( normaliseMatrice ) THEN
193 _GLOBAL_MAX_RL( a2dMax, myThid )
194 IF ( a2dMax .GT. 0. _d 0 ) a2dNorm = 1. _d 0/a2dMax
195 b2dNorm = a2dNorm
196 ENDIF
197 IF ( diagNormaliseRHS ) THEN
198 _GLOBAL_MAX_RL( rhsMax, myThid )
199 IF ( rhsMax .GT. 0. _d 0 ) THEN
200 b2dNorm = 1. _d 0/rhsMax
201 x2dNorm = a2dNorm*rhsMax
202 ENDIF
203 residCriter = diagCG_resTarget
204 ELSE
205 residCriter = a2dNorm * ABS(diagCG_resTarget)
206 & * globalArea / deltaTMom
207 ENDIF
208 IF ( normaliseMatrice .OR. diagNormaliseRHS ) THEN
209 DO bj = myByLo(myThid), myByHi(myThid)
210 DO bi = myBxLo(myThid), myBxHi(myThid)
211 DO j = 1,sNy+1
212 DO i = 1,sNx+1
213 aW2d(i,j,bi,bj) = aW2d(i,j,bi,bj)*a2dNorm
214 aS2d(i,j,bi,bj) = aS2d(i,j,bi,bj)*a2dNorm
215 b2d(i,j,bi,bj) = b2d(i,j,bi,bj) *b2dNorm
216 c x2d(i,j,bi,bj) = x2d(i,j,bi,bj) /x2dNorm
217 ENDDO
218 ENDDO
219 ENDDO
220 ENDDO
221 ENDIF
222
223 IF ( debugLevel.GE.debLevA .AND. k.EQ.1 ) THEN
224 _BEGIN_MASTER( myThid )
225 WRITE(standardMessageUnit,'(A,I9,2(A,1P1E13.6),A,1P1E9.2)')
226 & ' diag_cg2d (it=', myIter,') a2dNorm,x2dNorm=', a2dNorm,
227 & ' ,', x2dNorm, ' ; Criter=', residCriter
228 _END_MASTER( myThid )
229 ENDIF
230
231 numIters = diagCG_maxIters
232 CALL DIAG_CG2D(
233 I aW2d, aS2d, b2d,
234 I diagCG_pcOffDFac, residCriter,
235 O firstResidual, minResidual, lastResidual,
236 U x2d, numIters,
237 O nIterMin,
238 I diagCG_prtResFrq, myThid )
239
240 IF ( debugLevel.GE.debLevA ) THEN
241 _BEGIN_MASTER( myThid )
242 WRITE(standardMessageUnit,'(A,I4,A,2I6,A,1P3E14.7)')
243 & ' diag_cg2d : k=', k, ' , it=', nIterMin, numIters,
244 & ' ; ini,min,last_Res=',firstResidual,minResidual,lastResidual
245 _END_MASTER( myThid )
246 ENDIF
247
248 _EXCH_XY_RL( x2d, myThid )
249
250 C- Un-normalise the answer
251 IF (diagNormaliseRHS) THEN
252 DO bj = myByLo(myThid), myByHi(myThid)
253 DO bi = myBxLo(myThid), myBxHi(myThid)
254 DO j = 1-OLy,sNy+OLy
255 DO i = 1-OLx,sNx+OLx
256 x2d(i,j,bi,bj) = x2d(i,j,bi,bj)*x2dNorm
257 ENDDO
258 ENDDO
259 ENDDO
260 ENDDO
261 ENDIF
262
263 C- Compte divergence-free transport:
264 DO bj = myByLo(myThid), myByHi(myThid)
265 DO bi = myBxLo(myThid), myBxHi(myThid)
266 DO j = 1,sNy+1
267 DO i = 1,sNx+1
268 uTrans(i,j,bi,bj) = uTrans(i,j,bi,bj)
269 & - ( x2d(i,j,bi,bj) - x2d(i-1,j,bi,bj) )
270 & *recip_dxC(i,j,bi,bj)*dyG(i,j,bi,bj)
271 & *drF(k)*hFacW(i,j,k,bi,bj)
272 & *maskInW(i,j,bi,bj)
273 vTrans(i,j,bi,bj) = vTrans(i,j,bi,bj)
274 & - ( x2d(i,j,bi,bj) - x2d(i,j-1,bi,bj) )
275 & *recip_dyC(i,j,bi,bj)*dxG(i,j,bi,bj)
276 & *drF(k)*hFacS(i,j,k,bi,bj)
277 & *maskInS(i,j,bi,bj)
278 ENDDO
279 ENDDO
280 ENDDO
281 ENDDO
282 CALL DIAG_CALC_PSIVEL(
283 I k, iPsi0, jPsi0, uTrans, vTrans,
284 O psiVel, psiLoc,
285 I prtFirstCall, myTime, myIter, myThid )
286
287 _BEGIN_MASTER( myThid)
288 IF ( useCubedSphereExchange .AND.
289 & diag_mdsio .AND. myProcId.EQ.0 ) THEN
290 C- Missing-corner value are not written in MDS output file
291 C Write separately these 2 values (should be part of DIAGNOSTICS_OUT)
292 IF ( diagLoc_ioUnit.EQ.0 ) THEN
293 CALL MDSFINDUNIT( diagLoc_ioUnit, myThid )
294 WRITE(dataFName,'(2A,I10.10,A)')
295 & 'diags_CScorners', '.', nIter0, '.txt'
296 OPEN( diagLoc_ioUnit, FILE=dataFName, STATUS='unknown' )
297 iL = ILNBLNK(dataFName)
298 WRITE(msgBuf,'(2A,I6,2A)') 'DIAGNOSTICS_CALC_PHIVEL: ',
299 & 'open unit=',diagLoc_ioUnit, ', file: ',dataFName(1:iL)
300 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
301 & SQUEEZE_RIGHT, myThid )
302 ENDIF
303 IF ( diagLoc_ioUnit.GT.0 ) THEN
304 WRITE(diagLoc_ioUnit,'(1P2E18.10,A,2I4,I8,A,2I4,I6,2A)')
305 & psiLoc, ' #', k, lm, myIter,
306 & ' :',listId, md, ndId, ' ', cdiag(ndId)
307 C- check accuracy (f1.SW-corner = f6.NW-corner = f5-NE-corner)
308 c WRITE(0,'(1P2E18.10,A,2I4,I8)')
309 c & psiVel(1,1+sNy,nSx,nSy)- psiVel(1,1,1,1),
310 c & psiVel(1+sNx,1+sNy,nSx-1,nSy)-psiVel(1,1,1,1),
311 c & ' #', k, lm, myIter
312 ENDIF
313 ENDIF
314 IF ( prtFirstCall ) prtFirstCall = .FALSE.
315 _END_MASTER( myThid)
316
317 C- Put the results back in qtmp[1,2]
318 DO bj = myByLo(myThid), myByHi(myThid)
319 DO bi = myBxLo(myThid), myBxHi(myThid)
320 DO j = 1,sNy+1
321 DO i = 1,sNx+1
322 qtmp1(i,j,ks,bi,bj) = x2d(i,j,bi,bj)
323 qtmp2(i,j,ks,bi,bj) = psiVel(i,j,bi,bj)
324 ENDDO
325 ENDDO
326 ENDDO
327 ENDDO
328
329 ENDDO
330
331 #ifdef ALLOW_DEBUG
332 IF (debugMode) CALL DEBUG_LEAVE('DIAGNOSTICS_CALC_PHIVEL',myThid)
333 #endif
334
335 RETURN
336 END

  ViewVC Help
Powered by ViewVC 1.1.22