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

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

Removing one useless line that prevents compilation without rrtm

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