source: LMDZ6/branches/Ocean_skin/libf/phylmd/StratAer/calcaerosolstrato_rrtm.F90 @ 3605

Last change on this file since 3605 was 3605, checked in by lguez, 4 years ago

Merge revisions 3427:3600 of trunk into branch Ocean_skin

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