[5104] | 1 | SUBROUTINE nightingale(u, v, u_10m, v_10m, paprs, pplay, & |
---|
| 2 | cdragh, cdragm, t, q, ftsol, tsol, & |
---|
| 3 | pctsrf, lmt_dmsconc, lmt_dms) |
---|
| 4 | ! |
---|
| 5 | USE dimphy |
---|
| 6 | USE indice_sol_mod |
---|
| 7 | IMPLICIT NONE |
---|
| 8 | ! |
---|
| 9 | INCLUDE "dimensions.h" |
---|
| 10 | INCLUDE "YOMCST.h" |
---|
| 11 | ! |
---|
| 12 | REAL :: u(klon, klev), v(klon, klev) |
---|
| 13 | REAL :: u_10m(klon), v_10m(klon) |
---|
| 14 | REAL :: ftsol(klon, nbsrf) |
---|
| 15 | REAL :: tsol(klon) |
---|
| 16 | REAL :: paprs(klon, klev + 1), pplay(klon, klev) |
---|
| 17 | REAL :: t(klon, klev) |
---|
| 18 | REAL :: q(klon, klev) |
---|
| 19 | REAL :: cdragh(klon), cdragm(klon) |
---|
| 20 | REAL :: pctsrf(klon, nbsrf) |
---|
| 21 | REAL :: lmt_dmsconc(klon) ! concentration oceanique DMS |
---|
| 22 | REAL :: lmt_dms(klon) ! flux de DMS |
---|
| 23 | ! |
---|
| 24 | REAL :: ustar(klon), obklen(klon) |
---|
| 25 | REAL :: u10(klon), u10n(klon) |
---|
| 26 | REAL :: tvelocity, schmidt_corr |
---|
| 27 | REAL :: t1, t2, t3, t4, viscosity_kin, diffusivity, schmidt |
---|
| 28 | INTEGER :: i |
---|
| 29 | ! |
---|
| 30 | CALL bl_for_dms(u, v, paprs, pplay, cdragh, cdragm, & |
---|
| 31 | t, q, tsol, ustar, obklen) |
---|
| 32 | ! |
---|
| 33 | DO i = 1, klon |
---|
| 34 | u10(i) = SQRT(u_10m(i)**2 + v_10m(i)**2) |
---|
| 35 | ENDDO |
---|
| 36 | ! |
---|
| 37 | CALL neutral(u10, ustar, obklen, u10n) |
---|
| 38 | ! |
---|
| 39 | DO i = 1, klon |
---|
| 40 | ! |
---|
| 41 | ! tvelocity - transfer velocity, also known as kw (cm/s) |
---|
| 42 | ! schmidt_corr - Schmidt number correction factor (dimensionless) |
---|
| 43 | ! Reference: Nightingale, P.D., G. Malin, C. S. Law, J. J. Watson, P.S. Liss |
---|
| 44 | ! M. I. Liddicoat, J. Boutin, R.C. Upstill-Goddard. 'In situ evaluation |
---|
| 45 | ! of air-sea gas exchange parameterizations using conservative and |
---|
| 46 | ! volatile tracers.' Glob. Biogeochem. Cycles, 14:373-387, 2000. |
---|
| 47 | ! compute transfer velocity using u10neutral |
---|
| 48 | ! |
---|
| 49 | tvelocity = 0.222 * u10n(i) * u10n(i) + 0.333 * u10n(i) |
---|
| 50 | ! |
---|
| 51 | ! above expression gives tvelocity in cm/hr. convert to cm/s. 1hr =3600 sec |
---|
[2630] | 52 | |
---|
[5104] | 53 | tvelocity = tvelocity / 3600. |
---|
[2630] | 54 | |
---|
[5104] | 55 | ! compute the correction factor, which for Nightingale parameterization is |
---|
| 56 | ! based on how different the schmidt number is from 600. |
---|
| 57 | ! correction factor based on temperature in Kelvin. good |
---|
| 58 | ! only for t<=30 deg C. for temperatures above that, set correction factor |
---|
| 59 | ! equal to value at 30 deg C. |
---|
[2630] | 60 | |
---|
[5104] | 61 | IF (ftsol(i, is_oce) <= 303.15) THEN |
---|
| 62 | t1 = ftsol(i, is_oce) |
---|
| 63 | ELSE |
---|
| 64 | t1 = 303.15 |
---|
| 65 | ENDIF |
---|
[2630] | 66 | |
---|
[5104] | 67 | t2 = t1 * t1 |
---|
| 68 | t3 = t2 * t1 |
---|
| 69 | t4 = t3 * t1 |
---|
| 70 | viscosity_kin = 3.0363e-9 * t4 - 3.655198e-6 * t3 + 1.65333e-3 * t2 & |
---|
| 71 | - 3.332083e-1 * t1 + 25.26819 |
---|
| 72 | diffusivity = 0.01922 * exp(-2177.1 / t1) |
---|
| 73 | schmidt = viscosity_kin / diffusivity |
---|
| 74 | schmidt_corr = (schmidt / 600.)**(-.5) |
---|
| 75 | ! |
---|
| 76 | lmt_dms(i) = tvelocity * pctsrf(i, is_oce) & |
---|
| 77 | * lmt_dmsconc(i) / 1.0e12 * schmidt_corr * RNAVO |
---|
| 78 | ! |
---|
| 79 | IF (lmt_dmsconc(i)<=1.e-20) lmt_dms(i) = 0.0 |
---|
| 80 | ! |
---|
| 81 | ENDDO |
---|
| 82 | ! |
---|
| 83 | END SUBROUTINE nightingale |
---|