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