source: LMDZ6/trunk/libf/phylmd/StratAer/calcaerosolstrato_rrtm.F90

Last change on this file was 4293, checked in by dcugnet, 20 months ago

Commit for Nicolas: fixes for StratAer?.

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