[5104] | 1 | ! Subroutine that estimates the Deposition velocities and the depostion |
---|
| 2 | ! for the different tracers |
---|
| 3 | SUBROUTINE deposition(vdep_oce, vdep_sic, vdep_ter, vdep_lic, pctsrf, & |
---|
| 4 | zrho, zdz, pdtphys, RHcl, masse, t_seri, pplay, & |
---|
| 5 | paprs, lminmax, qmin, qmax, & |
---|
| 6 | his_ds, source_tr, tr_seri) |
---|
[2630] | 7 | |
---|
[5104] | 8 | USE dimphy |
---|
[5182] | 9 | USE lmdz_infotrac |
---|
[5104] | 10 | USE indice_sol_mod |
---|
[5144] | 11 | USE lmdz_yomcst |
---|
[2630] | 12 | |
---|
[5159] | 13 | USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm |
---|
| 14 | USE lmdz_paramet |
---|
[5160] | 15 | USE lmdz_chem, ONLY: idms, iso2, iso4, ih2s, idmso, imsa, ih2o2, & |
---|
| 16 | n_avogadro, masse_s, masse_so4, rho_water, rho_ice |
---|
[5104] | 17 | IMPLICIT NONE |
---|
[2630] | 18 | |
---|
[5159] | 19 | |
---|
[2630] | 20 | |
---|
[5159] | 21 | |
---|
[5160] | 22 | |
---|
[5104] | 23 | !----------------------------- INPUT ----------------------------------- |
---|
| 24 | LOGICAL :: lminmax |
---|
| 25 | REAL :: qmin, qmax |
---|
| 26 | REAL :: vdep_oce(nbtr), vdep_sic(nbtr) |
---|
| 27 | REAL :: vdep_ter(nbtr), vdep_lic(nbtr) |
---|
| 28 | REAL :: pctsrf(klon, nbsrf) |
---|
| 29 | REAL :: zrho(klon, klev) !Density of air at mid points of Z (kg/m3) |
---|
| 30 | REAL :: zdz(klon, klev) |
---|
| 31 | REAL :: pdtphys ! pas d'integration pour la physique (seconde) |
---|
| 32 | REAL :: RHcl(klon, klev) ! humidite relativen ciel clair |
---|
| 33 | REAL :: t_seri(klon, klev) ! temperature |
---|
| 34 | REAL :: pplay(klon, klev) ! pression pour le mileu de chaque couche (en Pa) |
---|
| 35 | REAL :: paprs(klon, klev + 1) !pressure at interface of layers Z (Pa) |
---|
| 36 | REAL :: masse(nbtr) |
---|
[2630] | 37 | |
---|
[5104] | 38 | !----------------------------- OUTPUT ---------------------------------- |
---|
| 39 | REAL :: his_ds(klon, nbtr) |
---|
| 40 | REAL :: source_tr(klon, nbtr) |
---|
| 41 | REAL :: tr_seri(klon, klev, nbtr) !conc of tracers |
---|
| 42 | !--------------------- INTERNAL VARIABLES ------------------------------ |
---|
| 43 | INTEGER :: i, it |
---|
| 44 | REAL :: vdep !sed. velocity |
---|
| 45 | |
---|
| 46 | DO it = 1, nbtr |
---|
| 47 | DO i = 1, klon |
---|
| 48 | vdep = vdep_oce(it) * pctsrf(i, is_oce) + & |
---|
| 49 | vdep_sic(it) * pctsrf(i, is_sic) + & |
---|
| 50 | vdep_ter(it) * pctsrf(i, is_ter) + & |
---|
| 51 | vdep_lic(it) * pctsrf(i, is_lic) |
---|
| 52 | !--Unit: molec/m2/s for it=1 to nbtr-3, mg/m2/s for it=nbtr-2 to nbtr |
---|
| 53 | source_tr(i, it) = source_tr(i, it) & |
---|
| 54 | - vdep * tr_seri(i, 1, it) * zrho(i, 1) / 1.e2 |
---|
| 55 | his_ds(i, it) = vdep * tr_seri(i, 1, it) * zrho(i, 1) / 1.e2 & |
---|
| 56 | / RNAVO * masse(it) * 1.e3 ! mg/m2/s |
---|
| 57 | ENDDO |
---|
| 58 | ENDDO |
---|
[5159] | 59 | |
---|
[5104] | 60 | END SUBROUTINE deposition |
---|