/[MITgcm]/MITgcm/model/src/find_rho.F
ViewVC logotype

Contents of /MITgcm/model/src/find_rho.F

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


Revision 1.43 - (show annotations) (download)
Thu Mar 10 20:36:31 2016 UTC (8 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65v, checkpoint65w, checkpoint65u, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.42: +31 -3 lines
add Ideal Gas equation of state for height coordinate

1 C $Header: /u/gcmpack/MITgcm/model/src/find_rho.F,v 1.42 2014/04/04 20:56:32 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6 #ifdef TARGET_NEC_SX
7 C make sure that the factorized EOS is used on NEC vector computers
8 # define USE_FACTORIZED_EOS
9 #endif
10 C this was the default, so we keep it that way
11 #define USE_FACTORIZED_POLY
12
13 C-- File find_rho.F: Routines to compute density
14 C-- Contents
15 C-- o FIND_RHO_2D
16 C-- o FIND_RHOP0
17 C-- o FIND_BULKMOD
18 C-- o FIND_RHONUM
19 C-- o FIND_RHODEN
20 C-- o FIND_RHO_SCALAR: in-situ density for individual points
21 C-- o LOOK_FOR_NEG_SALINITY
22
23 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
24 CBOP
25 C !ROUTINE: FIND_RHO_2D
26 C !INTERFACE:
27 SUBROUTINE FIND_RHO_2D(
28 I iMin, iMax, jMin, jMax, kRef,
29 I tFld, sFld,
30 O rhoLoc,
31 I k, bi, bj, myThid )
32
33 C !DESCRIPTION: \bv
34 C *==========================================================*
35 C | o SUBROUTINE FIND_RHO_2D
36 C | Calculates [rho(S,T,z)-rhoConst] of a 2-D slice
37 C *==========================================================*
38 C | kRef - determines pressure reference level
39 C | (not used in 'LINEAR' mode)
40 C | Note: k is not used ; keep it for debugging.
41 C *==========================================================*
42 C \ev
43
44 C !USES:
45 IMPLICIT NONE
46 C == Global variables ==
47 #include "SIZE.h"
48 #include "EEPARAMS.h"
49 #include "PARAMS.h"
50 #include "EOS.h"
51
52 C !INPUT/OUTPUT PARAMETERS:
53 C == Routine arguments ==
54 C k :: Level of Theta/Salt slice
55 C kRef :: Pressure reference level
56 INTEGER iMin,iMax,jMin,jMax
57 INTEGER kRef
58 _RL tFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59 _RL sFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60 _RL rhoLoc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61 INTEGER k, bi, bj
62 INTEGER myThid
63
64 C !LOCAL VARIABLES:
65 C == Local variables ==
66 INTEGER i,j
67 _RL refTemp,refSalt,sigRef,tP,sP,deltaSig,dRho
68 _RL oneMinusKap, facPres, theta_v
69 _RL locPres(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70 _RL rhoP0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 _RL bulkMod(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72 _RL rhoNum (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73 _RL rhoDen (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74 CHARACTER*(MAX_LEN_MBUF) msgBuf
75 CEOP
76
77 #ifdef ALLOW_AUTODIFF
78 DO j=1-OLy,sNy+OLy
79 DO i=1-OLx,sNx+OLx
80 rhoLoc(i,j) = 0. _d 0
81 rhoP0(i,j) = 0. _d 0
82 bulkMod(i,j) = 0. _d 0
83 ENDDO
84 ENDDO
85 #endif
86
87 #ifdef CHECK_SALINITY_FOR_NEGATIVE_VALUES
88 CALL LOOK_FOR_NEG_SALINITY(
89 I iMin, iMax, jMin, jMax,
90 U sFld,
91 I k, bi, bj, myThid )
92 #endif
93
94 IF (equationOfState.EQ.'LINEAR') THEN
95
96 C ***NOTE***
97 C In the linear EOS, to make the static stability calculation meaningful
98 C we use reference temp & salt from level kRef ;
99 C **********
100 refTemp=tRef(kRef)
101 refSalt=sRef(kRef)
102
103 dRho = rhoNil-rhoConst
104
105 DO j=jMin,jMax
106 DO i=iMin,iMax
107 rhoLoc(i,j)=rhoNil*(
108 & sBeta*(sFld(i,j)-refSalt)
109 & -tAlpha*(tFld(i,j)-refTemp) )
110 & + dRho
111 ENDDO
112 ENDDO
113
114 ELSEIF (equationOfState.EQ.'POLY3') THEN
115
116 refTemp=eosRefT(kRef)
117 refSalt=eosRefS(kRef)
118 sigRef=eosSig0(kRef) + (1000.-rhoConst)
119
120 DO j=jMin,jMax
121 DO i=iMin,iMax
122 tP=tFld(i,j)-refTemp
123 sP=sFld(i,j)-refSalt
124 #ifdef USE_FACTORIZED_POLY
125 deltaSig=
126 & (( eosC(9,kRef)*sP + eosC(5,kRef) )*sP + eosC(2,kRef) )*sP
127 & + ( ( eosC(6,kRef)
128 & *tP
129 & +eosC(7,kRef)*sP + eosC(3,kRef)
130 & )*tP
131 & +(eosC(8,kRef)*sP + eosC(4,kRef) )*sP + eosC(1,kRef)
132 & )*tP
133 #else
134 deltaSig=
135 & eosC(1,kRef)*tP
136 & +eosC(2,kRef) *sP
137 & +eosC(3,kRef)*tP*tP
138 & +eosC(4,kRef)*tP *sP
139 & +eosC(5,kRef) *sP*sP
140 & +eosC(6,kRef)*tP*tP*tP
141 & +eosC(7,kRef)*tP*tP *sP
142 & +eosC(8,kRef)*tP *sP*sP
143 & +eosC(9,kRef) *sP*sP*sP
144 #endif
145 rhoLoc(i,j)=sigRef+deltaSig
146 ENDDO
147 ENDDO
148
149 ELSEIF ( equationOfState(1:5).EQ.'JMD95'
150 & .OR. equationOfState.EQ.'UNESCO' ) THEN
151 C nonlinear equation of state in pressure coordinates
152
153 CALL PRESSURE_FOR_EOS(
154 I bi, bj, iMin, iMax, jMin, jMax, kRef,
155 O locPres,
156 I myThid )
157
158 CALL FIND_RHOP0(
159 I iMin, iMax, jMin, jMax,
160 I tFld, sFld,
161 O rhoP0,
162 I myThid )
163
164 CALL FIND_BULKMOD(
165 I iMin, iMax, jMin, jMax,
166 I locPres, tFld, sFld,
167 O bulkMod,
168 I myThid )
169
170 c#ifdef ALLOW_AUTODIFF_TAMC
171 cph can not DO storing here since find_rho is called multiple times;
172 cph additional recomp. should be acceptable
173 c#endif /* ALLOW_AUTODIFF_TAMC */
174 DO j=jMin,jMax
175 DO i=iMin,iMax
176
177 C density of sea water at pressure p
178 rhoLoc(i,j) = rhoP0(i,j)
179 & /(1. _d 0 -
180 & locPres(i,j)*SItoBar/bulkMod(i,j) )
181 & - rhoConst
182
183 ENDDO
184 ENDDO
185
186 ELSEIF ( equationOfState.EQ.'MDJWF' ) THEN
187
188 CALL PRESSURE_FOR_EOS(
189 I bi, bj, iMin, iMax, jMin, jMax, kRef,
190 O locPres,
191 I myThid )
192
193 CALL FIND_RHONUM(
194 I iMin, iMax, jMin, jMax,
195 I locPres, tFld, sFld,
196 O rhoNum,
197 I myThid )
198
199 CALL FIND_RHODEN(
200 I iMin, iMax, jMin, jMax,
201 I locPres, tFld, sFld,
202 O rhoDen,
203 I myThid )
204
205 c#ifdef ALLOW_AUTODIFF_TAMC
206 cph can not DO storing here since find_rho is called multiple times;
207 cph additional recomp. should be acceptable
208 c#endif /* ALLOW_AUTODIFF_TAMC */
209 DO j=jMin,jMax
210 DO i=iMin,iMax
211 rhoLoc(i,j) = rhoNum(i,j)*rhoDen(i,j) - rhoConst
212 ENDDO
213 ENDDO
214
215 ELSEIF ( equationOfState.EQ.'TEOS10' ) THEN
216
217 CALL PRESSURE_FOR_EOS(
218 I bi, bj, iMin, iMax, jMin, jMax, kRef,
219 O locPres,
220 I myThid )
221
222 CALL FIND_RHOTEOS(
223 I iMin, iMax, jMin, jMax,
224 I locPres, tFld, sFld,
225 O rhoNum, rhoDen,
226 I myThid )
227
228 c#ifdef ALLOW_AUTODIFF_TAMC
229 cph can not DO storing here since find_rho is called multiple times;
230 cph additional recomp. should be acceptable
231 c#endif /* ALLOW_AUTODIFF_TAMC */
232 DO j=jMin,jMax
233 DO i=iMin,iMax
234 rhoLoc(i,j) = rhoNum(i,j)*rhoDen(i,j) - rhoConst
235 ENDDO
236 ENDDO
237
238 ELSEIF( equationOfState .EQ. 'IDEALG' ) THEN
239
240 CALL PRESSURE_FOR_EOS(
241 I bi, bj, iMin, iMax, jMin, jMax, kRef,
242 O locPres,
243 I myThid )
244
245 oneMinusKap = oneRL - atm_kappa
246 C rho = P/(R*T_v) = Po/(R*theta_v)*(P/Po)^(1-kappa)
247 DO j=jMin,jMax
248 DO i=iMin,iMax
249 IF ( locPres(i,j).GT.zeroRL .AND. tFld(i,j).GT.zeroRL ) THEN
250 facPres = ( locPres(i,j)/atm_Po )**oneMinusKap
251 theta_v = tFld(i,j)*( sFld(i,j)*atm_Rq + oneRL )
252 rhoLoc(i,j) = atm_Po*facPres
253 & /( atm_Rd*theta_v ) - rhoConst
254 ELSE
255 rhoLoc(i,j) = zeroRL
256 ENDIF
257 ENDDO
258 ENDDO
259
260 ELSE
261 WRITE(msgBuf,'(3a)')
262 & ' FIND_RHO_2D: equationOfState = "',equationOfState,'"'
263 CALL PRINT_ERROR( msgBuf, myThid )
264 STOP 'ABNORMAL END: S/R FIND_RHO_2D'
265 ENDIF
266
267 RETURN
268 END
269
270 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
271 CBOP
272 C !ROUTINE: FIND_RHOP0
273 C !INTERFACE:
274 SUBROUTINE FIND_RHOP0(
275 I iMin, iMax, jMin, jMax,
276 I tFld, sFld,
277 O rhoP0,
278 I myThid )
279
280 C !DESCRIPTION: \bv
281 C *==========================================================*
282 C | o SUBROUTINE FIND_RHOP0
283 C | Calculates rho(S,T,0) of a slice
284 C *==========================================================*
285 C *==========================================================*
286 C \ev
287
288 C !USES:
289 IMPLICIT NONE
290 C == Global variables ==
291 #include "SIZE.h"
292 #include "EEPARAMS.h"
293 #include "PARAMS.h"
294 #include "EOS.h"
295
296 C !INPUT/OUTPUT PARAMETERS:
297 C == Routine arguments ==
298 INTEGER iMin,iMax,jMin,jMax
299 _RL tFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
300 _RL sFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
301 _RL rhoP0(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
302 INTEGER myThid
303
304 C !LOCAL VARIABLES:
305 C == Local variables ==
306 INTEGER i,j
307 _RL rfresh, rsalt
308 _RL t, t2, t3, t4, s, s3o2
309 #ifdef USE_FACTORIZED_EOS
310 _RL eosF1, eosF2, eosF3, eosF4, eosF5, eosF6
311 _RL eosS1, eosS2, eosS3, eosS4, eosS5, eosS6
312 _RL eosS7, eosS8, eosS9
313 #endif /* USE_FACTORIZED_EOS */
314 CEOP
315 #ifdef USE_FACTORIZED_EOS
316 eosF1 = eosJMDCFw(1)
317 eosF2 = eosJMDCFw(2)
318 eosF3 = eosJMDCFw(3)
319 eosF4 = eosJMDCFw(4)
320 eosF5 = eosJMDCFw(5)
321 eosF6 = eosJMDCFw(6)
322 eosS1 = eosJMDCSw(1)
323 eosS2 = eosJMDCSw(2)
324 eosS3 = eosJMDCSw(3)
325 eosS4 = eosJMDCSw(4)
326 eosS5 = eosJMDCSw(5)
327 eosS6 = eosJMDCSw(6)
328 eosS7 = eosJMDCSw(7)
329 eosS8 = eosJMDCSw(8)
330 eosS9 = eosJMDCSw(9)
331 #endif /* USE_FACTORIZED_EOS */
332
333 DO j=jMin,jMax
334 DO i=iMin,iMax
335 C abbreviations
336 t = tFld(i,j)
337 t2 = t*t
338 t3 = t2*t
339 t4 = t3*t
340
341 #if (defined ALLOW_AUTODIFF && defined TARGET_NEC_SX)
342 C this line makes TAF create vectorizable code
343 s3o2 = 0. _d 0
344 #endif
345 s = sFld(i,j)
346 IF ( s .GT. 0. _d 0 ) THEN
347 s3o2 = s*SQRT(s)
348 ELSE
349 s = 0. _d 0
350 s3o2 = 0. _d 0
351 ENDIF
352
353 C density of freshwater at the surface
354 #ifdef USE_FACTORIZED_EOS
355 rfresh =
356 & eosF1 +
357 & t* ( eosF2 +
358 & t* ( eosF3 +
359 & t* ( eosF4 +
360 & t* ( eosF5 +
361 & t* eosF6 ))))
362 #else
363 rfresh =
364 & eosJMDCFw(1)
365 & + eosJMDCFw(2)*t
366 & + eosJMDCFw(3)*t2
367 & + eosJMDCFw(4)*t3
368 & + eosJMDCFw(5)*t4
369 & + eosJMDCFw(6)*t4*t
370 #endif /* USE_FACTORIZED_EOS */
371 C density of sea water at the surface
372 #ifdef USE_FACTORIZED_EOS
373 rsalt = s * ( eosS1 +
374 & t * ( eosS2 +
375 & t * ( eosS3 +
376 & t * ( eosS4 +
377 & t * eosS5 ))))
378 & + s3o2 * ( eosS6 +
379 & t * ( eosS7 +
380 & t * eosS8 ))
381 & + s*s * eosS9
382 #else
383 rsalt =
384 & s*(
385 & eosJMDCSw(1)
386 & + eosJMDCSw(2)*t
387 & + eosJMDCSw(3)*t2
388 & + eosJMDCSw(4)*t3
389 & + eosJMDCSw(5)*t4
390 & )
391 & + s3o2*(
392 & eosJMDCSw(6)
393 & + eosJMDCSw(7)*t
394 & + eosJMDCSw(8)*t2
395 & )
396 & + eosJMDCSw(9)*s*s
397 #endif /* USE_FACTORIZED_EOS */
398
399 rhoP0(i,j) = rfresh + rsalt
400
401 ENDDO
402 ENDDO
403
404 RETURN
405 END
406
407 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
408 CBOP
409 C !ROUTINE: FIND_BULKMOD
410 C !INTERFACE:
411 SUBROUTINE FIND_BULKMOD(
412 I iMin, iMax, jMin, jMax,
413 I locPres, tFld, sFld,
414 O bulkMod,
415 I myThid )
416
417 C !DESCRIPTION: \bv
418 C *==========================================================*
419 C | o SUBROUTINE FIND_BULKMOD
420 C | Calculates the secant bulk modulus K(S,T,p) of a slice
421 C *==========================================================*
422 C | k - is the level of Theta/Salt slice
423 C *==========================================================*
424 C \ev
425
426 C !USES:
427 IMPLICIT NONE
428 C == Global variables ==
429 #include "SIZE.h"
430 #include "EEPARAMS.h"
431 #include "PARAMS.h"
432 #include "EOS.h"
433
434 C !INPUT/OUTPUT PARAMETERS:
435 C == Routine arguments ==
436 INTEGER iMin,iMax,jMin,jMax
437 _RL locPres(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
438 _RL tFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
439 _RL sFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
440 _RL bulkMod(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
441 INTEGER myThid
442
443 C !LOCAL VARIABLES:
444 C == Local variables ==
445 INTEGER i,j
446 _RL bMfresh, bMsalt, bMpres
447 _RL t, t2, t3, t4, s, s3o2, p, p2
448 #ifdef USE_FACTORIZED_EOS
449 _RL eosF1, eosF2, eosF3, eosF4, eosF5
450 _RL eosS1, eosS2, eosS3, eosS4, eosS5, eosS6, eosS7
451 _RL eosP1, eosP2, eosP3, eosP4, eosP5, eosP6, eosP7
452 _RL eosP8, eosP9, eosP10, eosP11, eosP12, eosP13, eosP14
453 #endif /* USE_FACTORIZED_EOS */
454 CEOP
455 #ifdef USE_FACTORIZED_EOS
456 eosF1 = eosJMDCKFw(1)
457 eosF2 = eosJMDCKFw(2)
458 eosF3 = eosJMDCKFw(3)
459 eosF4 = eosJMDCKFw(4)
460 eosF5 = eosJMDCKFw(5)
461
462 eosS1 = eosJMDCKSw(1)
463 eosS2 = eosJMDCKSw(2)
464 eosS3 = eosJMDCKSw(3)
465 eosS4 = eosJMDCKSw(4)
466 eosS5 = eosJMDCKSw(5)
467 eosS6 = eosJMDCKSw(6)
468 eosS7 = eosJMDCKSw(7)
469
470 eosP1 =eosJMDCKP(1)
471 eosP2 =eosJMDCKP(2)
472 eosP3 =eosJMDCKP(3)
473 eosP4 =eosJMDCKP(4)
474 eosP5 =eosJMDCKP(5)
475 eosP6 =eosJMDCKP(6)
476 eosP7 =eosJMDCKP(7)
477 eosP8 =eosJMDCKP(8)
478 eosP9 =eosJMDCKP(9)
479 eosP10 =eosJMDCKP(10)
480 eosP11 =eosJMDCKP(11)
481 eosP12 =eosJMDCKP(12)
482 eosP13 =eosJMDCKP(13)
483 eosP14 =eosJMDCKP(14)
484 #endif /* USE_FACTORIZED_EOS */
485
486 DO j=jMin,jMax
487 DO i=iMin,iMax
488 C abbreviations
489 t = tFld(i,j)
490 t2 = t*t
491 t3 = t2*t
492 t4 = t3*t
493
494 #if (defined ALLOW_AUTODIFF && defined TARGET_NEC_SX)
495 C this line makes TAF create vectorizable code
496 s3o2 = 0. _d 0
497 #endif
498 s = sFld(i,j)
499 IF ( s .GT. 0. _d 0 ) THEN
500 s3o2 = s*SQRT(s)
501 ELSE
502 s = 0. _d 0
503 s3o2 = 0. _d 0
504 ENDIF
505 C
506 p = locPres(i,j)*SItoBar
507 p2 = p*p
508 C secant bulk modulus of fresh water at the surface
509 #ifdef USE_FACTORIZED_EOS
510 bMfresh = eosF1 +
511 & t * ( eosF2 +
512 & t * ( eosF3 +
513 & t * ( eosF4 +
514 & t * eosF5 )))
515 #else
516 bMfresh =
517 & eosJMDCKFw(1)
518 & + eosJMDCKFw(2)*t
519 & + eosJMDCKFw(3)*t2
520 & + eosJMDCKFw(4)*t3
521 & + eosJMDCKFw(5)*t4
522 #endif /* USE_FACTORIZED_EOS */
523 C secant bulk modulus of sea water at the surface
524 #ifdef USE_FACTORIZED_EOS
525 bMsalt = s * ( eosS1 +
526 & t * ( eosS2 +
527 & t * ( eosS3 +
528 & t * eosS4 )))
529 & + s3o2* ( eosS5 +
530 & t * ( eosS6 +
531 & t * eosS7 ))
532 C secant bulk modulus of sea water at pressure p
533 bMpres = p * ( eosP1 +
534 & t * ( eosP2 +
535 & t * ( eosP3 +
536 & t * eosP4 )))
537 & + p*s* ( eosP5 +
538 & t * ( eosP6 +
539 & t * eosP7 ))
540 & + p*s3o2*eosP8
541 & + p2 * ( eosP9 +
542 & t * ( eosP10 +
543 & t * eosP11 ))
544 & + p2*s* ( eosP12 +
545 & t * ( eosP13 +
546 & t * eosP14 ))
547 #else
548 C secant bulk modulus of sea water at the surface
549 bMsalt =
550 & s*( eosJMDCKSw(1)
551 & + eosJMDCKSw(2)*t
552 & + eosJMDCKSw(3)*t2
553 & + eosJMDCKSw(4)*t3
554 & )
555 & + s3o2*( eosJMDCKSw(5)
556 & + eosJMDCKSw(6)*t
557 & + eosJMDCKSw(7)*t2
558 & )
559 C secant bulk modulus of sea water at pressure p
560 bMpres =
561 & p*( eosJMDCKP(1)
562 & + eosJMDCKP(2)*t
563 & + eosJMDCKP(3)*t2
564 & + eosJMDCKP(4)*t3
565 & )
566 & + p*s*( eosJMDCKP(5)
567 & + eosJMDCKP(6)*t
568 & + eosJMDCKP(7)*t2
569 & )
570 & + p*s3o2*eosJMDCKP(8)
571 & + p2*( eosJMDCKP(9)
572 & + eosJMDCKP(10)*t
573 & + eosJMDCKP(11)*t2
574 & )
575 & + p2*s*( eosJMDCKP(12)
576 & + eosJMDCKP(13)*t
577 & + eosJMDCKP(14)*t2
578 & )
579 #endif /* USE_FACTORIZED_EOS */
580
581 bulkMod(i,j) = bMfresh + bMsalt + bMpres
582
583 ENDDO
584 ENDDO
585
586 RETURN
587 END
588
589 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
590 CBOP
591 C !ROUTINE: FIND_RHONUM
592 C !INTERFACE:
593 SUBROUTINE FIND_RHONUM(
594 I iMin, iMax, jMin, jMax,
595 I locPres, tFld, sFld,
596 O rhoNum,
597 I myThid )
598
599 C !DESCRIPTION: \bv
600 C *==========================================================*
601 C | o SUBROUTINE FIND_RHONUM
602 C | Calculates the numerator of the McDougall et al.
603 C | equation of state
604 C | - the code is more or less a copy of MOM4
605 C *==========================================================*
606 C *==========================================================*
607 C \ev
608
609 C !USES:
610 IMPLICIT NONE
611 C == Global variables ==
612 #include "SIZE.h"
613 #include "EEPARAMS.h"
614 #include "PARAMS.h"
615 #include "EOS.h"
616
617 C !INPUT/OUTPUT PARAMETERS:
618 C == Routine arguments ==
619 INTEGER iMin,iMax,jMin,jMax
620 _RL locPres(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
621 _RL tFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
622 _RL sFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
623 _RL rhoNum (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
624 INTEGER myThid
625
626 C !LOCAL VARIABLES:
627 C == Local variables ==
628 INTEGER i,j
629 _RL t1, t2, s1, p1
630 CEOP
631 DO j=jMin,jMax
632 DO i=iMin,iMax
633 C abbreviations
634 t1 = tFld(i,j)
635 t2 = t1*t1
636 s1 = sFld(i,j)
637
638 p1 = locPres(i,j)*SItodBar
639
640 rhoNum(i,j) = eosMDJWFnum(0)
641 & + t1*(eosMDJWFnum(1)
642 & + t1*(eosMDJWFnum(2) + eosMDJWFnum(3)*t1) )
643 & + s1*(eosMDJWFnum(4)
644 & + eosMDJWFnum(5)*t1 + eosMDJWFnum(6)*s1)
645 & + p1*(eosMDJWFnum(7) + eosMDJWFnum(8)*t2
646 & + eosMDJWFnum(9)*s1
647 & + p1*(eosMDJWFnum(10) + eosMDJWFnum(11)*t2) )
648
649 ENDDO
650 ENDDO
651
652 RETURN
653 END
654
655 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
656 CBOP
657 C !ROUTINE: FIND_RHODEN
658 C !INTERFACE:
659 SUBROUTINE FIND_RHODEN(
660 I iMin, iMax, jMin, jMax,
661 I locPres, tFld, sFld,
662 O rhoDen,
663 I myThid )
664
665 C !DESCRIPTION: \bv
666 C *==========================================================*
667 C | o SUBROUTINE FIND_RHODEN
668 C | Calculates the denominator of the McDougall et al.
669 C | equation of state
670 C | - the code is more or less a copy of MOM4
671 C *==========================================================*
672 C *==========================================================*
673 C \ev
674
675 C !USES:
676 IMPLICIT NONE
677 C == Global variables ==
678 #include "SIZE.h"
679 #include "EEPARAMS.h"
680 #include "PARAMS.h"
681 #include "EOS.h"
682
683 C !INPUT/OUTPUT PARAMETERS:
684 C == Routine arguments ==
685 INTEGER iMin,iMax,jMin,jMax
686 _RL locPres(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
687 _RL tFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
688 _RL sFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
689 _RL rhoDen (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
690 INTEGER myThid
691
692 C !LOCAL VARIABLES:
693 C == Local variables ==
694 INTEGER i,j
695 _RL t1, t2, s1, sp5, p1, p1t1
696 _RL den, epsln
697 parameter ( epsln = 0. _d 0 )
698 CEOP
699 DO j=jMin,jMax
700 DO i=iMin,iMax
701 C abbreviations
702 t1 = tFld(i,j)
703 t2 = t1*t1
704 s1 = sFld(i,j)
705 #if (defined ALLOW_AUTODIFF && defined TARGET_NEC_SX)
706 C this line makes TAF create vectorizable code
707 sp5 = 0. _d 0
708 #endif
709 IF ( s1 .GT. 0. _d 0 ) THEN
710 sp5 = SQRT(s1)
711 ELSE
712 s1 = 0. _d 0
713 sp5 = 0. _d 0
714 ENDIF
715
716 p1 = locPres(i,j)*SItodBar
717 p1t1 = p1*t1
718
719 den = eosMDJWFden(0)
720 & + t1*(eosMDJWFden(1)
721 & + t1*(eosMDJWFden(2)
722 & + t1*(eosMDJWFden(3) + t1*eosMDJWFden(4) ) ) )
723 & + s1*(eosMDJWFden(5)
724 & + t1*(eosMDJWFden(6)
725 & + eosMDJWFden(7)*t2)
726 & + sp5*(eosMDJWFden(8) + eosMDJWFden(9)*t2) )
727 & + p1*(eosMDJWFden(10)
728 & + p1t1*(eosMDJWFden(11)*t2 + eosMDJWFden(12)*p1) )
729
730 rhoDen(i,j) = 1.0/(epsln+den)
731
732 ENDDO
733 ENDDO
734
735 RETURN
736 END
737
738 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
739 CBOP
740 C !ROUTINE: FIND_RHOTEOS
741 C !INTERFACE:
742 SUBROUTINE FIND_RHOTEOS(
743 I iMin, iMax, jMin, jMax,
744 I locPres, tFld, sFld,
745 O rhoNum, rhoDen,
746 I myThid )
747
748 C !DESCRIPTION: \bv
749 C *==========================================================*
750 C | o SUBROUTINE FIND_RHOTEOS
751 C | Calculates numerator and inverse of denominator of the
752 C | TEOS-10 (McDougall et al. 2011) equation of state
753 C | - the code is more or less a copy the teos-10 toolbox
754 C | available at http://www.teos-10.org
755 C *==========================================================*
756 C \ev
757
758 C !USES:
759 IMPLICIT NONE
760 C == Global variables ==
761 #include "SIZE.h"
762 #include "EEPARAMS.h"
763 #include "PARAMS.h"
764 #include "EOS.h"
765
766 C !INPUT/OUTPUT PARAMETERS:
767 C == Routine arguments ==
768 INTEGER iMin,iMax,jMin,jMax
769 _RL locPres(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
770 _RL tFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
771 _RL sFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
772 _RL rhoNum (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
773 _RL rhoDen (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
774 INTEGER myThid
775
776 C !LOCAL VARIABLES:
777 C == Local variables ==
778 INTEGER i,j
779 _RL ct, sa, sqrtsa, p
780 _RL den, epsln
781 parameter ( epsln = 0. _d 0 )
782 CEOP
783 DO j=jMin,jMax
784 DO i=iMin,iMax
785 C abbreviations
786 ct = tFld(i,j)
787 sa = sFld(i,j)
788 #if (defined ALLOW_AUTODIFF && defined TARGET_NEC_SX)
789 C this line makes TAF create vectorizable code
790 sqrtsa = 0. _d 0
791 #endif
792 IF ( sa .GT. 0. _d 0 ) THEN
793 sqrtsa = SQRT(sa)
794 ELSE
795 sa = 0. _d 0
796 sqrtsa = 0. _d 0
797 ENDIF
798 p = locPres(i,j)*SItodBar
799
800 rhoNum(i,j) = teos(01)
801 & + ct*(teos(02) + ct*(teos(03) + teos(04)*ct))
802 & + sa*(teos(05) + ct*(teos(06) + teos(07)*ct)
803 & + sqrtsa*(teos(08) + ct*(teos(09)
804 & + ct*(teos(10) + teos(11)*ct))))
805 & + p*(teos(12) + ct*(teos(13) + teos(14)*ct)
806 & + sa*(teos(15) + teos(16)*ct)
807 & + p*(teos(17) + ct*(teos(18) + teos(19)*ct) + teos(20)*sa))
808
809 den = teos(21)
810 & + ct*(teos(22) + ct*(teos(23) + ct*(teos(24) + teos(25)*ct)))
811 & + sa*(teos(26) + ct*(teos(27) + ct*(teos(28)
812 & + ct*(teos(29) + teos(30)*ct)))
813 & + teos(36)*sa
814 & + sqrtsa*(teos(31) + ct*(teos(32) + ct*(teos(33)
815 & + ct*(teos(34) + teos(35)*ct)))))
816 & + p*(teos(37) + ct*(teos(38) + ct*(teos(39) + teos(40)*ct))
817 & + sa*(teos(41) + teos(42)*ct)
818 & + p*(teos(43) + ct*(teos(44) + teos(45)*ct + teos(46)*sa)
819 & + p*(teos(47) + teos(48)*ct)))
820
821 rhoDen(i,j) = 1.0/(epsln+den)
822
823 ENDDO
824 ENDDO
825
826 RETURN
827 END
828
829 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
830 CBOP
831 C !ROUTINE: FIND_RHO_SCALAR
832 C !INTERFACE:
833 SUBROUTINE FIND_RHO_SCALAR(
834 I tLoc, sLoc, pLoc,
835 O rhoLoc,
836 I myThid )
837
838 C !DESCRIPTION: \bv
839 C *==========================================================*
840 C | o SUBROUTINE FIND_RHO_SCALAR
841 C | Calculates rho(S,T,p)
842 C *==========================================================*
843 C \ev
844
845 C !USES:
846 IMPLICIT NONE
847 C == Global variables ==
848 #include "SIZE.h"
849 #include "EEPARAMS.h"
850 #include "PARAMS.h"
851 #include "EOS.h"
852
853 C !INPUT/OUTPUT PARAMETERS:
854 C == Routine arguments ==
855 _RL tLoc, sLoc, pLoc
856 _RL rhoLoc
857 INTEGER myThid
858
859 C !LOCAL VARIABLES:
860 C == Local variables ==
861 _RL t1, t2, t3, t4, s1, s3o2, p1, p2, sp5, p1t1
862 _RL ct, sa, sqrtsa, p
863 _RL rfresh, rsalt, rhoP0
864 _RL bMfresh, bMsalt, bMpres, BulkMod
865 _RL rhoNum, rhoDen, den, epsln
866 _RL oneMinusKap, facPres, theta_v
867 PARAMETER ( epsln = 0. _d 0 )
868 CHARACTER*(MAX_LEN_MBUF) msgBuf
869 #ifdef USE_FACTORIZED_EOS
870 _RL eosF1, eosF2, eosF3, eosF4, eosF5, eosF6
871 _RL eosS1, eosS2, eosS3, eosS4, eosS5, eosS6
872 _RL eosS7, eosS8, eosS9
873 _RL eosP1, eosP2, eosP3, eosP4, eosP5, eosP6, eosP7
874 _RL eosP8, eosP9, eosP10, eosP11, eosP12, eosP13, eosP14
875 #endif /* USE_FACTORIZED_EOS */
876 CEOP
877 #ifdef USE_FACTORIZED_EOS
878 eosF1 = eosJMDCFw(1)
879 eosF2 = eosJMDCFw(2)
880 eosF3 = eosJMDCFw(3)
881 eosF4 = eosJMDCFw(4)
882 eosF5 = eosJMDCFw(5)
883 eosF6 = eosJMDCFw(6)
884 eosS1 = eosJMDCSw(1)
885 eosS2 = eosJMDCSw(2)
886 eosS3 = eosJMDCSw(3)
887 eosS4 = eosJMDCSw(4)
888 eosS5 = eosJMDCSw(5)
889 eosS6 = eosJMDCSw(6)
890 eosS7 = eosJMDCSw(7)
891 eosS8 = eosJMDCSw(8)
892 eosS9 = eosJMDCSw(9)
893
894 eosP1 =eosJMDCKP(1)
895 eosP2 =eosJMDCKP(2)
896 eosP3 =eosJMDCKP(3)
897 eosP4 =eosJMDCKP(4)
898 eosP5 =eosJMDCKP(5)
899 eosP6 =eosJMDCKP(6)
900 eosP7 =eosJMDCKP(7)
901 eosP8 =eosJMDCKP(8)
902 eosP9 =eosJMDCKP(9)
903 eosP10 =eosJMDCKP(10)
904 eosP11 =eosJMDCKP(11)
905 eosP12 =eosJMDCKP(12)
906 eosP13 =eosJMDCKP(13)
907 eosP14 =eosJMDCKP(14)
908 #endif /* USE_FACTORIZED_EOS */
909
910 rhoLoc = 0. _d 0
911 rhoP0 = 0. _d 0
912 bulkMod = 0. _d 0
913 rfresh = 0. _d 0
914 rsalt = 0. _d 0
915 bMfresh = 0. _d 0
916 bMsalt = 0. _d 0
917 bMpres = 0. _d 0
918 rhoNum = 0. _d 0
919 rhoDen = 0. _d 0
920 den = 0. _d 0
921
922 t1 = tLoc
923 t2 = t1*t1
924 t3 = t2*t1
925 t4 = t3*t1
926
927 s1 = sLoc
928 IF ( s1 .LT. 0. _d 0 ) THEN
929 C issue a warning
930 WRITE(msgBuf,'(A,E13.5)')
931 & ' FIND_RHO_SCALAR: WARNING, salinity = ', s1
932 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
933 & SQUEEZE_RIGHT , myThid )
934 s1 = 0. _d 0
935 ENDIF
936
937 IF (equationOfState.EQ.'LINEAR') THEN
938
939 rholoc = rhoNil*(
940 & sBeta *(sLoc-sRef(1))
941 & -tAlpha*(tLoc-tRef(1))
942 & ) + rhoNil
943 c rhoLoc = 0. _d 0
944
945 ELSEIF (equationOfState.EQ.'POLY3') THEN
946
947 C this is not correct, there is a field eosSig0 which should be use here
948 C but I DO not intent to include the reference level in this routine
949 WRITE(msgBuf,'(A)')
950 & ' FIND_RHO_SCALAR: for POLY3, the density is not'
951 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
952 & SQUEEZE_RIGHT , myThid )
953 WRITE(msgBuf,'(A)')
954 & ' computed correctly in this routine'
955 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
956 & SQUEEZE_RIGHT , myThid )
957 rhoLoc = 0. _d 0
958
959 ELSEIF ( equationOfState(1:5).EQ.'JMD95'
960 & .OR. equationOfState.EQ.'UNESCO' ) THEN
961 C nonlinear equation of state in pressure coordinates
962
963 s3o2 = s1*SQRT(s1)
964
965 p1 = pLoc*SItoBar
966 p2 = p1*p1
967
968 C density of freshwater at the surface
969 #ifdef USE_FACTORIZED_EOS
970 rfresh =
971 & eosF1 +
972 & t1* ( eosF2 +
973 & t1* ( eosF3 +
974 & t1* ( eosF4 +
975 & t1* ( eosF5 +
976 & t1* eosF6 ))))
977 #else
978 rfresh =
979 & eosJMDCFw(1)
980 & + eosJMDCFw(2)*t1
981 & + eosJMDCFw(3)*t2
982 & + eosJMDCFw(4)*t3
983 & + eosJMDCFw(5)*t4
984 & + eosJMDCFw(6)*t4*t1
985 #endif /* USE_FACTORIZED_EOS */
986 C density of sea water at the surface
987 #ifdef USE_FACTORIZED_EOS
988 rsalt = s1 * ( eosS1 +
989 & t1 * ( eosS2 +
990 & t1 * ( eosS3 +
991 & t1 * ( eosS4 +
992 & t1 * eosS5 ))))
993 & + s3o2 * ( eosS6 +
994 & t1 * ( eosS7 +
995 & t1 * eosS8 ))
996 & + s1*s1* eosS9
997 #else
998 rsalt =
999 & s1*(
1000 & eosJMDCSw(1)
1001 & + eosJMDCSw(2)*t1
1002 & + eosJMDCSw(3)*t2
1003 & + eosJMDCSw(4)*t3
1004 & + eosJMDCSw(5)*t4
1005 & )
1006 & + s3o2*(
1007 & eosJMDCSw(6)
1008 & + eosJMDCSw(7)*t1
1009 & + eosJMDCSw(8)*t2
1010 & )
1011 & + eosJMDCSw(9)*s1*s1
1012 #endif /* USE_FACTORIZED_EOS */
1013
1014 rhoP0 = rfresh + rsalt
1015
1016 C secant bulk modulus of fresh water at the surface
1017 #ifdef USE_FACTORIZED_EOS
1018 bMfresh = eosF1 +
1019 & t1 * ( eosF2 +
1020 & t1 * ( eosF3 +
1021 & t1 * ( eosF4 +
1022 & t1 * eosF5 )))
1023 #else
1024 bMfresh =
1025 & eosJMDCKFw(1)
1026 & + eosJMDCKFw(2)*t1
1027 & + eosJMDCKFw(3)*t2
1028 & + eosJMDCKFw(4)*t3
1029 & + eosJMDCKFw(5)*t4
1030 #endif /* USE_FACTORIZED_EOS */
1031 C secant bulk modulus of sea water at the surface
1032 #ifdef USE_FACTORIZED_EOS
1033 bMsalt = s1 * ( eosS1 +
1034 & t1 * ( eosS2 +
1035 & t1 * ( eosS3 +
1036 & t1 * eosS4 )))
1037 & + s3o2 * ( eosS5 +
1038 & t1 * ( eosS6 +
1039 & t1 * eosS7 ))
1040 C secant bulk modulus of sea water at pressure p
1041 bMpres = p1 * ( eosP1 +
1042 & t1 * ( eosP2 +
1043 & t1 * ( eosP3 +
1044 & t1 * eosP4 )))
1045 & + p1*s1*( eosP5 +
1046 & t1 * ( eosP6 +
1047 & t1 * eosP7 ))
1048 & + p1*s3o2*eosP8
1049 & + p2 * ( eosP9 +
1050 & t1 * ( eosP10 +
1051 & t1 * eosP11 ))
1052 & + p2*s1* ( eosP12 +
1053 & t1 * ( eosP13 +
1054 & t1 * eosP14 ))
1055 #else
1056 C secant bulk modulus of sea water at the surface
1057 bMsalt =
1058 & s1*( eosJMDCKSw(1)
1059 & + eosJMDCKSw(2)*t1
1060 & + eosJMDCKSw(3)*t2
1061 & + eosJMDCKSw(4)*t3
1062 & )
1063 & + s3o2*( eosJMDCKSw(5)
1064 & + eosJMDCKSw(6)*t1
1065 & + eosJMDCKSw(7)*t2
1066 & )
1067 C secant bulk modulus of sea water at pressure p
1068 bMpres =
1069 & p1*( eosJMDCKP(1)
1070 & + eosJMDCKP(2)*t1
1071 & + eosJMDCKP(3)*t2
1072 & + eosJMDCKP(4)*t3
1073 & )
1074 & + p1*s1*( eosJMDCKP(5)
1075 & + eosJMDCKP(6)*t1
1076 & + eosJMDCKP(7)*t2
1077 & )
1078 & + p1*s3o2*eosJMDCKP(8)
1079 & + p2*( eosJMDCKP(9)
1080 & + eosJMDCKP(10)*t1
1081 & + eosJMDCKP(11)*t2
1082 & )
1083 & + p2*s1*( eosJMDCKP(12)
1084 & + eosJMDCKP(13)*t1
1085 & + eosJMDCKP(14)*t2
1086 & )
1087 #endif /* USE_FACTORIZED_EOS */
1088
1089 bulkMod = bMfresh + bMsalt + bMpres
1090
1091 C density of sea water at pressure p
1092 rhoLoc = rhoP0/(1. _d 0 - p1/bulkMod)
1093
1094 ELSEIF ( equationOfState.EQ.'MDJWF' ) THEN
1095
1096 sp5 = SQRT(s1)
1097
1098 p1 = pLoc*SItodBar
1099 p1t1 = p1*t1
1100
1101 rhoNum = eosMDJWFnum(0)
1102 & + t1*(eosMDJWFnum(1)
1103 & + t1*(eosMDJWFnum(2) + eosMDJWFnum(3)*t1) )
1104 & + s1*(eosMDJWFnum(4)
1105 & + eosMDJWFnum(5)*t1 + eosMDJWFnum(6)*s1)
1106 & + p1*(eosMDJWFnum(7) + eosMDJWFnum(8)*t2
1107 & + eosMDJWFnum(9)*s1
1108 & + p1*(eosMDJWFnum(10) + eosMDJWFnum(11)*t2) )
1109
1110 den = eosMDJWFden(0)
1111 & + t1*(eosMDJWFden(1)
1112 & + t1*(eosMDJWFden(2)
1113 & + t1*(eosMDJWFden(3) + t1*eosMDJWFden(4) ) ) )
1114 & + s1*(eosMDJWFden(5)
1115 & + t1*(eosMDJWFden(6)
1116 & + eosMDJWFden(7)*t2)
1117 & + sp5*(eosMDJWFden(8) + eosMDJWFden(9)*t2) )
1118 & + p1*(eosMDJWFden(10)
1119 & + p1t1*(eosMDJWFden(11)*t2 + eosMDJWFden(12)*p1) )
1120
1121 rhoDen = 1.0/(epsln+den)
1122
1123 rhoLoc = rhoNum*rhoDen
1124
1125 ELSEIF( equationOfState .EQ. 'TEOS10' ) THEN
1126
1127 ct = tLoc
1128 sa = sLoc
1129 IF ( sa .GT. 0. _d 0 ) THEN
1130 sqrtsa = SQRT(sa)
1131 ELSE
1132 sa = 0. _d 0
1133 sqrtsa = 0. _d 0
1134 ENDIF
1135 p = pLoc*SItodBar
1136
1137 rhoNum = teos(01)
1138 & + ct*(teos(02) + ct*(teos(03) + teos(04)*ct))
1139 & + sa*(teos(05) + ct*(teos(06) + teos(07)*ct)
1140 & + sqrtsa*(teos(08) + ct*(teos(09)
1141 & + ct*(teos(10) + teos(11)*ct))))
1142 & + p*(teos(12) + ct*(teos(13) + teos(14)*ct)
1143 & + sa*(teos(15) + teos(16)*ct)
1144 & + p*(teos(17) + ct*(teos(18) + teos(19)*ct) + teos(20)*sa))
1145
1146 den = teos(21)
1147 & + ct*(teos(22) + ct*(teos(23) + ct*(teos(24) + teos(25)*ct)))
1148 & + sa*(teos(26) + ct*(teos(27) + ct*(teos(28)
1149 & + ct*(teos(29) + teos(30)*ct)))
1150 & + teos(36)*sa
1151 % + sqrtsa*(teos(31) + ct*(teos(32) + ct*(teos(33)
1152 & + ct*(teos(34) + teos(35)*ct)))))
1153 % + p*(teos(37) + ct*(teos(38) + ct*(teos(39) + teos(40)*ct))
1154 % + sa*(teos(41) + teos(42)*ct)
1155 % + p*(teos(43) + ct*(teos(44) + teos(45)*ct + teos(46)*sa)
1156 % + p*(teos(47) + teos(48)*ct)))
1157
1158 rhoDen = 1.0/(epsln+den)
1159
1160 rhoLoc = rhoNum*rhoDen
1161
1162 ELSEIF( equationOfState .EQ. 'IDEALG' ) THEN
1163
1164 oneMinusKap = oneRL - atm_kappa
1165 C rho = P/(R*T_v) = Po/(R*theta_v)*(P/Po)^(1-kappa)
1166 facPres = ( pLoc/atm_Po )**oneMinusKap
1167 theta_v = tLoc*( sLoc*atm_Rq + oneRL )
1168 rhoLoc = atm_Po*facPres /( atm_Rd*theta_v )
1169
1170 ELSE
1171 WRITE(msgBuf,'(3A)')
1172 & ' FIND_RHO_SCALAR : equationOfState = "',
1173 & equationOfState,'"'
1174 CALL PRINT_ERROR( msgBuf, myThid )
1175 STOP 'ABNORMAL END: S/R FIND_RHO_SCALAR'
1176 ENDIF
1177
1178 RETURN
1179 END
1180
1181 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
1182 CBOP
1183 C !ROUTINE: LOOK_FOR_NEG_SALINITY
1184 C !INTERFACE:
1185 SUBROUTINE LOOK_FOR_NEG_SALINITY(
1186 I iMin, iMax, jMin, jMax,
1187 U sFld,
1188 I k, bi, bj, myThid )
1189
1190 C !DESCRIPTION: \bv
1191 C *==========================================================*
1192 C | o SUBROUTINE LOOK_FOR_NEG_SALINITY
1193 C | looks for and fixes negative salinity values
1194 C | this is necessary IF the equation of state uses
1195 C | the square root of salinity
1196 C *==========================================================*
1197 C | k - is the Salt level
1198 C *==========================================================*
1199 C \ev
1200
1201 C !USES:
1202 IMPLICIT NONE
1203 C == Global variables ==
1204 #include "SIZE.h"
1205 #include "EEPARAMS.h"
1206 #include "PARAMS.h"
1207
1208 C !INPUT/OUTPUT PARAMETERS:
1209 C == Routine arguments ==
1210 C k :: Level of Salt slice
1211 INTEGER iMin,iMax,jMin,jMax
1212 _RL sFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
1213 INTEGER k, bi, bj
1214 INTEGER myThid
1215
1216 C !LOCAL VARIABLES:
1217 C == Local variables ==
1218 INTEGER i,j, localWarning
1219 CHARACTER*(MAX_LEN_MBUF) msgBuf
1220 CEOP
1221
1222 localWarning = 0
1223 DO j=jMin,jMax
1224 DO i=iMin,iMax
1225 C abbreviations
1226 IF ( sFld(i,j) .LT. 0. _d 0 ) THEN
1227 localWarning = localWarning + 1
1228 sFld(i,j) = 0. _d 0
1229 ENDIF
1230 ENDDO
1231 ENDDO
1232 C issue a warning
1233 IF ( localWarning .GT. 0 ) THEN
1234 WRITE(msgBuf,'(2A,I5,A,2I4)') 'S/R LOOK_FOR_NEG_SALINITY:',
1235 & ' from level k =', k, ' ; bi,bj =', bi, bj
1236 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1237 & SQUEEZE_RIGHT , myThid )
1238 WRITE(msgBuf,'(2A,I6,A)') 'S/R LOOK_FOR_NEG_SALINITY:',
1239 & ' reset to zero', localWarning, ' negative salinity.'
1240 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1241 & SQUEEZE_RIGHT , myThid )
1242 ENDIF
1243
1244 RETURN
1245 END

  ViewVC Help
Powered by ViewVC 1.1.22