source: LMDZ6/trunk/libf/phylmd/macv2sp.F90 @ 3274

Last change on this file since 3274 was 3274, checked in by oboucher, 6 years ago

Implementing the MACspV2 aerosol plume climatology
which can be called by setting flag_aerosol=7
and aerosols1980.nc pointing to aerosols.nat.nc.
Also requires the MACv2.0-SP_v1.nc file.

File size: 6.9 KB
Line 
1SUBROUTINE MACv2SP(pphis,pplay,paprs,xlon,xlat,tau_allaer,piz_allaer,cg_allaer)
2  !
3  !--routine to read the MACv2SP plume and compute optical properties
4  !--requires flag_aerosol = 7
5  !--feeds into aerosol optical properties and newmicro cloud droplet size if ok_cdnc activated
6  !--for this one needs to feed natural (pre-industrial) aerosols twice for nat and 1980 files
7  !--pre-ind aerosols (index=1) are not changed, present-day aerosols (index=2) are incremented
8  !--uses model year so year_cur needs to be correct in the model simulation
9  !
10  !--aod_prof = AOD per layer
11  !--ssa_prof = SSA
12  !--asy_prof = asymetry parameter
13  !--dNovrN   = enhancement factor for CDNC
14  !
15  USE mo_simple_plumes, ONLY: sp_aop_profile
16  USE phys_cal_mod, ONLY : year_cur, day_cur, year_len
17  USE dimphy
18  USE aero_mod
19  USE phys_local_var_mod, ONLY: t_seri, od443aer, od550aer, od865aer, ec550aer, dryod550aer, od550lt1aer, dNovrN
20  USE YOERAD, ONLY : NLW
21  USE YOMCST, ONLY : RD, RG
22  !
23  IMPLICIT NONE
24  !
25  REAL,DIMENSION(klon),INTENT(IN)        :: pphis   ! Geopotentiel de surface
26  REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
27  REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour les interfaces de chaque couche (en Pa)
28  REAL,DIMENSION(klon),INTENT(IN)        :: xlat    ! latitudes pour chaque point
29  REAL,DIMENSION(klon),INTENT(IN)        :: xlon    ! longitudes pour chaque point
30  !
31  REAL, DIMENSION(klon,klev,2,nbands_sw_rrtm), INTENT(OUT) :: tau_allaer !  epaisseur optique aerosol
32  REAL, DIMENSION(klon,klev,2,nbands_sw_rrtm), INTENT(OUT) :: piz_allaer !  single scattering albedo aerosol
33  REAL, DIMENSION(klon,klev,2,nbands_sw_rrtm), INTENT(OUT) :: cg_allaer  !  asymmetry parameter aerosol
34  !
35  REAL,DIMENSION(klon,klev) :: aod_prof, ssa_prof, asy_prof
36  REAL,DIMENSION(klon,klev) :: z, dz
37  REAL,DIMENSION(klon)      :: oro, zrho
38  !
39  INTEGER, PARAMETER :: nmon = 12
40  !
41  REAL, PARAMETER    :: l443 = 443.0, l550 = 550.0, l865 = 865.0 !--wavelengths in nm
42  !
43  INTEGER, PARAMETER :: Nwvmax=25
44  REAL, DIMENSION(0:Nwvmax), PARAMETER :: lambda=(/ 240.0, &  !--this one is for band 1
45                  280.0,  300.0,  330.0,  360.0,  400.0,   &  !--these are bounds of Streamer bands
46                  440.0,  480.0,  520.0,  570.0,  640.0,   &
47                  690.0,  750.0,  780.0,  870.0, 1000.0,   &
48                 1100.0, 1190.0, 1280.0, 1530.0, 1640.0,   &
49                 2130.0, 2380.0, 2910.0, 3420.0, 4000.0   /)
50  !
51  REAL, DIMENSION(1:Nwvmax-1), PARAMETER :: weight =(/    &   !--and the weights to be given to the bands
52                 0.01,  4.05,  9.51, 15.99, 26.07, 33.10, &   !--corresponding to a typical solar spectrum
53                33.07, 39.91, 52.67, 27.89, 43.60, 13.67, &
54                42.22, 40.12, 32.70, 14.44, 19.48, 14.23, &
55                13.43, 16.42,  8.33,  0.95,  0.65,  2.76  /)
56  !
57  REAL :: zlambda, zweight
58  REAL :: year_fr
59  !
60  INTEGER band, i, k, Nwv
61  !
62  ! define the height and dheight arrays
63  !
64  z(:,1)  = 0.                                      ! altitude of surface taken as 0
65  DO k = 1, klev-1
66    oro(:) = pphis(:)/RG                            ! surface height in m
67    zrho(:) = pplay(:, k)/t_seri(:, k)/RD           ! air density in kg/m3
68    dz(:,k) = (paprs(:,k)-paprs(:,k+1))/zrho(:)/RG  ! layer thickness in m
69    z(:,k+1) = z(:,k) + dz(:,k)                     ! height of interfaces in m, starting from 0 at surface
70  ENDDO
71  !
72  !--fractional year
73  !
74  year_fr = FLOAT(year_cur) + (FLOAT(day_cur)-0.5) / FLOAT(year_len)
75  print *,'year_fr=',year_fr
76  !
77  !--call to sp routine -- 443 nm
78  !
79  CALL sp_aop_profile                                    ( &
80       klev     ,klon ,l443 ,oro    ,xlon     ,xlat      , &
81       year_fr  ,z    ,dz   ,dNovrN ,aod_prof ,ssa_prof  , &
82       asy_prof )
83  !
84  !--AOD calculations for diagnostics
85  od443aer(:)= od443aer(:)+SUM(aod_prof(:,:),dim=2)
86  !
87  !--call to sp routine -- 550 nm
88  !
89  CALL sp_aop_profile                                    ( &
90       klev     ,klon ,l550 ,oro    ,xlon     ,xlat      , &
91       year_fr  ,z    ,dz   ,dNovrN ,aod_prof ,ssa_prof  , &
92       asy_prof )
93  !
94  !--AOD calculations for diagnostics
95  od550aer(:)=od550aer(:)+SUM(aod_prof(:,:),dim=2)
96  !
97  !--dry AOD calculation for diagnostics
98  dryod550aer(:)=dryod550aer(:)+od550aer(:)
99  !
100  !--fine-mode AOD calculation for diagnostics
101  od550lt1aer(:)=od550lt1aer(:)+od550aer(:)
102  !
103  !--extinction coefficient for diagnostic
104  ec550aer(:,:)=ec550aer(:,:)+aod_prof(:,:)/dz(:,:)
105  !
106  !--call to sp routine -- 865 nm
107  !
108  CALL sp_aop_profile                                    ( &
109       klev     ,klon ,l865 ,oro    ,xlon     ,xlat      , &
110       year_fr  ,z    ,dz   ,dNovrN ,aod_prof ,ssa_prof  , &
111       asy_prof )
112  !
113  !--AOD calculations for diagnostics
114  od865aer(:)=od865aer(:)+SUM(aod_prof(:,:),dim=2)
115  !
116  !--re-weighting of piz and cg arrays before adding the anthropogenic aerosols
117  !--index 2 = all natural + anthropogenic aerosols
118  piz_allaer(:,:,2,:)=piz_allaer(:,:,2,:)*tau_allaer(:,:,2,:)
119  cg_allaer(:,:,2,:) =cg_allaer(:,:,2,:)*piz_allaer(:,:,2,:)
120  !
121  !--now computing the same at many wavelengths to fill the model bands
122  !
123  DO Nwv=0,Nwvmax-1
124
125    IF (Nwv.EQ.0) THEN          !--RRTM spectral band 1
126      zlambda=lambda(Nwv)
127      zweight=1.0
128      band=1
129    ELSEIF (Nwv.LE.5) THEN      !--RRTM spectral band 2
130      zlambda=0.5*(lambda(Nwv)+lambda(Nwv+1))
131      zweight=weight(Nwv)/SUM(weight(1:5))
132      band=2
133    ELSEIF (Nwv.LE.10) THEN     !--RRTM spectral band 3
134      zlambda=0.5*(lambda(Nwv)+lambda(Nwv+1))
135      zweight=weight(Nwv)/SUM(weight(6:10))
136      band=3
137    ELSEIF (Nwv.LE.16) THEN     !--RRTM spectral band 4
138      zlambda=0.5*(lambda(Nwv)+lambda(Nwv+1))
139      zweight=weight(Nwv)/SUM(weight(11:16))
140      band=4
141    ELSEIF (Nwv.LE.21) THEN     !--RRTM spectral band 5
142      zlambda=0.5*(lambda(Nwv)+lambda(Nwv+1))
143      zweight=weight(Nwv)/SUM(weight(17:21))
144      band=5
145    ELSE                        !--RRTM spectral band 6
146      zlambda=0.5*(lambda(Nwv)+lambda(Nwv+1))
147      zweight=weight(Nwv)/SUM(weight(22:Nwvmax-1))
148      band=6
149    ENDIF
150    !
151    CALL sp_aop_profile                                       ( &
152         klev     ,klon ,zlambda ,oro    ,xlon     ,xlat      , &
153         year_fr  ,z    ,dz      ,dNovrN ,aod_prof ,ssa_prof  , &
154         asy_prof )
155    !
156    !--adding up the quantities tau, piz*tau and cg*piz*tau
157    tau_allaer(:,:,2,band)=tau_allaer(:,:,2,band)+zweight*MAX(aod_prof(:,:),1.e-15)
158    piz_allaer(:,:,2,band)=piz_allaer(:,:,2,band)+zweight*MAX(aod_prof(:,:),1.e-15)*ssa_prof(:,:)
159    cg_allaer(:,:,2,band) =cg_allaer(:,:,2,band) +zweight*MAX(aod_prof(:,:),1.e-15)*ssa_prof(:,:)*asy_prof(:,:)
160    !
161  ENDDO
162  !
163  !--renpomalizing cg and piz now that MACv2SP increments have been added
164  cg_allaer(:,:,2,:) =cg_allaer(:,:,2,:) /piz_allaer(:,:,2,:)
165  piz_allaer(:,:,2,:)=piz_allaer(:,:,2,:)/tau_allaer(:,:,2,:)
166  !
167END SUBROUTINE MACv2SP
Note: See TracBrowser for help on using the repository browser.