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

Last change on this file since 5267 was 5246, checked in by abarral, 4 days ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

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