source: LMDZ6/branches/Amaury_dev/libf/phylmd/mo_simple_plumes.F90 @ 5136

Last change on this file since 5136 was 5111, checked in by abarral, 2 months ago

Put abort_physic into a module
Remove -g option from makelmdz_fcm, since that option is linked to a header file that isn't included anywhere.
(lint) light lint on traversed files

File size: 21.2 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, ONLY: nf90_get_var, nf90_close, nf90_inq_varid, nf90_inq_dimid, &
27          nf90_inquire_dimension, nf90_noerr, nf90_nowrite, nf90_open
28
29  IMPLICIT NONE
30
31  INTEGER, PARAMETER :: &
32          nplumes = 9, & !< Number of plumes
33          nfeatures = 2, & !< Number of features per plume
34          ntimes = 52, & !< Number of times resolved per year (52 => weekly resolution)
35          nyears = 251                           !< Number of years of available forcing
36
37  LOGICAL, SAVE :: &
38          sp_initialized = .FALSE.                  !< parameter determining whether input needs to be read
39  !$OMP THREADPRIVATE(sp_initialized)
40
41  REAL, SAVE :: &
42          plume_lat      (nplumes), & !< latitude of plume center (AOD maximum)
43          plume_lon      (nplumes), & !< longitude of plume center (AOD maximum)
44          beta_a         (nplumes), & !< parameter a for beta function vertical profile
45          beta_b         (nplumes), & !< parameter b for beta function vertical profile
46          aod_spmx       (nplumes), & !< anthropogenic AOD maximum at 550 for plumes
47          aod_fmbg       (nplumes), & !< anthropogenic AOD at 550 for fine-mode natural background (idealized to mimic Twomey effect)
48          asy550         (nplumes), & !< asymmetry parameter at 550nm for plume
49          ssa550         (nplumes), & !< single scattering albedo at 550nm for plume
50          angstrom       (nplumes), & !< Angstrom parameter for plume
51          sig_lon_E      (nfeatures, nplumes), & !< Eastward extent of plume feature
52          sig_lon_W      (nfeatures, nplumes), & !< Westward extent of plume feature
53          sig_lat_E      (nfeatures, nplumes), & !< Southward extent of plume feature
54          sig_lat_W      (nfeatures, nplumes), & !< Northward extent of plume feature
55          theta          (nfeatures, nplumes), & !< Rotation angle of plume feature
56          ftr_weight     (nfeatures, nplumes), & !< Feature weights
57          year_weight    (nyears, nplumes), & !< Yearly weight for plume
58          ann_cycle      (nfeatures, ntimes, nplumes) !< annual cycle for plume feature
59  !$OMP THREADPRIVATE(plume_lat,plume_lon,beta_a,beta_b,aod_spmx,aod_fmbg,asy550,ssa550,angstrom)
60  !$OMP THREADPRIVATE(sig_lon_E,sig_lon_W,sig_lat_E,sig_lat_W,theta,ftr_weight,year_weight,ann_cycle)
61
62  REAL :: &
63          time_weight    (nfeatures, nplumes), & !< Time weights
64          time_weight_bg (nfeatures, nplumes)        !< as time_weight but for natural background in Twomey effect
65
66  PUBLIC sp_aop_profile
67
68CONTAINS
69
70  ! ------------------------------------------------------------------------------------------------------------------------
71  ! SP_SETUP:  This SUBROUTINE should be called at initialization to read the netcdf data that describes the simple plume
72  ! climatology.  The information needs to be either read by each processor or distributed to processors.
73
74  SUBROUTINE sp_setup
75
76    USE lmdz_phys_mpi_data, ONLY: is_mpi_root
77    USE lmdz_phys_omp_data, ONLY: is_omp_root
78    USE lmdz_phys_transfert_para, ONLY: bcast
79    USE lmdz_abort_physic, ONLY: abort_physic
80
81    ! ----------
82
83    INTEGER :: iret, ncid, DimID, VarID, xdmy
84    CHARACTER (len = 50) :: modname = 'mo_simple_plumes.sp_setup'
85    CHARACTER (len = 80) :: abort_message
86
87    ! ----------
88    !--only one processor reads the input data
89    IF (is_mpi_root.AND.is_omp_root) THEN
90
91      iret = nf90_open("MACv2.0-SP_v1.nc", nf90_nowrite, ncid)
92      IF (iret /= nf90_noerr) THEN
93        abort_message = 'NetCDF File not opened'
94        CALL abort_physic(modname, abort_message, 1)
95      ENDIF
96
97      ! read dimensions and make sure file conforms to expected size
98
99      iret = nf90_inq_dimid(ncid, "plume_number", DimId)
100      iret = nf90_inquire_dimension(ncid, DimId, len = xdmy)
101      IF (xdmy /= nplumes) THEN
102        abort_message = 'NetCDF improperly dimensioned -- plume_number'
103        CALL abort_physic(modname, abort_message, 1)
104      ENDIF
105
106      iret = nf90_inq_dimid(ncid, "plume_feature", DimId)
107      iret = nf90_inquire_dimension(ncid, DimId, len = xdmy)
108      IF (xdmy /= nfeatures) THEN
109        abort_message = 'NetCDF improperly dimensioned -- plume_feature'
110        CALL abort_physic(modname, abort_message, 1)
111      ENDIF
112
113      iret = nf90_inq_dimid(ncid, "year_fr", DimId)
114      iret = nf90_inquire_dimension(ncid, DimID, len = xdmy)
115      IF (xdmy /= ntimes) THEN
116        abort_message = 'NetCDF improperly dimensioned -- year_fr'
117        CALL abort_physic(modname, abort_message, 1)
118      ENDIF
119
120      iret = nf90_inq_dimid(ncid, "years", DimId)
121      iret = nf90_inquire_dimension(ncid, DimID, len = xdmy)
122      IF (xdmy /= nyears) THEN
123        abort_message = 'NetCDF improperly dimensioned -- years'
124        CALL abort_physic(modname, abort_message, 1)
125      ENDIF
126
127      ! read variables that define the simple plume climatology
128
129      iret = nf90_inq_varid(ncid, "plume_lat", VarId)
130      iret = nf90_get_var(ncid, VarID, plume_lat(:), start = (/1/), count = (/nplumes/))
131      IF (iret /= nf90_noerr) THEN
132        abort_message = 'NetCDF Error reading plume_lat'
133        CALL abort_physic(modname, abort_message, 1)
134      ENDIF
135
136      iret = nf90_inq_varid(ncid, "plume_lon", VarId)
137      iret = nf90_get_var(ncid, VarID, plume_lon(:), start = (/1/), count = (/nplumes/))
138      IF (iret /= nf90_noerr) THEN
139        abort_message = 'NetCDF Error reading plume_lon'
140        CALL abort_physic(modname, abort_message, 1)
141      ENDIF
142
143      iret = nf90_inq_varid(ncid, "beta_a", VarId)
144      iret = nf90_get_var(ncid, VarID, beta_a(:), start = (/1/), count = (/nplumes/))
145      IF (iret /= nf90_noerr) THEN
146        abort_message = 'NetCDF Error reading beta_a'
147        CALL abort_physic(modname, abort_message, 1)
148      ENDIF
149
150      iret = nf90_inq_varid(ncid, "beta_b", VarId)
151      iret = nf90_get_var(ncid, VarID, beta_b(:), start = (/1/), count = (/nplumes/))
152      IF (iret /= nf90_noerr) THEN
153        abort_message = 'NetCDF Error reading beta_b'
154        CALL abort_physic(modname, abort_message, 1)
155      ENDIF
156
157      iret = nf90_inq_varid(ncid, "aod_spmx", VarId)
158      iret = nf90_get_var(ncid, VarID, aod_spmx(:), start = (/1/), count = (/nplumes/))
159      IF (iret /= nf90_noerr) THEN
160        abort_message = 'NetCDF Error reading aod_spmx'
161        CALL abort_physic(modname, abort_message, 1)
162      ENDIF
163
164      iret = nf90_inq_varid(ncid, "aod_fmbg", VarId)
165      iret = nf90_get_var(ncid, VarID, aod_fmbg(:), start = (/1/), count = (/nplumes/))
166      IF (iret /= nf90_noerr) THEN
167        abort_message = 'NetCDF Error reading aod_fmbg'
168        CALL abort_physic(modname, abort_message, 1)
169      ENDIF
170
171      iret = nf90_inq_varid(ncid, "ssa550", VarId)
172      iret = nf90_get_var(ncid, VarID, ssa550(:), start = (/1/), count = (/nplumes/))
173      IF (iret /= nf90_noerr) THEN
174        abort_message = 'NetCDF Error reading ssa550'
175        CALL abort_physic(modname, abort_message, 1)
176      ENDIF
177
178      iret = nf90_inq_varid(ncid, "asy550", VarId)
179      iret = nf90_get_var(ncid, VarID, asy550(:), start = (/1/), count = (/nplumes/))
180      IF (iret /= nf90_noerr) THEN
181        abort_message = 'NetCDF Error reading asy550'
182        CALL abort_physic(modname, abort_message, 1)
183      ENDIF
184
185      iret = nf90_inq_varid(ncid, "angstrom", VarId)
186      iret = nf90_get_var(ncid, VarID, angstrom(:), start = (/1/), count = (/nplumes/))
187      IF (iret /= nf90_noerr) THEN
188        abort_message = 'NetCDF Error reading angstrom'
189        CALL abort_physic(modname, abort_message, 1)
190      ENDIF
191
192      iret = nf90_inq_varid(ncid, "sig_lat_W", VarId)
193      iret = nf90_get_var(ncid, VarID, sig_lat_W(:, :), start = (/1, 1/), count = (/nfeatures, nplumes/))
194      IF (iret /= nf90_noerr) THEN
195        abort_message = 'NetCDF Error reading sig_lat_W'
196        CALL abort_physic(modname, abort_message, 1)
197      ENDIF
198
199      iret = nf90_inq_varid(ncid, "sig_lat_E", VarId)
200      iret = nf90_get_var(ncid, VarID, sig_lat_E(:, :), start = (/1, 1/), count = (/nfeatures, nplumes/))
201      IF (iret /= nf90_noerr) THEN
202        abort_message = 'NetCDF Error reading sig_lat_E'
203        CALL abort_physic(modname, abort_message, 1)
204      ENDIF
205
206      iret = nf90_inq_varid(ncid, "sig_lon_E", VarId)
207      iret = nf90_get_var(ncid, VarID, sig_lon_E(:, :), start = (/1, 1/), count = (/nfeatures, nplumes/))
208      IF (iret /= nf90_noerr) THEN
209        abort_message = 'NetCDF Error reading sig_lon_E'
210        CALL abort_physic(modname, abort_message, 1)
211      ENDIF
212
213      iret = nf90_inq_varid(ncid, "sig_lon_W", VarId)
214      iret = nf90_get_var(ncid, VarID, sig_lon_W(:, :), start = (/1, 1/), count = (/nfeatures, nplumes/))
215      IF (iret /= nf90_noerr) THEN
216        abort_message = 'NetCDF Error reading sig_lon_W'
217        CALL abort_physic(modname, abort_message, 1)
218      ENDIF
219
220      iret = nf90_inq_varid(ncid, "theta", VarId)
221      iret = nf90_get_var(ncid, VarID, theta(:, :), start = (/1, 1/), count = (/nfeatures, nplumes/))
222      IF (iret /= nf90_noerr) THEN
223        abort_message = 'NetCDF Error reading theta'
224        CALL abort_physic(modname, abort_message, 1)
225      ENDIF
226
227      iret = nf90_inq_varid(ncid, "ftr_weight", VarId)
228      iret = nf90_get_var(ncid, VarID, ftr_weight(:, :), start = (/1, 1/), count = (/nfeatures, nplumes/))
229      IF (iret /= nf90_noerr) THEN
230        abort_message = 'NetCDF Error reading plume_lat'
231        CALL abort_physic(modname, abort_message, 1)
232      ENDIF
233
234      iret = nf90_inq_varid(ncid, "year_weight", VarId)
235      iret = nf90_get_var(ncid, VarID, year_weight(:, :), start = (/1, 1/), count = (/nyears, nplumes   /))
236      IF (iret /= nf90_noerr) THEN
237        abort_message = 'NetCDF Error reading year_weight'
238        CALL abort_physic(modname, abort_message, 1)
239      ENDIF
240
241      iret = nf90_inq_varid(ncid, "ann_cycle", VarId)
242      iret = nf90_get_var(ncid, VarID, ann_cycle(:, :, :), start = (/1, 1, 1/), count = (/nfeatures, ntimes, nplumes/))
243      IF (iret /= nf90_noerr) THEN
244        abort_message = 'NetCDF Error reading ann_cycle'
245        CALL abort_physic(modname, abort_message, 1)
246      ENDIF
247
248      iret = nf90_close(ncid)
249
250    ENDIF !--root processor
251
252    CALL bcast(plume_lat)
253    CALL bcast(plume_lon)
254    CALL bcast(beta_a)
255    CALL bcast(beta_b)
256    CALL bcast(aod_spmx)
257    CALL bcast(aod_fmbg)
258    CALL bcast(asy550)
259    CALL bcast(ssa550)
260    CALL bcast(angstrom)
261    CALL bcast(sig_lon_E)
262    CALL bcast(sig_lon_W)
263    CALL bcast(sig_lat_E)
264    CALL bcast(sig_lat_W)
265    CALL bcast(theta)
266    CALL bcast(ftr_weight)
267    CALL bcast(year_weight)
268    CALL bcast(ann_cycle)
269
270    sp_initialized = .TRUE.
271
272  END SUBROUTINE sp_setup
273
274  ! ------------------------------------------------------------------------------------------------------------------------
275  ! SET_TIME_WEIGHT:  The simple plume model assumes that meteorology constrains plume shape and that only source strength
276  ! influences the amplitude of a plume associated with a given source region.   This routine retrieves the temporal weights
277  ! for the plumes.  Each plume feature has its own temporal weights which varies yearly.  The annual cycle is indexed by
278  ! week in the year and superimposed on the yearly mean value of the weight.
279
280  SUBROUTINE set_time_weight(year_fr)
281
282    ! ----------
283    USE lmdz_abort_physic, ONLY: abort_physic
284    REAL, INTENT(IN) :: &
285            year_fr           !< Fractional Year (1850.0 - 2100.99)
286
287    INTEGER :: &
288            iyear, & !< Integer year values between 1 and 156 (1850-2100)
289            iweek, & !< Integer index (between 1 and ntimes); for ntimes=52 this corresponds to weeks (roughly)
290            iplume            ! plume number
291
292    ! ----------
293
294    iyear = FLOOR(year_fr) - 1849
295    iweek = FLOOR((year_fr - FLOOR(year_fr)) * ntimes) + 1
296
297    IF ((iweek > ntimes) .OR. (iweek < 1) .OR. (iyear > nyears) .OR. (iyear < 1)) THEN
298      CALL abort_physic('set_time_weight', 'Time out of bounds', 1)
299    ENDIF
300
301    DO iplume = 1, nplumes
302      time_weight(1, iplume) = year_weight(iyear, iplume) * ann_cycle(1, iweek, iplume)
303      time_weight(2, iplume) = year_weight(iyear, iplume) * ann_cycle(2, iweek, iplume)
304      time_weight_bg(1, iplume) = ann_cycle(1, iweek, iplume)
305      time_weight_bg(2, iplume) = ann_cycle(2, iweek, iplume)
306    ENDDO
307
308  END SUBROUTINE set_time_weight
309
310  ! ------------------------------------------------------------------------------------------------------------------------
311  ! SP_AOP_PROFILE:  This SUBROUTINE calculates the simple plume aerosol and cloud active optical properties based on the
312  ! the simple plume fit to the MPI Aerosol Climatology (Version 2).  It sums over nplumes to provide a profile of aerosol
313  ! optical properties on a host models vertical grid.
314
315  SUBROUTINE sp_aop_profile(&
316          nlevels, ncol, lambda, oro, lon, lat, &
317          year_fr, z, dz, dNovrN, aod_prof, ssa_prof, &
318          asy_prof)
319
320    ! ----------
321
322    INTEGER, INTENT(IN) :: &
323            nlevels, & !< number of levels
324            ncol                       !< number of columns
325
326    REAL, INTENT(IN) :: &
327            lambda, & !< wavelength
328            year_fr, & !< Fractional Year (1903.0 is the 0Z on the first of January 1903, Gregorian)
329            oro(ncol), & !< orographic height (m)
330            lon(ncol), & !< longitude
331            lat(ncol), & !< latitude
332            z (ncol, nlevels), & !< height above sea-level (m)
333            dz(ncol, nlevels)           !< level thickness (difference between half levels) (m)
334
335    REAL, INTENT(OUT) :: &
336            dNovrN(ncol), & !< anthropogenic increase in cloud drop number concentration (factor)
337            aod_prof(ncol, nlevels), & !< profile of aerosol optical depth
338            ssa_prof(ncol, nlevels), & !< profile of single scattering albedo
339            asy_prof(ncol, nlevels)     !< profile of asymmetry parameter
340
341    INTEGER :: iplume, icol, k
342
343    REAL :: &
344            eta(ncol, nlevels), & !< normalized height (by 15 km)
345            z_beta(ncol, nlevels), & !< profile for scaling column optical depth
346            prof(ncol, nlevels), & !< scaled profile (by beta function)
347            beta_sum(ncol), & !< vertical sum of beta function
348            ssa(ncol), & !< single scattering albedo
349            asy(ncol), & !< asymmetry parameter
350            cw_an(ncol), & !< column weight for simple plume (anthropogenic) AOD at 550 nm
351            cw_bg(ncol), & !< column weight for fine-mode natural background AOD at 550 nm
352            caod_sp(ncol), & !< column simple plume anthropogenic AOD at 550 nm
353            caod_bg(ncol), & !< column fine-mode natural background AOD at 550 nm
354            a_plume1, & !< gaussian longitude factor for feature 1
355            a_plume2, & !< gaussian longitude factor for feature 2
356            b_plume1, & !< gaussian latitude factor for feature 1
357            b_plume2, & !< gaussian latitude factor for feature 2
358            delta_lat, & !< latitude offset
359            delta_lon, & !< longitude offset
360            delta_lon_t, & !< threshold for maximum longitudinal plume extent used in transition from 360 to 0 degrees
361            lon1, & !< rotated longitude for feature 1
362            lat1, & !< rotated latitude for feature 2
363            lon2, & !< rotated longitude for feature 1
364            lat2, & !< rotated latitude for feature 2
365            f1, & !< contribution from feature 1
366            f2, & !< contribution from feature 2
367            f3, & !< contribution from feature 1 in natural background of Twomey effect
368            f4, & !< contribution from feature 2 in natural background of Twomey effect
369            aod_550, & !< aerosol optical depth at 550nm
370            aod_lmd, & !< aerosol optical depth at input wavelength
371            lfactor                     !< factor to compute wavelength dependence of optical properties
372
373    ! ----------
374
375    ! initialize input data (by calling setup at first instance)
376
377    IF (.NOT.sp_initialized) CALL sp_setup
378
379    ! get time weights
380
381    CALL set_time_weight(year_fr)
382
383    ! initialize variables, including output
384
385    DO k = 1, nlevels
386      DO icol = 1, ncol
387        aod_prof(icol, k) = 0.0
388        ssa_prof(icol, k) = 0.0
389        asy_prof(icol, k) = 0.0
390        z_beta(icol, k) = MERGE(1.0, 0.0, z(icol, k) >= oro(icol))
391        eta(icol, k) = MAX(0.0, MIN(1.0, z(icol, k) / 15000.))
392      ENDDO
393    ENDDO
394    DO icol = 1, ncol
395      dNovrN(icol) = 1.0
396      caod_sp(icol) = 0.0
397      caod_bg(icol) = 0.02
398    ENDDO
399
400    ! sum contribution from plumes to construct composite profiles of aerosol optical properties
401
402    DO iplume = 1, nplumes
403
404      ! calculate vertical distribution function from parameters of beta distribution
405
406      DO icol = 1, ncol
407        beta_sum(icol) = 0.
408      ENDDO
409      DO k = 1, nlevels
410        DO icol = 1, ncol
411          prof(icol, k) = (eta(icol, k)**(beta_a(iplume) - 1.) * (1. - eta(icol, k))**(beta_b(iplume) - 1.)) * dz(icol, k)
412          beta_sum(icol) = beta_sum(icol) + prof(icol, k)
413        ENDDO
414      ENDDO
415      DO k = 1, nlevels
416        DO icol = 1, ncol
417          prof(icol, k) = (prof(icol, k) / beta_sum(icol)) * z_beta(icol, k)
418        ENDDO
419      ENDDO
420
421      ! calculate plume weights
422
423      DO icol = 1, ncol
424
425        ! get plume-center relative spatial parameters for specifying amplitude of plume at given lat and lon
426
427        delta_lat = lat(icol) - plume_lat(iplume)
428        delta_lon = lon(icol) - plume_lon(iplume)
429        delta_lon_t = MERGE (260., 180., iplume == 1)
430        delta_lon = MERGE (delta_lon - SIGN(360., delta_lon), delta_lon, ABS(delta_lon) > delta_lon_t)
431
432        a_plume1 = 0.5 / (MERGE(sig_lon_E(1, iplume), sig_lon_W(1, iplume), delta_lon > 0)**2)
433        b_plume1 = 0.5 / (MERGE(sig_lat_E(1, iplume), sig_lat_W(1, iplume), delta_lon > 0)**2)
434        a_plume2 = 0.5 / (MERGE(sig_lon_E(2, iplume), sig_lon_W(2, iplume), delta_lon > 0)**2)
435        b_plume2 = 0.5 / (MERGE(sig_lat_E(2, iplume), sig_lat_W(2, iplume), delta_lon > 0)**2)
436
437        ! adjust for a plume specific rotation which helps match plume state to climatology.
438
439        lon1 = COS(theta(1, iplume)) * (delta_lon) + SIN(theta(1, iplume)) * (delta_lat)
440        lat1 = - SIN(theta(1, iplume)) * (delta_lon) + COS(theta(1, iplume)) * (delta_lat)
441        lon2 = COS(theta(2, iplume)) * (delta_lon) + SIN(theta(2, iplume)) * (delta_lat)
442        lat2 = - SIN(theta(2, iplume)) * (delta_lon) + COS(theta(2, iplume)) * (delta_lat)
443
444        ! calculate contribution to plume from its different features, to get a column weight for the anthropogenic
445        ! (cw_an) and the fine-mode natural background aerosol (cw_bg)
446
447        f1 = time_weight(1, iplume) * ftr_weight(1, iplume) * EXP(-1. * (a_plume1 * ((lon1)**2) + (b_plume1 * ((lat1)**2))))
448        f2 = time_weight(2, iplume) * ftr_weight(2, iplume) * EXP(-1. * (a_plume2 * ((lon2)**2) + (b_plume2 * ((lat2)**2))))
449        f3 = time_weight_bg(1, iplume) * ftr_weight(1, iplume) * EXP(-1. * (a_plume1 * ((lon1)**2) + (b_plume1 * ((lat1)**2))))
450        f4 = time_weight_bg(2, iplume) * ftr_weight(2, iplume) * EXP(-1. * (a_plume2 * ((lon2)**2) + (b_plume2 * ((lat2)**2))))
451
452        cw_an(icol) = f1 * aod_spmx(iplume) + f2 * aod_spmx(iplume)
453        cw_bg(icol) = f3 * aod_fmbg(iplume) + f4 * aod_fmbg(iplume)
454
455        ! calculate wavelength-dependent scattering properties
456
457        lfactor = MIN(1.0, 700.0 / lambda)
458        ssa(icol) = (ssa550(iplume) * lfactor**4) / ((ssa550(iplume) * lfactor**4) + ((1 - ssa550(iplume)) * lfactor))
459        asy(icol) = asy550(iplume) * SQRT(lfactor)
460      ENDDO
461
462      ! distribute plume optical properties across its vertical profile weighting by optical depth and scaling for
463      ! wavelength using the angstrom parameter.
464
465      lfactor = EXP(-angstrom(iplume) * LOG(lambda / 550.0))
466      DO k = 1, nlevels
467        DO icol = 1, ncol
468          aod_550 = prof(icol, k) * cw_an(icol)
469          aod_lmd = aod_550 * lfactor
470          caod_sp(icol) = caod_sp(icol) + aod_550
471          caod_bg(icol) = caod_bg(icol) + prof(icol, k) * cw_bg(icol)
472          asy_prof(icol, k) = asy_prof(icol, k) + aod_lmd * ssa(icol) * asy(icol)
473          ssa_prof(icol, k) = ssa_prof(icol, k) + aod_lmd * ssa(icol)
474          aod_prof(icol, k) = aod_prof(icol, k) + aod_lmd
475        ENDDO
476      ENDDO
477    ENDDO
478
479    ! complete optical depth weighting
480
481    DO k = 1, nlevels
482      DO icol = 1, ncol
483        asy_prof(icol, k) = MERGE(asy_prof(icol, k) / ssa_prof(icol, k), 0.0, ssa_prof(icol, k) > TINY(1.))
484        ssa_prof(icol, k) = MERGE(ssa_prof(icol, k) / aod_prof(icol, k), 1.0, aod_prof(icol, k) > TINY(1.))
485      ENDDO
486    ENDDO
487
488    ! calculate effective radius normalization (divisor) factor
489
490    DO icol = 1, ncol
491      dNovrN(icol) = LOG((1000.0 * (caod_sp(icol) + caod_bg(icol))) + 1.0) / LOG((1000.0 * caod_bg(icol)) + 1.0)
492    ENDDO
493
494  END SUBROUTINE sp_aop_profile
495
496END MODULE MO_SIMPLE_PLUMES
Note: See TracBrowser for help on using the repository browser.