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

Last change on this file was 5272, checked in by abarral, 3 days ago

Turn paramet.h into a module

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