[3526] | 1 | ! |
---|
| 2 | ! $Id: calcaerosolstrato_rrtm.f90 5559 2025-02-24 14:39:32Z lebasn $ |
---|
| 3 | ! |
---|
[2690] | 4 | SUBROUTINE calcaerosolstrato_rrtm(pplay,t_seri,paprs,debut) |
---|
| 5 | |
---|
[5282] | 6 | USE clesphys_mod_h |
---|
| 7 | USE iniprint_mod_h |
---|
[2690] | 8 | USE phys_state_var_mod, ONLY: tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, tau_aero_lw_rrtm |
---|
[2715] | 9 | USE phys_local_var_mod, ONLY: mdw, tausum_aero, tausum_strat, tau_strat_550, tau_strat_1020, stratomask |
---|
[2690] | 10 | USE aero_mod |
---|
| 11 | USE dimphy |
---|
[5338] | 12 | ! USE temps_mod |
---|
[5264] | 13 | USE yomcst_mod_h |
---|
[2690] | 14 | |
---|
[5338] | 15 | !USE paramet_mod_h |
---|
[5271] | 16 | IMPLICIT NONE |
---|
[2690] | 17 | |
---|
[5271] | 18 | |
---|
[5272] | 19 | |
---|
[2690] | 20 | |
---|
| 21 | ! Variable input |
---|
| 22 | REAL,DIMENSION(klon,klev),INTENT(IN) :: t_seri ! Temperature |
---|
| 23 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pplay ! pression pour le mileu de chaque couche (en Pa) |
---|
| 24 | LOGICAL,INTENT(IN) :: debut ! le flag de l'initialisation de la physique |
---|
| 25 | REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs ! pression pour chaque inter-couche (en Pa) |
---|
| 26 | |
---|
| 27 | ! Stratospheric aerosols optical properties |
---|
| 28 | REAL, DIMENSION(klon,klev,nbands_sw_rrtm) :: tau_strat, piz_strat, cg_strat |
---|
| 29 | REAL, DIMENSION(klon,klev,nwave_sw+nwave_lw) :: tau_strat_wave |
---|
| 30 | REAL, DIMENSION(klon,klev,nbands_lw_rrtm) :: tau_lw_abs_rrtm |
---|
| 31 | |
---|
| 32 | INTEGER k, band, wave, i |
---|
| 33 | REAL zrho, zdz |
---|
| 34 | |
---|
| 35 | !--calculate optical properties of the aerosol size distribution from tr_seri |
---|
| 36 | tau_strat=0.0 |
---|
| 37 | piz_strat=0.0 |
---|
| 38 | cg_strat=0.0 |
---|
| 39 | tau_strat_wave=0.0 |
---|
| 40 | tau_lw_abs_rrtm=0.0 |
---|
[5559] | 41 | |
---|
| 42 | !-- init tau_strat vars |
---|
| 43 | tau_strat_550(:,:) =0.0 |
---|
| 44 | tau_strat_1020(:,:)=0.0 |
---|
| 45 | |
---|
[2690] | 46 | CALL miecalc_aer(tau_strat, piz_strat, cg_strat, tau_strat_wave, tau_lw_abs_rrtm, paprs, debut) |
---|
| 47 | |
---|
| 48 | !--total vertical aod at the 5 SW + 1 LW wavelengths |
---|
| 49 | DO wave=1, nwave_sw+nwave_lw |
---|
| 50 | DO k=1, klev |
---|
| 51 | tausum_aero(:,wave,id_STRAT_phy)=tausum_aero(:,wave,id_STRAT_phy)+tau_strat_wave(:,k,wave) |
---|
| 52 | ENDDO |
---|
| 53 | ENDDO |
---|
| 54 | |
---|
| 55 | !--weighted average for cg, piz and tau, adding strat aerosols on top of tropospheric ones |
---|
| 56 | DO band=1, nbands_sw_rrtm |
---|
| 57 | !--no stratospheric aerosol in index 1 |
---|
| 58 | cg_aero_sw_rrtm(:,:,1,band) = cg_aero_sw_rrtm(:,:,2,band) |
---|
| 59 | piz_aero_sw_rrtm(:,:,1,band) = piz_aero_sw_rrtm(:,:,2,band) |
---|
| 60 | tau_aero_sw_rrtm(:,:,1,band) = tau_aero_sw_rrtm(:,:,2,band) |
---|
| 61 | |
---|
| 62 | !--tropospheric and stratospheric aerosol in index 2 |
---|
| 63 | cg_aero_sw_rrtm(:,:,2,band) = ( cg_aero_sw_rrtm(:,:,2,band)*piz_aero_sw_rrtm(:,:,2,band)*tau_aero_sw_rrtm(:,:,2,band) + & |
---|
| 64 | cg_strat(:,:,band)*piz_strat(:,:,band)*tau_strat(:,:,band) ) / & |
---|
| 65 | MAX( piz_aero_sw_rrtm(:,:,2,band)*tau_aero_sw_rrtm(:,:,2,band) + & |
---|
| 66 | piz_strat(:,:,band)*tau_strat(:,:,band), 1.e-15 ) |
---|
| 67 | piz_aero_sw_rrtm(:,:,2,band)= ( piz_aero_sw_rrtm(:,:,2,band)*tau_aero_sw_rrtm(:,:,2,band) + & |
---|
| 68 | piz_strat(:,:,band)*tau_strat(:,:,band) ) / & |
---|
| 69 | MAX( tau_aero_sw_rrtm(:,:,2,band) + tau_strat(:,:,band), 1.e-15 ) |
---|
| 70 | tau_aero_sw_rrtm(:,:,2,band)= tau_aero_sw_rrtm(:,:,2,band) + tau_strat(:,:,band) |
---|
| 71 | ENDDO |
---|
| 72 | |
---|
| 73 | DO band=1, nbands_lw_rrtm |
---|
| 74 | !--no stratospheric aerosols in index 1 |
---|
| 75 | tau_aero_lw_rrtm(:,:,1,band) = tau_aero_lw_rrtm(:,:,2,band) |
---|
| 76 | !--tropospheric and stratospheric aerosol in index 2 |
---|
| 77 | tau_aero_lw_rrtm(:,:,2,band) = tau_aero_lw_rrtm(:,:,2,band) + tau_lw_abs_rrtm(:,:,band) |
---|
| 78 | ENDDO |
---|
| 79 | |
---|
| 80 | WHERE (tau_aero_sw_rrtm .LT. 1.e-14) piz_aero_sw_rrtm=1.0 |
---|
| 81 | WHERE (tau_aero_sw_rrtm .LT. 1.e-14) tau_aero_sw_rrtm=1.e-15 |
---|
| 82 | WHERE (tau_aero_lw_rrtm .LT. 1.e-14) tau_aero_lw_rrtm=1.e-15 |
---|
| 83 | |
---|
| 84 | tausum_strat(:,:)=0.0 |
---|
| 85 | DO i=1,klon |
---|
| 86 | DO k=1,klev |
---|
[2715] | 87 | IF (stratomask(i,k).GT.0.5) THEN |
---|
[2690] | 88 | tausum_strat(i,1)=tausum_strat(i,1)+tau_strat_wave(i,k,2) !--550 nm |
---|
| 89 | tausum_strat(i,2)=tausum_strat(i,2)+tau_strat_wave(i,k,5) !--1020 nm |
---|
| 90 | tausum_strat(i,3)=tausum_strat(i,3)+tau_strat_wave(i,k,6) !--10 um |
---|
| 91 | ENDIF |
---|
| 92 | ENDDO |
---|
| 93 | ENDDO |
---|
| 94 | |
---|
| 95 | DO i=1,klon |
---|
| 96 | DO k=1,klev |
---|
| 97 | zrho=pplay(i,k)/t_seri(i,k)/RD !air density in kg/m3 |
---|
| 98 | zdz=(paprs(i,k)-paprs(i,k+1))/zrho/RG !thickness of layer in m |
---|
| 99 | tau_strat_550(i,k)=tau_strat_wave(i,k,2)/zdz |
---|
[3660] | 100 | tau_strat_1020(i,k)=tau_strat_wave(i,k,5)/zdz |
---|
[2690] | 101 | ENDDO |
---|
| 102 | ENDDO |
---|
| 103 | |
---|
| 104 | END SUBROUTINE calcaerosolstrato_rrtm |
---|