source: LMDZ5/trunk/libf/phylmd/rrtm/aeropt_lw_rrtm.F90 @ 2738

Last change on this file since 2738 was 2738, checked in by oboucher, 8 years ago

Swapping the order of CSSO4 and ASSO4 aerosols (and fixing an issue on aerindex). Preparing the ground for nitrate aerosols (coarse soluble, accumulation soluble, coarse insoluble). Modifying the LW aeropt routine so that it is compatible with both INCA and climatological aerosols (for dust only). Adding a new flag ok_alw for activating aerosol direct LW effect (for dust only). This change is bit comparable for flag_aerosol=6, flag_rrtm=1, NSW=6.

  • Property svn:executable set to *
File size: 2.2 KB
Line 
1!
2! aeropt_lw_rrtm.F90 2014-05-13 C. Kleinschmitt
3!                    2016-05-03 O. Boucher
4!                    2016-12-17 O. Boucher
5!
6! This routine feeds aerosol LW properties to RRTM
7! we only consider absorption (not scattering)
8! we only consider dust for now
9
10SUBROUTINE AEROPT_LW_RRTM(ok_alw, pdel, zrho, flag_aerosol, m_allaer, m_allaer_pi)
11
12  USE dimphy
13  USE aero_mod
14  USE phys_state_var_mod, ONLY : tau_aero_lw_rrtm
15  USE YOERAD, ONLY : NLW
16  USE YOMCST
17
18  IMPLICIT NONE
19
20  INCLUDE "clesphys.h"
21  !
22  ! Input arguments:
23  !
24  LOGICAL, INTENT(IN)                                 :: ok_alw
25  INTEGER, INTENT(IN)                                 :: flag_aerosol
26  REAL, DIMENSION(klon,klev),     INTENT(in)          :: pdel, zrho
27  REAL, DIMENSION(klon,klev,naero_tot),   INTENT(in)  :: m_allaer, m_allaer_pi
28  !
29  INTEGER inu, i, k
30  REAL :: zdh(klon,klev)
31  REAL :: tmp_var, tmp_var_pi
32  !
33  !--absorption coefficient for CIDUST
34  REAL:: alpha_abs_CIDUST_16bands(nbands_lw_rrtm)   !--unit m2/g
35  DATA alpha_abs_CIDUST_16bands /              &
36  0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
37  0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /
38  !
39  IF (NLW.NE.nbands_lw_rrtm) THEN
40     PRINT *,'Erreur NLW doit etre egal a 16 pour cette routine'
41     STOP
42  ENDIF
43  !
44  IF (ok_alw) THEN                                   !--aerosol LW effects
45   !
46   IF (flag_aerosol.EQ.5.OR.flag_aerosol.EQ.6) THEN  !--Dust
47    !
48    zdh(:,:)=pdel(:,:)/(RG*zrho(:,:))      !-- m
49    !
50    DO k=1, klev
51      DO i=1, klon
52         !
53         tmp_var   =m_allaer(i,k,id_CIDUSTM_phy)   /1.e6*zdh(i,k) !-- g/m2
54         tmp_var_pi=m_allaer_pi(i,k,id_CIDUSTM_phy)/1.e6*zdh(i,k) !-- g/m2
55         !
56         DO inu=1, NLW
57           !
58           !--total aerosol
59           tau_aero_lw_rrtm(i,k,2,inu) = MAX(1.e-15,tmp_var*alpha_abs_CIDUST_16bands(inu))
60           !--natural aerosol
61           tau_aero_lw_rrtm(i,k,1,inu) = MAX(1.e-15,tmp_var_pi*alpha_abs_CIDUST_16bands(inu))
62           !
63         ENDDO
64      ENDDO
65      !
66    ENDDO
67    !
68   ENDIF
69   !
70  ELSE !--no aerosol LW effects
71    !
72    tau_aero_lw_rrtm = 1.e-15
73  ENDIF
74  !
75END SUBROUTINE AEROPT_LW_RRTM
Note: See TracBrowser for help on using the repository browser.