source: LMDZ5/trunk/libf/phylmd/StratAer/calcaerosolstrato_rrtm.F90 @ 2715

Last change on this file since 2715 was 2715, checked in by oboucher, 7 years ago

Fixing a small glitch in my StratAer? module
p_tropopause was used but not defined...
now it is diagnosed but not used !

File size: 4.5 KB
Line 
1SUBROUTINE calcaerosolstrato_rrtm(pplay,t_seri,paprs,debut)
2
3  USE infotrac, ONLY : nbtr
4  USE phys_state_var_mod, ONLY: tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, tau_aero_lw_rrtm
5  USE phys_local_var_mod, ONLY: mdw, tausum_aero, tausum_strat, tau_strat_550, tau_strat_1020, stratomask
6  USE aero_mod
7  USE dimphy
8  USE temps_mod
9  USE YOMCST
10
11  IMPLICIT NONE
12
13  INCLUDE "dimensions.h"
14  INCLUDE "clesphys.h"
15  INCLUDE "paramet.h"
16  INCLUDE "thermcell.h"
17  INCLUDE "iniprint.h"
18
19! Variable input
20  REAL,DIMENSION(klon,klev),INTENT(IN)   :: t_seri  ! Temperature
21  REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
22  LOGICAL,INTENT(IN)                     :: debut   ! le flag de l'initialisation de la physique
23  REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour chaque inter-couche (en Pa)
24
25! Stratospheric aerosols optical properties
26  REAL, DIMENSION(klon,klev,nbands_sw_rrtm) :: tau_strat, piz_strat, cg_strat
27  REAL, DIMENSION(klon,klev,nwave_sw+nwave_lw) :: tau_strat_wave
28  REAL, DIMENSION(klon,klev,nbands_lw_rrtm) :: tau_lw_abs_rrtm
29
30  INTEGER k, band, wave, i
31  REAL zrho, zdz
32
33!--calculate optical properties of the aerosol size distribution from tr_seri
34  tau_strat=0.0
35  piz_strat=0.0
36  cg_strat=0.0
37  tau_strat_wave=0.0
38  tau_lw_abs_rrtm=0.0
39
40  CALL miecalc_aer(tau_strat, piz_strat, cg_strat, tau_strat_wave, tau_lw_abs_rrtm, paprs, debut)
41
42!!--test CK: deactivate radiative effect of aerosol
43!  tau_strat=0.0
44!  piz_strat=0.0
45!  cg_strat=0.0
46!  tau_strat_wave=0.0
47!  tau_lw_abs_rrtm=0.0
48
49!--test CK: deactivate SW radiative effect of aerosol (but leave LW)
50!  tau_strat=0.0
51!  piz_strat=0.0
52!  cg_strat=0.0
53
54!  DO wave=1, nwave_sw
55!  tau_strat_wave(:,:,wave)=0.0
56!  ENDDO
57
58!--test CK: deactivate LW radiative effect of aerosol (but leave SW)
59!  tau_lw_abs_rrtm=0.0
60
61!  DO wave=nwave_sw+1, nwave_sw+nwave_lw
62!  tau_strat_wave(:,:,wave)=0.0
63!  ENDDO
64
65!--total vertical aod at the 5 SW + 1 LW wavelengths
66  DO wave=1, nwave_sw+nwave_lw
67    DO k=1, klev
68      tausum_aero(:,wave,id_STRAT_phy)=tausum_aero(:,wave,id_STRAT_phy)+tau_strat_wave(:,k,wave)
69    ENDDO
70  ENDDO
71
72!--weighted average for cg, piz and tau, adding strat aerosols on top of tropospheric ones
73  DO band=1, nbands_sw_rrtm
74    !--no stratospheric aerosol in index 1
75    cg_aero_sw_rrtm(:,:,1,band)  =  cg_aero_sw_rrtm(:,:,2,band)
76    piz_aero_sw_rrtm(:,:,1,band)  = piz_aero_sw_rrtm(:,:,2,band)
77    tau_aero_sw_rrtm(:,:,1,band)  = tau_aero_sw_rrtm(:,:,2,band)
78
79    !--tropospheric and stratospheric aerosol in index 2
80    cg_aero_sw_rrtm(:,:,2,band) = ( cg_aero_sw_rrtm(:,:,2,band)*piz_aero_sw_rrtm(:,:,2,band)*tau_aero_sw_rrtm(:,:,2,band) + &
81                                cg_strat(:,:,band)*piz_strat(:,:,band)*tau_strat(:,:,band) ) /                              &
82                                MAX( piz_aero_sw_rrtm(:,:,2,band)*tau_aero_sw_rrtm(:,:,2,band) +                            &
83                                piz_strat(:,:,band)*tau_strat(:,:,band), 1.e-15 )
84    piz_aero_sw_rrtm(:,:,2,band)= ( piz_aero_sw_rrtm(:,:,2,band)*tau_aero_sw_rrtm(:,:,2,band) +                             &
85                                piz_strat(:,:,band)*tau_strat(:,:,band) ) /                                                 &
86                                MAX( tau_aero_sw_rrtm(:,:,2,band) + tau_strat(:,:,band), 1.e-15 )
87    tau_aero_sw_rrtm(:,:,2,band)= tau_aero_sw_rrtm(:,:,2,band) + tau_strat(:,:,band)
88  ENDDO
89
90  DO band=1, nbands_lw_rrtm
91    !--no stratospheric aerosols in index 1
92    tau_aero_lw_rrtm(:,:,1,band)  = tau_aero_lw_rrtm(:,:,2,band)
93    !--tropospheric and stratospheric aerosol in index 2
94    tau_aero_lw_rrtm(:,:,2,band)  = tau_aero_lw_rrtm(:,:,2,band) + tau_lw_abs_rrtm(:,:,band)
95  ENDDO
96
97  WHERE (tau_aero_sw_rrtm .LT. 1.e-14) piz_aero_sw_rrtm=1.0
98  WHERE (tau_aero_sw_rrtm .LT. 1.e-14) tau_aero_sw_rrtm=1.e-15
99  WHERE (tau_aero_lw_rrtm .LT. 1.e-14) tau_aero_lw_rrtm=1.e-15
100
101  tausum_strat(:,:)=0.0
102  DO i=1,klon
103  DO k=1,klev
104    IF (stratomask(i,k).GT.0.5) THEN
105      tausum_strat(i,1)=tausum_strat(i,1)+tau_strat_wave(i,k,2)  !--550 nm
106      tausum_strat(i,2)=tausum_strat(i,2)+tau_strat_wave(i,k,5)  !--1020 nm
107      tausum_strat(i,3)=tausum_strat(i,3)+tau_strat_wave(i,k,6)  !--10 um
108    ENDIF
109  ENDDO
110  ENDDO
111
112  DO i=1,klon
113  DO k=1,klev
114    zrho=pplay(i,k)/t_seri(i,k)/RD            !air density in kg/m3
115    zdz=(paprs(i,k)-paprs(i,k+1))/zrho/RG     !thickness of layer in m
116    tau_strat_550(i,k)=tau_strat_wave(i,k,2)/zdz
117    tau_strat_1020(i,k)=tau_strat_wave(i,k,6)/zdz
118  ENDDO
119  ENDDO
120
121END SUBROUTINE calcaerosolstrato_rrtm
Note: See TracBrowser for help on using the repository browser.