source: LMDZ6/trunk/libf/phylmd/mo_simple_plumes_v1.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: 19.0 KB
Line 
1!>
2!!
3!! @brief Module MO_SIMPLE_PLUMES: provides anthropogenic aerosol optical properties as a function of lat, lon
4!!   height, time, and wavelength
5!!
6!! @remarks
7!!
8!! @author Bjorn Stevens, Stephanie Fiedler and Karsten Peters MPI-Met, Hamburg (v1 release 2016-11-10)
9!!
10!! @change-log:
11!!          - 2016-12-05: beta release (BS, SF and KP, MPI-Met)
12!!          - 2016-09-28: revised representation of Twomey effect (SF, MPI-Met)
13!!          - 2015-09-28: bug fixes  (SF, MPI-Met)
14!!          - 2016-10-12: revised maximum longitudinal extent of European plume (KP, SF, MPI-Met)
15!! $ID: n/a$
16!!
17!! @par Origin
18!!   Based on code originally developed at the MPI-Met by Karsten Peters, Bjorn Stevens, Stephanie Fiedler
19!!   and Stefan Kinne with input from Thorsten Mauritsen and Robert Pincus
20!!
21!! @par Copyright
22!!
23!
24MODULE MO_SIMPLE_PLUMES
25
26  USE netcdf
27
28  IMPLICIT NONE
29
30  INTEGER, PARAMETER ::                        &
31       nplumes   = 9                          ,& !< Number of plumes
32       nfeatures = 2                          ,& !< Number of features per plume
33       ntimes    = 52                         ,& !< Number of times resolved per year (52 => weekly resolution)
34       nyears    = 251                           !< Number of years of available forcing
35
36  LOGICAL, SAVE ::                             &
37       sp_initialized = .FALSE.                  !< parameter determining whether input needs to be read
38
39  REAL ::                                      &
40       plume_lat      (nplumes)               ,& !< latitude of plume center (AOD maximum)
41       plume_lon      (nplumes)               ,& !< longitude of plume center (AOD maximum)
42       beta_a         (nplumes)               ,& !< parameter a for beta function vertical profile
43       beta_b         (nplumes)               ,& !< parameter b for beta function vertical profile
44       aod_spmx       (nplumes)               ,& !< anthropogenic AOD maximum at 550 for plumes
45       aod_fmbg       (nplumes)               ,& !< anthropogenic AOD at 550 for fine-mode natural background (idealized to mimic Twomey effect)
46       asy550         (nplumes)               ,& !< asymmetry parameter at 550nm for plume
47       ssa550         (nplumes)               ,& !< single scattering albedo at 550nm for plume
48       angstrom       (nplumes)               ,& !< Angstrom parameter for plume
49       sig_lon_E      (nfeatures,nplumes)     ,& !< Eastward extent of plume feature
50       sig_lon_W      (nfeatures,nplumes)     ,& !< Westward extent of plume feature
51       sig_lat_E      (nfeatures,nplumes)     ,& !< Southward extent of plume feature
52       sig_lat_W      (nfeatures,nplumes)     ,& !< Northward extent of plume feature
53       theta          (nfeatures,nplumes)     ,& !< Rotation angle of plume feature
54       ftr_weight     (nfeatures,nplumes)     ,& !< Feature weights
55       time_weight    (nfeatures,nplumes)     ,& !< Time weights
56       time_weight_bg (nfeatures,nplumes)     ,& !< as time_weight but for natural background in Twomey effect
57       year_weight    (nyears,nplumes)        ,& !< Yearly weight for plume
58       ann_cycle      (nfeatures,ntimes,nplumes) !< annual cycle for plume feature
59
60  PUBLIC sp_aop_profile
61
62CONTAINS
63  !
64  ! ------------------------------------------------------------------------------------------------------------------------
65  ! SP_SETUP:  This subroutine should be called at initialization to read the netcdf data that describes the simple plume
66  ! climatology.  The information needs to be either read by each processor or distributed to processors.
67  !
68  SUBROUTINE sp_setup
69    !
70    ! ----------
71    !
72    INTEGER :: iret, ncid, DimID, VarID, xdmy
73    !
74    ! ----------
75    !   
76    iret = nf90_open("MACv2.0-SP_v1.nc", NF90_NOWRITE, ncid)
77    IF (iret /= NF90_NOERR) STOP 'NetCDF File not opened'
78    !
79    ! read dimensions and make sure file conforms to expected size
80    !
81    iret = nf90_inq_dimid(ncid, "plume_number"  , DimId)
82    iret = nf90_inquire_dimension(ncid, DimId, len = xdmy)
83    IF (xdmy /= nplumes) STOP 'NetCDF improperly dimensioned -- plume_number'
84
85    iret = nf90_inq_dimid(ncid, "plume_feature", DimId)
86    iret = nf90_inquire_dimension(ncid, DimId, len = xdmy)
87    IF (xdmy /= nfeatures) STOP 'NetCDF improperly dimensioned -- plume_feature'
88
89    iret = nf90_inq_dimid(ncid, "year_fr"   , DimId)
90    iret = nf90_inquire_dimension(ncid, DimID, len = xdmy)
91    IF (xdmy /= ntimes) STOP 'NetCDF improperly dimensioned -- year_fr'
92
93    iret = nf90_inq_dimid(ncid, "years"   , DimId)
94    iret = nf90_inquire_dimension(ncid, DimID, len = xdmy)
95    IF (xdmy /= nyears) STOP 'NetCDF improperly dimensioned -- years'
96    !
97    ! read variables that define the simple plume climatology
98    !
99    iret = nf90_inq_varid(ncid, "plume_lat", VarId)
100    iret = nf90_get_var(ncid, VarID, plume_lat(:), start=(/1/),count=(/nplumes/))
101    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading plume_lat'
102    iret = nf90_inq_varid(ncid, "plume_lon", VarId)
103    iret = nf90_get_var(ncid, VarID, plume_lon(:), start=(/1/),count=(/nplumes/))
104    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading plume_lon'
105    iret = nf90_inq_varid(ncid, "beta_a"   , VarId)
106    iret = nf90_get_var(ncid, VarID, beta_a(:)   , start=(/1/),count=(/nplumes/))
107    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading beta_a'
108    iret = nf90_inq_varid(ncid, "beta_b"   , VarId)
109    iret = nf90_get_var(ncid, VarID, beta_b(:)   , start=(/1/),count=(/nplumes/))
110    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading beta_b'
111    iret = nf90_inq_varid(ncid, "aod_spmx" , VarId)
112    iret = nf90_get_var(ncid, VarID, aod_spmx(:)  , start=(/1/),count=(/nplumes/))
113    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading aod_spmx'
114    iret = nf90_inq_varid(ncid, "aod_fmbg" , VarId)
115    iret = nf90_get_var(ncid, VarID, aod_fmbg(:)  , start=(/1/),count=(/nplumes/))
116    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading aod_fmbg'
117    iret = nf90_inq_varid(ncid, "ssa550"   , VarId)
118    iret = nf90_get_var(ncid, VarID, ssa550(:)  , start=(/1/),count=(/nplumes/))
119    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading ssa550'
120    iret = nf90_inq_varid(ncid, "asy550"   , VarId)
121    iret = nf90_get_var(ncid, VarID, asy550(:)  , start=(/1/),count=(/nplumes/))
122    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading asy550'
123    iret = nf90_inq_varid(ncid, "angstrom" , VarId)
124    iret = nf90_get_var(ncid, VarID, angstrom(:), start=(/1/),count=(/nplumes/))
125    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading angstrom'
126
127    iret = nf90_inq_varid(ncid, "sig_lat_W"     , VarId)
128    iret = nf90_get_var(ncid, VarID, sig_lat_W(:,:)    , start=(/1,1/),count=(/nfeatures,nplumes/))
129    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading sig_lat_W'
130    iret = nf90_inq_varid(ncid, "sig_lat_E"     , VarId)
131    iret = nf90_get_var(ncid, VarID, sig_lat_E(:,:)    , start=(/1,1/),count=(/nfeatures,nplumes/))
132    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading sig_lat_E'
133    iret = nf90_inq_varid(ncid, "sig_lon_E"     , VarId)
134    iret = nf90_get_var(ncid, VarID, sig_lon_E(:,:)    , start=(/1,1/),count=(/nfeatures,nplumes/))
135    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading sig_lon_E'
136    iret = nf90_inq_varid(ncid, "sig_lon_W"     , VarId)
137    iret = nf90_get_var(ncid, VarID, sig_lon_W(:,:)    , start=(/1,1/),count=(/nfeatures,nplumes/))
138    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading sig_lon_W'
139    iret = nf90_inq_varid(ncid, "theta"         , VarId)
140    iret = nf90_get_var(ncid, VarID, theta(:,:)        , start=(/1,1/),count=(/nfeatures,nplumes/))
141    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading theta'
142    iret = nf90_inq_varid(ncid, "ftr_weight"    , VarId)
143    iret = nf90_get_var(ncid, VarID, ftr_weight(:,:)   , start=(/1,1/),count=(/nfeatures,nplumes/))
144    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading plume_lat'
145    iret = nf90_inq_varid(ncid, "year_weight"   , VarId)
146    iret = nf90_get_var(ncid, VarID, year_weight(:,:)  , start=(/1,1/),count=(/nyears,nplumes   /))
147    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading year_weight'
148    iret = nf90_inq_varid(ncid, "ann_cycle"     , VarId)
149    iret = nf90_get_var(ncid, VarID, ann_cycle(:,:,:)  , start=(/1,1,1/),count=(/nfeatures,ntimes,nplumes/))
150    IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading ann_cycle'
151
152    iret = nf90_close(ncid)
153
154    sp_initialized = .TRUE.
155
156    RETURN
157  END SUBROUTINE sp_setup
158  !
159  ! ------------------------------------------------------------------------------------------------------------------------
160  ! SET_TIME_WEIGHT:  The simple plume model assumes that meteorology constrains plume shape and that only source strength
161  ! influences the amplitude of a plume associated with a given source region.   This routine retrieves the temporal weights
162  ! for the plumes.  Each plume feature has its own temporal weights which varies yearly.  The annual cycle is indexed by
163  ! week in the year and superimposed on the yearly mean value of the weight.
164  !
165  SUBROUTINE set_time_weight(year_fr)
166    !
167    ! ----------
168    !
169    REAL, INTENT(IN) ::  &
170         year_fr           !< Fractional Year (1850.0 - 2100.99)
171
172    INTEGER          ::  &
173         iyear          ,& !< Integer year values between 1 and 156 (1850-2100)
174         iweek          ,& !< Integer index (between 1 and ntimes); for ntimes=52 this corresponds to weeks (roughly)
175         iplume            ! plume number
176    !
177    ! ----------
178    !
179    iyear = FLOOR(year_fr) - 1849
180    iweek = FLOOR((year_fr - FLOOR(year_fr)) * ntimes) + 1
181
182    IF ((iweek > ntimes) .OR. (iweek < 1) .OR. (iyear > nyears) .OR. (iyear < 1)) THEN
183      CALL abort_physic('set_time_weight','Time out of bounds')
184    ENDIF
185
186    DO iplume=1,nplumes
187      time_weight(1,iplume) = year_weight(iyear,iplume) * ann_cycle(1,iweek,iplume)
188      time_weight(2,iplume) = year_weight(iyear,iplume) * ann_cycle(2,iweek,iplume)
189      time_weight_bg(1,iplume) = ann_cycle(1,iweek,iplume)
190      time_weight_bg(2,iplume) = ann_cycle(2,iweek,iplume)
191    END DO
192   
193    RETURN
194  END SUBROUTINE set_time_weight
195  !
196  ! ------------------------------------------------------------------------------------------------------------------------
197  ! SP_AOP_PROFILE:  This subroutine calculates the simple plume aerosol and cloud active optical properties based on the
198  ! the simple plume fit to the MPI Aerosol Climatology (Version 2).  It sums over nplumes to provide a profile of aerosol
199  ! optical properties on a host models vertical grid.
200  !
201  SUBROUTINE sp_aop_profile                                                                           ( &
202       nlevels        ,ncol           ,lambda         ,oro            ,lon            ,lat            , &
203       year_fr        ,z              ,dz             ,dNovrN         ,aod_prof       ,ssa_prof       , &
204       asy_prof       )
205    !
206    ! ----------
207    !
208    INTEGER, INTENT(IN)        :: &
209         nlevels,                 & !< number of levels
210         ncol                       !< number of columns
211
212    REAL, INTENT(IN)           :: &
213         lambda,                  & !< wavelength
214         year_fr,                 & !< Fractional Year (1903.0 is the 0Z on the first of January 1903, Gregorian)
215         oro(ncol),               & !< orographic height (m)
216         lon(ncol),               & !< longitude
217         lat(ncol),               & !< latitude
218         z (ncol,nlevels),        & !< height above sea-level (m)
219         dz(ncol,nlevels)           !< level thickness (difference between half levels) (m)
220
221    REAL, INTENT(OUT)          :: &
222         dNovrN(ncol)           , & !< anthropogenic increase in cloud drop number concentration (factor)
223         aod_prof(ncol,nlevels) , & !< profile of aerosol optical depth
224         ssa_prof(ncol,nlevels) , & !< profile of single scattering albedo
225         asy_prof(ncol,nlevels)     !< profile of asymmetry parameter
226
227    INTEGER                    :: iplume, icol, k
228
229    REAL                       ::  &
230         eta(ncol,nlevels),        & !< normalized height (by 15 km)
231         z_beta(ncol,nlevels),     & !< profile for scaling column optical depth
232         prof(ncol,nlevels),       & !< scaled profile (by beta function)
233         beta_sum(ncol),           & !< vertical sum of beta function
234         ssa(ncol),                & !< single scattering albedo
235         asy(ncol),                & !< asymmetry parameter
236         cw_an(ncol),              & !< column weight for simple plume (anthropogenic) AOD at 550 nm
237         cw_bg(ncol),              & !< column weight for fine-mode natural background AOD at 550 nm
238         caod_sp(ncol),            & !< column simple plume anthropogenic AOD at 550 nm
239         caod_bg(ncol),            & !< column fine-mode natural background AOD at 550 nm
240         a_plume1,                 & !< gaussian longitude factor for feature 1
241         a_plume2,                 & !< gaussian longitude factor for feature 2
242         b_plume1,                 & !< gaussian latitude factor for feature 1
243         b_plume2,                 & !< gaussian latitude factor for feature 2
244         delta_lat,                & !< latitude offset
245         delta_lon,                & !< longitude offset
246         delta_lon_t,              & !< threshold for maximum longitudinal plume extent used in transition from 360 to 0 degrees
247         lon1,                     & !< rotated longitude for feature 1
248         lat1,                     & !< rotated latitude for feature 2
249         lon2,                     & !< rotated longitude for feature 1
250         lat2,                     & !< rotated latitude for feature 2
251         f1,                       & !< contribution from feature 1
252         f2,                       & !< contribution from feature 2
253         f3,                       & !< contribution from feature 1 in natural background of Twomey effect
254         f4,                       & !< contribution from feature 2 in natural background of Twomey effect
255         aod_550,                  & !< aerosol optical depth at 550nm
256         aod_lmd,                  & !< aerosol optical depth at input wavelength
257         lfactor                     !< factor to compute wavelength dependence of optical properties
258    !
259    ! ----------
260    !
261    ! initialize input data (by calling setup at first instance)
262    !
263    IF (.NOT.sp_initialized) CALL sp_setup
264    !
265    ! get time weights
266    !
267    CALL set_time_weight(year_fr)
268    !
269    ! initialize variables, including output
270    !
271    DO k=1,nlevels
272      DO icol=1,ncol
273        aod_prof(icol,k) = 0.0
274        ssa_prof(icol,k) = 0.0
275        asy_prof(icol,k) = 0.0
276        z_beta(icol,k)   = MERGE(1.0, 0.0, z(icol,k) >= oro(icol))
277        eta(icol,k)      = MAX(0.0,MIN(1.0,z(icol,k)/15000.))
278      END DO
279    END DO
280    DO icol=1,ncol
281      dNovrN(icol)   = 1.0
282      caod_sp(icol)  = 0.0
283      caod_bg(icol)  = 0.02
284    END DO
285    !
286    ! sum contribution from plumes to construct composite profiles of aerosol optical properties
287    !
288    DO iplume=1,nplumes
289      !
290      ! calculate vertical distribution function from parameters of beta distribution
291      !
292      DO icol=1,ncol
293        beta_sum(icol) = 0.
294      END DO
295      DO k=1,nlevels
296        DO icol=1,ncol
297          prof(icol,k)   = (eta(icol,k)**(beta_a(iplume)-1.) * (1.-eta(icol,k))**(beta_b(iplume)-1.)) * dz(icol,k)
298          beta_sum(icol) = beta_sum(icol) + prof(icol,k)
299        END DO
300      END DO
301      DO k=1,nlevels
302        DO icol=1,ncol
303          prof(icol,k)   = ( prof(icol,k) / beta_sum(icol) ) * z_beta(icol,k)
304        END DO
305      END DO
306      !
307      ! calculate plume weights
308      !
309      DO icol=1,ncol
310        !
311        ! get plume-center relative spatial parameters for specifying amplitude of plume at given lat and lon
312        !
313        delta_lat   = lat(icol) - plume_lat(iplume)
314        delta_lon   = lon(icol) - plume_lon(iplume)
315        delta_lon_t = MERGE (260., 180., iplume == 1)
316        delta_lon   = MERGE ( delta_lon-SIGN(360.,delta_lon) , delta_lon , ABS(delta_lon) > delta_lon_t)
317
318        a_plume1  = 0.5 / (MERGE(sig_lon_E(1,iplume), sig_lon_W(1,iplume), delta_lon > 0)**2)
319        b_plume1  = 0.5 / (MERGE(sig_lat_E(1,iplume), sig_lat_W(1,iplume), delta_lon > 0)**2)
320        a_plume2  = 0.5 / (MERGE(sig_lon_E(2,iplume), sig_lon_W(2,iplume), delta_lon > 0)**2)
321        b_plume2  = 0.5 / (MERGE(sig_lat_E(2,iplume), sig_lat_W(2,iplume), delta_lon > 0)**2)
322        !
323        ! adjust for a plume specific rotation which helps match plume state to climatology.
324        !
325        lon1 =   COS(theta(1,iplume))*(delta_lon) + SIN(theta(1,iplume))*(delta_lat)
326        lat1 = - SIN(theta(1,iplume))*(delta_lon) + COS(theta(1,iplume))*(delta_lat)
327        lon2 =   COS(theta(2,iplume))*(delta_lon) + SIN(theta(2,iplume))*(delta_lat)
328        lat2 = - SIN(theta(2,iplume))*(delta_lon) + COS(theta(2,iplume))*(delta_lat)
329        !
330        ! calculate contribution to plume from its different features, to get a column weight for the anthropogenic
331        ! (cw_an) and the fine-mode natural background aerosol (cw_bg)
332        !
333        f1 = time_weight(1,iplume) * ftr_weight(1,iplume) * EXP(-1.* (a_plume1 * ((lon1)**2) + (b_plume1 * ((lat1)**2))))
334        f2 = time_weight(2,iplume) * ftr_weight(2,iplume) * EXP(-1.* (a_plume2 * ((lon2)**2) + (b_plume2 * ((lat2)**2))))
335        f3 = time_weight_bg(1,iplume) * ftr_weight(1,iplume) * EXP(-1.* (a_plume1 * ((lon1)**2) + (b_plume1 * ((lat1)**2))))
336        f4 = time_weight_bg(2,iplume) * ftr_weight(2,iplume) * EXP(-1.* (a_plume2 * ((lon2)**2) + (b_plume2 * ((lat2)**2))))
337
338        cw_an(icol) = f1 * aod_spmx(iplume) + f2 * aod_spmx(iplume) 
339        cw_bg(icol) = f3 * aod_fmbg(iplume) + f4 * aod_fmbg(iplume)
340        !
341        ! calculate wavelength-dependent scattering properties
342        !
343        lfactor   = MIN(1.0,700.0/lambda)
344        ssa(icol) = (ssa550(iplume) * lfactor**4) / ((ssa550(iplume) * lfactor**4) + ((1-ssa550(iplume)) * lfactor))
345        asy(icol) =  asy550(iplume) * SQRT(lfactor)
346      END DO
347      !
348      ! distribute plume optical properties across its vertical profile weighting by optical depth and scaling for
349      ! wavelength using the angstrom parameter.
350      !     
351      lfactor = EXP(-angstrom(iplume) * LOG(lambda/550.0))
352      DO k=1,nlevels
353        DO icol = 1,ncol
354          aod_550          = prof(icol,k)     * cw_an(icol)
355          aod_lmd          = aod_550          * lfactor
356          caod_sp(icol)    = caod_sp(icol)    + aod_550
357          caod_bg(icol)    = caod_bg(icol)    + prof(icol,k) * cw_bg(icol)
358          asy_prof(icol,k) = asy_prof(icol,k) + aod_lmd * ssa(icol) * asy(icol)
359          ssa_prof(icol,k) = ssa_prof(icol,k) + aod_lmd * ssa(icol)
360          aod_prof(icol,k) = aod_prof(icol,k) + aod_lmd
361        END DO
362      END DO
363    END DO
364    !
365    ! complete optical depth weighting
366    !
367    DO k=1,nlevels
368      DO icol = 1,ncol
369        asy_prof(icol,k) = MERGE(asy_prof(icol,k)/ssa_prof(icol,k), 0.0, ssa_prof(icol,k) > TINY(1.))
370        ssa_prof(icol,k) = MERGE(ssa_prof(icol,k)/aod_prof(icol,k), 1.0, aod_prof(icol,k) > TINY(1.))
371      END DO
372    END DO
373    !
374    ! calculate effective radius normalization (divisor) factor
375    !
376    DO icol=1,ncol
377      dNovrN(icol) = LOG((1000.0 * (caod_sp(icol) + caod_bg(icol))) + 1.0)/LOG((1000.0 * caod_bg(icol)) + 1.0)
378    END DO
379
380    RETURN
381  END SUBROUTINE sp_aop_profile
382 
383END MODULE MO_SIMPLE_PLUMES
Note: See TracBrowser for help on using the repository browser.