source: LMDZ6/trunk/libf/phylmd/Dust/deposition.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: 2.8 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
12  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
13USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
14          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
15USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
16          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
17          , R_ecc, R_peri, R_incl                                      &
18          , RA, RG, R1SA                                         &
19          , RSIGMA                                                     &
20          , R, RMD, RMV, RD, RV, RCPD                    &
21          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
22          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
23          , RCW, RCS                                                 &
24          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
25          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
26          , RALPD, RBETD, RGAMD
27IMPLICIT NONE
28
29
30  INCLUDE "chem.h"
31
32
33
34  !----------------------------- INPUT -----------------------------------
35  LOGICAL :: lminmax
36  REAL :: qmin, qmax
37  REAL :: vdep_oce(nbtr), vdep_sic(nbtr)
38  REAL :: vdep_ter(nbtr), vdep_lic(nbtr)
39  REAL :: pctsrf(klon,nbsrf)
40  REAL :: zrho(klon,klev)        !Density of air at mid points of Z (kg/m3)
41  REAL :: zdz(klon,klev)
42  REAL :: pdtphys  ! pas d'integration pour la physique (seconde)
43  REAL :: RHcl(klon,klev)  ! humidite relativen ciel clair
44  REAL :: t_seri(klon,klev)  ! temperature
45  REAL :: pplay(klon,klev)  ! pression pour le mileu de chaque couche (en Pa)
46  REAL :: paprs(klon, klev+1)    !pressure at interface of layers Z (Pa)
47  REAL :: masse(nbtr)
48
49  !----------------------------- OUTPUT ----------------------------------
50  REAL :: his_ds(klon,nbtr)
51  REAL :: source_tr(klon,nbtr)
52  REAL :: tr_seri(klon, klev,nbtr) !conc of tracers
53  !--------------------- INTERNAL VARIABLES ------------------------------
54  INTEGER :: i, it
55  REAL :: vdep        !sed. velocity
56
57  DO it=1, nbtr
58  DO i=1, klon
59      vdep=vdep_oce(it)*pctsrf(i,is_oce)+ &
60            vdep_sic(it)*pctsrf(i,is_sic)+ &
61            vdep_ter(it)*pctsrf(i,is_ter)+ &
62            vdep_lic(it)*pctsrf(i,is_lic)
63  !--Unit: molec/m2/s for it=1 to nbtr-3, mg/m2/s for it=nbtr-2 to nbtr
64      source_tr(i,it)=source_tr(i,it) &
65            -vdep*tr_seri(i,1,it)*zrho(i,1)/1.e2
66      his_ds(i,it)=vdep*tr_seri(i,1,it)*zrho(i,1)/1.e2 &
67            /RNAVO*masse(it)*1.e3               ! mg/m2/s
68  ENDDO
69  ENDDO
70  !
71END SUBROUTINE deposition
Note: See TracBrowser for help on using the repository browser.