source: LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/deposition.f90 @ 5159

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

Put dimensions.h and paramet.h into modules

File size: 2.0 KB
Line 
1! Subroutine that estimates the Deposition velocities and the depostion
2! for the different tracers
3SUBROUTINE 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)
7
8  USE dimphy
9  USE infotrac
10  USE indice_sol_mod
11  USE lmdz_yomcst
12
13USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
14  USE lmdz_paramet
15  IMPLICIT NONE
16
17
18  INCLUDE "chem.h"
19
20
21  !----------------------------- INPUT -----------------------------------
22  LOGICAL :: lminmax
23  REAL :: qmin, qmax
24  REAL :: vdep_oce(nbtr), vdep_sic(nbtr)
25  REAL :: vdep_ter(nbtr), vdep_lic(nbtr)
26  REAL :: pctsrf(klon, nbsrf)
27  REAL :: zrho(klon, klev)        !Density of air at mid points of Z (kg/m3)
28  REAL :: zdz(klon, klev)
29  REAL :: pdtphys  ! pas d'integration pour la physique (seconde)
30  REAL :: RHcl(klon, klev)  ! humidite relativen ciel clair
31  REAL :: t_seri(klon, klev)  ! temperature
32  REAL :: pplay(klon, klev)  ! pression pour le mileu de chaque couche (en Pa)
33  REAL :: paprs(klon, klev + 1)    !pressure at interface of layers Z (Pa)
34  REAL :: masse(nbtr)
35
36  !----------------------------- OUTPUT ----------------------------------
37  REAL :: his_ds(klon, nbtr)
38  REAL :: source_tr(klon, nbtr)
39  REAL :: tr_seri(klon, klev, nbtr) !conc of tracers
40  !--------------------- INTERNAL VARIABLES ------------------------------
41  INTEGER :: i, it
42  REAL :: vdep        !sed. velocity
43
44  DO it = 1, nbtr
45    DO i = 1, klon
46      vdep = vdep_oce(it) * pctsrf(i, is_oce) + &
47              vdep_sic(it) * pctsrf(i, is_sic) + &
48              vdep_ter(it) * pctsrf(i, is_ter) + &
49              vdep_lic(it) * pctsrf(i, is_lic)
50      !--Unit: molec/m2/s for it=1 to nbtr-3, mg/m2/s for it=nbtr-2 to nbtr
51      source_tr(i, it) = source_tr(i, it) &
52              - vdep * tr_seri(i, 1, it) * zrho(i, 1) / 1.e2
53      his_ds(i, it) = vdep * tr_seri(i, 1, it) * zrho(i, 1) / 1.e2 &
54              / RNAVO * masse(it) * 1.e3               ! mg/m2/s
55    ENDDO
56  ENDDO
57
58END SUBROUTINE deposition
Note: See TracBrowser for help on using the repository browser.