source: LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/nightingale.f90 @ 5185

Last change on this file since 5185 was 5159, checked in by abarral, 5 months ago

Put dimensions.h and paramet.h into modules

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