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