! Subroutine that estimates the Deposition velocities and the depostion ! for the different tracers subroutine deposition(vdep_oce,vdep_sic,vdep_ter,vdep_lic,pctsrf, & zrho,zdz,pdtphys,RHcl,masse,t_seri,pplay, & paprs,lminmax,qmin,qmax, & his_ds,source_tr,tr_seri) USE dimphy USE infotrac USE indice_sol_mod USE dimensions_mod, ONLY: iim, jjm, llm, ndm USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, & ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO & , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA & , R_ecc, R_peri, R_incl & , RA, RG, R1SA & , RSIGMA & , R, RMD, RMV, RD, RV, RCPD & , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12 & , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w & , RCW, RCS & , RLVTT, RLSTT, RLMLT, RTT, RATM & , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS & , RALPD, RBETD, RGAMD IMPLICIT NONE INCLUDE "chem.h" !----------------------------- INPUT ----------------------------------- LOGICAL :: lminmax REAL :: qmin, qmax REAL :: vdep_oce(nbtr), vdep_sic(nbtr) REAL :: vdep_ter(nbtr), vdep_lic(nbtr) REAL :: pctsrf(klon,nbsrf) REAL :: zrho(klon,klev) !Density of air at mid points of Z (kg/m3) REAL :: zdz(klon,klev) REAL :: pdtphys ! pas d'integration pour la physique (seconde) REAL :: RHcl(klon,klev) ! humidite relativen ciel clair REAL :: t_seri(klon,klev) ! temperature REAL :: pplay(klon,klev) ! pression pour le mileu de chaque couche (en Pa) REAL :: paprs(klon, klev+1) !pressure at interface of layers Z (Pa) REAL :: masse(nbtr) !----------------------------- OUTPUT ---------------------------------- REAL :: his_ds(klon,nbtr) REAL :: source_tr(klon,nbtr) REAL :: tr_seri(klon, klev,nbtr) !conc of tracers !--------------------- INTERNAL VARIABLES ------------------------------ INTEGER :: i, it REAL :: vdep !sed. velocity DO it=1, nbtr DO i=1, klon vdep=vdep_oce(it)*pctsrf(i,is_oce)+ & vdep_sic(it)*pctsrf(i,is_sic)+ & vdep_ter(it)*pctsrf(i,is_ter)+ & vdep_lic(it)*pctsrf(i,is_lic) !--Unit: molec/m2/s for it=1 to nbtr-3, mg/m2/s for it=nbtr-2 to nbtr source_tr(i,it)=source_tr(i,it) & -vdep*tr_seri(i,1,it)*zrho(i,1)/1.e2 his_ds(i,it)=vdep*tr_seri(i,1,it)*zrho(i,1)/1.e2 & /RNAVO*masse(it)*1.e3 ! mg/m2/s ENDDO ENDDO ! END SUBROUTINE deposition