source: LMDZ6/trunk/libf/phylmd/Dust/gastoparticle.f90 @ 5354

Last change on this file since 5354 was 5337, checked in by Laurent Fairhead, 3 weeks ago

Getting rid of dependance to dynamics

File size: 2.5 KB
Line 
1SUBROUTINE gastoparticle(pdtphys,zdz,zrho,xlat,pplay,t_seri, &
2        id_prec,id_fine, &
3        tr_seri,his_g2pgas ,his_g2paer )
4  !nhl     .                         fluxso4chem, flux_sparam_sulf,
5
6USE chem_spla_mod_h
7  USE chem_mod_h
8  USE yoecumf_mod_h
9    USE dimphy
10  USE infotrac_phy, ONLY: nbtr
11   ! USE indice_sol_mod
12
13USE yomcst_mod_h
14IMPLICIT NONE
15  !
16
17
18  !
19  REAL :: pdtphys
20  REAL :: zrho(klon,klev)
21  REAL :: zdz(klon,klev)
22  REAL :: tr_seri(klon,klev,nbtr)   ! traceurs
23  REAL :: tend                 ! tendance par espece
24  REAL :: xlat(klon)       ! latitudes pour chaque point
25  REAL :: pi
26  !   JE: 20140120
27  REAL :: his_g2pgas(klon)
28  REAL :: his_g2paer(klon)
29  REAL :: tendincm3(klon,klev)
30  REAL :: tempvar(klon,klev)
31  REAL :: pplay(klon,klev)
32  REAL :: t_seri(klon,klev)
33  REAL :: tend2d(klon,klev)
34  INTEGER :: id_prec,id_fine
35  !
36  !------------------------- Scaling Parameter --------------------------
37  !
38  !  REAL scale_param_so4(klon)  !Scaling parameter for sulfate
39
40  INTEGER :: i, k
41  REAL :: tau_chem     !---chemical lifetime in s
42  !
43  !------------------------- Variables to save --------------------------
44  !
45  !nhl      REAL fluxso4chem(klon,klev)
46  !nhl      REAL flux_sparam_sulf(klon,klev)
47
48  !======================================================================
49  pi=atan(1.)*4.
50  !
51  IF (id_prec>0 .AND. id_fine>0) THEN
52  DO k = 1, klev
53  DO i = 1, klon
54  !
55  !    tau_chem=scale_param_so4(i)*86400.*(8.-5.*cos(xlat(i)*pi/180.))    !tchemfctn2
56  !nhl        tau_chem=86400.*(8.-5.*cos(xlat(i)*pi/180.))    !tchemfctn2
57    tau_chem=86400.*(5.-4.*cos(xlat(i)*pi/180.))    !
58    tend=tr_seri(i,k,id_prec)*(1.-exp(-pdtphys/tau_chem)) ! Sulfate production
59  !nhl        tend=(1.-exp(-pdtphys/tau_chem))
60  !nhl        tend=scale_param_so4(i) !as this it works
61  !
62    tr_seri(i,k,id_prec) =tr_seri(i,k,id_prec) - tend
63    tr_seri(i,k,id_fine) =tr_seri(i,k,id_fine) + &
64          tend/RNAVO*masse_ammsulfate  !--gAER/KgAir
65    tend2d(i,k)=tend
66  !
67  !nhl        fluxso4chem(i,k) = tend/RNAVO*masse_ammsulfate
68  !nhl        flux_sparam_sulf(i,k) = tend/RNAVO*masse_ammsulfate
69  ENDDO
70  ENDDO
71
72
73
74    tempvar=tend2d
75     CALL kg_to_cm3(pplay,t_seri,tempvar)
76    tendincm3=tempvar
77
78  DO k = 1, klev
79  DO i = 1, klon
80
81     ! his_g2pgas(i) = his_g2pgas(i) + tendincm3(i,k)*1e6*zdz(i,k)/pdtphys
82    his_g2paer(i) = his_g2paer(i) + &
83          tendincm3(i,k)/RNAVO*masse_ammsulfate*1.e3* &
84          1.e6*zdz(i,k)/pdtphys    ! mg/m2/s
85    his_g2pgas(i) = his_g2paer(i)*masse_s/masse_ammsulfate ! mg-S/m2/s
86
87  ENDDO
88  ENDDO
89  ENDIF
90
91  !
92  RETURN
93END SUBROUTINE gastoparticle
Note: See TracBrowser for help on using the repository browser.