source: LMDZ6/trunk/libf/phylmd/Dust/nightingale.f90 @ 5277

Last change on this file since 5277 was 5274, checked in by abarral, 9 hours ago

Replace yomcst.h by existing module

File size: 3.3 KB
Line 
1SUBROUTINE 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  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
8USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
9          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
10          , R_ecc, R_peri, R_incl                                      &
11          , RA, RG, R1SA                                         &
12          , RSIGMA                                                     &
13          , R, RMD, RMV, RD, RV, RCPD                    &
14          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
15          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
16          , RCW, RCS                                                 &
17          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
18          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
19          , RALPD, RBETD, RGAMD
20IMPLICIT NONE
21  !
22
23
24  !
25  REAL :: u(klon,klev), v(klon,klev)
26  REAL :: u_10m(klon), v_10m(klon)
27  REAL :: ftsol(klon,nbsrf)
28  REAL :: tsol(klon)
29  REAL :: paprs(klon,klev+1), pplay(klon,klev)
30  REAL :: t(klon,klev)
31  REAL :: q(klon,klev)
32  REAL :: cdragh(klon), cdragm(klon)
33  REAL :: pctsrf(klon,nbsrf)
34  REAL :: lmt_dmsconc(klon)  ! concentration oceanique DMS
35  REAL :: lmt_dms(klon)      ! flux de DMS
36  !
37  REAL :: ustar(klon), obklen(klon)
38  REAL :: u10(klon), u10n(klon)
39  REAL :: tvelocity, schmidt_corr
40  REAL :: t1, t2, t3, t4, viscosity_kin, diffusivity, schmidt
41  INTEGER :: i
42  !
43  CALL bl_for_dms(u, v, paprs, pplay, cdragh, cdragm, &
44        t, q, tsol, ustar, obklen)
45  !
46  DO i=1,klon
47    u10(i)=SQRT(u_10m(i)**2+v_10m(i)**2)
48  ENDDO
49  !
50  CALL neutral(u10, ustar, obklen, u10n)
51  !
52  DO i=1,klon
53  !
54  ! tvelocity - transfer velocity, also known as kw (cm/s)
55  ! schmidt_corr - Schmidt number correction factor (dimensionless)
56  ! Reference:  Nightingale, P.D., G. Malin, C. S. Law, J. J. Watson, P.S. Liss
57  !  M. I. Liddicoat, J. Boutin, R.C. Upstill-Goddard. 'In situ evaluation
58  !  of air-sea gas exchange parameterizations using conservative and
59  !  volatile tracers.'  Glob. Biogeochem. Cycles, 14:373-387, 2000.
60  ! compute transfer velocity using u10neutral
61  !
62  tvelocity = 0.222*u10n(i)*u10n(i) + 0.333*u10n(i)
63  !
64  ! above expression gives tvelocity in cm/hr. convert to cm/s. 1hr =3600 sec
65
66  tvelocity = tvelocity / 3600.
67
68  ! compute the correction factor, which for Nightingale parameterization is
69  ! based on how different the schmidt number is from 600.
70  ! correction factor based on temperature in Kelvin. good
71  ! only for t<=30 deg C.  for temperatures above that, set correction factor
72  ! equal to value at 30 deg C.
73
74  IF (ftsol(i,is_oce) .LE. 303.15) THEN
75     t1 = ftsol(i,is_oce)
76  ELSE
77     t1 = 303.15
78  ENDIF
79
80  t2 = t1 * t1
81  t3 = t2 * t1
82  t4 = t3 * t1
83  viscosity_kin = 3.0363e-9*t4 - 3.655198e-6*t3 + 1.65333e-3*t2 &
84        - 3.332083e-1*t1 + 25.26819
85  diffusivity = 0.01922 * exp(-2177.1/t1)
86  schmidt = viscosity_kin / diffusivity
87  schmidt_corr = (schmidt/600.)**(-.5)
88  !
89  lmt_dms(i) = tvelocity  *  pctsrf(i,is_oce) &
90        * lmt_dmsconc(i)/1.0e12 * schmidt_corr * RNAVO
91  !
92  IF (lmt_dmsconc(i).LE.1.e-20) lmt_dms(i)=0.0
93  !
94  ENDDO
95  !
96END SUBROUTINE nightingale
Note: See TracBrowser for help on using the repository browser.