source: LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/calcaerosolstrato_rrtm.F90

Last change on this file was 5159, checked in by abarral, 7 weeks ago

Put dimensions.h and paramet.h into modules

  • Property svn:keywords set to Id
File size: 4.5 KB
Line 
1! $Id: calcaerosolstrato_rrtm.F90 5159 2024-08-02 19:58:25Z fairhead $
2
3SUBROUTINE calcaerosolstrato_rrtm(pplay, t_seri, paprs, debut)
4
5  USE phys_state_var_mod, ONLY: tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, tau_aero_lw_rrtm
6  USE phys_local_var_mod, ONLY: mdw, tausum_aero, tausum_strat, tau_strat_550, tau_strat_1020, stratomask
7  USE aero_mod
8  USE dimphy
9  USE temps_mod
10  USE lmdz_yomcst
11  USE lmdz_iniprint, ONLY: lunout, prt_level
12  USE lmdz_clesphys
13
14USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
15  USE lmdz_paramet
16  IMPLICIT NONE
17
18
19
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
41
42  CALL miecalc_aer(tau_strat, piz_strat, cg_strat, tau_strat_wave, tau_lw_abs_rrtm, paprs, debut)
43
44  !!--test CK: deactivate radiative effect of aerosol
45  !  tau_strat=0.0
46  !  piz_strat=0.0
47  !  cg_strat=0.0
48  !  tau_strat_wave=0.0
49  !  tau_lw_abs_rrtm=0.0
50
51  !--test CK: deactivate SW radiative effect of aerosol (but leave LW)
52  !  tau_strat=0.0
53  !  piz_strat=0.0
54  !  cg_strat=0.0
55
56  !  DO wave=1, nwave_sw
57  !  tau_strat_wave(:,:,wave)=0.0
58  !  ENDDO
59
60  !--test CK: deactivate LW radiative effect of aerosol (but leave SW)
61  !  tau_lw_abs_rrtm=0.0
62
63  !  DO wave=nwave_sw+1, nwave_sw+nwave_lw
64  !  tau_strat_wave(:,:,wave)=0.0
65  !  ENDDO
66
67  !--total vertical aod at the 5 SW + 1 LW wavelengths
68  DO wave = 1, nwave_sw + nwave_lw
69    DO k = 1, klev
70      tausum_aero(:, wave, id_STRAT_phy) = tausum_aero(:, wave, id_STRAT_phy) + tau_strat_wave(:, k, wave)
71    ENDDO
72  ENDDO
73
74  !--weighted average for cg, piz and tau, adding strat aerosols on top of tropospheric ones
75  DO band = 1, nbands_sw_rrtm
76    !--no stratospheric aerosol in index 1
77    cg_aero_sw_rrtm(:, :, 1, band) = cg_aero_sw_rrtm(:, :, 2, band)
78    piz_aero_sw_rrtm(:, :, 1, band) = piz_aero_sw_rrtm(:, :, 2, band)
79    tau_aero_sw_rrtm(:, :, 1, band) = tau_aero_sw_rrtm(:, :, 2, band)
80
81    !--tropospheric and stratospheric aerosol in index 2
82    cg_aero_sw_rrtm(:, :, 2, band) = (cg_aero_sw_rrtm(:, :, 2, band) * piz_aero_sw_rrtm(:, :, 2, band) * tau_aero_sw_rrtm(:, :, 2, band) + &
83            cg_strat(:, :, band) * piz_strat(:, :, band) * tau_strat(:, :, band)) / &
84            MAX(piz_aero_sw_rrtm(:, :, 2, band) * tau_aero_sw_rrtm(:, :, 2, band) + &
85                    piz_strat(:, :, band) * tau_strat(:, :, band), 1.e-15)
86    piz_aero_sw_rrtm(:, :, 2, band) = (piz_aero_sw_rrtm(:, :, 2, band) * tau_aero_sw_rrtm(:, :, 2, band) + &
87            piz_strat(:, :, band) * tau_strat(:, :, band)) / &
88            MAX(tau_aero_sw_rrtm(:, :, 2, band) + tau_strat(:, :, band), 1.e-15)
89    tau_aero_sw_rrtm(:, :, 2, band) = tau_aero_sw_rrtm(:, :, 2, band) + tau_strat(:, :, band)
90  ENDDO
91
92  DO band = 1, nbands_lw_rrtm
93    !--no stratospheric aerosols in index 1
94    tau_aero_lw_rrtm(:, :, 1, band) = tau_aero_lw_rrtm(:, :, 2, band)
95    !--tropospheric and stratospheric aerosol in index 2
96    tau_aero_lw_rrtm(:, :, 2, band) = tau_aero_lw_rrtm(:, :, 2, band) + tau_lw_abs_rrtm(:, :, band)
97  ENDDO
98
99  WHERE (tau_aero_sw_rrtm < 1.e-14) piz_aero_sw_rrtm = 1.0
100  WHERE (tau_aero_sw_rrtm < 1.e-14) tau_aero_sw_rrtm = 1.e-15
101  WHERE (tau_aero_lw_rrtm < 1.e-14) tau_aero_lw_rrtm = 1.e-15
102
103  tausum_strat(:, :) = 0.0
104  DO i = 1, klon
105    DO k = 1, klev
106      IF (stratomask(i, k)>0.5) THEN
107        tausum_strat(i, 1) = tausum_strat(i, 1) + tau_strat_wave(i, k, 2)  !--550 nm
108        tausum_strat(i, 2) = tausum_strat(i, 2) + tau_strat_wave(i, k, 5)  !--1020 nm
109        tausum_strat(i, 3) = tausum_strat(i, 3) + tau_strat_wave(i, k, 6)  !--10 um
110      ENDIF
111    ENDDO
112  ENDDO
113
114  DO i = 1, klon
115    DO k = 1, klev
116      zrho = pplay(i, k) / t_seri(i, k) / RD            !air density in kg/m3
117      zdz = (paprs(i, k) - paprs(i, k + 1)) / zrho / RG     !thickness of layer in m
118      tau_strat_550(i, k) = tau_strat_wave(i, k, 2) / zdz
119      tau_strat_1020(i, k) = tau_strat_wave(i, k, 5) / zdz
120    ENDDO
121  ENDDO
122
123END SUBROUTINE calcaerosolstrato_rrtm
Note: See TracBrowser for help on using the repository browser.