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

Last change on this file since 5301 was 5292, checked in by abarral, 4 days ago

Move academic.h chem.h chem_spla.h to module

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