source: palm/trunk/SOURCE/salsa_mod.f90 @ 4280

Last change on this file since 4280 was 4280, checked in by monakurppa, 6 years ago

Correct recent bugs in salsa_mod and remove chemistry specific stuff in netcdf_data_iput_mod

  • A boundary conditions bug in salsa_mod: set top boundary to its default value (neumann) if nesting is turned off
  • In salsa_nesting_offl_bc, correct fac_dt to apply time_utc_init
  • Remove chemistry specific parts (inside an if clause id==id_emis) in get_variable_4d_to_3d_real and get_variable_5d_to_4d_real
  • Property svn:keywords set to Id
File size: 603.6 KB
Line 
1!> @file salsa_mod.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM-4U.
4!
5! PALM-4U is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM-4U is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2018-2019 University of Helsinki
18! Copyright 1997-2019 Leibniz Universitaet Hannover
19!--------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: salsa_mod.f90 4280 2019-10-29 14:34:15Z monakurppa $
28! Corrected a bug in boundary conditions and fac_dt in offline nesting
29!
30! 4273 2019-10-24 13:40:54Z monakurppa
31! - Rename nest_salsa to nesting_salsa
32! - Correct some errors in boundary condition flags
33! - Add a check for not trying to output gas concentrations in salsa if the
34!   chemistry module is applied
35! - Set the default value of nesting_salsa and nesting_offline_salsa to .TRUE.
36!
37! 4272 2019-10-23 15:18:57Z schwenkel
38! Further modularization of boundary conditions: moved boundary conditions to
39! respective modules
40!
41! 4270 2019-10-23 10:46:20Z monakurppa
42! - Implement offline nesting for salsa
43! - Alphabetic ordering for module interfaces
44! - Remove init_aerosol_type and init_gases_type from salsa_parin and define them
45!   based on the initializing_actions
46! - parameter definition removed from "season" and "season_z01" is added to parin
47! - bugfix in application of index_hh after implementing the new
48!   palm_date_time_mod
49! - Reformat salsa emission data with LOD=2: size distribution given for each
50!   emission category
51!
52! 4268 2019-10-17 11:29:38Z schwenkel
53! Moving module specific boundary conditions from time_integration to module
54!
55! 4256 2019-10-07 10:08:52Z monakurppa
56! Document previous changes: use global variables nx, ny and nz in salsa_header
57!
58! 4227 2019-09-10 18:04:34Z gronemeier
59! implement new palm_date_time_mod
60!
61! 4226 2019-09-10 17:03:24Z suehring
62! Netcdf input routine for dimension length renamed
63!
64! 4182 2019-08-22 15:20:23Z scharf
65! Corrected "Former revisions" section
66!
67! 4167 2019-08-16 11:01:48Z suehring
68! Changed behaviour of masked output over surface to follow terrain and ignore
69! buildings (J.Resler, T.Gronemeier)
70!
71! 4131 2019-08-02 11:06:18Z monakurppa
72! - Add "salsa_" before each salsa output variable
73! - Add a possibility to output the number (salsa_N_UFP) and mass concentration
74!   (salsa_PM0.1) of ultrafine particles, i.e. particles with a diameter smaller
75!   than 100 nm
76! - Implement aerosol emission mode "parameterized" which is based on the street
77!   type (similar to the chemistry module).
78! - Remove unnecessary nucleation subroutines.
79! - Add the z-dimension for gaseous emissions to correspond the implementation
80!   in the chemistry module
81!
82! 4118 2019-07-25 16:11:45Z suehring
83! - When Dirichlet condition is applied in decycling, the boundary conditions are
84!   only set at the ghost points and not at the prognostic grid points as done
85!   before
86! - Rename decycle_ns/lr to decycle_salsa_ns/lr and decycle_method to
87!   decycle_method_salsa
88! - Allocation and initialization of special advection flags salsa_advc_flags_s
89!   used for salsa. These are exclusively used for salsa variables to
90!   distinguish from the usually-used flags which might be different when
91!   decycling is applied in combination with cyclic boundary conditions.
92!   Moreover, salsa_advc_flags_s considers extended zones around buildings where
93!   the first-order upwind scheme is applied for the horizontal advection terms.
94!   This is done to overcome high concentration peaks due to stationary numerical
95!   oscillations caused by horizontal advection discretization.
96!
97! 4117 2019-07-25 08:54:02Z monakurppa
98! Pass integer flag array as well as boundary flags to WS scalar advection
99! routine
100!
101! 4109 2019-07-22 17:00:34Z suehring
102! Slightly revise setting of boundary conditions at horizontal walls, use
103! data-structure offset index instead of pre-calculate it for each facing
104!
105! 4079 2019-07-09 18:04:41Z suehring
106! Application of monotonic flux limiter for the vertical scalar advection
107! up to the topography top (only for the cache-optimized version at the
108! moment).
109!
110! 4069 2019-07-01 14:05:51Z Giersch
111! Masked output running index mid has been introduced as a local variable to
112! avoid runtime error (Loop variable has been modified) in time_integration
113!
114! 4058 2019-06-27 15:25:42Z knoop
115! Bugfix: to_be_resorted was uninitialized in case of s_H2O in 3d_data_averaging
116!
117! 4012 2019-05-31 15:19:05Z monakurppa
118! Merge salsa branch to trunk. List of changes:
119! - Error corrected in distr_update that resulted in the aerosol number size
120!   distribution not converging if the concentration was nclim.
121! - Added a separate output for aerosol liquid water (s_H2O)
122! - aerosol processes for a size bin are now calculated only if the aerosol
123!   number of concentration of that bin is > 2*nclim
124! - An initialisation error in the subroutine "deposition" corrected and the
125!   subroutine reformatted.
126! - stuff from salsa_util_mod.f90 moved into salsa_mod.f90
127! - calls for closing the netcdf input files added
128!
129! 3956 2019-05-07 12:32:52Z monakurppa
130! - Conceptual bug in depo_surf correct for urban and land surface model
131! - Subroutine salsa_tendency_ij optimized.
132! - Interfaces salsa_non_advective_processes and salsa_exchange_horiz_bounds
133!   created. These are now called in module_interface.
134!   salsa_exchange_horiz_bounds after calling salsa_driver only when needed
135!   (i.e. every dt_salsa).
136!
137! 3924 2019-04-23 09:33:06Z monakurppa
138! Correct a bug introduced by the previous update.
139!
140! 3899 2019-04-16 14:05:27Z monakurppa
141! - remove unnecessary error / location messages
142! - corrected some error message numbers
143! - allocate source arrays only if emissions or dry deposition is applied.
144!
145! 3885 2019-04-11 11:29:34Z kanani
146! Changes related to global restructuring of location messages and introduction
147! of additional debug messages
148!
149! 3876 2019-04-08 18:41:49Z knoop
150! Introduced salsa_actions module interface
151!
152! 3871 2019-04-08 14:38:39Z knoop
153! Major changes in formatting, performance and data input structure (see branch
154! the history for details)
155! - Time-dependent emissions enabled: lod=1 for yearly PM emissions that are
156!   normalised depending on the time, and lod=2 for preprocessed emissions
157!   (similar to the chemistry module).
158! - Additionally, 'uniform' emissions allowed. This emission is set constant on
159!   all horisontal upward facing surfaces and it is created based on parameters
160!   surface_aerosol_flux, aerosol_flux_dpg/sigmag/mass_fracs_a/mass_fracs_b.
161! - All emissions are now implemented as surface fluxes! No 3D sources anymore.
162! - Update the emission information by calling salsa_emission_update if
163!   skip_time_do_salsa >= time_since_reference_point and
164!   next_aero_emission_update <= time_since_reference_point
165! - Aerosol background concentrations read from PIDS_DYNAMIC. The vertical grid
166!   must match the one applied in the model.
167! - Gas emissions and background concentrations can be also read in in salsa_mod
168!   if the chemistry module is not applied.
169! - In deposition, information on the land use type can be now imported from
170!   the land use model
171! - Use SI units in PARIN, i.e. n_lognorm given in #/m3 and dpg in metres.
172! - Apply 100 character line limit
173! - Change all variable names from capital to lowercase letter
174! - Change real exponents to integer if possible. If not, precalculate the value
175!   value of exponent
176! - Rename in1a to start_subrange_1a, fn2a to end_subrange_1a etc.
177! - Rename nbins --> nbins_aerosol, ncc_tot --> ncomponents_mass and ngast -->
178!   ngases_salsa
179! - Rename ibc to index_bc, idu to index_du etc.
180! - Renamed loop indices b, c and sg to ib, ic and ig
181! - run_salsa subroutine removed
182! - Corrected a bud in salsa_driver: falsely applied ino instead of inh
183! - Call salsa_tendency within salsa_prognostic_equations which is called in
184!   module_interface_mod instead of prognostic_equations_mod
185! - Removed tailing white spaces and unused variables
186! - Change error message to start by PA instead of SA
187!
188! 3833 2019-03-28 15:04:04Z forkel
189! added USE chem_gasphase_mod for nvar, nspec and spc_names
190!
191! 3787 2019-03-07 08:43:54Z raasch
192! unused variables removed
193!
194! 3780 2019-03-05 11:19:45Z forkel
195! unused variable for file index removed from rrd-subroutines parameter list
196!
197! 3685 2019-01-21 01:02:11Z knoop
198! Some interface calls moved to module_interface + cleanup
199!
200! 3655 2019-01-07 16:51:22Z knoop
201! Implementation of the PALM module interface
202! 3412 2018-10-24 07:25:57Z monakurppa
203!
204! Authors:
205! --------
206! @author Mona Kurppa (University of Helsinki)
207!
208!
209! Description:
210! ------------
211!> Sectional aerosol module for large scale applications SALSA
212!> (Kokkola et al., 2008, ACP 8, 2469-2483). Solves the aerosol number and mass
213!> concentration as well as chemical composition. Includes aerosol dynamic
214!> processes: nucleation, condensation/evaporation of vapours, coagulation and
215!> deposition on tree leaves, ground and roofs.
216!> Implementation is based on formulations implemented in UCLALES-SALSA except
217!> for deposition which is based on parametrisations by Zhang et al. (2001,
218!> Atmos. Environ. 35, 549-560) or Petroff&Zhang (2010, Geosci. Model Dev. 3,
219!> 753-769)
220!>
221!> @todo Apply information from emission_stack_height to lift emission sources
222!> @todo Allow insoluble emissions
223!------------------------------------------------------------------------------!
224 MODULE salsa_mod
225
226    USE basic_constants_and_equations_mod,                                                         &
227        ONLY:  c_p, g, p_0, pi, r_d
228
229    USE chem_gasphase_mod,                                                                         &
230        ONLY:  nspec, nvar, spc_names
231
232    USE chem_modules,                                                                              &
233        ONLY:  call_chem_at_all_substeps, chem_gasphase_on, chem_species
234
235    USE control_parameters,                                                                        &
236        ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r, bc_dirichlet_s,      &
237               bc_lr, bc_lr_cyc, bc_ns, bc_ns_cyc, bc_radiation_l, bc_radiation_n, bc_radiation_r, &
238               bc_radiation_s, coupling_char, debug_output, dt_3d, intermediate_timestep_count,    &
239               intermediate_timestep_count_max, land_surface, max_pr_salsa, message_string,        &
240               monotonic_limiter_z, plant_canopy, pt_surface, salsa, scalar_advec,                 &
241               surface_pressure, time_since_reference_point, timestep_scheme, tsc, urban_surface,  &
242               ws_scheme_sca
243
244    USE indices,                                                                                   &
245        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzb, nz, nzt, wall_flags_0
246
247    USE kinds
248
249    USE netcdf_data_input_mod,                                                                     &
250        ONLY:  chem_emis_att_type, chem_emis_val_type
251
252    USE pegrid
253
254    USE statistics,                                                                                &
255        ONLY:  sums_salsa_ws_l
256
257    IMPLICIT NONE
258!
259!-- SALSA constants:
260!
261!-- Local constants:
262    INTEGER(iwp), PARAMETER ::  luc_urban = 15     !< default landuse type for urban
263    INTEGER(iwp), PARAMETER ::  ngases_salsa  = 5  !< total number of gaseous tracers:
264                                                   !< 1 = H2SO4, 2 = HNO3, 3 = NH3, 4 = OCNV
265                                                   !< (non-volatile OC), 5 = OCSV (semi-volatile)
266    INTEGER(iwp), PARAMETER ::  nmod = 7     !< number of modes for initialising the aerosol size distribution
267    INTEGER(iwp), PARAMETER ::  nreg = 2     !< Number of main size subranges
268    INTEGER(iwp), PARAMETER ::  maxspec = 7  !< Max. number of aerosol species
269
270
271    REAL(wp), PARAMETER ::  fill_value = -9999.0_wp    !< value for the _FillValue attribute
272!
273!-- Universal constants
274    REAL(wp), PARAMETER ::  abo    = 1.380662E-23_wp   !< Boltzmann constant (J/K)
275    REAL(wp), PARAMETER ::  alv    = 2.260E+6_wp       !< latent heat for H2O vaporisation (J/kg)
276    REAL(wp), PARAMETER ::  alv_d_rv  = 4896.96865_wp  !< alv / rv
277    REAL(wp), PARAMETER ::  am_airmol = 4.8096E-26_wp  !< Average mass of an air molecule (Jacobson 2005, Eq.2.3)
278    REAL(wp), PARAMETER ::  api6   = 0.5235988_wp      !< pi / 6
279    REAL(wp), PARAMETER ::  argas  = 8.314409_wp       !< Gas constant (J/(mol K))
280    REAL(wp), PARAMETER ::  argas_d_cpd = 8.281283865E-3_wp  !< argas per cpd
281    REAL(wp), PARAMETER ::  avo    = 6.02214E+23_wp    !< Avogadro constant (1/mol)
282    REAL(wp), PARAMETER ::  d_sa   = 5.539376964394570E-10_wp  !< diameter of condensing H2SO4 molecule (m)
283    REAL(wp), PARAMETER ::  for_ppm_to_nconc =  7.243016311E+16_wp !< ppm * avo / R (K/(Pa*m3))
284    REAL(wp), PARAMETER ::  epsoc  = 0.15_wp          !< water uptake of organic material
285    REAL(wp), PARAMETER ::  mclim  = 1.0E-23_wp       !< mass concentration min limit (kg/m3)
286    REAL(wp), PARAMETER ::  n3     = 158.79_wp        !< Number of H2SO4 molecules in 3 nm cluster if d_sa=5.54e-10m
287    REAL(wp), PARAMETER ::  nclim  = 1.0_wp           !< number concentration min limit (#/m3)
288    REAL(wp), PARAMETER ::  surfw0 = 0.073_wp         !< surface tension of water at 293 K (J/m2)
289!
290!-- Molar masses in kg/mol
291    REAL(wp), PARAMETER ::  ambc     = 12.0E-3_wp     !< black carbon (BC)
292    REAL(wp), PARAMETER ::  amdair   = 28.970E-3_wp   !< dry air
293    REAL(wp), PARAMETER ::  amdu     = 100.E-3_wp     !< mineral dust
294    REAL(wp), PARAMETER ::  amh2o    = 18.0154E-3_wp  !< H2O
295    REAL(wp), PARAMETER ::  amh2so4  = 98.06E-3_wp    !< H2SO4
296    REAL(wp), PARAMETER ::  amhno3   = 63.01E-3_wp    !< HNO3
297    REAL(wp), PARAMETER ::  amn2o    = 44.013E-3_wp   !< N2O
298    REAL(wp), PARAMETER ::  amnh3    = 17.031E-3_wp   !< NH3
299    REAL(wp), PARAMETER ::  amo2     = 31.9988E-3_wp  !< O2
300    REAL(wp), PARAMETER ::  amo3     = 47.998E-3_wp   !< O3
301    REAL(wp), PARAMETER ::  amoc     = 150.E-3_wp     !< organic carbon (OC)
302    REAL(wp), PARAMETER ::  amss     = 58.44E-3_wp    !< sea salt (NaCl)
303!
304!-- Densities in kg/m3
305    REAL(wp), PARAMETER ::  arhobc     = 2000.0_wp  !< black carbon
306    REAL(wp), PARAMETER ::  arhodu     = 2650.0_wp  !< mineral dust
307    REAL(wp), PARAMETER ::  arhoh2o    = 1000.0_wp  !< H2O
308    REAL(wp), PARAMETER ::  arhoh2so4  = 1830.0_wp  !< SO4
309    REAL(wp), PARAMETER ::  arhohno3   = 1479.0_wp  !< HNO3
310    REAL(wp), PARAMETER ::  arhonh3    = 1530.0_wp  !< NH3
311    REAL(wp), PARAMETER ::  arhooc     = 2000.0_wp  !< organic carbon
312    REAL(wp), PARAMETER ::  arhoss     = 2165.0_wp  !< sea salt (NaCl)
313!
314!-- Volume of molecule in m3/#
315    REAL(wp), PARAMETER ::  amvh2o   = amh2o /avo / arhoh2o      !< H2O
316    REAL(wp), PARAMETER ::  amvh2so4 = amh2so4 / avo / arhoh2so4 !< SO4
317    REAL(wp), PARAMETER ::  amvhno3  = amhno3 / avo / arhohno3   !< HNO3
318    REAL(wp), PARAMETER ::  amvnh3   = amnh3 / avo / arhonh3     !< NH3
319    REAL(wp), PARAMETER ::  amvoc    = amoc / avo / arhooc       !< OC
320    REAL(wp), PARAMETER ::  amvss    = amss / avo / arhoss       !< sea salt
321!
322!-- Constants for the dry deposition model by Petroff and Zhang (2010):
323!-- obstacle characteristic dimension "L" (cm) (plane obstacle by default) and empirical constants
324!-- C_B, C_IN, C_IM, beta_IM and C_IT for each land use category (15, as in Zhang et al. (2001))
325    REAL(wp), DIMENSION(1:15), PARAMETER :: l_p10 = &
326        (/0.15,  4.0,   0.15,  3.0,   3.0,   0.5,   3.0,   -99., 0.5,  2.0,  1.0,   -99., -99., -99., 3.0/)
327    REAL(wp), DIMENSION(1:15), PARAMETER :: c_b_p10 = &
328        (/0.887, 1.262, 0.887, 1.262, 1.262, 0.996, 0.996, -99., 0.7,  0.93, 0.996, -99., -99., -99., 1.262/)
329    REAL(wp), DIMENSION(1:15), PARAMETER :: c_in_p10 = &
330        (/0.81,  0.216, 0.81,  0.216, 0.216, 0.191, 0.162, -99., 0.7,  0.14, 0.162, -99., -99., -99., 0.216/)
331    REAL(wp), DIMENSION(1:15), PARAMETER :: c_im_p10 = &
332        (/0.162, 0.13,  0.162, 0.13,  0.13,  0.191, 0.081, -99., 0.191,0.086,0.081, -99., -99., -99., 0.13/)
333    REAL(wp), DIMENSION(1:15), PARAMETER :: beta_im_p10 = &
334        (/0.6,   0.47,  0.6,   0.47,  0.47,  0.47,  0.47,  -99., 0.6,  0.47, 0.47,  -99., -99., -99., 0.47/)
335    REAL(wp), DIMENSION(1:15), PARAMETER :: c_it_p10 = &
336        (/0.0,   0.056, 0.0,   0.056, 0.056, 0.042, 0.056, -99., 0.042,0.014,0.056, -99., -99., -99., 0.056/)
337!
338!-- Constants for the dry deposition model by Zhang et al. (2001):
339!-- empirical constants "alpha" and "gamma" and characteristic radius "A" for
340!-- each land use category (15) and season (5)
341    REAL(wp), DIMENSION(1:15), PARAMETER :: alpha_z01 = &
342        (/1.0, 0.6, 1.1, 0.8, 0.8, 1.2, 1.2, 50.0, 50.0, 1.3, 2.0, 50.0, 100.0, 100.0, 1.5/)
343    REAL(wp), DIMENSION(1:15), PARAMETER :: gamma_z01 = &
344        (/0.56, 0.58, 0.56, 0.56, 0.56, 0.54, 0.54, 0.54, 0.54, 0.54, 0.54, 0.54, 0.50, 0.50, 0.56/)
345    REAL(wp), DIMENSION(1:15,1:5), PARAMETER :: A_z01 =  RESHAPE( (/& 
346         2.0, 5.0, 2.0,  5.0, 5.0, 2.0, 2.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0,&  ! SC1
347         2.0, 5.0, 2.0,  5.0, 5.0, 2.0, 2.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0,&  ! SC2
348         2.0, 5.0, 5.0, 10.0, 5.0, 5.0, 5.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0,&  ! SC3
349         2.0, 5.0, 5.0, 10.0, 5.0, 5.0, 5.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0,&  ! SC4
350         2.0, 5.0, 2.0,  5.0, 5.0, 2.0, 2.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0 &  ! SC5
351                                                           /), (/ 15, 5 /) )
352!-- Land use categories (based on Z01 but the same applies here also for P10):
353!-- 1 = evergreen needleleaf trees,
354!-- 2 = evergreen broadleaf trees,
355!-- 3 = deciduous needleleaf trees,
356!-- 4 = deciduous broadleaf trees,
357!-- 5 = mixed broadleaf and needleleaf trees (deciduous broadleaf trees for P10),
358!-- 6 = grass (short grass for P10),
359!-- 7 = crops, mixed farming,
360!-- 8 = desert,
361!-- 9 = tundra,
362!-- 10 = shrubs and interrupted woodlands (thorn shrubs for P10),
363!-- 11 = wetland with plants (long grass for P10)
364!-- 12 = ice cap and glacier,
365!-- 13 = inland water (inland lake for P10)
366!-- 14 = ocean (water for P10),
367!-- 15 = urban
368!
369!-- SALSA variables:
370    CHARACTER(LEN=20)  ::  bc_salsa_b = 'neumann'                 !< bottom boundary condition
371    CHARACTER(LEN=20)  ::  bc_salsa_t = 'neumann'                 !< top boundary condition
372    CHARACTER(LEN=20)  ::  depo_pcm_par = 'zhang2001'             !< or 'petroff2010'
373    CHARACTER(LEN=20)  ::  depo_pcm_type = 'deciduous_broadleaf'  !< leaf type
374    CHARACTER(LEN=20)  ::  depo_surf_par = 'zhang2001'            !< or 'petroff2010'
375    CHARACTER(LEN=100) ::  input_file_dynamic = 'PIDS_DYNAMIC'    !< file name for dynamic input
376    CHARACTER(LEN=100) ::  input_file_salsa   = 'PIDS_SALSA'      !< file name for emission data
377    CHARACTER(LEN=20)  ::  salsa_emission_mode = 'no_emission'    !< 'no_emission', 'uniform',
378                                                                  !< 'parameterized', 'read_from_file'
379
380    CHARACTER(LEN=20), DIMENSION(4) ::  decycle_method_salsa =                                     &
381                                                 (/'dirichlet','dirichlet','dirichlet','dirichlet'/)
382                                     !< Decycling method at horizontal boundaries
383                                     !< 1=left, 2=right, 3=south, 4=north
384                                     !< dirichlet = initial profiles for the ghost and first 3 layers
385                                     !< neumann = zero gradient
386
387    CHARACTER(LEN=3), DIMENSION(maxspec) ::  listspec = &  !< Active aerosols
388                                   (/'SO4','   ','   ','   ','   ','   ','   '/)
389
390    INTEGER(iwp) ::  depo_pcm_par_num = 1   !< parametrisation type: 1=zhang2001, 2=petroff2010
391    INTEGER(iwp) ::  depo_pcm_type_num = 0  !< index for the dry deposition type on the plant canopy
392    INTEGER(iwp) ::  depo_surf_par_num = 1  !< parametrisation type: 1=zhang2001, 2=petroff2010
393    INTEGER(iwp) ::  end_subrange_1a = 1    !< last index for bin subrange 1a
394    INTEGER(iwp) ::  end_subrange_2a = 1    !< last index for bin subrange 2a
395    INTEGER(iwp) ::  end_subrange_2b = 1    !< last index for bin subrange 2b
396    INTEGER(iwp) ::  ibc_salsa_b            !< index for the bottom boundary condition
397    INTEGER(iwp) ::  ibc_salsa_t            !< index for the top boundary condition
398    INTEGER(iwp) ::  index_bc  = -1         !< index for black carbon (BC)
399    INTEGER(iwp) ::  index_du  = -1         !< index for dust
400    INTEGER(iwp) ::  index_nh  = -1         !< index for NH3
401    INTEGER(iwp) ::  index_no  = -1         !< index for HNO3
402    INTEGER(iwp) ::  index_oc  = -1         !< index for organic carbon (OC)
403    INTEGER(iwp) ::  index_so4 = -1         !< index for SO4 or H2SO4
404    INTEGER(iwp) ::  index_ss  = -1         !< index for sea salt
405    INTEGER(iwp) ::  init_aerosol_type = 0  !< Initial size distribution type
406                                            !< 0 = uniform (read from PARIN)
407                                            !< 1 = read vertical profiles from an input file
408    INTEGER(iwp) ::  init_gases_type = 0    !< Initial gas concentration type
409                                            !< 0 = uniform (read from PARIN)
410                                            !< 1 = read vertical profiles from an input file
411    INTEGER(iwp) ::  lod_gas_emissions = 0  !< level of detail of the gaseous emission data
412    INTEGER(iwp) ::  main_street_id = 0     !< lower bound of main street IDs for parameterized emission mode
413    INTEGER(iwp) ::  max_street_id = 0      !< upper bound of main street IDs for parameterized emission mode
414    INTEGER(iwp) ::  nbins_aerosol = 1      !< total number of size bins
415    INTEGER(iwp) ::  ncc   = 1              !< number of chemical components used
416    INTEGER(iwp) ::  ncomponents_mass = 1   !< total number of chemical compounds (ncc+1)
417                                            !< if particle water is advected)
418    INTEGER(iwp) ::  nj3 = 1                !< J3 parametrization (nucleation)
419                                            !< 1 = condensational sink (Kerminen&Kulmala, 2002)
420                                            !< 2 = coagulational sink (Lehtinen et al. 2007)
421                                            !< 3 = coagS+self-coagulation (Anttila et al. 2010)
422    INTEGER(iwp) ::  nsnucl = 0             !< Choice of the nucleation scheme:
423                                            !< 0 = off
424                                            !< 1 = binary nucleation
425                                            !< 2 = activation type nucleation
426                                            !< 3 = kinetic nucleation
427                                            !< 4 = ternary nucleation
428                                            !< 5 = nucleation with ORGANICs
429                                            !< 6 = activation type of nucleation with H2SO4+ORG
430                                            !< 7 = heteromolecular nucleation with H2SO4*ORG
431                                            !< 8 = homomolecular nucleation of H2SO4
432                                            !<     + heteromolecular nucleation with H2SO4*ORG
433                                            !< 9 = homomolecular nucleation of H2SO4 and ORG
434                                            !<     + heteromolecular nucleation with H2SO4*ORG
435    INTEGER(iwp) ::  salsa_pr_count = 0     !< counter for salsa variable profiles
436    INTEGER(iwp) ::  season_z01 = 1         !< For dry deposition by Zhang et al.: 1 = summer,
437                                            !< 2 = autumn (no harvest yet), 3 = late autumn
438                                            !< (already frost), 4 = winter, 5 = transitional spring
439    INTEGER(iwp) ::  side_street_id = 0     !< lower bound of side street IDs for parameterized emission mode
440    INTEGER(iwp) ::  start_subrange_1a = 1  !< start index for bin subranges: subrange 1a
441    INTEGER(iwp) ::  start_subrange_2a = 1  !<                                subrange 2a
442    INTEGER(iwp) ::  start_subrange_2b = 1  !<                                subrange 2b
443
444    INTEGER(iwp), DIMENSION(nreg) ::  nbin = (/ 3, 7/)  !< Number of size bins per subrange: 1 & 2
445
446    INTEGER(iwp), DIMENSION(ngases_salsa) ::  gas_index_chem = (/ 1, 1, 1, 1, 1/)  !< gas indices in chemistry_model_mod
447                                                                                   !< 1 = H2SO4, 2 = HNO3,
448                                                                                   !< 3 = NH3,   4 = OCNV, 5 = OCSV
449    INTEGER(iwp), DIMENSION(ngases_salsa) ::  emission_index_chem  !< gas indices in the gas emission file
450    INTEGER(iwp), DIMENSION(99) ::  salsa_pr_index  = 0            !< index for salsa profiles
451
452    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  k_topo_top  !< vertical index of the topography top
453
454    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE  ::  salsa_advc_flags_s !< flags used to degrade order of advection
455                                                                        !< scheme for salsa variables near walls and
456                                                                        !< lateral boundaries
457!
458!-- SALSA switches:
459    LOGICAL ::  advect_particle_water   = .TRUE.   !< Advect water concentration of particles
460    LOGICAL ::  decycle_salsa_lr        = .FALSE.  !< Undo cyclic boundaries: left and right
461    LOGICAL ::  decycle_salsa_ns        = .FALSE.  !< Undo cyclic boundaries: north and south
462    LOGICAL ::  include_emission        = .FALSE.  !< Include or not emissions
463    LOGICAL ::  feedback_to_palm        = .FALSE.  !< Allow feedback due to condensation of H2O
464    LOGICAL ::  nesting_salsa           = .TRUE.   !< Apply nesting for salsa
465    LOGICAL ::  nesting_offline_salsa   = .TRUE.   !< Apply offline nesting for salsa
466    LOGICAL ::  no_insoluble            = .FALSE.  !< Exclude insoluble chemical components
467    LOGICAL ::  read_restart_data_salsa = .FALSE.  !< Read restart data for salsa
468    LOGICAL ::  salsa_gases_from_chem   = .FALSE.  !< Transfer the gaseous components to SALSA
469    LOGICAL ::  van_der_waals_coagc     = .FALSE.  !< Include van der Waals and viscous forces in coagulation
470    LOGICAL ::  write_binary_salsa      = .FALSE.  !< read binary for salsa
471!
472!-- Process switches: nl* is read from the NAMELIST and is NOT changed.
473!--                   ls* is the switch used and will get the value of nl*
474!--                       except for special circumstances (spinup period etc.)
475    LOGICAL ::  nlcoag       = .FALSE.  !< Coagulation master switch
476    LOGICAL ::  lscoag       = .FALSE.  !<
477    LOGICAL ::  nlcnd        = .FALSE.  !< Condensation master switch
478    LOGICAL ::  lscnd        = .FALSE.  !<
479    LOGICAL ::  nlcndgas     = .FALSE.  !< Condensation of precursor gases
480    LOGICAL ::  lscndgas     = .FALSE.  !<
481    LOGICAL ::  nlcndh2oae   = .FALSE.  !< Condensation of H2O on aerosol
482    LOGICAL ::  lscndh2oae   = .FALSE.  !< particles (FALSE -> equilibrium calc.)
483    LOGICAL ::  nldepo       = .FALSE.  !< Deposition master switch
484    LOGICAL ::  lsdepo       = .FALSE.  !<
485    LOGICAL ::  nldepo_surf  = .FALSE.  !< Deposition on vegetation master switch
486    LOGICAL ::  lsdepo_surf  = .FALSE.  !<
487    LOGICAL ::  nldepo_pcm   = .FALSE.  !< Deposition on walls master switch
488    LOGICAL ::  lsdepo_pcm   = .FALSE.  !<
489    LOGICAL ::  nldistupdate = .TRUE.   !< Size distribution update master switch
490    LOGICAL ::  lsdistupdate = .FALSE.  !<
491    LOGICAL ::  lspartition  = .FALSE.  !< Partition of HNO3 and NH3
492
493    REAL(wp) ::  act_coeff = 1.0E-7_wp               !< Activation coefficient (1/s)
494    REAL(wp) ::  dt_salsa  = 0.00001_wp              !< Time step of SALSA
495    REAL(wp) ::  emiss_factor_main = 0.0_wp          !< relative emission factor for main streets
496    REAL(wp) ::  emiss_factor_side = 0.0_wp          !< relative emission factor for side streets
497    REAL(wp) ::  h2so4_init = nclim                  !< Init value for sulphuric acid gas
498    REAL(wp) ::  hno3_init  = nclim                  !< Init value for nitric acid gas
499    REAL(wp) ::  last_salsa_time = 0.0_wp            !< previous salsa call
500    REAL(wp) ::  next_aero_emission_update = 0.0_wp  !< previous emission update
501    REAL(wp) ::  next_gas_emission_update = 0.0_wp   !< previous emission update
502    REAL(wp) ::  nf2a = 1.0_wp                       !< Number fraction allocated to 2a-bins
503    REAL(wp) ::  nh3_init  = nclim                   !< Init value for ammonia gas
504    REAL(wp) ::  ocnv_init = nclim                   !< Init value for non-volatile organic gases
505    REAL(wp) ::  ocsv_init = nclim                   !< Init value for semi-volatile organic gases
506    REAL(wp) ::  rhlim = 1.20_wp                     !< RH limit in %/100. Prevents unrealistical RH
507    REAL(wp) ::  time_utc_init                       !< time in seconds-of-day of origin_date_time
508    REAL(wp) ::  skip_time_do_salsa = 0.0_wp         !< Starting time of SALSA (s)
509!
510!-- Initial log-normal size distribution: mode diameter (dpg, metres),
511!-- standard deviation (sigmag) and concentration (n_lognorm, #/m3)
512    REAL(wp), DIMENSION(nmod) ::  dpg   = &
513                     (/1.3E-8_wp, 5.4E-8_wp, 8.6E-7_wp, 2.0E-7_wp, 2.0E-7_wp, 2.0E-7_wp, 2.0E-7_wp/)
514    REAL(wp), DIMENSION(nmod) ::  sigmag  = &
515                                        (/1.8_wp, 2.16_wp, 2.21_wp, 2.0_wp, 2.0_wp, 2.0_wp, 2.0_wp/)
516    REAL(wp), DIMENSION(nmod) ::  n_lognorm = &
517                             (/1.04e+11_wp, 3.23E+10_wp, 5.4E+6_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp/)
518!
519!-- Initial mass fractions / chemical composition of the size distribution
520    REAL(wp), DIMENSION(maxspec) ::  mass_fracs_a = &  !< mass fractions between
521             (/1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)     !< aerosol species for A bins
522    REAL(wp), DIMENSION(maxspec) ::  mass_fracs_b = &  !< mass fractions between
523             (/0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)     !< aerosol species for B bins
524    REAL(wp), DIMENSION(nreg+1) ::  reglim = &         !< Min&max diameters of size subranges
525                                 (/ 3.0E-9_wp, 5.0E-8_wp, 1.0E-5_wp/)
526!
527!-- Initial log-normal size distribution: mode diameter (dpg, metres), standard deviation (sigmag)
528!-- concentration (n_lognorm, #/m3) and mass fractions of all chemical components (listed in
529!-- listspec) for both a (soluble) and b (insoluble) bins.
530    REAL(wp), DIMENSION(nmod) ::  aerosol_flux_dpg   = &
531                     (/1.3E-8_wp, 5.4E-8_wp, 8.6E-7_wp, 2.0E-7_wp, 2.0E-7_wp, 2.0E-7_wp, 2.0E-7_wp/)
532    REAL(wp), DIMENSION(nmod) ::  aerosol_flux_sigmag  = &
533                                        (/1.8_wp, 2.16_wp, 2.21_wp, 2.0_wp, 2.0_wp, 2.0_wp, 2.0_wp/)
534    REAL(wp), DIMENSION(maxspec) ::  aerosol_flux_mass_fracs_a = &
535                                                               (/1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)
536    REAL(wp), DIMENSION(maxspec) ::  aerosol_flux_mass_fracs_b = &
537                                                               (/0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)
538    REAL(wp), DIMENSION(nmod) ::  surface_aerosol_flux = &
539                                 (/1.0E+8_wp, 1.0E+9_wp, 1.0E+5_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp/)
540
541    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bin_low_limits     !< to deliver information about
542                                                               !< the lower diameters per bin
543    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_am_t_val        !< vertical gradient of: aerosol mass
544    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_an_t_val        !< of: aerosol number
545    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_gt_t_val        !< salsa gases near domain top
546    REAL(wp), DIMENSION(:), ALLOCATABLE ::  gas_emission_time  !< Time array in gas emission data (s)
547    REAL(wp), DIMENSION(:), ALLOCATABLE ::  nsect              !< Background number concentrations
548    REAL(wp), DIMENSION(:), ALLOCATABLE ::  massacc            !< Mass accomodation coefficients
549!
550!-- SALSA derived datatypes:
551!
552!-- Component index
553    TYPE component_index
554       CHARACTER(len=3), ALLOCATABLE ::  comp(:)  !< Component name
555       INTEGER(iwp) ::  ncomp  !< Number of components
556       INTEGER(iwp), ALLOCATABLE ::  ind(:)  !< Component index
557    END TYPE component_index
558!
559!-- For matching LSM and USM surface types and the deposition module surface types
560    TYPE match_surface
561       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_lupg  !< index for pavement / green roofs
562       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_luvw  !< index for vegetation / walls
563       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_luww  !< index for water / windows
564    END TYPE match_surface
565!
566!-- Aerosol emission data attributes
567    TYPE salsa_emission_attribute_type
568
569       CHARACTER(LEN=25) ::   units
570
571       CHARACTER(LEN=25), DIMENSION(:), ALLOCATABLE ::   cat_name    !<
572       CHARACTER(LEN=25), DIMENSION(:), ALLOCATABLE ::   cc_name     !<
573       CHARACTER(LEN=25), DIMENSION(:), ALLOCATABLE ::   unit_time   !<
574       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names   !<
575
576       INTEGER(iwp) ::  lod = 0            !< level of detail
577       INTEGER(iwp) ::  nbins = 10         !< number of aerosol size bins
578       INTEGER(iwp) ::  ncat  = 0          !< number of emission categories
579       INTEGER(iwp) ::  ncc   = 7          !< number of aerosol chemical components
580       INTEGER(iwp) ::  nhoursyear = 0     !< number of hours: HOURLY mode
581       INTEGER(iwp) ::  nmonthdayhour = 0  !< number of month days and hours: MDH mode
582       INTEGER(iwp) ::  num_vars           !< number of variables
583       INTEGER(iwp) ::  nt  = 0            !< number of time steps
584       INTEGER(iwp) ::  nz  = 0            !< number of vertical levels
585       INTEGER(iwp) ::  tind               !< time index for reference time in salsa emission data
586
587       INTEGER(iwp), DIMENSION(maxspec) ::  cc_in2mod = 0   !<
588
589       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  cat_index  !< Index of emission categories
590       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  cc_index   !< Index of chemical components
591
592       REAL(wp) ::  conversion_factor  !< unit conversion factor for aerosol emissions
593
594       REAL(wp), DIMENSION(:), ALLOCATABLE ::  dmid         !< mean diameters of size bins (m)
595       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rho          !< average density (kg/m3)
596       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time         !< time (s)
597       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time_factor  !< emission time factor
598       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z            !< height (m)
599
600       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  etf  !< emission time factor
601       REAL(wp), DIMENSION(:,:), ALLOCATABLE :: stack_height
602
603    END TYPE salsa_emission_attribute_type
604!
605!-- The default size distribution and mass composition per emission category:
606!-- 1 = traffic, 2 = road dust, 3 = wood combustion, 4 = other
607!-- Mass fractions: H2SO4, OC, BC, DU, SS, HNO3, NH3
608    TYPE salsa_emission_mode_type
609
610       INTEGER(iwp) ::  ndm = 3  !< number of default modes
611       INTEGER(iwp) ::  ndc = 4  !< number of default categories
612
613       CHARACTER(LEN=25), DIMENSION(1:4) ::  cat_name_table = (/'traffic exhaust', &
614                                                                'road dust      ', &
615                                                                'wood combustion', &
616                                                                'other          '/)
617
618       INTEGER(iwp), DIMENSION(1:4) ::  cat_input_to_model   !<
619
620       REAL(wp), DIMENSION(1:3) ::  dpg_table = (/ 13.5E-9_wp, 1.4E-6_wp, 5.4E-8_wp/)  !<
621       REAL(wp), DIMENSION(1:3) ::  ntot_table  !<
622       REAL(wp), DIMENSION(1:3) ::  sigmag_table = (/ 1.6_wp, 1.4_wp, 1.7_wp /)  !<
623
624       REAL(wp), DIMENSION(1:maxspec,1:4) ::  mass_frac_table = &  !<
625          RESHAPE( (/ 0.04_wp, 0.48_wp, 0.48_wp, 0.0_wp,  0.0_wp, 0.0_wp, 0.0_wp, &
626                      0.0_wp,  0.05_wp, 0.0_wp,  0.95_wp, 0.0_wp, 0.0_wp, 0.0_wp, &
627                      0.0_wp,  0.5_wp,  0.5_wp,  0.0_wp,  0.0_wp, 0.0_wp, 0.0_wp, &
628                      0.0_wp,  0.5_wp,  0.5_wp,  0.0_wp,  0.0_wp, 0.0_wp, 0.0_wp  &
629                   /), (/maxspec,4/) )
630
631       REAL(wp), DIMENSION(1:3,1:4) ::  pm_frac_table = & !< rel. mass
632                                     RESHAPE( (/ 0.016_wp, 0.000_wp, 0.984_wp, &
633                                                 0.000_wp, 1.000_wp, 0.000_wp, &
634                                                 0.000_wp, 0.000_wp, 1.000_wp, &
635                                                 1.000_wp, 0.000_wp, 1.000_wp  &
636                                              /), (/3,4/) )
637
638    END TYPE salsa_emission_mode_type
639!
640!-- Aerosol emission data values
641    TYPE salsa_emission_value_type
642
643       REAL(wp) ::  fill  !< fill value
644
645       REAL(wp), DIMENSION(:,:), ALLOCATABLE :: mass_fracs  !< mass fractions per emis. category
646       REAL(wp), DIMENSION(:,:), ALLOCATABLE :: num_fracs   !< number fractions per emis. category
647
648       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: def_data      !< surface emission in PM
649       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: preproc_data  !< surface emission per category
650
651    END TYPE salsa_emission_value_type
652!
653!-- Offline nesting data type
654    TYPE salsa_nest_offl_type
655
656       CHARACTER(LEN=16) ::  char_l = 'ls_forcing_left_'  !< leading substring at left boundary
657       CHARACTER(LEN=17) ::  char_n = 'ls_forcing_north_' !< leading substring at north boundary
658       CHARACTER(LEN=17) ::  char_r = 'ls_forcing_right_' !< leading substring at right boundary
659       CHARACTER(LEN=17) ::  char_s = 'ls_forcing_south_' !< leading substring at south boundary
660       CHARACTER(LEN=15) ::  char_t = 'ls_forcing_top_'   !< leading substring at top boundary
661
662       CHARACTER(LEN=5), DIMENSION(1:ngases_salsa) ::  gas_name = (/'H2SO4','HNO3 ','NH3  ','OCNV ','OCSV '/)
663
664       CHARACTER(LEN=25),  DIMENSION(:), ALLOCATABLE ::  cc_name    !< chemical component name
665       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< list of variable names
666
667       INTEGER(iwp) ::  id_dynamic  !< NetCDF id of dynamic input file
668       INTEGER(iwp) ::  ncc         !< number of aerosol chemical components
669       INTEGER(iwp) ::  nt          !< number of time levels in dynamic input file
670       INTEGER(iwp) ::  nzu         !< number of vertical levels on scalar grid in dynamic input file
671       INTEGER(iwp) ::  tind        !< time index for reference time in mesoscale-offline nesting
672       INTEGER(iwp) ::  tind_p      !< time index for following time in mesoscale-offline nesting
673
674       INTEGER(iwp), DIMENSION(maxspec) ::  cc_in2mod = 0  !< to transfer chemical composition from input to model
675
676       LOGICAL ::  init  = .FALSE. !< flag indicating the initialisation of offline nesting
677
678       REAL(wp), DIMENSION(:), ALLOCATABLE ::  dmid      !< vertical profile of aerosol bin diameters
679       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time      !< time in dynamic input file
680       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos  !< zu in dynamic input file
681
682       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_left   !< gas conc. at left boundary
683       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_north  !< gas conc. at north boundary
684       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_right  !< gas conc. at right boundary
685       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_south  !< gas conc. at south boundary
686       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_top    !< gas conc.at top boundary
687       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_left   !< aerosol mass conc. at left boundary
688       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_north  !< aerosol mass conc. at north boundary
689       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_right  !< aerosol mass conc. at right boundary
690       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_south  !< aerosol mass conc. at south boundary
691       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_top    !< aerosol mass conc. at top boundary
692       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_left   !< aerosol number conc. at left boundary
693       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_north  !< aerosol number conc. at north boundary
694       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_right  !< aerosol number conc. at right boundary
695       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_south  !< aerosol number conc. at south boundary
696       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_top    !< aerosol number conc. at top boundary
697
698    END TYPE salsa_nest_offl_type
699!
700!-- Prognostic variable: Aerosol size bin information (number (#/m3) and mass (kg/m3) concentration)
701!-- and the concentration of gaseous tracers (#/m3). Gas tracers are contained sequentially in
702!-- dimension 4 as:
703!-- 1. H2SO4, 2. HNO3, 3. NH3, 4. OCNV (non-volatile organics), 5. OCSV (semi-volatile)
704    TYPE salsa_variable
705
706       REAL(wp), DIMENSION(:), ALLOCATABLE     ::  init  !<
707
708       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s     !<
709       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s     !<
710       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  source     !<
711       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ws_l  !<
712
713       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l  !<
714       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l  !<
715
716       REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  conc     !<
717       REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  conc_p   !<
718       REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tconc_m  !<
719
720    END TYPE salsa_variable
721!
722!-- Datatype used to store information about the binned size distributions of aerosols
723    TYPE t_section
724
725       REAL(wp) ::  dmid     !< bin middle diameter (m)
726       REAL(wp) ::  vhilim   !< bin volume at the high limit
727       REAL(wp) ::  vlolim   !< bin volume at the low limit
728       REAL(wp) ::  vratiohi !< volume ratio between the center and high limit
729       REAL(wp) ::  vratiolo !< volume ratio between the center and low limit
730       !******************************************************
731       ! ^ Do NOT change the stuff above after initialization !
732       !******************************************************
733       REAL(wp) ::  core    !< Volume of dry particle
734       REAL(wp) ::  dwet    !< Wet diameter or mean droplet diameter (m)
735       REAL(wp) ::  numc    !< Number concentration of particles/droplets (#/m3)
736       REAL(wp) ::  veqh2o  !< Equilibrium H2O concentration for each particle
737
738       REAL(wp), DIMENSION(maxspec+1) ::  volc !< Volume concentrations (m^3/m^3) of aerosols +
739                                               !< water. Since most of the stuff in SALSA is hard
740                                               !< coded, these *have to be* in the order
741                                               !< 1:SO4, 2:OC, 3:BC, 4:DU, 5:SS, 6:NO, 7:NH, 8:H2O
742    END TYPE t_section
743
744    TYPE(salsa_emission_attribute_type) ::  aero_emission_att  !< emission attributes
745    TYPE(salsa_emission_value_type)     ::  aero_emission      !< emission values
746    TYPE(salsa_emission_mode_type)      ::  def_modes          !< default emission modes
747
748    TYPE(chem_emis_att_type) ::  chem_emission_att  !< chemistry emission attributes
749
750    TYPE(chem_emis_val_type), DIMENSION(:), ALLOCATABLE ::  chem_emission  !< chemistry emissions
751
752    TYPE(t_section), DIMENSION(:), ALLOCATABLE ::  aero  !< local aerosol properties
753
754    TYPE(match_surface) ::  lsm_to_depo_h  !< to match the deposition module and horizontal LSM surfaces
755    TYPE(match_surface) ::  usm_to_depo_h  !< to match the deposition module and horizontal USM surfaces
756
757    TYPE(match_surface), DIMENSION(0:3) ::  lsm_to_depo_v  !< to match the deposition mod. and vertical LSM surfaces
758    TYPE(match_surface), DIMENSION(0:3) ::  usm_to_depo_v  !< to match the deposition mod. and vertical USM surfaces
759!
760!-- SALSA variables: as x = x(k,j,i,bin).
761!-- The 4th dimension contains all the size bins sequentially for each aerosol species  + water.
762!
763!-- Prognostic variables:
764!
765!-- Number concentration (#/m3)
766    TYPE(salsa_variable), DIMENSION(:), ALLOCATABLE, TARGET ::  aerosol_number  !<
767    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  nconc_1  !<
768    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  nconc_2  !<
769    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  nconc_3  !<
770!
771!-- Mass concentration (kg/m3)
772    TYPE(salsa_variable), DIMENSION(:), ALLOCATABLE, TARGET ::  aerosol_mass  !<
773    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  mconc_1  !<
774    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  mconc_2  !<
775    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  mconc_3  !<
776!
777!-- Gaseous concentrations (#/m3)
778    TYPE(salsa_variable), DIMENSION(:), ALLOCATABLE, TARGET ::  salsa_gas  !<
779    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  gconc_1  !<
780    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  gconc_2  !<
781    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  gconc_3  !<
782!
783!-- Diagnostic tracers
784    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  sedim_vd  !< sedimentation velocity per bin (m/s)
785    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  ra_dry    !< aerosol dry radius (m)
786
787!-- Particle component index tables
788    TYPE(component_index) :: prtcl  !< Contains "getIndex" which gives the index for a given aerosol
789                                    !< component name: 1:SO4, 2:OC, 3:BC, 4:DU, 5:SS, 6:NO, 7:NH, 8:H2O
790!
791!-- Offline nesting:
792    TYPE(salsa_nest_offl_type) ::  salsa_nest_offl  !< data structure for offline nesting
793!
794!-- Data output arrays:
795!
796!-- Gases:
797    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  g_h2so4_av  !< H2SO4
798    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  g_hno3_av   !< HNO3
799    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  g_nh3_av    !< NH3
800    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  g_ocnv_av   !< non-volatile OC
801    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  g_ocsv_av   !< semi-volatile OC
802!
803!-- Integrated:
804    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ldsa_av  !< lung-deposited surface area
805    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ntot_av  !< total number concentration
806    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nufp_av  !< ultrafine particles (UFP)
807    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pm01_av  !< PM0.1
808    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pm25_av  !< PM2.5
809    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pm10_av  !< PM10
810!
811!-- In the particle phase:
812    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_bc_av   !< black carbon
813    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_du_av   !< dust
814    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_h2o_av  !< liquid water
815    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_nh_av   !< ammonia
816    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_no_av   !< nitrates
817    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_oc_av   !< org. carbon
818    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_so4_av  !< sulphates
819    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_ss_av   !< sea salt
820!
821!-- Bin specific mass and number concentrations:
822    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  mbins_av  !< bin mas
823    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  nbins_av  !< bin number
824
825!
826!-- PALM interfaces:
827
828    INTERFACE salsa_actions
829       MODULE PROCEDURE salsa_actions
830       MODULE PROCEDURE salsa_actions_ij
831    END INTERFACE salsa_actions
832
833    INTERFACE salsa_3d_data_averaging
834       MODULE PROCEDURE salsa_3d_data_averaging
835    END INTERFACE salsa_3d_data_averaging
836
837    INTERFACE salsa_boundary_conds
838       MODULE PROCEDURE salsa_boundary_conds
839       MODULE PROCEDURE salsa_boundary_conds_decycle
840    END INTERFACE salsa_boundary_conds
841
842    INTERFACE salsa_boundary_conditions
843       MODULE PROCEDURE salsa_boundary_conditions
844    END INTERFACE salsa_boundary_conditions
845
846    INTERFACE salsa_check_data_output
847       MODULE PROCEDURE salsa_check_data_output
848    END INTERFACE salsa_check_data_output
849
850    INTERFACE salsa_check_data_output_pr
851       MODULE PROCEDURE salsa_check_data_output_pr
852    END INTERFACE salsa_check_data_output_pr
853
854    INTERFACE salsa_check_parameters
855       MODULE PROCEDURE salsa_check_parameters
856    END INTERFACE salsa_check_parameters
857
858    INTERFACE salsa_data_output_2d
859       MODULE PROCEDURE salsa_data_output_2d
860    END INTERFACE salsa_data_output_2d
861
862    INTERFACE salsa_data_output_3d
863       MODULE PROCEDURE salsa_data_output_3d
864    END INTERFACE salsa_data_output_3d
865
866    INTERFACE salsa_data_output_mask
867       MODULE PROCEDURE salsa_data_output_mask
868    END INTERFACE salsa_data_output_mask
869
870    INTERFACE salsa_define_netcdf_grid
871       MODULE PROCEDURE salsa_define_netcdf_grid
872    END INTERFACE salsa_define_netcdf_grid
873
874    INTERFACE salsa_emission_update
875       MODULE PROCEDURE salsa_emission_update
876    END INTERFACE salsa_emission_update
877
878    INTERFACE salsa_exchange_horiz_bounds
879       MODULE PROCEDURE salsa_exchange_horiz_bounds
880    END INTERFACE salsa_exchange_horiz_bounds
881
882    INTERFACE salsa_header
883       MODULE PROCEDURE salsa_header
884    END INTERFACE salsa_header
885
886    INTERFACE salsa_init
887       MODULE PROCEDURE salsa_init
888    END INTERFACE salsa_init
889
890    INTERFACE salsa_init_arrays
891       MODULE PROCEDURE salsa_init_arrays
892    END INTERFACE salsa_init_arrays
893
894    INTERFACE salsa_nesting_offl_bc
895       MODULE PROCEDURE salsa_nesting_offl_bc
896    END INTERFACE salsa_nesting_offl_bc
897
898    INTERFACE salsa_nesting_offl_init
899       MODULE PROCEDURE salsa_nesting_offl_init
900    END INTERFACE salsa_nesting_offl_init
901
902    INTERFACE salsa_nesting_offl_input
903       MODULE PROCEDURE salsa_nesting_offl_input
904    END INTERFACE salsa_nesting_offl_input
905
906    INTERFACE salsa_non_advective_processes
907       MODULE PROCEDURE salsa_non_advective_processes
908       MODULE PROCEDURE salsa_non_advective_processes_ij
909    END INTERFACE salsa_non_advective_processes
910
911    INTERFACE salsa_parin
912       MODULE PROCEDURE salsa_parin
913    END INTERFACE salsa_parin
914
915    INTERFACE salsa_prognostic_equations
916       MODULE PROCEDURE salsa_prognostic_equations
917       MODULE PROCEDURE salsa_prognostic_equations_ij
918    END INTERFACE salsa_prognostic_equations
919
920    INTERFACE salsa_rrd_local
921       MODULE PROCEDURE salsa_rrd_local
922    END INTERFACE salsa_rrd_local
923
924    INTERFACE salsa_statistics
925       MODULE PROCEDURE salsa_statistics
926    END INTERFACE salsa_statistics
927
928    INTERFACE salsa_swap_timelevel
929       MODULE PROCEDURE salsa_swap_timelevel
930    END INTERFACE salsa_swap_timelevel
931
932    INTERFACE salsa_tendency
933       MODULE PROCEDURE salsa_tendency
934       MODULE PROCEDURE salsa_tendency_ij
935    END INTERFACE salsa_tendency
936
937    INTERFACE salsa_wrd_local
938       MODULE PROCEDURE salsa_wrd_local
939    END INTERFACE salsa_wrd_local
940
941
942    SAVE
943
944    PRIVATE
945!
946!-- Public functions:
947    PUBLIC salsa_3d_data_averaging,       &
948           salsa_actions,                 &
949           salsa_boundary_conds,          &
950           salsa_boundary_conditions,     &
951           salsa_check_data_output,       &
952           salsa_check_data_output_pr,    &
953           salsa_check_parameters,        &
954           salsa_data_output_2d,          &
955           salsa_data_output_3d,          &
956           salsa_data_output_mask,        &
957           salsa_define_netcdf_grid,      &
958           salsa_diagnostics,             &
959           salsa_emission_update,         &
960           salsa_exchange_horiz_bounds,   &
961           salsa_header,                  &
962           salsa_init,                    &
963           salsa_init_arrays,             &
964           salsa_nesting_offl_bc,         &
965           salsa_nesting_offl_init,       &
966           salsa_nesting_offl_input,      &
967           salsa_non_advective_processes, &
968           salsa_parin,                   &
969           salsa_prognostic_equations,    &
970           salsa_rrd_local,               &
971           salsa_statistics,              &
972           salsa_swap_timelevel,          &
973           salsa_wrd_local
974
975!
976!-- Public parameters, constants and initial values
977    PUBLIC bc_am_t_val,           &
978           bc_an_t_val,           &
979           bc_gt_t_val,           &
980           ibc_salsa_b,           &
981           init_aerosol_type,     &
982           init_gases_type,       &
983           nesting_salsa,         &
984           nesting_offline_salsa, &
985           salsa_gases_from_chem, &
986           skip_time_do_salsa
987!
988!-- Public variables
989    PUBLIC aerosol_mass,     &
990           aerosol_number,   &
991           gconc_2,          &
992           mconc_2,          &
993           nbins_aerosol,    &
994           ncomponents_mass, &
995           nconc_2,          &
996           ngases_salsa,     &
997           salsa_gas,        &
998           salsa_nest_offl
999
1000
1001 CONTAINS
1002
1003!------------------------------------------------------------------------------!
1004! Description:
1005! ------------
1006!> Parin for &salsa_par for new modules
1007!------------------------------------------------------------------------------!
1008 SUBROUTINE salsa_parin
1009
1010    USE control_parameters,                                                                        &
1011        ONLY:  data_output_pr
1012
1013    IMPLICIT NONE
1014
1015    CHARACTER(LEN=80) ::  line   !< dummy string that contains the current line of parameter file
1016
1017    INTEGER(iwp) ::  i                 !< loop index
1018    INTEGER(iwp) ::  max_pr_salsa_tmp  !< dummy variable
1019
1020    NAMELIST /salsa_parameters/      aerosol_flux_dpg,                         &
1021                                     aerosol_flux_mass_fracs_a,                &
1022                                     aerosol_flux_mass_fracs_b,                &
1023                                     aerosol_flux_sigmag,                      &
1024                                     advect_particle_water,                    &
1025                                     bc_salsa_b,                               &
1026                                     bc_salsa_t,                               &
1027                                     decycle_salsa_lr,                         &
1028                                     decycle_method_salsa,                     &
1029                                     decycle_salsa_ns,                         &
1030                                     depo_pcm_par,                             &
1031                                     depo_pcm_type,                            &
1032                                     depo_surf_par,                            &
1033                                     dpg,                                      &
1034                                     dt_salsa,                                 &
1035                                     emiss_factor_main,                        &
1036                                     emiss_factor_side,                        &
1037                                     feedback_to_palm,                         &
1038                                     h2so4_init,                               &
1039                                     hno3_init,                                &
1040                                     listspec,                                 &
1041                                     main_street_id,                           &
1042                                     mass_fracs_a,                             &
1043                                     mass_fracs_b,                             &
1044                                     max_street_id,                            &
1045                                     n_lognorm,                                &
1046                                     nbin,                                     &
1047                                     nesting_salsa,                            &
1048                                     nesting_offline_salsa,                    &
1049                                     nf2a,                                     &
1050                                     nh3_init,                                 &
1051                                     nj3,                                      &
1052                                     nlcnd,                                    &
1053                                     nlcndgas,                                 &
1054                                     nlcndh2oae,                               &
1055                                     nlcoag,                                   &
1056                                     nldepo,                                   &
1057                                     nldepo_pcm,                               &
1058                                     nldepo_surf,                              &
1059                                     nldistupdate,                             &
1060                                     nsnucl,                                   &
1061                                     ocnv_init,                                &
1062                                     ocsv_init,                                &
1063                                     read_restart_data_salsa,                  &
1064                                     reglim,                                   &
1065                                     salsa,                                    &
1066                                     salsa_emission_mode,                      &
1067                                     season_z01,                               &
1068                                     sigmag,                                   &
1069                                     side_street_id,                           &
1070                                     skip_time_do_salsa,                       &
1071                                     surface_aerosol_flux,                     &
1072                                     van_der_waals_coagc,                      &
1073                                     write_binary_salsa
1074
1075    line = ' '
1076!
1077!-- Try to find salsa package
1078    REWIND ( 11 )
1079    line = ' '
1080    DO WHILE ( INDEX( line, '&salsa_parameters' ) == 0 )
1081       READ ( 11, '(A)', END=10 )  line
1082    ENDDO
1083    BACKSPACE ( 11 )
1084!
1085!-- Read user-defined namelist
1086    READ ( 11, salsa_parameters )
1087!
1088!-- Enable salsa (salsa switch in modules.f90)
1089    salsa = .TRUE.
1090
1091 10 CONTINUE
1092!
1093!-- Update the number of output profiles
1094    max_pr_salsa_tmp = 0
1095    i = 1
1096    DO WHILE ( data_output_pr(i) /= ' '  .AND.  i <= 100 )
1097       IF ( TRIM( data_output_pr(i)(1:6) ) == 'salsa_' )  max_pr_salsa_tmp = max_pr_salsa_tmp + 1
1098       i = i + 1
1099    ENDDO
1100    IF ( max_pr_salsa_tmp > 0 )  max_pr_salsa = max_pr_salsa_tmp
1101
1102 END SUBROUTINE salsa_parin
1103
1104!------------------------------------------------------------------------------!
1105! Description:
1106! ------------
1107!> Check parameters routine for salsa.
1108!------------------------------------------------------------------------------!
1109 SUBROUTINE salsa_check_parameters
1110
1111    USE control_parameters,                                                                        &
1112        ONLY:  child_domain, humidity, initializing_actions, nesting_offline
1113
1114    IMPLICIT NONE
1115
1116!
1117!-- Check that humidity is switched on
1118    IF ( salsa  .AND.  .NOT.  humidity )  THEN
1119       WRITE( message_string, * ) 'salsa = ', salsa, ' is not allowed with humidity = ', humidity
1120       CALL message( 'salsa_check_parameters', 'PA0594', 1, 2, 0, 6, 0 )
1121    ENDIF
1122!
1123!-- For nested runs, explicitly set nesting boundary conditions.
1124    IF ( child_domain )  THEN
1125       IF ( nesting_salsa )  THEN
1126          bc_salsa_t = 'nested'
1127       ELSE
1128          bc_salsa_t = 'neumann'
1129       ENDIF
1130    ENDIF
1131!
1132!-- Set boundary conditions also in case the model is offline-nested in larger-scale models.
1133    IF ( nesting_offline )  THEN
1134       IF ( nesting_offline_salsa )  THEN
1135          bc_salsa_t = 'nesting_offline'
1136       ELSE
1137          bc_salsa_t = 'neumann'
1138       ENDIF
1139    ENDIF
1140!
1141!-- Set bottom boundary condition flag
1142    IF ( bc_salsa_b == 'dirichlet' )  THEN
1143       ibc_salsa_b = 0
1144    ELSEIF ( bc_salsa_b == 'neumann' )  THEN
1145       ibc_salsa_b = 1
1146    ELSE
1147       message_string = 'unknown boundary condition: bc_salsa_b = "' // TRIM( bc_salsa_t ) // '"'
1148       CALL message( 'salsa_check_parameters', 'PA0595', 1, 2, 0, 6, 0 )
1149    ENDIF
1150!
1151!-- Set top boundary conditions flag
1152    IF ( bc_salsa_t == 'dirichlet' )  THEN
1153       ibc_salsa_t = 0
1154    ELSEIF ( bc_salsa_t == 'neumann' )  THEN
1155       ibc_salsa_t = 1
1156    ELSEIF ( bc_salsa_t == 'initial_gradient' )  THEN
1157       ibc_salsa_t = 2
1158    ELSEIF ( bc_salsa_t == 'nested'  .OR.  bc_salsa_t == 'nesting_offline' )  THEN
1159       ibc_salsa_t = 3
1160    ELSE
1161       message_string = 'unknown boundary condition: bc_salsa_t = "' // TRIM( bc_salsa_t ) // '"'
1162       CALL message( 'salsa_check_parameters', 'PA0596', 1, 2, 0, 6, 0 )
1163    ENDIF
1164!
1165!-- Check J3 parametrisation
1166    IF ( nj3 < 1  .OR.  nj3 > 3 )  THEN
1167       message_string = 'unknown nj3 (must be 1-3)'
1168       CALL message( 'salsa_check_parameters', 'PA0597', 1, 2, 0, 6, 0 )
1169    ENDIF
1170!
1171!-- Check bottom boundary condition in case of surface emissions
1172    IF ( salsa_emission_mode /= 'no_emission'  .AND.  ibc_salsa_b  == 0 ) THEN
1173       message_string = 'salsa_emission_mode /= "no_emission" requires bc_salsa_b = "Neumann"'
1174       CALL message( 'salsa_check_parameters','PA0598', 1, 2, 0, 6, 0 )
1175    ENDIF
1176!
1177!-- Check whether emissions are applied
1178    IF ( salsa_emission_mode /= 'no_emission' )  include_emission = .TRUE.
1179!
1180!-- Set the initialisation type: background concentration are read from PIDS_DYNAMIC if
1181!-- initializing_actions = 'inifor set_constant_profiles'
1182    IF ( INDEX( initializing_actions, 'inifor' ) /= 0 )  THEN
1183       init_aerosol_type = 1
1184       init_gases_type = 1
1185    ENDIF
1186
1187
1188 END SUBROUTINE salsa_check_parameters
1189
1190!------------------------------------------------------------------------------!
1191!
1192! Description:
1193! ------------
1194!> Subroutine defining appropriate grid for netcdf variables.
1195!> It is called out from subroutine netcdf.
1196!> Same grid as for other scalars (see netcdf_interface_mod.f90)
1197!------------------------------------------------------------------------------!
1198 SUBROUTINE salsa_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
1199
1200    IMPLICIT NONE
1201
1202    CHARACTER(LEN=*), INTENT(OUT) ::  grid_x   !<
1203    CHARACTER(LEN=*), INTENT(OUT) ::  grid_y   !<
1204    CHARACTER(LEN=*), INTENT(OUT) ::  grid_z   !<
1205    CHARACTER(LEN=*), INTENT(IN)  ::  var      !<
1206
1207    LOGICAL, INTENT(OUT) ::  found   !<
1208
1209    found  = .TRUE.
1210!
1211!-- Check for the grid
1212
1213    IF ( var(1:6) == 'salsa_' )  THEN  ! same grid for all salsa output variables
1214       grid_x = 'x'
1215       grid_y = 'y'
1216       grid_z = 'zu'
1217    ELSE
1218       found  = .FALSE.
1219       grid_x = 'none'
1220       grid_y = 'none'
1221       grid_z = 'none'
1222    ENDIF
1223
1224 END SUBROUTINE salsa_define_netcdf_grid
1225
1226!------------------------------------------------------------------------------!
1227! Description:
1228! ------------
1229!> Header output for new module
1230!------------------------------------------------------------------------------!
1231 SUBROUTINE salsa_header( io )
1232
1233    USE indices,                                                                                   &
1234        ONLY:  nx, ny, nz
1235
1236    IMPLICIT NONE
1237 
1238    INTEGER(iwp), INTENT(IN) ::  io   !< Unit of the output file
1239!
1240!-- Write SALSA header
1241    WRITE( io, 1 )
1242    WRITE( io, 2 ) skip_time_do_salsa
1243    WRITE( io, 3 ) dt_salsa
1244    WRITE( io, 4 )  nz, ny, nx, nbins_aerosol
1245    IF ( advect_particle_water )  THEN
1246       WRITE( io, 5 )  nz, ny, nx, ncomponents_mass*nbins_aerosol, advect_particle_water
1247    ELSE
1248       WRITE( io, 5 )  nz, ny, nx, ncc*nbins_aerosol, advect_particle_water
1249    ENDIF
1250    IF ( .NOT. salsa_gases_from_chem )  THEN
1251       WRITE( io, 6 )  nz, ny, nx, ngases_salsa, salsa_gases_from_chem
1252    ENDIF
1253    WRITE( io, 7 )
1254    IF ( nsnucl > 0 )   WRITE( io, 8 ) nsnucl, nj3
1255    IF ( nlcoag )       WRITE( io, 9 )
1256    IF ( nlcnd )        WRITE( io, 10 ) nlcndgas, nlcndh2oae
1257    IF ( lspartition )  WRITE( io, 11 )
1258    IF ( nldepo )       WRITE( io, 12 ) nldepo_pcm, nldepo_surf
1259    WRITE( io, 13 )  reglim, nbin, bin_low_limits
1260    IF ( init_aerosol_type == 0 )  WRITE( io, 14 ) nsect
1261    WRITE( io, 15 ) ncc, listspec, mass_fracs_a, mass_fracs_b
1262    IF ( .NOT. salsa_gases_from_chem )  THEN
1263       WRITE( io, 16 ) ngases_salsa, h2so4_init, hno3_init, nh3_init, ocnv_init, ocsv_init
1264    ENDIF
1265    WRITE( io, 17 )  init_aerosol_type, init_gases_type
1266    IF ( init_aerosol_type == 0 )  THEN
1267       WRITE( io, 18 )  dpg, sigmag, n_lognorm
1268    ELSE
1269       WRITE( io, 19 )
1270    ENDIF
1271    IF ( nesting_salsa )  WRITE( io, 20 )  nesting_salsa
1272    IF ( nesting_offline_salsa )  WRITE( io, 21 )  nesting_offline_salsa
1273    WRITE( io, 22 ) salsa_emission_mode
1274    IF ( salsa_emission_mode == 'uniform' )  THEN
1275       WRITE( io, 23 ) surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag,                &
1276                       aerosol_flux_mass_fracs_a
1277    ENDIF
1278    IF ( SUM( aerosol_flux_mass_fracs_b ) > 0.0_wp  .OR. salsa_emission_mode == 'read_from_file' ) &
1279    THEN
1280       WRITE( io, 24 )
1281    ENDIF
1282
12831   FORMAT (//' SALSA information:'/                                                               &
1284              ' ------------------------------'/)
12852   FORMAT   ('    Starts at: skip_time_do_salsa = ', F10.2, '  s')
12863   FORMAT  (/'    Timestep: dt_salsa = ', F6.2, '  s')
12874   FORMAT  (/'    Array shape (z,y,x,bins):'/                                                     &
1288              '       aerosol_number:  ', 4(I3)) 
12895   FORMAT  (/'       aerosol_mass:    ', 4(I3),/                                                  &
1290              '       (advect_particle_water = ', L1, ')')
12916   FORMAT   ('       salsa_gas: ', 4(I3),/                                                        &
1292              '       (salsa_gases_from_chem = ', L1, ')')
12937   FORMAT  (/'    Aerosol dynamic processes included: ')
12948   FORMAT  (/'       nucleation (scheme = ', I1, ' and J3 parametrization = ', I1, ')')
12959   FORMAT  (/'       coagulation')
129610  FORMAT  (/'       condensation (of precursor gases = ', L1, ' and water vapour = ', L1, ')' )
129711  FORMAT  (/'       dissolutional growth by HNO3 and NH3')
129812  FORMAT  (/'       dry deposition (on vegetation = ', L1, ' and on topography = ', L1, ')')
129913  FORMAT  (/'    Aerosol bin subrange limits (in metres): ',  3(ES10.2E3), /                     &
1300              '    Number of size bins for each aerosol subrange: ', 2I3,/                         &
1301              '    Aerosol bin limits (in metres): ', 9(ES10.2E3))
130214  FORMAT   ('    Initial number concentration in bins at the lowest level (#/m**3):', 9(ES10.2E3))
130315  FORMAT  (/'    Number of chemical components used: ', I1,/                                     &
1304              '       Species: ',7(A6),/                                                           &
1305              '    Initial relative contribution of each species to particle volume in:',/         &
1306              '       a-bins: ', 7(F6.3),/                                                         &
1307              '       b-bins: ', 7(F6.3))
130816  FORMAT  (/'    Number of gaseous tracers used: ', I1,/                                         &
1309              '    Initial gas concentrations:',/                                                  &
1310              '       H2SO4: ',ES12.4E3, ' #/m**3',/                                               &
1311              '       HNO3:  ',ES12.4E3, ' #/m**3',/                                               &
1312              '       NH3:   ',ES12.4E3, ' #/m**3',/                                               &
1313              '       OCNV:  ',ES12.4E3, ' #/m**3',/                                               &
1314              '       OCSV:  ',ES12.4E3, ' #/m**3')
131517   FORMAT (/'   Initialising concentrations: ', /                                                &
1316              '      Aerosol size distribution: init_aerosol_type = ', I1,/                        &
1317              '      Gas concentrations: init_gases_type = ', I1 )
131818   FORMAT ( '      Mode diametres: dpg(nmod) = ', 7(F7.3), ' (m)', /                             &
1319              '      Standard deviation: sigmag(nmod) = ', 7(F7.2),/                               &
1320              '      Number concentration: n_lognorm(nmod) = ', 7(ES12.4E3), ' (#/m3)' )
132119   FORMAT (/'      Size distribution read from a file.')
132220   FORMAT (/'   Nesting for salsa variables: ', L1 )
132321   FORMAT (/'   Offline nesting for salsa variables: ', L1 )
132422   FORMAT (/'   Emissions: salsa_emission_mode = ', A )
132523   FORMAT (/'      surface_aerosol_flux = ', ES12.4E3, ' #/m**2/s', /                            &
1326              '      aerosol_flux_dpg     =  ', 7(F7.3), ' (m)', /                                 &
1327              '      aerosol_flux_sigmag  =  ', 7(F7.2), /                                         &
1328              '      aerosol_mass_fracs_a =  ', 7(ES12.4E3) )
132924   FORMAT (/'      (currently all emissions are soluble!)')
1330
1331 END SUBROUTINE salsa_header
1332
1333!------------------------------------------------------------------------------!
1334! Description:
1335! ------------
1336!> Allocate SALSA arrays and define pointers if required
1337!------------------------------------------------------------------------------!
1338 SUBROUTINE salsa_init_arrays
1339
1340    USE advec_ws,                                                                                  &
1341        ONLY: ws_init_flags_scalar
1342
1343    USE surface_mod,                                                                               &
1344        ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
1345
1346    IMPLICIT NONE
1347
1348    INTEGER(iwp) ::  gases_available !< Number of available gas components in the chemistry model
1349    INTEGER(iwp) ::  i               !< loop index for allocating
1350    INTEGER(iwp) ::  ii              !< index for indexing chemical components
1351    INTEGER(iwp) ::  l               !< loop index for allocating: surfaces
1352    INTEGER(iwp) ::  lsp             !< loop index for chem species in the chemistry model
1353
1354    gases_available = 0
1355!
1356!-- Allocate prognostic variables (see salsa_swap_timelevel)
1357!
1358!-- Set derived indices:
1359!-- (This does the same as the subroutine salsa_initialize in SALSA/UCLALES-SALSA)
1360    start_subrange_1a = 1  ! 1st index of subrange 1a
1361    start_subrange_2a = start_subrange_1a + nbin(1)  ! 1st index of subrange 2a
1362    end_subrange_1a   = start_subrange_2a - 1        ! last index of subrange 1a
1363    end_subrange_2a   = end_subrange_1a + nbin(2)    ! last index of subrange 2a
1364
1365!
1366!-- If the fraction of insoluble aerosols in subrange 2 is zero: do not allocate arrays for them
1367    IF ( nf2a > 0.999999_wp  .AND.  SUM( mass_fracs_b ) < 0.00001_wp )  THEN
1368       no_insoluble = .TRUE.
1369       start_subrange_2b = end_subrange_2a+1  ! 1st index of subrange 2b
1370       end_subrange_2b   = end_subrange_2a    ! last index of subrange 2b
1371    ELSE
1372       start_subrange_2b = start_subrange_2a + nbin(2)  ! 1st index of subrange 2b
1373       end_subrange_2b   = end_subrange_2a + nbin(2)    ! last index of subrange 2b
1374    ENDIF
1375
1376    nbins_aerosol = end_subrange_2b   ! total number of aerosol size bins
1377!
1378!-- Create index tables for different aerosol components
1379    CALL component_index_constructor( prtcl, ncc, maxspec, listspec )
1380
1381    ncomponents_mass = ncc
1382    IF ( advect_particle_water )  ncomponents_mass = ncc + 1  ! Add water
1383!
1384!-- Indices for chemical components used (-1 = not used)
1385    ii = 0
1386    IF ( is_used( prtcl, 'SO4' ) )  THEN
1387       index_so4 = get_index( prtcl,'SO4' )
1388       ii = ii + 1
1389    ENDIF
1390    IF ( is_used( prtcl,'OC' ) )  THEN
1391       index_oc = get_index(prtcl, 'OC')
1392       ii = ii + 1
1393    ENDIF
1394    IF ( is_used( prtcl, 'BC' ) )  THEN
1395       index_bc = get_index( prtcl, 'BC' )
1396       ii = ii + 1
1397    ENDIF
1398    IF ( is_used( prtcl, 'DU' ) )  THEN
1399       index_du = get_index( prtcl, 'DU' )
1400       ii = ii + 1
1401    ENDIF
1402    IF ( is_used( prtcl, 'SS' ) )  THEN
1403       index_ss = get_index( prtcl, 'SS' )
1404       ii = ii + 1
1405    ENDIF
1406    IF ( is_used( prtcl, 'NO' ) )  THEN
1407       index_no = get_index( prtcl, 'NO' )
1408       ii = ii + 1
1409    ENDIF
1410    IF ( is_used( prtcl, 'NH' ) )  THEN
1411       index_nh = get_index( prtcl, 'NH' )
1412       ii = ii + 1
1413    ENDIF
1414!
1415!-- All species must be known
1416    IF ( ii /= ncc )  THEN
1417       message_string = 'Unknown aerosol species/component(s) given in the initialization'
1418       CALL message( 'salsa_mod: salsa_init', 'PA0600', 1, 2, 0, 6, 0 )
1419    ENDIF
1420!
1421!-- Allocate:
1422    ALLOCATE( aero(nbins_aerosol), bc_am_t_val(nbins_aerosol*ncomponents_mass),                    &
1423              bc_an_t_val(nbins_aerosol), bc_gt_t_val(ngases_salsa), bin_low_limits(nbins_aerosol),&
1424              nsect(nbins_aerosol), massacc(nbins_aerosol) )
1425    ALLOCATE( k_topo_top(nysg:nyng,nxlg:nxrg) )
1426    IF ( nldepo ) ALLOCATE( sedim_vd(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
1427    ALLOCATE( ra_dry(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
1428!
1429!-- Initialise the sectional particle size distribution
1430    CALL set_sizebins
1431!
1432!-- Aerosol number concentration
1433    ALLOCATE( aerosol_number(nbins_aerosol) )
1434    ALLOCATE( nconc_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol),                                &
1435              nconc_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol),                                &
1436              nconc_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
1437    nconc_1 = 0.0_wp
1438    nconc_2 = 0.0_wp
1439    nconc_3 = 0.0_wp
1440
1441    DO i = 1, nbins_aerosol
1442       aerosol_number(i)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    => nconc_1(:,:,:,i)
1443       aerosol_number(i)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => nconc_2(:,:,:,i)
1444       aerosol_number(i)%tconc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => nconc_3(:,:,:,i)
1445       ALLOCATE( aerosol_number(i)%flux_s(nzb+1:nzt,0:threads_per_task-1),                         &
1446                 aerosol_number(i)%diss_s(nzb+1:nzt,0:threads_per_task-1),                         &
1447                 aerosol_number(i)%flux_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                 &
1448                 aerosol_number(i)%diss_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                 &
1449                 aerosol_number(i)%init(nzb:nzt+1),                                                &
1450                 aerosol_number(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1) )
1451       aerosol_number(i)%init = nclim
1452       IF ( include_emission  .OR.  ( nldepo  .AND.  nldepo_surf ) )  THEN
1453          ALLOCATE( aerosol_number(i)%source(nys:nyn,nxl:nxr) )
1454          aerosol_number(i)%source = 0.0_wp
1455       ENDIF
1456    ENDDO
1457
1458!
1459!-- Aerosol mass concentration
1460    ALLOCATE( aerosol_mass(ncomponents_mass*nbins_aerosol) )
1461    ALLOCATE( mconc_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ncomponents_mass*nbins_aerosol),               &
1462              mconc_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ncomponents_mass*nbins_aerosol),               &
1463              mconc_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ncomponents_mass*nbins_aerosol) )
1464    mconc_1 = 0.0_wp
1465    mconc_2 = 0.0_wp
1466    mconc_3 = 0.0_wp
1467
1468    DO i = 1, ncomponents_mass*nbins_aerosol
1469       aerosol_mass(i)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    => mconc_1(:,:,:,i)
1470       aerosol_mass(i)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => mconc_2(:,:,:,i)
1471       aerosol_mass(i)%tconc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => mconc_3(:,:,:,i)
1472       ALLOCATE( aerosol_mass(i)%flux_s(nzb+1:nzt,0:threads_per_task-1),                           &
1473                 aerosol_mass(i)%diss_s(nzb+1:nzt,0:threads_per_task-1),                           &
1474                 aerosol_mass(i)%flux_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                   &
1475                 aerosol_mass(i)%diss_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                   &
1476                 aerosol_mass(i)%init(nzb:nzt+1),                                                  &
1477                 aerosol_mass(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1)  )
1478       aerosol_mass(i)%init = mclim
1479       IF ( include_emission  .OR.  ( nldepo  .AND.  nldepo_surf ) )  THEN
1480          ALLOCATE( aerosol_mass(i)%source(nys:nyn,nxl:nxr) )
1481          aerosol_mass(i)%source = 0.0_wp
1482       ENDIF
1483    ENDDO
1484
1485!
1486!-- Surface fluxes: answs = aerosol number, amsws = aerosol mass
1487!
1488!-- Horizontal surfaces: default type
1489    DO  l = 0, 2   ! upward (l=0), downward (l=1) and model top (l=2)
1490       ALLOCATE( surf_def_h(l)%answs( 1:surf_def_h(l)%ns, nbins_aerosol ) )
1491       ALLOCATE( surf_def_h(l)%amsws( 1:surf_def_h(l)%ns, nbins_aerosol*ncomponents_mass ) )
1492       surf_def_h(l)%answs = 0.0_wp
1493       surf_def_h(l)%amsws = 0.0_wp
1494    ENDDO
1495!
1496!-- Horizontal surfaces: natural type
1497    ALLOCATE( surf_lsm_h%answs( 1:surf_lsm_h%ns, nbins_aerosol ) )
1498    ALLOCATE( surf_lsm_h%amsws( 1:surf_lsm_h%ns, nbins_aerosol*ncomponents_mass ) )
1499    surf_lsm_h%answs = 0.0_wp
1500    surf_lsm_h%amsws = 0.0_wp
1501!
1502!-- Horizontal surfaces: urban type
1503    ALLOCATE( surf_usm_h%answs( 1:surf_usm_h%ns, nbins_aerosol ) )
1504    ALLOCATE( surf_usm_h%amsws( 1:surf_usm_h%ns, nbins_aerosol*ncomponents_mass ) )
1505    surf_usm_h%answs = 0.0_wp
1506    surf_usm_h%amsws = 0.0_wp
1507
1508!
1509!-- Vertical surfaces: northward (l=0), southward (l=1), eastward (l=2) and westward (l=3) facing
1510    DO  l = 0, 3
1511       ALLOCATE( surf_def_v(l)%answs( 1:surf_def_v(l)%ns, nbins_aerosol ) )
1512       surf_def_v(l)%answs = 0.0_wp
1513       ALLOCATE( surf_def_v(l)%amsws( 1:surf_def_v(l)%ns, nbins_aerosol*ncomponents_mass ) )
1514       surf_def_v(l)%amsws = 0.0_wp
1515
1516       ALLOCATE( surf_lsm_v(l)%answs( 1:surf_lsm_v(l)%ns, nbins_aerosol ) )
1517       surf_lsm_v(l)%answs = 0.0_wp
1518       ALLOCATE( surf_lsm_v(l)%amsws( 1:surf_lsm_v(l)%ns, nbins_aerosol*ncomponents_mass ) )
1519       surf_lsm_v(l)%amsws = 0.0_wp
1520
1521       ALLOCATE( surf_usm_v(l)%answs( 1:surf_usm_v(l)%ns, nbins_aerosol ) )
1522       surf_usm_v(l)%answs = 0.0_wp
1523       ALLOCATE( surf_usm_v(l)%amsws( 1:surf_usm_v(l)%ns, nbins_aerosol*ncomponents_mass ) )
1524       surf_usm_v(l)%amsws = 0.0_wp
1525
1526    ENDDO
1527
1528!
1529!-- Concentration of gaseous tracers (1. SO4, 2. HNO3, 3. NH3, 4. OCNV, 5. OCSV)
1530!-- (number concentration (#/m3) )
1531!
1532!-- If chemistry is on, read gas phase concentrations from there. Otherwise,
1533!-- allocate salsa_gas array.
1534
1535    IF ( air_chemistry )  THEN
1536       DO  lsp = 1, nvar
1537          SELECT CASE ( TRIM( chem_species(lsp)%name ) )
1538             CASE ( 'H2SO4', 'h2so4' )
1539                gases_available = gases_available + 1
1540                gas_index_chem(1) = lsp
1541             CASE ( 'HNO3', 'hno3' )
1542                gases_available = gases_available + 1
1543                gas_index_chem(2) = lsp
1544             CASE ( 'NH3', 'nh3' )
1545                gases_available = gases_available + 1
1546                gas_index_chem(3) = lsp
1547             CASE ( 'OCNV', 'ocnv' )
1548                gases_available = gases_available + 1
1549                gas_index_chem(4) = lsp
1550             CASE ( 'OCSV', 'ocsv' )
1551                gases_available = gases_available + 1
1552                gas_index_chem(5) = lsp
1553          END SELECT
1554       ENDDO
1555
1556       IF ( gases_available == ngases_salsa )  THEN
1557          salsa_gases_from_chem = .TRUE.
1558       ELSE
1559          WRITE( message_string, * ) 'SALSA is run together with chemistry but not all gaseous '// &
1560                                     'components are provided by kpp (H2SO4, HNO3, NH3, OCNV, OCSV)'
1561       CALL message( 'check_parameters', 'PA0599', 1, 2, 0, 6, 0 )
1562       ENDIF
1563
1564    ELSE
1565
1566       ALLOCATE( salsa_gas(ngases_salsa) )
1567       ALLOCATE( gconc_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ngases_salsa),                 &
1568                 gconc_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ngases_salsa),                 &
1569                 gconc_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ngases_salsa) )
1570       gconc_1 = 0.0_wp
1571       gconc_2 = 0.0_wp
1572       gconc_3 = 0.0_wp
1573
1574       DO i = 1, ngases_salsa
1575          salsa_gas(i)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    => gconc_1(:,:,:,i)
1576          salsa_gas(i)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => gconc_2(:,:,:,i)
1577          salsa_gas(i)%tconc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => gconc_3(:,:,:,i)
1578          ALLOCATE( salsa_gas(i)%flux_s(nzb+1:nzt,0:threads_per_task-1),       &
1579                    salsa_gas(i)%diss_s(nzb+1:nzt,0:threads_per_task-1),       &
1580                    salsa_gas(i)%flux_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),&
1581                    salsa_gas(i)%diss_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),&
1582                    salsa_gas(i)%init(nzb:nzt+1),                              &
1583                    salsa_gas(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1) )
1584          salsa_gas(i)%init = nclim
1585          IF ( include_emission )  THEN
1586             ALLOCATE( salsa_gas(i)%source(nys:nys,nxl:nxr) )
1587             salsa_gas(i)%source = 0.0_wp
1588          ENDIF
1589       ENDDO
1590!
1591!--    Surface fluxes: gtsws = gaseous tracer flux
1592!
1593!--    Horizontal surfaces: default type
1594       DO  l = 0, 2   ! upward (l=0), downward (l=1) and model top (l=2)
1595          ALLOCATE( surf_def_h(l)%gtsws( 1:surf_def_h(l)%ns, ngases_salsa ) )
1596          surf_def_h(l)%gtsws = 0.0_wp
1597       ENDDO
1598!--    Horizontal surfaces: natural type
1599       ALLOCATE( surf_lsm_h%gtsws( 1:surf_lsm_h%ns, ngases_salsa ) )
1600       surf_lsm_h%gtsws = 0.0_wp
1601!--    Horizontal surfaces: urban type
1602       ALLOCATE( surf_usm_h%gtsws( 1:surf_usm_h%ns, ngases_salsa ) )
1603       surf_usm_h%gtsws = 0.0_wp
1604!
1605!--    Vertical surfaces: northward (l=0), southward (l=1), eastward (l=2) and
1606!--    westward (l=3) facing
1607       DO  l = 0, 3
1608          ALLOCATE( surf_def_v(l)%gtsws( 1:surf_def_v(l)%ns, ngases_salsa ) )
1609          surf_def_v(l)%gtsws = 0.0_wp
1610          ALLOCATE( surf_lsm_v(l)%gtsws( 1:surf_lsm_v(l)%ns, ngases_salsa ) )
1611          surf_lsm_v(l)%gtsws = 0.0_wp
1612          ALLOCATE( surf_usm_v(l)%gtsws( 1:surf_usm_v(l)%ns, ngases_salsa ) )
1613          surf_usm_v(l)%gtsws = 0.0_wp
1614       ENDDO
1615    ENDIF
1616
1617    IF ( ws_scheme_sca )  THEN
1618
1619       IF ( salsa )  THEN
1620          ALLOCATE( sums_salsa_ws_l(nzb:nzt+1,0:threads_per_task-1) )
1621          sums_salsa_ws_l = 0.0_wp
1622       ENDIF
1623
1624    ENDIF
1625!
1626!-- Set control flags for decycling only at lateral boundary cores. Within the inner cores the
1627!-- decycle flag is set to .FALSE.. Even though it does not affect the setting of chemistry boundary
1628!-- conditions, this flag is used to set advection control flags appropriately.
1629    decycle_salsa_lr = MERGE( decycle_salsa_lr, .FALSE., nxl == 0  .OR.  nxr == nx )
1630    decycle_salsa_ns = MERGE( decycle_salsa_ns, .FALSE., nys == 0  .OR.  nyn == ny )
1631!
1632!-- Decycling can be applied separately for aerosol variables, while wind and other scalars may have
1633!-- cyclic or nested boundary conditions. However, large gradients near the boundaries may produce
1634!-- stationary numerical oscillations near the lateral boundaries when a higher-order scheme is
1635!-- applied near these boundaries. To get rid-off this, set-up additional flags that control the
1636!-- order of the scalar advection scheme near the lateral boundaries for passive scalars with
1637!-- decycling.
1638    IF ( scalar_advec == 'ws-scheme' )  THEN
1639       ALLOCATE( salsa_advc_flags_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1640!
1641!--    In case of decycling, set Neuman boundary conditions for wall_flags_0 bit 31 instead of
1642!--    cyclic boundary conditions. Bit 31 is used to identify extended degradation zones (please see
1643!--    the following comment). Note, since several also other modules may access this bit but may
1644!--    have other boundary conditions, the original value of wall_flags_0 bit 31 must not be
1645!--    modified. Hence, store the boundary conditions directly on salsa_advc_flags_s.
1646!--    salsa_advc_flags_s will be later overwritten in ws_init_flags_scalar and bit 31 won't be used
1647!--    to control the numerical order.
1648!--    Initialize with flag 31 only.
1649       salsa_advc_flags_s = 0
1650       salsa_advc_flags_s = MERGE( IBSET( salsa_advc_flags_s, 31 ), 0, BTEST( wall_flags_0, 31 ) )
1651
1652       IF ( decycle_salsa_ns )  THEN
1653          IF ( nys == 0 )  THEN
1654             DO  i = 1, nbgp
1655                salsa_advc_flags_s(:,nys-i,:) = MERGE( IBSET( salsa_advc_flags_s(:,nys,:), 31 ),   &
1656                                                       IBCLR( salsa_advc_flags_s(:,nys,:), 31 ),   &
1657                                                       BTEST( salsa_advc_flags_s(:,nys,:), 31 ) )
1658             ENDDO
1659          ENDIF
1660          IF ( nyn == ny )  THEN
1661             DO  i = 1, nbgp
1662                salsa_advc_flags_s(:,nyn+i,:) = MERGE( IBSET( salsa_advc_flags_s(:,nyn,:), 31 ),   &
1663                                                       IBCLR( salsa_advc_flags_s(:,nyn,:), 31 ),   &
1664                                                       BTEST( salsa_advc_flags_s(:,nyn,:), 31 ) )
1665             ENDDO
1666          ENDIF
1667       ENDIF
1668       IF ( decycle_salsa_lr )  THEN
1669          IF ( nxl == 0 )  THEN
1670             DO  i = 1, nbgp
1671                salsa_advc_flags_s(:,:,nxl-i) = MERGE( IBSET( salsa_advc_flags_s(:,:,nxl), 31 ),   &
1672                                                       IBCLR( salsa_advc_flags_s(:,:,nxl), 31 ),   &
1673                                                       BTEST( salsa_advc_flags_s(:,:,nxl), 31 ) )
1674             ENDDO
1675          ENDIF
1676          IF ( nxr == nx )  THEN
1677             DO  i = 1, nbgp
1678                salsa_advc_flags_s(:,:,nxr+i) = MERGE( IBSET( salsa_advc_flags_s(:,:,nxr), 31 ),   &
1679                                                       IBCLR( salsa_advc_flags_s(:,:,nxr), 31 ),   &
1680                                                       BTEST( salsa_advc_flags_s(:,:,nxr), 31 ) )
1681             ENDDO
1682          ENDIF
1683       ENDIF
1684!
1685!--    To initialise the advection flags appropriately, pass the boundary flags to
1686!--    ws_init_flags_scalar. The last argument in ws_init_flags_scalar indicates that a passive
1687!--    scalar is being treated and the horizontal advection terms are degraded already 2 grid points
1688!--    before the lateral boundary. Also, extended degradation zones are applied, where
1689!--    horizontal advection of scalars is discretised by the first-order scheme at all grid points
1690!--    in the vicinity of buildings (<= 3 grid points). Even though no building is within the
1691!--    numerical stencil, the first-order scheme is used. At fourth and fifth grid points, the order
1692!--    of the horizontal advection scheme is successively upgraded.
1693!--    These degradations of the advection scheme are done to avoid stationary numerical
1694!--    oscillations, which are responsible for high concentration maxima that may appear e.g. under
1695!--    shear-free stable conditions.
1696       CALL ws_init_flags_scalar( bc_dirichlet_l  .OR.  bc_radiation_l  .OR.  decycle_salsa_lr,    &
1697                                  bc_dirichlet_n  .OR.  bc_radiation_n  .OR.  decycle_salsa_ns,    &
1698                                  bc_dirichlet_r  .OR.  bc_radiation_r  .OR.  decycle_salsa_lr,    &
1699                                  bc_dirichlet_s  .OR.  bc_radiation_s  .OR.  decycle_salsa_ns,    &
1700                                  salsa_advc_flags_s, .TRUE. )
1701    ENDIF
1702
1703
1704 END SUBROUTINE salsa_init_arrays
1705
1706!------------------------------------------------------------------------------!
1707! Description:
1708! ------------
1709!> Initialization of SALSA. Based on salsa_initialize in UCLALES-SALSA.
1710!> Subroutines salsa_initialize, SALSAinit and DiagInitAero in UCLALES-SALSA are
1711!> also merged here.
1712!------------------------------------------------------------------------------!
1713 SUBROUTINE salsa_init
1714
1715    IMPLICIT NONE
1716
1717    INTEGER(iwp) :: i   !<
1718    INTEGER(iwp) :: ib  !< loop index for aerosol number bins
1719    INTEGER(iwp) :: ic  !< loop index for aerosol mass bins
1720    INTEGER(iwp) :: ig  !< loop index for gases
1721    INTEGER(iwp) :: j   !<
1722
1723    IF ( debug_output )  CALL debug_message( 'salsa_init', 'start' )
1724
1725    bin_low_limits = 0.0_wp
1726    k_topo_top     = 0
1727    nsect          = 0.0_wp
1728    massacc        = 1.0_wp
1729!
1730!-- Initialise
1731    IF ( nldepo )  sedim_vd = 0.0_wp
1732
1733    IF ( .NOT. salsa_gases_from_chem )  THEN
1734       IF ( .NOT. read_restart_data_salsa )  THEN
1735          salsa_gas(1)%conc = h2so4_init
1736          salsa_gas(2)%conc = hno3_init
1737          salsa_gas(3)%conc = nh3_init
1738          salsa_gas(4)%conc = ocnv_init
1739          salsa_gas(5)%conc = ocsv_init
1740       ENDIF
1741       DO  ig = 1, ngases_salsa
1742          salsa_gas(ig)%conc_p    = 0.0_wp
1743          salsa_gas(ig)%tconc_m   = 0.0_wp
1744          salsa_gas(ig)%flux_s    = 0.0_wp
1745          salsa_gas(ig)%diss_s    = 0.0_wp
1746          salsa_gas(ig)%flux_l    = 0.0_wp
1747          salsa_gas(ig)%diss_l    = 0.0_wp
1748          salsa_gas(ig)%sums_ws_l = 0.0_wp
1749          salsa_gas(ig)%conc_p    = salsa_gas(ig)%conc
1750       ENDDO
1751!
1752!--    Set initial value for gas compound tracer
1753       salsa_gas(1)%init = h2so4_init
1754       salsa_gas(2)%init = hno3_init
1755       salsa_gas(3)%init = nh3_init
1756       salsa_gas(4)%init = ocnv_init
1757       salsa_gas(5)%init = ocsv_init
1758    ENDIF
1759!
1760!-- Aerosol radius in each bin: dry and wet (m)
1761    ra_dry = 1.0E-10_wp
1762!
1763!-- Initialise location-dependent aerosol size distributions and chemical compositions:
1764    CALL aerosol_init
1765
1766!-- Initalisation run of SALSA + calculate the vertical top index of the topography
1767    DO  i = nxl, nxr
1768       DO  j = nys, nyn
1769
1770          k_topo_top(j,i) = MAXLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,j,i), 12 ) ), DIM = 1 ) - 1
1771
1772          CALL salsa_driver( i, j, 1 )
1773          CALL salsa_diagnostics( i, j )
1774       ENDDO
1775    ENDDO
1776
1777    DO  ib = 1, nbins_aerosol
1778       aerosol_number(ib)%conc_p    = aerosol_number(ib)%conc
1779       aerosol_number(ib)%tconc_m   = 0.0_wp
1780       aerosol_number(ib)%flux_s    = 0.0_wp
1781       aerosol_number(ib)%diss_s    = 0.0_wp
1782       aerosol_number(ib)%flux_l    = 0.0_wp
1783       aerosol_number(ib)%diss_l    = 0.0_wp
1784       aerosol_number(ib)%sums_ws_l = 0.0_wp
1785    ENDDO
1786    DO  ic = 1, ncomponents_mass*nbins_aerosol
1787       aerosol_mass(ic)%conc_p    = aerosol_mass(ic)%conc
1788       aerosol_mass(ic)%tconc_m   = 0.0_wp
1789       aerosol_mass(ic)%flux_s    = 0.0_wp
1790       aerosol_mass(ic)%diss_s    = 0.0_wp
1791       aerosol_mass(ic)%flux_l    = 0.0_wp
1792       aerosol_mass(ic)%diss_l    = 0.0_wp
1793       aerosol_mass(ic)%sums_ws_l = 0.0_wp
1794    ENDDO
1795!
1796!
1797!-- Initialise the deposition scheme and surface types
1798    IF ( nldepo )  CALL init_deposition
1799
1800    IF ( include_emission )  THEN
1801!
1802!--    Read in and initialize emissions
1803       CALL salsa_emission_setup( .TRUE. )
1804       IF ( .NOT. salsa_gases_from_chem  .AND.  salsa_emission_mode == 'read_from_file' )  THEN
1805          CALL salsa_gas_emission_setup( .TRUE. )
1806       ENDIF
1807    ENDIF
1808!
1809!-- Partition and dissolutional growth by gaseous HNO3 and NH3
1810    IF ( index_no > 0  .AND.  index_nh > 0  .AND.  index_so4 > 0 )  lspartition = .TRUE.
1811
1812    IF ( debug_output )  CALL debug_message( 'salsa_init', 'end' )
1813
1814 END SUBROUTINE salsa_init
1815
1816!------------------------------------------------------------------------------!
1817! Description:
1818! ------------
1819!> Initializes particle size distribution grid by calculating size bin limits
1820!> and mid-size for *dry* particles in each bin. Called from salsa_initialize
1821!> (only at the beginning of simulation).
1822!> Size distribution described using:
1823!>   1) moving center method (subranges 1 and 2)
1824!>      (Jacobson, Atmos. Env., 31, 131-144, 1997)
1825!>   2) fixed sectional method (subrange 3)
1826!> Size bins in each subrange are spaced logarithmically
1827!> based on given subrange size limits and bin number.
1828!
1829!> Mona changed 06/2017: Use geometric mean diameter to describe the mean
1830!> particle diameter in a size bin, not the arithmeric mean which clearly
1831!> overestimates the total particle volume concentration.
1832!
1833!> Coded by:
1834!> Hannele Korhonen (FMI) 2005
1835!> Harri Kokkola (FMI) 2006
1836!
1837!> Bug fixes for box model + updated for the new aerosol datatype:
1838!> Juha Tonttila (FMI) 2014
1839!------------------------------------------------------------------------------!
1840 SUBROUTINE set_sizebins
1841
1842    IMPLICIT NONE
1843
1844    INTEGER(iwp) ::  cc  !< running index
1845    INTEGER(iwp) ::  dd  !< running index
1846
1847    REAL(wp) ::  ratio_d  !< ratio of the upper and lower diameter of subranges
1848
1849    aero(:)%dwet     = 1.0E-10_wp
1850    aero(:)%veqh2o   = 1.0E-10_wp
1851    aero(:)%numc     = nclim
1852    aero(:)%core     = 1.0E-10_wp
1853    DO  cc = 1, maxspec+1    ! 1:SO4, 2:OC, 3:BC, 4:DU, 5:SS, 6:NO, 7:NH, 8:H2O
1854       aero(:)%volc(cc) = 0.0_wp
1855    ENDDO
1856!
1857!-- vlolim&vhilim: min & max *dry* volumes [fxm]
1858!-- dmid: bin mid *dry* diameter (m)
1859!-- vratiolo&vratiohi: volume ratio between the center and low/high limit
1860!
1861!-- 1) Size subrange 1:
1862    ratio_d = reglim(2) / reglim(1)   ! section spacing (m)
1863    DO  cc = start_subrange_1a, end_subrange_1a
1864       aero(cc)%vlolim = api6 * ( reglim(1) * ratio_d**( REAL( cc-1 ) / nbin(1) ) )**3
1865       aero(cc)%vhilim = api6 * ( reglim(1) * ratio_d**( REAL( cc ) / nbin(1) ) )**3
1866       aero(cc)%dmid = SQRT( ( aero(cc)%vhilim / api6 )**0.33333333_wp *                           &
1867                             ( aero(cc)%vlolim / api6 )**0.33333333_wp )
1868       aero(cc)%vratiohi = aero(cc)%vhilim / ( api6 * aero(cc)%dmid**3 )
1869       aero(cc)%vratiolo = aero(cc)%vlolim / ( api6 * aero(cc)%dmid**3 )
1870    ENDDO
1871!
1872!-- 2) Size subrange 2:
1873!-- 2.1) Sub-subrange 2a: high hygroscopicity
1874    ratio_d = reglim(3) / reglim(2)   ! section spacing
1875    DO  dd = start_subrange_2a, end_subrange_2a
1876       cc = dd - start_subrange_2a
1877       aero(dd)%vlolim = api6 * ( reglim(2) * ratio_d**( REAL( cc ) / nbin(2) ) )**3
1878       aero(dd)%vhilim = api6 * ( reglim(2) * ratio_d**( REAL( cc+1 ) / nbin(2) ) )**3
1879       aero(dd)%dmid = SQRT( ( aero(dd)%vhilim / api6 )**0.33333333_wp *                           &
1880                             ( aero(dd)%vlolim / api6 )**0.33333333_wp )
1881       aero(dd)%vratiohi = aero(dd)%vhilim / ( api6 * aero(dd)%dmid**3 )
1882       aero(dd)%vratiolo = aero(dd)%vlolim / ( api6 * aero(dd)%dmid**3 )
1883    ENDDO
1884!
1885!-- 2.2) Sub-subrange 2b: low hygroscopicity
1886    IF ( .NOT. no_insoluble )  THEN
1887       aero(start_subrange_2b:end_subrange_2b)%vlolim   = aero(start_subrange_2a:end_subrange_2a)%vlolim
1888       aero(start_subrange_2b:end_subrange_2b)%vhilim   = aero(start_subrange_2a:end_subrange_2a)%vhilim
1889       aero(start_subrange_2b:end_subrange_2b)%dmid     = aero(start_subrange_2a:end_subrange_2a)%dmid
1890       aero(start_subrange_2b:end_subrange_2b)%vratiohi = aero(start_subrange_2a:end_subrange_2a)%vratiohi
1891       aero(start_subrange_2b:end_subrange_2b)%vratiolo = aero(start_subrange_2a:end_subrange_2a)%vratiolo
1892    ENDIF
1893!
1894!-- Initialize the wet diameter with the bin dry diameter to avoid numerical problems later
1895    aero(:)%dwet = aero(:)%dmid
1896!
1897!-- Save bin limits (lower diameter) to be delivered to PALM if needed
1898    DO cc = 1, nbins_aerosol
1899       bin_low_limits(cc) = ( aero(cc)%vlolim / api6 )**0.33333333_wp
1900    ENDDO
1901
1902 END SUBROUTINE set_sizebins
1903
1904!------------------------------------------------------------------------------!
1905! Description:
1906! ------------
1907!> Initilize altitude-dependent aerosol size distributions and compositions.
1908!>
1909!> Mona added 06/2017: Correct the number and mass concentrations by normalizing
1910!< by the given total number and mass concentration.
1911!>
1912!> Tomi Raatikainen, FMI, 29.2.2016
1913!------------------------------------------------------------------------------!
1914 SUBROUTINE aerosol_init
1915
1916    USE netcdf_data_input_mod,                                                                     &
1917        ONLY:  check_existence, close_input_file, get_dimension_length,                            &
1918               get_attribute, get_variable,                                                        &
1919               inquire_num_variables, inquire_variable_names,                                      &
1920               open_read_file
1921
1922    IMPLICIT NONE
1923
1924    CHARACTER(LEN=25),  DIMENSION(:), ALLOCATABLE ::  cc_name    !< chemical component name
1925    CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< variable names
1926
1927    INTEGER(iwp) ::  ee        !< index: end
1928    INTEGER(iwp) ::  i         !< loop index: x-direction
1929    INTEGER(iwp) ::  ib        !< loop index: size bins
1930    INTEGER(iwp) ::  ic        !< loop index: chemical components
1931    INTEGER(iwp) ::  id_dyn    !< NetCDF id of PIDS_DYNAMIC_SALSA
1932    INTEGER(iwp) ::  ig        !< loop index: gases
1933    INTEGER(iwp) ::  j         !< loop index: y-direction
1934    INTEGER(iwp) ::  k         !< loop index: z-direction
1935    INTEGER(iwp) ::  lod_aero  !< level of detail of inital aerosol concentrations
1936    INTEGER(iwp) ::  num_vars  !< number of variables
1937    INTEGER(iwp) ::  pr_nbins  !< number of aerosol size bins in file
1938    INTEGER(iwp) ::  pr_ncc    !< number of aerosol chemical components in file
1939    INTEGER(iwp) ::  pr_nz     !< number of vertical grid-points in file
1940    INTEGER(iwp) ::  prunmode  !< running mode of SALSA
1941    INTEGER(iwp) ::  ss        !< index: start
1942
1943    INTEGER(iwp), DIMENSION(maxspec) ::  cc_in2mod
1944
1945    LOGICAL  ::  netcdf_extend = .FALSE. !< Flag: netcdf file exists
1946
1947    REAL(wp) ::  flag  !< flag to mask topography grid points
1948
1949    REAL(wp), DIMENSION(nbins_aerosol) ::  core   !< size of the bin mid aerosol particle
1950
1951    REAL(wp), DIMENSION(0:nz+1) ::  pnf2a   !< number fraction in 2a
1952    REAL(wp), DIMENSION(0:nz+1) ::  pmfoc1a !< mass fraction of OC in 1a
1953
1954    REAL(wp), DIMENSION(0:nz+1,nbins_aerosol)   ::  pndist  !< vertical profile of size dist. (#/m3)
1955    REAL(wp), DIMENSION(0:nz+1,maxspec)         ::  pmf2a   !< mass distributions in subrange 2a
1956    REAL(wp), DIMENSION(0:nz+1,maxspec)         ::  pmf2b   !< mass distributions in subrange 2b
1957
1958    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pr_dmid  !< vertical profile of aerosol bin diameters
1959    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pr_z     !< z levels of profiles
1960
1961    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pr_mass_fracs_a  !< mass fraction: a
1962    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pr_mass_fracs_b  !< and b
1963
1964    cc_in2mod = 0
1965    prunmode = 1
1966!
1967!-- Bin mean aerosol particle volume (m3)
1968    core(1:nbins_aerosol) = api6 * aero(1:nbins_aerosol)%dmid**3
1969!
1970!-- Set concentrations to zero
1971    pndist(:,:)  = 0.0_wp
1972    pnf2a(:)     = nf2a
1973    pmf2a(:,:)   = 0.0_wp
1974    pmf2b(:,:)   = 0.0_wp
1975    pmfoc1a(:)   = 0.0_wp
1976
1977    IF ( init_aerosol_type == 1 )  THEN
1978!
1979!--    Read input profiles from PIDS_DYNAMIC_SALSA
1980#if defined( __netcdf )
1981!
1982!--    Location-dependent size distributions and compositions.
1983       INQUIRE( FILE = TRIM( input_file_dynamic ) //  TRIM( coupling_char ), EXIST = netcdf_extend )
1984       IF ( netcdf_extend )  THEN
1985!
1986!--       Open file in read-only mode
1987          CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), id_dyn )
1988!
1989!--       At first, inquire all variable names
1990          CALL inquire_num_variables( id_dyn, num_vars )
1991!
1992!--       Allocate memory to store variable names
1993          ALLOCATE( var_names(1:num_vars) )
1994          CALL inquire_variable_names( id_dyn, var_names )
1995!
1996!--       Inquire vertical dimension and number of aerosol chemical components
1997          CALL get_dimension_length( id_dyn, pr_nz, 'z' )
1998          IF ( pr_nz /= nz )  THEN
1999             WRITE( message_string, * ) 'Number of inifor horizontal grid points does not match '//&
2000                                        'the number of numeric grid points.'
2001             CALL message( 'aerosol_init', 'PA0601', 1, 2, 0, 6, 0 )
2002          ENDIF
2003          CALL get_dimension_length( id_dyn, pr_ncc, 'composition_index' )
2004!
2005!--       Allocate memory
2006          ALLOCATE( pr_z(1:pr_nz), pr_mass_fracs_a(nzb:nzt+1,pr_ncc),                              &
2007                    pr_mass_fracs_b(nzb:nzt+1,pr_ncc) )
2008          pr_mass_fracs_a = 0.0_wp
2009          pr_mass_fracs_b = 0.0_wp
2010!
2011!--       Read vertical levels
2012          CALL get_variable( id_dyn, 'z', pr_z )
2013!
2014!--       Read the names of chemical components
2015          IF ( check_existence( var_names, 'composition_name' ) )  THEN
2016             CALL get_variable( id_dyn, 'composition_name', cc_name, pr_ncc )
2017          ELSE
2018             WRITE( message_string, * ) 'Missing composition_name in ' // TRIM( input_file_dynamic )
2019             CALL message( 'aerosol_init', 'PA0655', 1, 2, 0, 6, 0 )
2020          ENDIF
2021!
2022!--       Define the index of each chemical component in the model
2023          DO  ic = 1, pr_ncc
2024             SELECT CASE ( TRIM( cc_name(ic) ) )
2025                CASE ( 'H2SO4', 'SO4', 'h2so4', 'so4' )
2026                   cc_in2mod(1) = ic
2027                CASE ( 'OC', 'oc' )
2028                   cc_in2mod(2) = ic
2029                CASE ( 'BC', 'bc' )
2030                   cc_in2mod(3) = ic
2031                CASE ( 'DU', 'du' )
2032                   cc_in2mod(4) = ic
2033                CASE ( 'SS', 'ss' )
2034                   cc_in2mod(5) = ic
2035                CASE ( 'HNO3', 'hno3', 'NO3', 'no3', 'NO', 'no' )
2036                   cc_in2mod(6) = ic
2037                CASE ( 'NH3', 'nh3', 'NH4', 'nh4', 'NH', 'nh' )
2038                   cc_in2mod(7) = ic
2039             END SELECT
2040          ENDDO
2041
2042          IF ( SUM( cc_in2mod ) == 0 )  THEN
2043             message_string = 'None of the aerosol chemical components in ' // TRIM(               &
2044                              input_file_dynamic ) // ' correspond to ones applied in SALSA.'
2045             CALL message( 'salsa_mod: aerosol_init', 'PA0602', 2, 2, 0, 6, 0 )
2046          ENDIF
2047!
2048!--       Vertical profiles of mass fractions of different chemical components:
2049          IF ( check_existence( var_names, 'init_atmosphere_mass_fracs_a' ) )  THEN
2050             CALL get_variable( id_dyn, 'init_atmosphere_mass_fracs_a', pr_mass_fracs_a,           &
2051                                0, pr_ncc-1, 0, pr_nz-1 )
2052          ELSE
2053             WRITE( message_string, * ) 'Missing init_atmosphere_mass_fracs_a in ' //              &
2054                                        TRIM( input_file_dynamic )
2055             CALL message( 'aerosol_init', 'PA0656', 1, 2, 0, 6, 0 )
2056          ENDIF
2057          CALL get_variable( id_dyn, 'init_atmosphere_mass_fracs_b', pr_mass_fracs_b,              &
2058                             0, pr_ncc-1, 0, pr_nz-1  )
2059!
2060!--       Match the input data with the chemical composition applied in the model
2061          DO  ic = 1, maxspec
2062             ss = cc_in2mod(ic)
2063             IF ( ss == 0 )  CYCLE
2064             pmf2a(nzb+1:nzt+1,ic) = pr_mass_fracs_a(nzb:nzt,ss)
2065             pmf2b(nzb+1:nzt+1,ic) = pr_mass_fracs_b(nzb:nzt,ss)
2066          ENDDO
2067!
2068!--       Aerosol concentrations: lod=1 (vertical profile of sectional number size distribution)
2069          CALL get_attribute( id_dyn, 'lod', lod_aero, .FALSE., 'init_atmosphere_aerosol' )
2070          IF ( lod_aero /= 1 )  THEN
2071             message_string = 'Currently only lod=1 accepted for init_atmosphere_aerosol'
2072             CALL message( 'salsa_mod: aerosol_init', 'PA0603', 2, 2, 0, 6, 0 )
2073          ELSE
2074!
2075!--          Bin mean diameters in the input file
2076             CALL get_dimension_length( id_dyn, pr_nbins, 'Dmid')
2077             IF ( pr_nbins /= nbins_aerosol )  THEN
2078                message_string = 'Number of size bins in init_atmosphere_aerosol does not match '  &
2079                                 // 'with that applied in the model'
2080                CALL message( 'salsa_mod: aerosol_init', 'PA0604', 2, 2, 0, 6, 0 )
2081             ENDIF
2082
2083             ALLOCATE( pr_dmid(pr_nbins) )
2084             pr_dmid    = 0.0_wp
2085
2086             CALL get_variable( id_dyn, 'Dmid', pr_dmid )
2087!
2088!--          Check whether the sectional representation conform to the one
2089!--          applied in the model
2090             IF ( ANY( ABS( ( aero(1:nbins_aerosol)%dmid - pr_dmid ) /                             &
2091                              aero(1:nbins_aerosol)%dmid )  > 0.1_wp )  ) THEN
2092                message_string = 'Mean diameters of the aerosol size bins in ' // TRIM(            &
2093                                 input_file_dynamic ) // ' do not match with the sectional '//     &
2094                                 'representation of the model.'
2095                CALL message( 'salsa_mod: aerosol_init', 'PA0605', 2, 2, 0, 6, 0 )
2096             ENDIF
2097!
2098!--          Inital aerosol concentrations
2099             CALL get_variable( id_dyn, 'init_atmosphere_aerosol', pndist(nzb+1:nzt,:),            &
2100                                0, pr_nbins-1, 0, pr_nz-1 )
2101          ENDIF
2102!
2103!--       Set bottom and top boundary condition (Neumann)
2104          pmf2a(nzb,:)    = pmf2a(nzb+1,:)
2105          pmf2a(nzt+1,:)  = pmf2a(nzt,:)
2106          pmf2b(nzb,:)    = pmf2b(nzb+1,:)
2107          pmf2b(nzt+1,:)  = pmf2b(nzt,:)
2108          pndist(nzb,:)   = pndist(nzb+1,:)
2109          pndist(nzt+1,:) = pndist(nzt,:)
2110
2111          IF ( index_so4 < 0 )  THEN
2112             pmf2a(:,1) = 0.0_wp
2113             pmf2b(:,1) = 0.0_wp
2114          ENDIF
2115          IF ( index_oc < 0 )  THEN
2116             pmf2a(:,2) = 0.0_wp
2117             pmf2b(:,2) = 0.0_wp
2118          ENDIF
2119          IF ( index_bc < 0 )  THEN
2120             pmf2a(:,3) = 0.0_wp
2121             pmf2b(:,3) = 0.0_wp
2122          ENDIF
2123          IF ( index_du < 0 )  THEN
2124             pmf2a(:,4) = 0.0_wp
2125             pmf2b(:,4) = 0.0_wp
2126          ENDIF
2127          IF ( index_ss < 0 )  THEN
2128             pmf2a(:,5) = 0.0_wp
2129             pmf2b(:,5) = 0.0_wp
2130          ENDIF
2131          IF ( index_no < 0 )  THEN
2132             pmf2a(:,6) = 0.0_wp
2133             pmf2b(:,6) = 0.0_wp
2134          ENDIF
2135          IF ( index_nh < 0 )  THEN
2136             pmf2a(:,7) = 0.0_wp
2137             pmf2b(:,7) = 0.0_wp
2138          ENDIF
2139
2140          IF ( SUM( pmf2a ) < 0.00001_wp  .AND.  SUM( pmf2b ) < 0.00001_wp )  THEN
2141             message_string = 'Error in initialising mass fractions of chemical components. ' //   &
2142                              'Check that all chemical components are included in parameter file!'
2143             CALL message( 'salsa_mod: aerosol_init', 'PA0606', 2, 2, 0, 6, 0 ) 
2144          ENDIF
2145!
2146!--       Then normalise the mass fraction so that SUM = 1
2147          DO  k = nzb, nzt+1
2148             pmf2a(k,:) = pmf2a(k,:) / SUM( pmf2a(k,:) )
2149             IF ( SUM( pmf2b(k,:) ) > 0.0_wp )  pmf2b(k,:) = pmf2b(k,:) / SUM( pmf2b(k,:) )
2150          ENDDO
2151
2152          DEALLOCATE( pr_z, pr_mass_fracs_a, pr_mass_fracs_b )
2153
2154       ELSE
2155          message_string = 'Input file '// TRIM( input_file_dynamic ) // TRIM( coupling_char ) //  &
2156                           ' for SALSA missing!'
2157          CALL message( 'salsa_mod: aerosol_init', 'PA0607', 1, 2, 0, 6, 0 )
2158!
2159!--       Close input file
2160          CALL close_input_file( id_dyn )
2161       ENDIF   ! netcdf_extend
2162
2163#else
2164       message_string = 'init_aerosol_type = 1 but preprocessor directive __netcdf is not used '// &
2165                        'in compiling!'
2166       CALL message( 'salsa_mod: aerosol_init', 'PA0608', 1, 2, 0, 6, 0 )
2167
2168#endif
2169
2170    ELSEIF ( init_aerosol_type == 0 )  THEN
2171!
2172!--    Mass fractions for species in a and b-bins
2173       IF ( index_so4 > 0 )  THEN
2174          pmf2a(:,1) = mass_fracs_a(index_so4)
2175          pmf2b(:,1) = mass_fracs_b(index_so4)
2176       ENDIF
2177       IF ( index_oc > 0 )  THEN
2178          pmf2a(:,2) = mass_fracs_a(index_oc)
2179          pmf2b(:,2) = mass_fracs_b(index_oc)
2180       ENDIF
2181       IF ( index_bc > 0 )  THEN
2182          pmf2a(:,3) = mass_fracs_a(index_bc)
2183          pmf2b(:,3) = mass_fracs_b(index_bc)
2184       ENDIF
2185       IF ( index_du > 0 )  THEN
2186          pmf2a(:,4) = mass_fracs_a(index_du)
2187          pmf2b(:,4) = mass_fracs_b(index_du)
2188       ENDIF
2189       IF ( index_ss > 0 )  THEN
2190          pmf2a(:,5) = mass_fracs_a(index_ss)
2191          pmf2b(:,5) = mass_fracs_b(index_ss)
2192       ENDIF
2193       IF ( index_no > 0 )  THEN
2194          pmf2a(:,6) = mass_fracs_a(index_no)
2195          pmf2b(:,6) = mass_fracs_b(index_no)
2196       ENDIF
2197       IF ( index_nh > 0 )  THEN
2198          pmf2a(:,7) = mass_fracs_a(index_nh)
2199          pmf2b(:,7) = mass_fracs_b(index_nh)
2200       ENDIF
2201       DO  k = nzb, nzt+1
2202          pmf2a(k,:) = pmf2a(k,:) / SUM( pmf2a(k,:) )
2203          IF ( SUM( pmf2b(k,:) ) > 0.0_wp ) pmf2b(k,:) = pmf2b(k,:) / SUM( pmf2b(k,:) )
2204       ENDDO
2205
2206       CALL size_distribution( n_lognorm, dpg, sigmag, nsect )
2207!
2208!--    Normalize by the given total number concentration
2209       nsect = nsect * SUM( n_lognorm ) / SUM( nsect )
2210       DO  ib = start_subrange_1a, end_subrange_2b
2211          pndist(:,ib) = nsect(ib)
2212       ENDDO
2213    ENDIF
2214
2215    IF ( init_gases_type == 1 )  THEN
2216!
2217!--    Read input profiles from PIDS_CHEM
2218#if defined( __netcdf )
2219!
2220!--    Location-dependent size distributions and compositions.
2221       INQUIRE( FILE = TRIM( input_file_dynamic ) //  TRIM( coupling_char ), EXIST = netcdf_extend )
2222       IF ( netcdf_extend  .AND.  .NOT. salsa_gases_from_chem )  THEN
2223!
2224!--       Open file in read-only mode
2225          CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), id_dyn )
2226!
2227!--       Inquire dimensions:
2228          CALL get_dimension_length( id_dyn, pr_nz, 'z' )
2229          IF ( pr_nz /= nz )  THEN
2230             WRITE( message_string, * ) 'Number of inifor horizontal grid points does not match '//&
2231                                        'the number of numeric grid points.'
2232             CALL message( 'aerosol_init', 'PA0609', 1, 2, 0, 6, 0 )
2233          ENDIF
2234!
2235!--       Read vertical profiles of gases:
2236          CALL get_variable( id_dyn, 'init_atmosphere_H2SO4', salsa_gas(1)%init(nzb+1:nzt) )
2237          CALL get_variable( id_dyn, 'init_atmosphere_HNO3',  salsa_gas(2)%init(nzb+1:nzt) )
2238          CALL get_variable( id_dyn, 'init_atmosphere_NH3',   salsa_gas(3)%init(nzb+1:nzt) )
2239          CALL get_variable( id_dyn, 'init_atmosphere_OCNV',  salsa_gas(4)%init(nzb+1:nzt) )
2240          CALL get_variable( id_dyn, 'init_atmosphere_OCSV',  salsa_gas(5)%init(nzb+1:nzt) )
2241!
2242!--       Set Neumann top and surface boundary condition for initial + initialise concentrations
2243          DO  ig = 1, ngases_salsa
2244             salsa_gas(ig)%init(nzb)   =  salsa_gas(ig)%init(nzb+1)
2245             salsa_gas(ig)%init(nzt+1) =  salsa_gas(ig)%init(nzt)
2246             IF ( .NOT. read_restart_data_salsa )  THEN
2247                DO  k = nzb, nzt+1
2248                   salsa_gas(ig)%conc(k,:,:) = salsa_gas(ig)%init(k)
2249                ENDDO
2250             ENDIF
2251          ENDDO
2252
2253       ELSEIF ( .NOT. netcdf_extend  .AND.  .NOT.  salsa_gases_from_chem )  THEN
2254          message_string = 'Input file '// TRIM( input_file_dynamic ) // TRIM( coupling_char ) //  &
2255                           ' for SALSA missing!'
2256          CALL message( 'salsa_mod: aerosol_init', 'PA0610', 1, 2, 0, 6, 0 )
2257!
2258!--       Close input file
2259          CALL close_input_file( id_dyn )
2260       ENDIF   ! netcdf_extend
2261#else
2262       message_string = 'init_gases_type = 1 but preprocessor directive __netcdf is not used in '//&
2263                        'compiling!'
2264       CALL message( 'salsa_mod: aerosol_init', 'PA0611', 1, 2, 0, 6, 0 )
2265
2266#endif
2267
2268    ENDIF
2269!
2270!-- Both SO4 and OC are included, so use the given mass fractions
2271    IF ( index_oc > 0  .AND.  index_so4 > 0 )  THEN
2272       pmfoc1a(:) = pmf2a(:,2) / ( pmf2a(:,2) + pmf2a(:,1) )  ! Normalize
2273!
2274!-- Pure organic carbon
2275    ELSEIF ( index_oc > 0 )  THEN
2276       pmfoc1a(:) = 1.0_wp
2277!
2278!-- Pure SO4
2279    ELSEIF ( index_so4 > 0 )  THEN
2280       pmfoc1a(:) = 0.0_wp
2281
2282    ELSE
2283       message_string = 'Either OC or SO4 must be active for aerosol region 1a!'
2284       CALL message( 'salsa_mod: aerosol_init', 'PA0612', 1, 2, 0, 6, 0 )
2285    ENDIF
2286
2287!
2288!-- Initialize concentrations
2289    DO  i = nxlg, nxrg
2290       DO  j = nysg, nyng
2291          DO  k = nzb, nzt+1
2292!
2293!--          Predetermine flag to mask topography
2294             flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
2295!
2296!--          a) Number concentrations
2297!--          Region 1:
2298             DO  ib = start_subrange_1a, end_subrange_1a
2299                IF ( .NOT. read_restart_data_salsa )  THEN
2300                   aerosol_number(ib)%conc(k,j,i) = pndist(k,ib) * flag
2301                ENDIF
2302                IF ( prunmode == 1 )  THEN
2303                   aerosol_number(ib)%init = pndist(:,ib)
2304                ENDIF
2305             ENDDO
2306!
2307!--          Region 2:
2308             IF ( nreg > 1 )  THEN
2309                DO  ib = start_subrange_2a, end_subrange_2a
2310                   IF ( .NOT. read_restart_data_salsa )  THEN
2311                      aerosol_number(ib)%conc(k,j,i) = MAX( 0.0_wp, pnf2a(k) ) * pndist(k,ib) * flag
2312                   ENDIF
2313                   IF ( prunmode == 1 )  THEN
2314                      aerosol_number(ib)%init = MAX( 0.0_wp, nf2a ) * pndist(:,ib)
2315                   ENDIF
2316                ENDDO
2317                IF ( .NOT. no_insoluble )  THEN
2318                   DO  ib = start_subrange_2b, end_subrange_2b
2319                      IF ( pnf2a(k) < 1.0_wp )  THEN
2320                         IF ( .NOT. read_restart_data_salsa )  THEN
2321                            aerosol_number(ib)%conc(k,j,i) = MAX( 0.0_wp, 1.0_wp - pnf2a(k) ) *    &
2322                                                             pndist(k,ib) * flag
2323                         ENDIF
2324                         IF ( prunmode == 1 )  THEN
2325                            aerosol_number(ib)%init = MAX( 0.0_wp, 1.0_wp - nf2a ) * pndist(:,ib)
2326                         ENDIF
2327                      ENDIF
2328                   ENDDO
2329                ENDIF
2330             ENDIF
2331!
2332!--          b) Aerosol mass concentrations
2333!--             bin subrange 1: done here separately due to the SO4/OC convention
2334!
2335!--          SO4:
2336             IF ( index_so4 > 0 )  THEN
2337                ss = ( index_so4 - 1 ) * nbins_aerosol + start_subrange_1a !< start
2338                ee = ( index_so4 - 1 ) * nbins_aerosol + end_subrange_1a !< end
2339                ib = start_subrange_1a
2340                DO  ic = ss, ee
2341                   IF ( .NOT. read_restart_data_salsa )  THEN
2342                      aerosol_mass(ic)%conc(k,j,i) = MAX( 0.0_wp, 1.0_wp - pmfoc1a(k) ) *          &
2343                                                     pndist(k,ib) * core(ib) * arhoh2so4 * flag
2344                   ENDIF
2345                   IF ( prunmode == 1 )  THEN
2346                      aerosol_mass(ic)%init(k) = MAX( 0.0_wp, 1.0_wp - pmfoc1a(k) ) * pndist(k,ib) &
2347                                                 * core(ib) * arhoh2so4
2348                   ENDIF
2349                   ib = ib+1
2350                ENDDO
2351             ENDIF
2352!
2353!--          OC:
2354             IF ( index_oc > 0 ) THEN
2355                ss = ( index_oc - 1 ) * nbins_aerosol + start_subrange_1a !< start
2356                ee = ( index_oc - 1 ) * nbins_aerosol + end_subrange_1a !< end
2357                ib = start_subrange_1a
2358                DO  ic = ss, ee
2359                   IF ( .NOT. read_restart_data_salsa )  THEN
2360                      aerosol_mass(ic)%conc(k,j,i) = MAX( 0.0_wp, pmfoc1a(k) ) * pndist(k,ib) *    &
2361                                                     core(ib) * arhooc * flag
2362                   ENDIF
2363                   IF ( prunmode == 1 )  THEN
2364                      aerosol_mass(ic)%init(k) = MAX( 0.0_wp, pmfoc1a(k) ) * pndist(k,ib) *        &
2365                                                 core(ib) * arhooc
2366                   ENDIF
2367                   ib = ib+1
2368                ENDDO 
2369             ENDIF
2370          ENDDO !< k
2371
2372          prunmode = 3  ! Init only once
2373
2374       ENDDO !< j
2375    ENDDO !< i
2376
2377!
2378!-- c) Aerosol mass concentrations
2379!--    bin subrange 2:
2380    IF ( nreg > 1 ) THEN
2381
2382       IF ( index_so4 > 0 ) THEN
2383          CALL set_aero_mass( index_so4, pmf2a(:,1), pmf2b(:,1), pnf2a, pndist, core, arhoh2so4 )
2384       ENDIF
2385       IF ( index_oc > 0 ) THEN
2386          CALL set_aero_mass( index_oc, pmf2a(:,2), pmf2b(:,2), pnf2a, pndist, core, arhooc )
2387       ENDIF
2388       IF ( index_bc > 0 ) THEN
2389          CALL set_aero_mass( index_bc, pmf2a(:,3), pmf2b(:,3), pnf2a, pndist, core, arhobc )
2390       ENDIF
2391       IF ( index_du > 0 ) THEN
2392          CALL set_aero_mass( index_du, pmf2a(:,4), pmf2b(:,4), pnf2a, pndist, core, arhodu )
2393       ENDIF
2394       IF ( index_ss > 0 ) THEN
2395          CALL set_aero_mass( index_ss, pmf2a(:,5), pmf2b(:,5), pnf2a, pndist, core, arhoss )
2396       ENDIF
2397       IF ( index_no > 0 ) THEN
2398          CALL set_aero_mass( index_no, pmf2a(:,6), pmf2b(:,6), pnf2a, pndist, core, arhohno3 )
2399       ENDIF
2400       IF ( index_nh > 0 ) THEN
2401          CALL set_aero_mass( index_nh, pmf2a(:,7), pmf2b(:,7), pnf2a, pndist, core, arhonh3 )
2402       ENDIF
2403
2404    ENDIF
2405
2406 END SUBROUTINE aerosol_init
2407
2408!------------------------------------------------------------------------------!
2409! Description:
2410! ------------
2411!> Create a lognormal size distribution and discretise to a sectional
2412!> representation.
2413!------------------------------------------------------------------------------!
2414 SUBROUTINE size_distribution( in_ntot, in_dpg, in_sigma, psd_sect )
2415
2416    IMPLICIT NONE
2417
2418    INTEGER(iwp) ::  ib         !< running index: bin
2419    INTEGER(iwp) ::  iteration  !< running index: iteration
2420
2421    REAL(wp) ::  d1         !< particle diameter (m, dummy)
2422    REAL(wp) ::  d2         !< particle diameter (m, dummy)
2423    REAL(wp) ::  delta_d    !< (d2-d1)/10
2424    REAL(wp) ::  deltadp    !< bin width
2425    REAL(wp) ::  dmidi      !< ( d1 + d2 ) / 2
2426
2427    REAL(wp), DIMENSION(:), INTENT(in) ::  in_dpg    !< geometric mean diameter (m)
2428    REAL(wp), DIMENSION(:), INTENT(in) ::  in_ntot   !< number conc. (#/m3)
2429    REAL(wp), DIMENSION(:), INTENT(in) ::  in_sigma  !< standard deviation
2430
2431    REAL(wp), DIMENSION(:), INTENT(inout) ::  psd_sect  !< sectional size distribution
2432
2433    DO  ib = start_subrange_1a, end_subrange_2b
2434       psd_sect(ib) = 0.0_wp
2435!
2436!--    Particle diameter at the low limit (largest in the bin) (m)
2437       d1 = ( aero(ib)%vlolim / api6 )**0.33333333_wp
2438!
2439!--    Particle diameter at the high limit (smallest in the bin) (m)
2440       d2 = ( aero(ib)%vhilim / api6 )**0.33333333_wp
2441!
2442!--    Span of particle diameter in a bin (m)
2443       delta_d = 0.1_wp * ( d2 - d1 )
2444!
2445!--    Iterate:
2446       DO  iteration = 1, 10
2447          d1 = ( aero(ib)%vlolim / api6 )**0.33333333_wp + ( ib - 1) * delta_d
2448          d2 = d1 + delta_d
2449          dmidi = 0.5_wp * ( d1 + d2 )
2450          deltadp = LOG10( d2 / d1 )
2451!
2452!--       Size distribution
2453!--       in_ntot = total number, total area, or total volume concentration
2454!--       in_dpg = geometric-mean number, area, or volume diameter
2455!--       n(k) = number, area, or volume concentration in a bin
2456          psd_sect(ib) = psd_sect(ib) + SUM( in_ntot * deltadp / ( SQRT( 2.0_wp * pi ) *           &
2457                        LOG10( in_sigma ) ) * EXP( -LOG10( dmidi / in_dpg )**2.0_wp /              &
2458                        ( 2.0_wp * LOG10( in_sigma ) ** 2.0_wp ) ) )
2459
2460       ENDDO
2461    ENDDO
2462
2463 END SUBROUTINE size_distribution
2464
2465!------------------------------------------------------------------------------!
2466! Description:
2467! ------------
2468!> Sets the mass concentrations to aerosol arrays in 2a and 2b.
2469!>
2470!> Tomi Raatikainen, FMI, 29.2.2016
2471!------------------------------------------------------------------------------!
2472 SUBROUTINE set_aero_mass( ispec, pmf2a, pmf2b, pnf2a, pndist, pcore, prho )
2473
2474    IMPLICIT NONE
2475
2476    INTEGER(iwp) ::  ee        !< index: end
2477    INTEGER(iwp) ::  i         !< loop index
2478    INTEGER(iwp) ::  ib        !< loop index
2479    INTEGER(iwp) ::  ic        !< loop index
2480    INTEGER(iwp) ::  j         !< loop index
2481    INTEGER(iwp) ::  k         !< loop index
2482    INTEGER(iwp) ::  prunmode  !< 1 = initialise
2483    INTEGER(iwp) ::  ss        !< index: start
2484
2485    INTEGER(iwp), INTENT(in) :: ispec  !< Aerosol species index
2486
2487    REAL(wp) ::  flag   !< flag to mask topography grid points
2488
2489    REAL(wp), INTENT(in) ::  prho !< Aerosol density
2490
2491    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pcore !< Aerosol bin mid core volume
2492    REAL(wp), DIMENSION(0:nz+1), INTENT(in)        ::  pnf2a !< Number fraction for 2a
2493    REAL(wp), DIMENSION(0:nz+1), INTENT(in)        ::  pmf2a !< Mass distributions for a
2494    REAL(wp), DIMENSION(0:nz+1), INTENT(in)        ::  pmf2b !< and b bins
2495
2496    REAL(wp), DIMENSION(0:nz+1,nbins_aerosol), INTENT(in) ::  pndist !< Aerosol size distribution
2497
2498    prunmode = 1
2499
2500    DO i = nxlg, nxrg
2501       DO j = nysg, nyng
2502          DO k = nzb, nzt+1
2503!
2504!--          Predetermine flag to mask topography
2505             flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) ) 
2506!
2507!--          Regime 2a:
2508             ss = ( ispec - 1 ) * nbins_aerosol + start_subrange_2a
2509             ee = ( ispec - 1 ) * nbins_aerosol + end_subrange_2a
2510             ib = start_subrange_2a
2511             DO ic = ss, ee
2512                IF ( .NOT. read_restart_data_salsa )  THEN
2513                   aerosol_mass(ic)%conc(k,j,i) = MAX( 0.0_wp, pmf2a(k) ) * pnf2a(k) * pndist(k,ib)&
2514                                                  * pcore(ib) * prho * flag
2515                ENDIF
2516                IF ( prunmode == 1 )  THEN
2517                   aerosol_mass(ic)%init(k) = MAX( 0.0_wp, pmf2a(k) ) * pnf2a(k) * pndist(k,ib) *  &
2518                                              pcore(ib) * prho
2519                ENDIF
2520                ib = ib + 1
2521             ENDDO
2522!
2523!--          Regime 2b:
2524             IF ( .NOT. no_insoluble )  THEN
2525                ss = ( ispec - 1 ) * nbins_aerosol + start_subrange_2b
2526                ee = ( ispec - 1 ) * nbins_aerosol + end_subrange_2b
2527                ib = start_subrange_2a
2528                DO ic = ss, ee
2529                   IF ( .NOT. read_restart_data_salsa )  THEN
2530                      aerosol_mass(ic)%conc(k,j,i) = MAX( 0.0_wp, pmf2b(k) ) * ( 1.0_wp - pnf2a(k))&
2531                                                     * pndist(k,ib) * pcore(ib) * prho * flag
2532                   ENDIF
2533                   IF ( prunmode == 1 )  THEN
2534                      aerosol_mass(ic)%init(k) = MAX( 0.0_wp, pmf2b(k) ) * ( 1.0_wp - pnf2a(k) ) * &
2535                                                 pndist(k,ib) * pcore(ib) * prho 
2536                   ENDIF
2537                   ib = ib + 1
2538                ENDDO  ! c
2539
2540             ENDIF
2541          ENDDO   ! k
2542
2543          prunmode = 3  ! Init only once
2544
2545       ENDDO   ! j
2546    ENDDO   ! i
2547
2548 END SUBROUTINE set_aero_mass
2549
2550!------------------------------------------------------------------------------!
2551! Description:
2552! ------------
2553!> Initialise the matching between surface types in LSM and deposition models.
2554!> Do the matching based on Zhang et al. (2001). Atmos. Environ. 35, 549-560
2555!> (here referred as Z01).
2556!------------------------------------------------------------------------------!
2557 SUBROUTINE init_deposition
2558
2559    USE surface_mod,                                                                               &
2560        ONLY:  surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
2561
2562    IMPLICIT NONE
2563
2564    INTEGER(iwp) ::  l  !< loop index for vertical surfaces
2565
2566    LOGICAL :: match_lsm  !< flag to initilise LSM surfaces (if false, initialise USM surfaces)
2567
2568    IF ( depo_pcm_par == 'zhang2001' )  THEN
2569       depo_pcm_par_num = 1
2570    ELSEIF ( depo_pcm_par == 'petroff2010' )  THEN
2571       depo_pcm_par_num = 2
2572    ENDIF
2573
2574    IF ( depo_surf_par == 'zhang2001' )  THEN
2575       depo_surf_par_num = 1
2576    ELSEIF ( depo_surf_par == 'petroff2010' )  THEN
2577       depo_surf_par_num = 2
2578    ENDIF
2579!
2580!-- LSM: Pavement, vegetation and water
2581    IF ( nldepo_surf  .AND.  land_surface )  THEN
2582       match_lsm = .TRUE.
2583       ALLOCATE( lsm_to_depo_h%match_lupg(1:surf_lsm_h%ns),                                         &
2584                 lsm_to_depo_h%match_luvw(1:surf_lsm_h%ns),                                         &
2585                 lsm_to_depo_h%match_luww(1:surf_lsm_h%ns) )
2586       lsm_to_depo_h%match_lupg = 0
2587       lsm_to_depo_h%match_luvw = 0
2588       lsm_to_depo_h%match_luww = 0
2589       CALL match_sm_zhang( surf_lsm_h, lsm_to_depo_h%match_lupg, lsm_to_depo_h%match_luvw,        &
2590                            lsm_to_depo_h%match_luww, match_lsm )
2591       DO  l = 0, 3
2592          ALLOCATE( lsm_to_depo_v(l)%match_lupg(1:surf_lsm_v(l)%ns),                               &
2593                    lsm_to_depo_v(l)%match_luvw(1:surf_lsm_v(l)%ns),                               &
2594                    lsm_to_depo_v(l)%match_luww(1:surf_lsm_v(l)%ns) )
2595          lsm_to_depo_v(l)%match_lupg = 0
2596          lsm_to_depo_v(l)%match_luvw = 0
2597          lsm_to_depo_v(l)%match_luww = 0
2598          CALL match_sm_zhang( surf_lsm_v(l), lsm_to_depo_v(l)%match_lupg,                         &
2599                               lsm_to_depo_v(l)%match_luvw, lsm_to_depo_v(l)%match_luww, match_lsm )
2600       ENDDO
2601    ENDIF
2602!
2603!-- USM: Green roofs/walls, wall surfaces and windows
2604    IF ( nldepo_surf  .AND.  urban_surface )  THEN
2605       match_lsm = .FALSE.
2606       ALLOCATE( usm_to_depo_h%match_lupg(1:surf_usm_h%ns),                                        &
2607                 usm_to_depo_h%match_luvw(1:surf_usm_h%ns),                                        &
2608                 usm_to_depo_h%match_luww(1:surf_usm_h%ns) )
2609       usm_to_depo_h%match_lupg = 0
2610       usm_to_depo_h%match_luvw = 0
2611       usm_to_depo_h%match_luww = 0
2612       CALL match_sm_zhang( surf_usm_h, usm_to_depo_h%match_lupg, usm_to_depo_h%match_luvw,        &
2613                            usm_to_depo_h%match_luww, match_lsm )
2614       DO  l = 0, 3
2615          ALLOCATE( usm_to_depo_v(l)%match_lupg(1:surf_usm_v(l)%ns),                               &
2616                    usm_to_depo_v(l)%match_luvw(1:surf_usm_v(l)%ns),                               &
2617                    usm_to_depo_v(l)%match_luww(1:surf_usm_v(l)%ns) )
2618          usm_to_depo_v(l)%match_lupg = 0
2619          usm_to_depo_v(l)%match_luvw = 0
2620          usm_to_depo_v(l)%match_luww = 0
2621          CALL match_sm_zhang( surf_usm_v(l), usm_to_depo_v(l)%match_lupg,                         &
2622                               usm_to_depo_v(l)%match_luvw, usm_to_depo_v(l)%match_luww, match_lsm )
2623       ENDDO
2624    ENDIF
2625
2626    IF ( nldepo_pcm )  THEN
2627       SELECT CASE ( depo_pcm_type )
2628          CASE ( 'evergreen_needleleaf' )
2629             depo_pcm_type_num = 1
2630          CASE ( 'evergreen_broadleaf' )
2631             depo_pcm_type_num = 2
2632          CASE ( 'deciduous_needleleaf' )
2633             depo_pcm_type_num = 3
2634          CASE ( 'deciduous_broadleaf' )
2635             depo_pcm_type_num = 4
2636          CASE DEFAULT
2637             message_string = 'depo_pcm_type not set correctly.'
2638             CALL message( 'salsa_mod: init_deposition', 'PA0613', 1, 2, 0, 6, 0 )
2639       END SELECT
2640    ENDIF
2641
2642 END SUBROUTINE init_deposition
2643
2644!------------------------------------------------------------------------------!
2645! Description:
2646! ------------
2647!> Match the surface types in PALM and Zhang et al. 2001 deposition module
2648!------------------------------------------------------------------------------!
2649 SUBROUTINE match_sm_zhang( surf, match_pav_green, match_veg_wall, match_wat_win, match_lsm )
2650
2651    USE surface_mod,                                                           &
2652        ONLY:  ind_pav_green, ind_veg_wall, ind_wat_win, surf_type
2653
2654    IMPLICIT NONE
2655
2656    INTEGER(iwp) ::  m              !< index for surface elements
2657    INTEGER(iwp) ::  pav_type_palm  !< pavement / green wall type in PALM
2658    INTEGER(iwp) ::  veg_type_palm  !< vegetation / wall type in PALM
2659    INTEGER(iwp) ::  wat_type_palm  !< water / window type in PALM
2660
2661    INTEGER(iwp), DIMENSION(:), INTENT(inout) ::  match_pav_green  !<  matching pavement/green walls
2662    INTEGER(iwp), DIMENSION(:), INTENT(inout) ::  match_veg_wall   !<  matching vegetation/walls
2663    INTEGER(iwp), DIMENSION(:), INTENT(inout) ::  match_wat_win    !<  matching water/windows
2664
2665    LOGICAL, INTENT(in) :: match_lsm  !< flag to initilise LSM surfaces (if false, initialise USM)
2666
2667    TYPE(surf_type), INTENT(in) :: surf  !< respective surface type
2668
2669    DO  m = 1, surf%ns
2670       IF ( match_lsm )  THEN
2671!
2672!--       Vegetation (LSM):
2673          IF ( surf%frac(ind_veg_wall,m) > 0 )  THEN
2674             veg_type_palm = surf%vegetation_type(m)
2675             SELECT CASE ( veg_type_palm )
2676                CASE ( 0 )
2677                   message_string = 'No vegetation type defined.'
2678                   CALL message( 'salsa_mod: init_depo_surfaces', 'PA0614', 1, 2, 0, 6, 0 )
2679                CASE ( 1 )  ! bare soil
2680                   match_veg_wall(m) = 6  ! grass in Z01
2681                CASE ( 2 )  ! crops, mixed farming
2682                   match_veg_wall(m) = 7  !  crops, mixed farming Z01
2683                CASE ( 3 )  ! short grass
2684                   match_veg_wall(m) = 6  ! grass in Z01
2685                CASE ( 4 )  ! evergreen needleleaf trees
2686                    match_veg_wall(m) = 1  ! evergreen needleleaf trees in Z01
2687                CASE ( 5 )  ! deciduous needleleaf trees
2688                   match_veg_wall(m) = 3  ! deciduous needleleaf trees in Z01
2689                CASE ( 6 )  ! evergreen broadleaf trees
2690                   match_veg_wall(m) = 2  ! evergreen broadleaf trees in Z01
2691                CASE ( 7 )  ! deciduous broadleaf trees
2692                   match_veg_wall(m) = 4  ! deciduous broadleaf trees in Z01
2693                CASE ( 8 )  ! tall grass
2694                   match_veg_wall(m) = 6  ! grass in Z01
2695                CASE ( 9 )  ! desert
2696                   match_veg_wall(m) = 8  ! desert in Z01
2697                CASE ( 10 )  ! tundra
2698                   match_veg_wall(m) = 9  ! tundra in Z01
2699                CASE ( 11 )  ! irrigated crops
2700                   match_veg_wall(m) = 7  !  crops, mixed farming Z01
2701                CASE ( 12 )  ! semidesert
2702                   match_veg_wall(m) = 8  ! desert in Z01
2703                CASE ( 13 )  ! ice caps and glaciers
2704                   match_veg_wall(m) = 12  ! ice cap and glacier in Z01
2705                CASE ( 14 )  ! bogs and marshes
2706                   match_veg_wall(m) = 11  ! wetland with plants in Z01
2707                CASE ( 15 )  ! evergreen shrubs
2708                   match_veg_wall(m) = 10  ! shrubs and interrupted woodlands in Z01
2709                CASE ( 16 )  ! deciduous shrubs
2710                   match_veg_wall(m) = 10  ! shrubs and interrupted woodlands in Z01
2711                CASE ( 17 )  ! mixed forest/woodland
2712                   match_veg_wall(m) = 5  ! mixed broadleaf and needleleaf trees in Z01
2713                CASE ( 18 )  ! interrupted forest
2714                   match_veg_wall(m) = 10  ! shrubs and interrupted woodlands in Z01
2715             END SELECT
2716          ENDIF
2717!
2718!--       Pavement (LSM):
2719          IF ( surf%frac(ind_pav_green,m) > 0 )  THEN
2720             pav_type_palm = surf%pavement_type(m)
2721             IF ( pav_type_palm == 0 )  THEN  ! error
2722                message_string = 'No pavement type defined.'
2723                CALL message( 'salsa_mod: match_sm_zhang', 'PA0615', 1, 2, 0, 6, 0 )
2724             ELSE
2725                match_pav_green(m) = 15  ! urban in Z01
2726             ENDIF
2727          ENDIF
2728!
2729!--       Water (LSM):
2730          IF ( surf%frac(ind_wat_win,m) > 0 )  THEN
2731             wat_type_palm = surf%water_type(m)
2732             IF ( wat_type_palm == 0 )  THEN  ! error
2733                message_string = 'No water type defined.'
2734                CALL message( 'salsa_mod: match_sm_zhang', 'PA0616', 1, 2, 0, 6, 0 )
2735             ELSEIF ( wat_type_palm == 3 )  THEN
2736                match_wat_win(m) = 14  ! ocean in Z01
2737             ELSEIF ( wat_type_palm == 1  .OR.  wat_type_palm == 2 .OR.  wat_type_palm == 4        &
2738                      .OR.  wat_type_palm == 5  )  THEN
2739                match_wat_win(m) = 13  ! inland water in Z01
2740             ENDIF
2741          ENDIF
2742       ELSE
2743!
2744!--       Wall surfaces (USM):
2745          IF ( surf%frac(ind_veg_wall,m) > 0 )  THEN
2746             match_veg_wall(m) = 15  ! urban in Z01
2747          ENDIF
2748!
2749!--       Green walls and roofs (USM):
2750          IF ( surf%frac(ind_pav_green,m) > 0 )  THEN
2751             match_pav_green(m) =  6 ! (short) grass in Z01
2752          ENDIF
2753!
2754!--       Windows (USM):
2755          IF ( surf%frac(ind_wat_win,m) > 0 )  THEN
2756             match_wat_win(m) = 15  ! urban in Z01
2757          ENDIF
2758       ENDIF
2759
2760    ENDDO
2761
2762 END SUBROUTINE match_sm_zhang
2763
2764!------------------------------------------------------------------------------!
2765! Description:
2766! ------------
2767!> Swapping of timelevels
2768!------------------------------------------------------------------------------!
2769 SUBROUTINE salsa_swap_timelevel( mod_count )
2770
2771    IMPLICIT NONE
2772
2773    INTEGER(iwp) ::  ib   !<
2774    INTEGER(iwp) ::  ic   !<
2775    INTEGER(iwp) ::  icc  !<
2776    INTEGER(iwp) ::  ig   !<
2777
2778    INTEGER(iwp), INTENT(IN) ::  mod_count  !<
2779
2780    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
2781
2782       SELECT CASE ( mod_count )
2783
2784          CASE ( 0 )
2785
2786             DO  ib = 1, nbins_aerosol
2787                aerosol_number(ib)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => nconc_1(:,:,:,ib)
2788                aerosol_number(ib)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => nconc_2(:,:,:,ib)
2789
2790                DO  ic = 1, ncomponents_mass
2791                   icc = ( ic-1 ) * nbins_aerosol + ib
2792                   aerosol_mass(icc)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => mconc_1(:,:,:,icc)
2793                   aerosol_mass(icc)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => mconc_2(:,:,:,icc)
2794                ENDDO
2795             ENDDO
2796
2797             IF ( .NOT. salsa_gases_from_chem )  THEN
2798                DO  ig = 1, ngases_salsa
2799                   salsa_gas(ig)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => gconc_1(:,:,:,ig)
2800                   salsa_gas(ig)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => gconc_2(:,:,:,ig)
2801                ENDDO
2802             ENDIF
2803
2804          CASE ( 1 )
2805
2806             DO  ib = 1, nbins_aerosol
2807                aerosol_number(ib)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => nconc_2(:,:,:,ib)
2808                aerosol_number(ib)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => nconc_1(:,:,:,ib)
2809                DO  ic = 1, ncomponents_mass
2810                   icc = ( ic-1 ) * nbins_aerosol + ib
2811                   aerosol_mass(icc)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => mconc_2(:,:,:,icc)
2812                   aerosol_mass(icc)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => mconc_1(:,:,:,icc)
2813                ENDDO
2814             ENDDO
2815
2816             IF ( .NOT. salsa_gases_from_chem )  THEN
2817                DO  ig = 1, ngases_salsa
2818                   salsa_gas(ig)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => gconc_2(:,:,:,ig)
2819                   salsa_gas(ig)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => gconc_1(:,:,:,ig)
2820                ENDDO
2821             ENDIF
2822
2823       END SELECT
2824
2825    ENDIF
2826
2827 END SUBROUTINE salsa_swap_timelevel
2828
2829
2830!------------------------------------------------------------------------------!
2831! Description:
2832! ------------
2833!> This routine reads the respective restart data.
2834!------------------------------------------------------------------------------!
2835 SUBROUTINE salsa_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,      &
2836                             nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
2837
2838    USE control_parameters,                                                                        &
2839        ONLY:  length, restart_string
2840
2841    IMPLICIT NONE
2842
2843    INTEGER(iwp) ::  ib              !<
2844    INTEGER(iwp) ::  ic              !<
2845    INTEGER(iwp) ::  ig              !<
2846    INTEGER(iwp) ::  k               !<
2847    INTEGER(iwp) ::  nxlc            !<
2848    INTEGER(iwp) ::  nxlf            !<
2849    INTEGER(iwp) ::  nxl_on_file     !<
2850    INTEGER(iwp) ::  nxrc            !<
2851    INTEGER(iwp) ::  nxrf            !<
2852    INTEGER(iwp) ::  nxr_on_file     !<
2853    INTEGER(iwp) ::  nync            !<
2854    INTEGER(iwp) ::  nynf            !<
2855    INTEGER(iwp) ::  nyn_on_file     !<
2856    INTEGER(iwp) ::  nysc            !<
2857    INTEGER(iwp) ::  nysf            !<
2858    INTEGER(iwp) ::  nys_on_file     !<
2859
2860    LOGICAL, INTENT(OUT)  ::  found  !<
2861
2862    REAL(wp), &
2863       DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
2864
2865    found = .FALSE.
2866
2867    IF ( read_restart_data_salsa )  THEN
2868
2869       SELECT CASE ( restart_string(1:length) )
2870
2871          CASE ( 'aerosol_number' )
2872             DO  ib = 1, nbins_aerosol
2873                IF ( k == 1 )  READ ( 13 ) tmp_3d
2874                aerosol_number(ib)%conc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =               &
2875                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2876                found = .TRUE.
2877             ENDDO
2878
2879          CASE ( 'aerosol_mass' )
2880             DO  ic = 1, ncomponents_mass * nbins_aerosol
2881                IF ( k == 1 )  READ ( 13 ) tmp_3d
2882                aerosol_mass(ic)%conc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                 &
2883                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2884                found = .TRUE.
2885             ENDDO
2886
2887          CASE ( 'salsa_gas' )
2888             DO  ig = 1, ngases_salsa
2889                IF ( k == 1 )  READ ( 13 ) tmp_3d
2890                salsa_gas(ig)%conc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                    &
2891                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2892                found = .TRUE.
2893             ENDDO
2894
2895          CASE DEFAULT
2896             found = .FALSE.
2897
2898       END SELECT
2899    ENDIF
2900
2901 END SUBROUTINE salsa_rrd_local
2902
2903!------------------------------------------------------------------------------!
2904! Description:
2905! ------------
2906!> This routine writes the respective restart data.
2907!> Note that the following input variables in PARIN have to be equal between
2908!> restart runs:
2909!>    listspec, nbin, nbin2, nf2a, ncc, mass_fracs_a, mass_fracs_b
2910!------------------------------------------------------------------------------!
2911 SUBROUTINE salsa_wrd_local
2912
2913    USE control_parameters,                                                                        &
2914        ONLY:  write_binary
2915
2916    IMPLICIT NONE
2917
2918    INTEGER(iwp) ::  ib   !<
2919    INTEGER(iwp) ::  ic   !<
2920    INTEGER(iwp) ::  ig  !<
2921
2922    IF ( write_binary  .AND.  write_binary_salsa )  THEN
2923
2924       CALL wrd_write_string( 'aerosol_number' )
2925       DO  ib = 1, nbins_aerosol
2926          WRITE ( 14 )  aerosol_number(ib)%conc
2927       ENDDO
2928
2929       CALL wrd_write_string( 'aerosol_mass' )
2930       DO  ic = 1, nbins_aerosol * ncomponents_mass
2931          WRITE ( 14 )  aerosol_mass(ic)%conc
2932       ENDDO
2933
2934       CALL wrd_write_string( 'salsa_gas' )
2935       DO  ig = 1, ngases_salsa
2936          WRITE ( 14 )  salsa_gas(ig)%conc
2937       ENDDO
2938
2939    ENDIF
2940
2941 END SUBROUTINE salsa_wrd_local
2942
2943!------------------------------------------------------------------------------!
2944! Description:
2945! ------------
2946!> Performs necessary unit and dimension conversion between the host model and
2947!> SALSA module, and calls the main SALSA routine.
2948!> Partially adobted form the original SALSA boxmodel version.
2949!> Now takes masses in as kg/kg from LES!! Converted to m3/m3 for SALSA
2950!> 05/2016 Juha: This routine is still pretty much in its original shape.
2951!>               It's dumb as a mule and twice as ugly, so implementation of
2952!>               an improved solution is necessary sooner or later.
2953!> Juha Tonttila, FMI, 2014
2954!> Jaakko Ahola, FMI, 2016
2955!> Only aerosol processes included, Mona Kurppa, UHel, 2017
2956!------------------------------------------------------------------------------!
2957 SUBROUTINE salsa_driver( i, j, prunmode )
2958
2959    USE arrays_3d,                                                                                 &
2960        ONLY: pt_p, q_p, u, v, w
2961
2962    USE plant_canopy_model_mod,                                                                    &
2963        ONLY: lad_s
2964
2965    USE surface_mod,                                                                               &
2966        ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
2967
2968    IMPLICIT NONE
2969
2970    INTEGER(iwp) ::  endi    !< end index
2971    INTEGER(iwp) ::  ib      !< loop index
2972    INTEGER(iwp) ::  ic      !< loop index
2973    INTEGER(iwp) ::  ig      !< loop index
2974    INTEGER(iwp) ::  k_wall  !< vertical index of topography top
2975    INTEGER(iwp) ::  k       !< loop index
2976    INTEGER(iwp) ::  l       !< loop index
2977    INTEGER(iwp) ::  nc_h2o  !< index of H2O in the prtcl index table
2978    INTEGER(iwp) ::  ss      !< loop index
2979    INTEGER(iwp) ::  str     !< start index
2980    INTEGER(iwp) ::  vc      !< default index in prtcl
2981
2982    INTEGER(iwp), INTENT(in) ::  i         !< loop index
2983    INTEGER(iwp), INTENT(in) ::  j         !< loop index
2984    INTEGER(iwp), INTENT(in) ::  prunmode  !< 1: Initialization, 2: Spinup, 3: Regular runtime
2985
2986    REAL(wp) ::  cw_old  !< previous H2O mixing ratio
2987    REAL(wp) ::  flag    !< flag to mask topography grid points
2988    REAL(wp) ::  in_lad  !< leaf area density (m2/m3)
2989    REAL(wp) ::  in_rh   !< relative humidity
2990    REAL(wp) ::  zgso4   !< SO4
2991    REAL(wp) ::  zghno3  !< HNO3
2992    REAL(wp) ::  zgnh3   !< NH3
2993    REAL(wp) ::  zgocnv  !< non-volatile OC
2994    REAL(wp) ::  zgocsv  !< semi-volatile OC
2995
2996    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_adn  !< air density (kg/m3)
2997    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_cs   !< H2O sat. vapour conc.
2998    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_cw   !< H2O vapour concentration
2999    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_p    !< pressure (Pa)
3000    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_t    !< temperature (K)
3001    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_u    !< wind magnitude (m/s)
3002    REAL(wp), DIMENSION(nzb:nzt+1) ::  kvis    !< kinematic viscosity of air(m2/s)
3003    REAL(wp), DIMENSION(nzb:nzt+1) ::  ppm_to_nconc  !< Conversion factor from ppm to #/m3
3004
3005    REAL(wp), DIMENSION(nzb:nzt+1,nbins_aerosol) ::  schmidt_num  !< particle Schmidt number
3006    REAL(wp), DIMENSION(nzb:nzt+1,nbins_aerosol) ::  vd           !< particle fall seed (m/s)
3007
3008    TYPE(t_section), DIMENSION(nbins_aerosol) ::  lo_aero   !< additional variable for OpenMP
3009    TYPE(t_section), DIMENSION(nbins_aerosol) ::  aero_old  !< helper array
3010
3011    aero_old(:)%numc = 0.0_wp
3012    in_lad           = 0.0_wp
3013    in_u             = 0.0_wp
3014    kvis             = 0.0_wp
3015    lo_aero          = aero
3016    schmidt_num      = 0.0_wp
3017    vd               = 0.0_wp
3018    zgso4            = nclim
3019    zghno3           = nclim
3020    zgnh3            = nclim
3021    zgocnv           = nclim
3022    zgocsv           = nclim
3023!
3024!-- Aerosol number is always set, but mass can be uninitialized
3025    DO ib = 1, nbins_aerosol
3026       lo_aero(ib)%volc(:)  = 0.0_wp
3027       aero_old(ib)%volc(:) = 0.0_wp
3028    ENDDO
3029!
3030!-- Set the salsa runtime config (How to make this more efficient?)
3031    CALL set_salsa_runtime( prunmode )
3032!
3033!-- Calculate thermodynamic quantities needed in SALSA
3034    CALL salsa_thrm_ij( i, j, p_ij=in_p, temp_ij=in_t, cw_ij=in_cw, cs_ij=in_cs, adn_ij=in_adn )
3035!
3036!-- Magnitude of wind: needed for deposition
3037    IF ( lsdepo )  THEN
3038       in_u(nzb+1:nzt) = SQRT( ( 0.5_wp * ( u(nzb+1:nzt,j,i) + u(nzb+1:nzt,j,i+1) ) )**2 +         &
3039                               ( 0.5_wp * ( v(nzb+1:nzt,j,i) + v(nzb+1:nzt,j+1,i) ) )**2 +         &
3040                               ( 0.5_wp * ( w(nzb:nzt-1,j,i) + w(nzb+1:nzt,j,  i) ) )**2 )
3041    ENDIF
3042!
3043!-- Calculate conversion factors for gas concentrations
3044    ppm_to_nconc(:) = for_ppm_to_nconc * in_p(:) / in_t(:)
3045!
3046!-- Determine topography-top index on scalar grid
3047    k_wall = k_topo_top(j,i)
3048
3049    DO k = nzb+1, nzt
3050!
3051!--    Predetermine flag to mask topography
3052       flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
3053!
3054!--    Wind velocity for dry depositon on vegetation
3055       IF ( lsdepo_pcm  .AND.  plant_canopy )  THEN
3056          in_lad = lad_s( MAX( k-k_wall,0 ),j,i)
3057       ENDIF
3058!
3059!--    For initialization and spinup, limit the RH with the parameter rhlim
3060       IF ( prunmode < 3 ) THEN
3061          in_cw(k) = MIN( in_cw(k), in_cs(k) * rhlim )
3062       ELSE
3063          in_cw(k) = in_cw(k)
3064       ENDIF
3065       cw_old = in_cw(k) !* in_adn(k)
3066!
3067!--    Set volume concentrations:
3068!--    Sulphate (SO4) or sulphuric acid H2SO4
3069       IF ( index_so4 > 0 )  THEN
3070          vc = 1
3071          str = ( index_so4-1 ) * nbins_aerosol + 1    ! start index
3072          endi = index_so4 * nbins_aerosol             ! end index
3073          ic = 1
3074          DO ss = str, endi
3075             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoh2so4
3076             ic = ic+1
3077          ENDDO
3078          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3079       ENDIF
3080!
3081!--    Organic carbon (OC) compounds
3082       IF ( index_oc > 0 )  THEN
3083          vc = 2
3084          str = ( index_oc-1 ) * nbins_aerosol + 1
3085          endi = index_oc * nbins_aerosol
3086          ic = 1
3087          DO ss = str, endi
3088             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhooc
3089             ic = ic+1
3090          ENDDO
3091          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3092       ENDIF
3093!
3094!--    Black carbon (BC)
3095       IF ( index_bc > 0 )  THEN
3096          vc = 3
3097          str = ( index_bc-1 ) * nbins_aerosol + 1 + end_subrange_1a
3098          endi = index_bc * nbins_aerosol
3099          ic = 1 + end_subrange_1a
3100          DO ss = str, endi
3101             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhobc
3102             ic = ic+1
3103          ENDDO
3104          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3105       ENDIF
3106!
3107!--    Dust (DU)
3108       IF ( index_du > 0 )  THEN
3109          vc = 4
3110          str = ( index_du-1 ) * nbins_aerosol + 1 + end_subrange_1a
3111          endi = index_du * nbins_aerosol
3112          ic = 1 + end_subrange_1a
3113          DO ss = str, endi
3114             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhodu
3115             ic = ic+1
3116          ENDDO
3117          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3118       ENDIF
3119!
3120!--    Sea salt (SS)
3121       IF ( index_ss > 0 )  THEN
3122          vc = 5
3123          str = ( index_ss-1 ) * nbins_aerosol + 1 + end_subrange_1a
3124          endi = index_ss * nbins_aerosol
3125          ic = 1 + end_subrange_1a
3126          DO ss = str, endi
3127             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoss
3128             ic = ic+1
3129          ENDDO
3130          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3131       ENDIF
3132!
3133!--    Nitrate (NO(3-)) or nitric acid HNO3
3134       IF ( index_no > 0 )  THEN
3135          vc = 6
3136          str = ( index_no-1 ) * nbins_aerosol + 1 
3137          endi = index_no * nbins_aerosol
3138          ic = 1
3139          DO ss = str, endi
3140             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhohno3
3141             ic = ic+1
3142          ENDDO
3143          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3144       ENDIF
3145!
3146!--    Ammonium (NH(4+)) or ammonia NH3
3147       IF ( index_nh > 0 )  THEN
3148          vc = 7
3149          str = ( index_nh-1 ) * nbins_aerosol + 1
3150          endi = index_nh * nbins_aerosol
3151          ic = 1
3152          DO ss = str, endi
3153             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhonh3
3154             ic = ic+1
3155          ENDDO
3156          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3157       ENDIF
3158!
3159!--    Water (always used)
3160       nc_h2o = get_index( prtcl,'H2O' )
3161       vc = 8
3162       str = ( nc_h2o-1 ) * nbins_aerosol + 1
3163       endi = nc_h2o * nbins_aerosol
3164       ic = 1
3165       IF ( advect_particle_water )  THEN
3166          DO ss = str, endi
3167             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoh2o
3168             ic = ic+1
3169          ENDDO
3170       ELSE
3171         lo_aero(1:nbins_aerosol)%volc(vc) = mclim
3172       ENDIF
3173       aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3174!
3175!--    Number concentrations (numc) and particle sizes
3176!--    (dwet = wet diameter, core = dry volume)
3177       DO  ib = 1, nbins_aerosol
3178          lo_aero(ib)%numc = aerosol_number(ib)%conc(k,j,i)
3179          aero_old(ib)%numc = lo_aero(ib)%numc
3180          IF ( lo_aero(ib)%numc > nclim )  THEN
3181             lo_aero(ib)%dwet = ( SUM( lo_aero(ib)%volc(:) ) / lo_aero(ib)%numc / api6 )**0.33333333_wp
3182             lo_aero(ib)%core = SUM( lo_aero(ib)%volc(1:7) ) / lo_aero(ib)%numc
3183          ELSE
3184             lo_aero(ib)%dwet = lo_aero(ib)%dmid
3185             lo_aero(ib)%core = api6 * ( lo_aero(ib)%dwet )**3
3186          ENDIF
3187       ENDDO
3188!
3189!--    Calculate the ambient sizes of particles by equilibrating soluble fraction of particles with
3190!--    water using the ZSR method.
3191       in_rh = in_cw(k) / in_cs(k)
3192       IF ( prunmode==1  .OR.  .NOT. advect_particle_water )  THEN
3193          CALL equilibration( in_rh, in_t(k), lo_aero, .TRUE. )
3194       ENDIF
3195!
3196!--    Gaseous tracer concentrations in #/m3
3197       IF ( salsa_gases_from_chem )  THEN
3198!
3199!--       Convert concentrations in ppm to #/m3
3200          zgso4  = chem_species(gas_index_chem(1))%conc(k,j,i) * ppm_to_nconc(k)
3201          zghno3 = chem_species(gas_index_chem(2))%conc(k,j,i) * ppm_to_nconc(k)
3202          zgnh3  = chem_species(gas_index_chem(3))%conc(k,j,i) * ppm_to_nconc(k)
3203          zgocnv = chem_species(gas_index_chem(4))%conc(k,j,i) * ppm_to_nconc(k)
3204          zgocsv = chem_species(gas_index_chem(5))%conc(k,j,i) * ppm_to_nconc(k)
3205       ELSE
3206          zgso4  = salsa_gas(1)%conc(k,j,i)
3207          zghno3 = salsa_gas(2)%conc(k,j,i)
3208          zgnh3  = salsa_gas(3)%conc(k,j,i)
3209          zgocnv = salsa_gas(4)%conc(k,j,i)
3210          zgocsv = salsa_gas(5)%conc(k,j,i)
3211       ENDIF
3212!
3213!--    Calculate aerosol processes:
3214!--    *********************************************************************************************
3215!
3216!--    Coagulation
3217       IF ( lscoag )   THEN
3218          CALL coagulation( lo_aero, dt_salsa, in_t(k), in_p(k) )
3219       ENDIF
3220!
3221!--    Condensation
3222       IF ( lscnd )   THEN
3223          CALL condensation( lo_aero, zgso4, zgocnv, zgocsv,  zghno3, zgnh3, in_cw(k), in_cs(k),   &
3224                             in_t(k), in_p(k), dt_salsa, prtcl )
3225       ENDIF
3226!
3227!--    Deposition
3228       IF ( lsdepo )  THEN
3229          CALL deposition( lo_aero, in_t(k), in_adn(k), in_u(k), in_lad, kvis(k), schmidt_num(k,:),&
3230                           vd(k,:) )
3231       ENDIF
3232!
3233!--    Size distribution bin update
3234       IF ( lsdistupdate )   THEN
3235          CALL distr_update( lo_aero )
3236       ENDIF
3237!--    *********************************************************************************************
3238
3239       IF ( lsdepo ) sedim_vd(k,j,i,:) = vd(k,:)
3240!
3241!--    Calculate changes in concentrations
3242       DO ib = 1, nbins_aerosol
3243          aerosol_number(ib)%conc(k,j,i) = aerosol_number(ib)%conc(k,j,i) + ( lo_aero(ib)%numc -   &
3244                                           aero_old(ib)%numc ) * flag
3245       ENDDO
3246
3247       IF ( index_so4 > 0 )  THEN
3248          vc = 1
3249          str = ( index_so4-1 ) * nbins_aerosol + 1
3250          endi = index_so4 * nbins_aerosol
3251          ic = 1
3252          DO ss = str, endi
3253             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3254                                            aero_old(ic)%volc(vc) ) * arhoh2so4 * flag
3255             ic = ic+1
3256          ENDDO
3257       ENDIF
3258
3259       IF ( index_oc > 0 )  THEN
3260          vc = 2
3261          str = ( index_oc-1 ) * nbins_aerosol + 1
3262          endi = index_oc * nbins_aerosol
3263          ic = 1
3264          DO ss = str, endi
3265             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3266                                            aero_old(ic)%volc(vc) ) * arhooc * flag
3267             ic = ic+1
3268          ENDDO
3269       ENDIF
3270
3271       IF ( index_bc > 0 )  THEN
3272          vc = 3
3273          str = ( index_bc-1 ) * nbins_aerosol + 1 + end_subrange_1a
3274          endi = index_bc * nbins_aerosol
3275          ic = 1 + end_subrange_1a
3276          DO ss = str, endi
3277             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3278                                            aero_old(ic)%volc(vc) ) * arhobc * flag
3279             ic = ic+1
3280          ENDDO
3281       ENDIF
3282
3283       IF ( index_du > 0 )  THEN
3284          vc = 4
3285          str = ( index_du-1 ) * nbins_aerosol + 1 + end_subrange_1a
3286          endi = index_du * nbins_aerosol
3287          ic = 1 + end_subrange_1a
3288          DO ss = str, endi
3289             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3290                                            aero_old(ic)%volc(vc) ) * arhodu * flag
3291             ic = ic+1
3292          ENDDO
3293       ENDIF
3294
3295       IF ( index_ss > 0 )  THEN
3296          vc = 5
3297          str = ( index_ss-1 ) * nbins_aerosol + 1 + end_subrange_1a
3298          endi = index_ss * nbins_aerosol
3299          ic = 1 + end_subrange_1a
3300          DO ss = str, endi
3301             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3302                                            aero_old(ic)%volc(vc) ) * arhoss * flag
3303             ic = ic+1
3304          ENDDO
3305       ENDIF
3306
3307       IF ( index_no > 0 )  THEN
3308          vc = 6
3309          str = ( index_no-1 ) * nbins_aerosol + 1
3310          endi = index_no * nbins_aerosol
3311          ic = 1
3312          DO ss = str, endi
3313             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3314                                            aero_old(ic)%volc(vc) ) * arhohno3 * flag
3315             ic = ic+1
3316          ENDDO
3317       ENDIF
3318
3319       IF ( index_nh > 0 )  THEN
3320          vc = 7
3321          str = ( index_nh-1 ) * nbins_aerosol + 1
3322          endi = index_nh * nbins_aerosol
3323          ic = 1
3324          DO ss = str, endi
3325             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3326                                            aero_old(ic)%volc(vc) ) * arhonh3 * flag
3327             ic = ic+1
3328          ENDDO
3329       ENDIF
3330
3331       IF ( advect_particle_water )  THEN
3332          nc_h2o = get_index( prtcl,'H2O' )
3333          vc = 8
3334          str = ( nc_h2o-1 ) * nbins_aerosol + 1
3335          endi = nc_h2o * nbins_aerosol
3336          ic = 1
3337          DO ss = str, endi
3338             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3339                                            aero_old(ic)%volc(vc) ) * arhoh2o * flag
3340             ic = ic+1
3341          ENDDO
3342       ENDIF
3343       IF ( prunmode == 1 )  THEN
3344          nc_h2o = get_index( prtcl,'H2O' )
3345          vc = 8
3346          str = ( nc_h2o-1 ) * nbins_aerosol + 1
3347          endi = nc_h2o * nbins_aerosol
3348          ic = 1
3349          DO ss = str, endi
3350             aerosol_mass(ss)%init(k) = MAX( aerosol_mass(ss)%init(k), ( lo_aero(ic)%volc(vc) - &
3351                                             aero_old(ic)%volc(vc) ) * arhoh2o )
3352             IF ( k == nzb+1 )  THEN
3353                aerosol_mass(ss)%init(k-1) = aerosol_mass(ss)%init(k)
3354             ELSEIF ( k == nzt  )  THEN
3355                aerosol_mass(ss)%init(k+1) = aerosol_mass(ss)%init(k)
3356                aerosol_mass(ss)%conc(k+1,j,i) = aerosol_mass(ss)%init(k)
3357             ENDIF
3358             ic = ic+1
3359          ENDDO
3360       ENDIF
3361!
3362!--    Condensation of precursor gases
3363       IF ( lscndgas )  THEN
3364          IF ( salsa_gases_from_chem )  THEN
3365!
3366!--          SO4 (or H2SO4)
3367             ig = gas_index_chem(1)
3368             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zgso4 /               &
3369                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3370!
3371!--          HNO3
3372             ig = gas_index_chem(2)
3373             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zghno3 /              &
3374                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3375!
3376!--          NH3
3377             ig = gas_index_chem(3)
3378             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zgnh3 /               &
3379                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3380!
3381!--          non-volatile OC
3382             ig = gas_index_chem(4)
3383             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zgocnv /              &
3384                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3385!
3386!--          semi-volatile OC
3387             ig = gas_index_chem(5)
3388             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zgocsv /              &
3389                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3390
3391          ELSE
3392!
3393!--          SO4 (or H2SO4)
3394             salsa_gas(1)%conc(k,j,i) = salsa_gas(1)%conc(k,j,i) + ( zgso4 -                       &
3395                                        salsa_gas(1)%conc(k,j,i) ) * flag
3396!
3397!--          HNO3
3398             salsa_gas(2)%conc(k,j,i) = salsa_gas(2)%conc(k,j,i) + ( zghno3 -                      &
3399                                        salsa_gas(2)%conc(k,j,i) ) * flag
3400!
3401!--          NH3
3402             salsa_gas(3)%conc(k,j,i) = salsa_gas(3)%conc(k,j,i) + ( zgnh3 -                       &
3403                                        salsa_gas(3)%conc(k,j,i) ) * flag
3404!
3405!--          non-volatile OC
3406             salsa_gas(4)%conc(k,j,i) = salsa_gas(4)%conc(k,j,i) + ( zgocnv -                      &
3407                                        salsa_gas(4)%conc(k,j,i) ) * flag
3408!
3409!--          semi-volatile OC
3410             salsa_gas(5)%conc(k,j,i) = salsa_gas(5)%conc(k,j,i) + ( zgocsv -                      &
3411                                        salsa_gas(5)%conc(k,j,i) ) * flag
3412          ENDIF
3413       ENDIF
3414!
3415!--    Tendency of water vapour mixing ratio is obtained from the change in RH during SALSA run.
3416!--    This releases heat and changes pt. Assumes no temperature change during SALSA run.
3417!--    q = r / (1+r), Euler method for integration
3418!
3419       IF ( feedback_to_palm )  THEN
3420          q_p(k,j,i) = q_p(k,j,i) + 1.0_wp / ( in_cw(k) * in_adn(k) + 1.0_wp )**2 *                &
3421                       ( in_cw(k) - cw_old ) * in_adn(k) * flag
3422          pt_p(k,j,i) = pt_p(k,j,i) + alv / c_p * ( in_cw(k) - cw_old ) * in_adn(k) / ( in_cw(k) / &
3423                        in_adn(k) + 1.0_wp )**2 * pt_p(k,j,i) / in_t(k) * flag
3424       ENDIF
3425
3426    ENDDO   ! k
3427
3428!
3429!-- Set surfaces and wall fluxes due to deposition
3430    IF ( lsdepo  .AND.  lsdepo_surf  .AND.  prunmode == 3 )  THEN
3431       IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
3432          CALL depo_surf( i, j, surf_def_h(0), vd, schmidt_num, kvis, in_u, .TRUE. )
3433          DO  l = 0, 3
3434             CALL depo_surf( i, j, surf_def_v(l), vd, schmidt_num, kvis, in_u, .FALSE. )
3435          ENDDO
3436       ELSE
3437          CALL depo_surf( i, j, surf_usm_h, vd, schmidt_num, kvis, in_u, .TRUE., usm_to_depo_h )
3438          DO  l = 0, 3
3439             CALL depo_surf( i, j, surf_usm_v(l), vd, schmidt_num, kvis, in_u, .FALSE.,            &
3440                             usm_to_depo_v(l) )
3441          ENDDO
3442          CALL depo_surf( i, j, surf_lsm_h, vd, schmidt_num, kvis, in_u, .TRUE., lsm_to_depo_h )
3443          DO  l = 0, 3
3444             CALL depo_surf( i, j, surf_lsm_v(l), vd, schmidt_num, kvis, in_u, .FALSE.,            &
3445                             lsm_to_depo_v(l) )
3446          ENDDO
3447       ENDIF
3448    ENDIF
3449
3450    IF ( prunmode < 3 )  THEN
3451       !$OMP MASTER
3452       aero = lo_aero
3453       !$OMP END MASTER
3454    END IF
3455
3456 END SUBROUTINE salsa_driver
3457
3458!------------------------------------------------------------------------------!
3459! Description:
3460! ------------
3461!> Set logical switches according to the salsa_parameters options.
3462!> Juha Tonttila, FMI, 2014
3463!> Only aerosol processes included, Mona Kurppa, UHel, 2017
3464!------------------------------------------------------------------------------!
3465 SUBROUTINE set_salsa_runtime( prunmode )
3466
3467    IMPLICIT NONE
3468
3469    INTEGER(iwp), INTENT(in) ::  prunmode
3470
3471    SELECT CASE(prunmode)
3472
3473       CASE(1) !< Initialization
3474          lscoag       = .FALSE.
3475          lscnd        = .FALSE.
3476          lscndgas     = .FALSE.
3477          lscndh2oae   = .FALSE.
3478          lsdepo       = .FALSE.
3479          lsdepo_pcm   = .FALSE.
3480          lsdepo_surf  = .FALSE.
3481          lsdistupdate = .TRUE.
3482          lspartition  = .FALSE.
3483
3484       CASE(2)  !< Spinup period
3485          lscoag      = ( .FALSE. .AND. nlcoag   )
3486          lscnd       = ( .TRUE.  .AND. nlcnd    )
3487          lscndgas    = ( .TRUE.  .AND. nlcndgas )
3488          lscndh2oae  = ( .TRUE.  .AND. nlcndh2oae )
3489
3490       CASE(3)  !< Run
3491          lscoag       = nlcoag
3492          lscnd        = nlcnd
3493          lscndgas     = nlcndgas
3494          lscndh2oae   = nlcndh2oae
3495          lsdepo       = nldepo
3496          lsdepo_pcm   = nldepo_pcm
3497          lsdepo_surf  = nldepo_surf
3498          lsdistupdate = nldistupdate
3499    END SELECT
3500
3501
3502 END SUBROUTINE set_salsa_runtime
3503 
3504!------------------------------------------------------------------------------!
3505! Description:
3506! ------------
3507!> Calculates the absolute temperature (using hydrostatic pressure), saturation
3508!> vapour pressure and mixing ratio over water, relative humidity and air
3509!> density needed in the SALSA model.
3510!> NOTE, no saturation adjustment takes place -> the resulting water vapour
3511!> mixing ratio can be supersaturated, allowing the microphysical calculations
3512!> in SALSA.
3513!
3514!> Juha Tonttila, FMI, 2014 (original SALSAthrm)
3515!> Mona Kurppa, UHel, 2017 (adjustment for PALM and only aerosol processes)
3516!------------------------------------------------------------------------------!
3517 SUBROUTINE salsa_thrm_ij( i, j, p_ij, temp_ij, cw_ij, cs_ij, adn_ij )
3518
3519    USE arrays_3d,                                                                                 &
3520        ONLY: pt, q, zu
3521
3522    USE basic_constants_and_equations_mod,                                                         &
3523        ONLY:  barometric_formula, exner_function, ideal_gas_law_rho, magnus
3524
3525    IMPLICIT NONE
3526
3527    INTEGER(iwp), INTENT(in) ::  i  !<
3528    INTEGER(iwp), INTENT(in) ::  j  !<
3529
3530    REAL(wp) ::  t_surface  !< absolute surface temperature (K)
3531
3532    REAL(wp), DIMENSION(nzb:nzt+1) ::  e_s  !< saturation vapour pressure over water (Pa)
3533
3534    REAL(wp), DIMENSION(:), INTENT(inout) ::  adn_ij   !< air density (kg/m3)
3535    REAL(wp), DIMENSION(:), INTENT(inout) ::  p_ij     !< air pressure (Pa)
3536    REAL(wp), DIMENSION(:), INTENT(inout) ::  temp_ij  !< air temperature (K)
3537
3538    REAL(wp), DIMENSION(:), INTENT(inout), OPTIONAL ::  cw_ij  !< water vapour concentration (kg/m3)
3539    REAL(wp), DIMENSION(:), INTENT(inout), OPTIONAL ::  cs_ij  !< saturation water vap. conc.(kg/m3)
3540!
3541!-- Pressure p_ijk (Pa) = hydrostatic pressure
3542    t_surface = pt_surface * exner_function( surface_pressure * 100.0_wp )
3543    p_ij(:) = barometric_formula( zu, t_surface, surface_pressure * 100.0_wp )
3544!
3545!-- Absolute ambient temperature (K)
3546    temp_ij(:) = pt(:,j,i) * exner_function( p_ij(:) )
3547!
3548!-- Air density
3549    adn_ij(:) = ideal_gas_law_rho( p_ij(:), temp_ij(:) )
3550!
3551!-- Water vapour concentration r_v (kg/m3)
3552    IF ( PRESENT( cw_ij ) )  THEN
3553       cw_ij(:) = ( q(:,j,i) / ( 1.0_wp - q(:,j,i) ) ) * adn_ij(:)
3554    ENDIF
3555!
3556!-- Saturation mixing ratio r_s (kg/kg) from vapour pressure at temp (Pa)
3557    IF ( PRESENT( cs_ij ) )  THEN
3558       e_s(:) = 611.0_wp * EXP( alv_d_rv * ( 3.6609E-3_wp - 1.0_wp /           &
3559                temp_ij(:) ) )! magnus( temp_ij(:) )
3560       cs_ij(:) = ( 0.622_wp * e_s / ( p_ij(:) - e_s(:) ) ) * adn_ij(:)
3561    ENDIF
3562
3563 END SUBROUTINE salsa_thrm_ij
3564
3565!------------------------------------------------------------------------------!
3566! Description:
3567! ------------
3568!> Calculates ambient sizes of particles by equilibrating soluble fraction of
3569!> particles with water using the ZSR method (Stokes and Robinson, 1966).
3570!> Method:
3571!> Following chemical components are assumed water-soluble
3572!> - (ammonium) sulphate (100%)
3573!> - sea salt (100 %)
3574!> - organic carbon (epsoc * 100%)
3575!> Exact thermodynamic considerations neglected.
3576!> - If particles contain no sea salt, calculation according to sulphate
3577!>   properties
3578!> - If contain sea salt but no sulphate, calculation according to sea salt
3579!>   properties
3580!> - If contain both sulphate and sea salt -> the molar fraction of these
3581!>   compounds determines which one of them is used as the basis of calculation.
3582!> If sulphate and sea salt coexist in a particle, it is assumed that the Cl is
3583!> replaced by sulphate; thus only either sulphate + organics or sea salt +
3584!> organics is included in the calculation of soluble fraction.
3585!> Molality parameterizations taken from Table 1 of Tang: Thermodynamic and
3586!> optical properties of mixed-salt aerosols of atmospheric importance,
3587!> J. Geophys. Res., 102 (D2), 1883-1893 (1997)
3588!
3589!> Coded by:
3590!> Hannele Korhonen (FMI) 2005
3591!> Harri Kokkola (FMI) 2006
3592!> Matti Niskanen(FMI) 2012
3593!> Anton Laakso  (FMI) 2013
3594!> Modified for the new aerosol datatype, Juha Tonttila (FMI) 2014
3595!
3596!> fxm: should sea salt form a solid particle when prh is very low (even though
3597!> it could be mixed with e.g. sulphate)?
3598!> fxm: crashes if no sulphate or sea salt
3599!> fxm: do we really need to consider Kelvin effect for subrange 2
3600!------------------------------------------------------------------------------!
3601 SUBROUTINE equilibration( prh, ptemp, paero, init )
3602
3603    IMPLICIT NONE
3604
3605    INTEGER(iwp) :: ib      !< loop index
3606    INTEGER(iwp) :: counti  !< loop index
3607
3608    LOGICAL, INTENT(in) ::  init   !< TRUE: Initialization, FALSE: Normal runtime: update water
3609                                   !< content only for 1a
3610
3611    REAL(wp) ::  zaw      !< water activity [0-1]
3612    REAL(wp) ::  zcore    !< Volume of dry particle
3613    REAL(wp) ::  zdold    !< Old diameter
3614    REAL(wp) ::  zdwet    !< Wet diameter or mean droplet diameter
3615    REAL(wp) ::  zke      !< Kelvin term in the Köhler equation
3616    REAL(wp) ::  zlwc     !< liquid water content [kg/m3-air]
3617    REAL(wp) ::  zrh      !< Relative humidity
3618
3619    REAL(wp), DIMENSION(maxspec) ::  zbinmol  !< binary molality of each components (mol/kg)
3620    REAL(wp), DIMENSION(maxspec) ::  zvpart   !< volume of chem. compounds in one particle
3621
3622    REAL(wp), INTENT(in) ::  prh    !< relative humidity [0-1]
3623    REAL(wp), INTENT(in) ::  ptemp  !< temperature (K)
3624
3625    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< aerosol properties
3626
3627    zaw       = 0.0_wp
3628    zlwc      = 0.0_wp
3629!
3630!-- Relative humidity:
3631    zrh = prh
3632    zrh = MAX( zrh, 0.05_wp )
3633    zrh = MIN( zrh, 0.98_wp)
3634!
3635!-- 1) Regime 1: sulphate and partly water-soluble OC. Done for every CALL
3636    DO  ib = start_subrange_1a, end_subrange_1a   ! size bin
3637
3638       zbinmol = 0.0_wp
3639       zdold   = 1.0_wp
3640       zke     = 1.02_wp
3641
3642       IF ( paero(ib)%numc > nclim )  THEN
3643!
3644!--       Volume in one particle
3645          zvpart = 0.0_wp
3646          zvpart(1:2) = paero(ib)%volc(1:2) / paero(ib)%numc
3647          zvpart(6:7) = paero(ib)%volc(6:7) / paero(ib)%numc
3648!
3649!--       Total volume and wet diameter of one dry particle
3650          zcore = SUM( zvpart(1:2) )
3651          zdwet = paero(ib)%dwet
3652
3653          counti = 0
3654          DO  WHILE ( ABS( zdwet / zdold - 1.0_wp ) > 1.0E-2_wp )
3655
3656             zdold = MAX( zdwet, 1.0E-20_wp )
3657             zaw = MAX( 1.0E-3_wp, zrh / zke ) ! To avoid underflow
3658!
3659!--          Binary molalities (mol/kg):
3660!--          Sulphate
3661             zbinmol(1) = 1.1065495E+2_wp - 3.6759197E+2_wp * zaw + 5.0462934E+2_wp * zaw**2 -     &
3662                          3.1543839E+2_wp * zaw**3 + 6.770824E+1_wp  * zaw**4
3663!--          Organic carbon
3664             zbinmol(2) = 1.0_wp / ( zaw * amh2o ) - 1.0_wp / amh2o
3665!--          Nitric acid
3666             zbinmol(6) = 2.306844303E+1_wp - 3.563608869E+1_wp * zaw - 6.210577919E+1_wp * zaw**2 &
3667                          + 5.510176187E+2_wp * zaw**3 - 1.460055286E+3_wp * zaw**4                &
3668                          + 1.894467542E+3_wp * zaw**5 - 1.220611402E+3_wp * zaw**6                &
3669                          + 3.098597737E+2_wp * zaw**7
3670!
3671!--          Calculate the liquid water content (kg/m3-air) using ZSR (see e.g. Eq. 10.98 in
3672!--          Seinfeld and Pandis (2006))
3673             zlwc = ( paero(ib)%volc(1) * ( arhoh2so4 / amh2so4 ) ) / zbinmol(1) +                 &
3674                    epsoc * paero(ib)%volc(2) * ( arhooc / amoc ) / zbinmol(2) +                   &
3675                    ( paero(ib)%volc(6) * ( arhohno3/amhno3 ) ) / zbinmol(6)
3676!
3677!--          Particle wet diameter (m)
3678             zdwet = ( zlwc / paero(ib)%numc / arhoh2o / api6 + ( SUM( zvpart(6:7) ) / api6 ) +    &
3679                       zcore / api6 )**0.33333333_wp
3680!
3681!--          Kelvin effect (Eq. 10.85 in in Seinfeld and Pandis (2006)). Avoid
3682!--          overflow.
3683             zke = EXP( MIN( 50.0_wp, 4.0_wp * surfw0 * amvh2so4 / ( abo * ptemp *  zdwet ) ) )
3684
3685             counti = counti + 1
3686             IF ( counti > 1000 )  THEN
3687                message_string = 'Subrange 1: no convergence!'
3688                CALL message( 'salsa_mod: equilibration', 'PA0617', 1, 2, 0, 6, 0 )
3689             ENDIF
3690          ENDDO
3691!
3692!--       Instead of lwc, use the volume concentration of water from now on
3693!--       (easy to convert...)
3694          paero(ib)%volc(8) = zlwc / arhoh2o
3695!
3696!--       If this is initialization, update the core and wet diameter
3697          IF ( init )  THEN
3698             paero(ib)%dwet = zdwet
3699             paero(ib)%core = zcore
3700          ENDIF
3701
3702       ELSE
3703!--       If initialization
3704!--       1.2) empty bins given bin average values
3705          IF ( init )  THEN
3706             paero(ib)%dwet = paero(ib)%dmid
3707             paero(ib)%core = api6 * paero(ib)%dmid**3
3708          ENDIF
3709
3710       ENDIF
3711
3712    ENDDO  ! ib
3713!
3714!-- 2) Regime 2a: sulphate, OC, BC and sea salt
3715!--    This is done only for initialization call, otherwise the water contents
3716!--    are computed via condensation
3717    IF ( init )  THEN
3718       DO  ib = start_subrange_2a, end_subrange_2b
3719!
3720!--       Initialize
3721          zke     = 1.02_wp
3722          zbinmol = 0.0_wp
3723          zdold   = 1.0_wp
3724!
3725!--       1) Particle properties calculated for non-empty bins
3726          IF ( paero(ib)%numc > nclim )  THEN
3727!
3728!--          Volume in one particle [fxm]
3729             zvpart = 0.0_wp
3730             zvpart(1:7) = paero(ib)%volc(1:7) / paero(ib)%numc
3731!
3732!--          Total volume and wet diameter of one dry particle [fxm]
3733             zcore = SUM( zvpart(1:5) )
3734             zdwet = paero(ib)%dwet
3735
3736             counti = 0
3737             DO  WHILE ( ABS( zdwet / zdold - 1.0_wp ) > 1.0E-12_wp )
3738
3739                zdold = MAX( zdwet, 1.0E-20_wp )
3740                zaw = zrh / zke
3741!
3742!--             Binary molalities (mol/kg):
3743!--             Sulphate
3744                zbinmol(1) = 1.1065495E+2_wp - 3.6759197E+2_wp * zaw + 5.0462934E+2_wp * zaw**2 -  &
3745                             3.1543839E+2_wp * zaw**3 + 6.770824E+1_wp  * zaw**4
3746!--             Organic carbon
3747                zbinmol(2) = 1.0_wp / ( zaw * amh2o ) - 1.0_wp / amh2o
3748!--             Nitric acid
3749                zbinmol(6) = 2.306844303E+1_wp          - 3.563608869E+1_wp * zaw -                &
3750                             6.210577919E+1_wp * zaw**2 + 5.510176187E+2_wp * zaw**3 -             &
3751                             1.460055286E+3_wp * zaw**4 + 1.894467542E+3_wp * zaw**5 -             &
3752                             1.220611402E+3_wp * zaw**6 + 3.098597737E+2_wp * zaw**7 
3753!--             Sea salt (natrium chloride)
3754                zbinmol(5) = 5.875248E+1_wp - 1.8781997E+2_wp * zaw + 2.7211377E+2_wp * zaw**2 -   &
3755                             1.8458287E+2_wp * zaw**3 + 4.153689E+1_wp  * zaw**4
3756!
3757!--             Calculate the liquid water content (kg/m3-air)
3758                zlwc = ( paero(ib)%volc(1) * ( arhoh2so4 / amh2so4 ) ) / zbinmol(1) +              &
3759                       epsoc * ( paero(ib)%volc(2) * ( arhooc / amoc ) ) / zbinmol(2) +            &
3760                       ( paero(ib)%volc(6) * ( arhohno3 / amhno3 ) ) / zbinmol(6) +                &
3761                       ( paero(ib)%volc(5) * ( arhoss / amss ) ) / zbinmol(5)
3762
3763!--             Particle wet radius (m)
3764                zdwet = ( zlwc / paero(ib)%numc / arhoh2o / api6 + ( SUM( zvpart(6:7) ) / api6 )  + &
3765                           zcore / api6 )**0.33333333_wp
3766!
3767!--             Kelvin effect (Eq. 10.85 in Seinfeld and Pandis (2006))
3768                zke = EXP( MIN( 50.0_wp, 4.0_wp * surfw0 * amvh2so4 / ( abo * zdwet * ptemp ) ) )
3769
3770                counti = counti + 1
3771                IF ( counti > 1000 )  THEN
3772                   message_string = 'Subrange 2: no convergence!'
3773                CALL message( 'salsa_mod: equilibration', 'PA0618', 1, 2, 0, 6, 0 )
3774                ENDIF
3775             ENDDO
3776!
3777!--          Liquid water content; instead of LWC use the volume concentration
3778             paero(ib)%volc(8) = zlwc / arhoh2o
3779             paero(ib)%dwet    = zdwet
3780             paero(ib)%core    = zcore
3781
3782          ELSE
3783!--          2.2) empty bins given bin average values
3784             paero(ib)%dwet = paero(ib)%dmid
3785             paero(ib)%core = api6 * paero(ib)%dmid**3
3786          ENDIF
3787
3788       ENDDO   ! ib
3789    ENDIF
3790
3791 END SUBROUTINE equilibration
3792
3793!------------------------------------------------------------------------------!
3794!> Description:
3795!> ------------
3796!> Calculation of the settling velocity vc (m/s) per aerosol size bin and
3797!> deposition on plant canopy (lsdepo_pcm).
3798!
3799!> Deposition is based on either the scheme presented in:
3800!> Zhang et al. (2001), Atmos. Environ. 35, 549-560 (includes collection due to
3801!> Brownian diffusion, impaction, interception and sedimentation; hereafter ZO1)
3802!> OR
3803!> Petroff & Zhang (2010), Geosci. Model Dev. 3, 753-769 (includes also
3804!> collection due to turbulent impaction, hereafter P10)
3805!
3806!> Equation numbers refer to equation in Jacobson (2005): Fundamentals of
3807!> Atmospheric Modeling, 2nd Edition.
3808!
3809!> Subroutine follows closely sedim_SALSA in UCLALES-SALSA written by Juha
3810!> Tonttila (KIT/FMI) and Zubair Maalick (UEF).
3811!> Rewritten to PALM by Mona Kurppa (UH), 2017.
3812!
3813!> Call for grid point i,j,k
3814!------------------------------------------------------------------------------!
3815
3816 SUBROUTINE deposition( paero, tk, adn, mag_u, lad, kvis, schmidt_num, vc )
3817
3818    USE plant_canopy_model_mod,                                                                    &
3819        ONLY:  cdc
3820
3821    IMPLICIT NONE
3822
3823    INTEGER(iwp) ::  ib   !< loop index
3824    INTEGER(iwp) ::  ic   !< loop index
3825
3826    REAL(wp) ::  alpha             !< parameter, Table 3 in Z01
3827    REAL(wp) ::  avis              !< molecular viscocity of air (kg/(m*s))
3828    REAL(wp) ::  beta_im           !< parameter for turbulent impaction
3829    REAL(wp) ::  c_brownian_diff   !< coefficient for Brownian diffusion
3830    REAL(wp) ::  c_impaction       !< coefficient for inertial impaction
3831    REAL(wp) ::  c_interception    !< coefficient for interception
3832    REAL(wp) ::  c_turb_impaction  !< coefficient for turbulent impaction
3833    REAL(wp) ::  depo              !< deposition velocity (m/s)
3834    REAL(wp) ::  gamma             !< parameter, Table 3 in Z01
3835    REAL(wp) ::  lambda            !< molecular mean free path (m)
3836    REAL(wp) ::  mdiff             !< particle diffusivity coefficient
3837    REAL(wp) ::  par_a             !< parameter A for the characteristic radius of collectors,
3838                                   !< Table 3 in Z01
3839    REAL(wp) ::  par_l             !< obstacle characteristic dimension in P10
3840    REAL(wp) ::  pdn               !< particle density (kg/m3)
3841    REAL(wp) ::  ustar             !< friction velocity (m/s)
3842    REAL(wp) ::  va                !< thermal speed of an air molecule (m/s)
3843
3844    REAL(wp), INTENT(in) ::  adn    !< air density (kg/m3)
3845    REAL(wp), INTENT(in) ::  lad    !< leaf area density (m2/m3)
3846    REAL(wp), INTENT(in) ::  mag_u  !< wind velocity (m/s)
3847    REAL(wp), INTENT(in) ::  tk     !< abs.temperature (K)
3848
3849    REAL(wp), INTENT(inout) ::  kvis   !< kinematic viscosity of air (m2/s)
3850
3851    REAL(wp), DIMENSION(nbins_aerosol) ::  beta   !< Cunningham slip-flow correction factor
3852    REAL(wp), DIMENSION(nbins_aerosol) ::  Kn     !< Knudsen number
3853    REAL(wp), DIMENSION(nbins_aerosol) ::  zdwet  !< wet diameter (m)
3854
3855    REAL(wp), DIMENSION(:), INTENT(inout) ::  schmidt_num  !< particle Schmidt number
3856    REAL(wp), DIMENSION(:), INTENT(inout) ::  vc  !< critical fall speed i.e. settling velocity of
3857                                                  !< an aerosol particle (m/s)
3858
3859    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< aerosol properties
3860!
3861!-- Initialise
3862    depo  = 0.0_wp
3863    pdn   = 1500.0_wp    ! default value
3864    ustar = 0.0_wp
3865!
3866!-- Molecular viscosity of air (Eq. 4.54)
3867    avis = 1.8325E-5_wp * ( 416.16_wp / ( tk + 120.0_wp ) ) * ( tk / 296.16_wp )**1.5_wp
3868!
3869!-- Kinematic viscosity (Eq. 4.55)
3870    kvis =  avis / adn
3871!
3872!-- Thermal velocity of an air molecule (Eq. 15.32)
3873    va = SQRT( 8.0_wp * abo * tk / ( pi * am_airmol ) )
3874!
3875!-- Mean free path (m) (Eq. 15.24)
3876    lambda = 2.0_wp * avis / ( adn * va )
3877!
3878!-- Particle wet diameter (m)
3879    zdwet = paero(:)%dwet
3880!
3881!-- Knudsen number (Eq. 15.23)
3882    Kn = MAX( 1.0E-2_wp, lambda / ( zdwet * 0.5_wp ) ) ! To avoid underflow
3883!
3884!-- Cunningham slip-flow correction (Eq. 15.30)
3885    beta = 1.0_wp + Kn * ( 1.249_wp + 0.42_wp * EXP( -0.87_wp / Kn ) )
3886!
3887!-- Critical fall speed i.e. settling velocity  (Eq. 20.4)
3888    vc = MIN( 1.0_wp, zdwet**2 * ( pdn - adn ) * g * beta / ( 18.0_wp * avis ) )
3889!
3890!-- Deposition on vegetation
3891    IF ( lsdepo_pcm  .AND.  plant_canopy  .AND.  lad > 0.0_wp )  THEN
3892!
3893!--    Parameters for the land use category 'deciduous broadleaf trees'(Table 3)
3894       alpha   = alpha_z01(depo_pcm_type_num)
3895       gamma   = gamma_z01(depo_pcm_type_num)
3896       par_a   = A_z01(depo_pcm_type_num, season_z01) * 1.0E-3_wp
3897!
3898!--    Deposition efficiencies from Table 1. Constants from Table 2.
3899       par_l            = l_p10(depo_pcm_type_num) * 0.01_wp
3900       c_brownian_diff  = c_b_p10(depo_pcm_type_num)
3901       c_interception   = c_in_p10(depo_pcm_type_num)
3902       c_impaction      = c_im_p10(depo_pcm_type_num)
3903       beta_im          = beta_im_p10(depo_pcm_type_num)
3904       c_turb_impaction = c_it_p10(depo_pcm_type_num)
3905
3906       DO  ib = 1, nbins_aerosol
3907
3908          IF ( paero(ib)%numc < ( 2.0_wp * nclim ) )  CYCLE
3909
3910!--       Particle diffusivity coefficient (Eq. 15.29)
3911          mdiff = ( abo * tk * beta(ib) ) / ( 3.0_wp * pi * avis * zdwet(ib) )
3912!
3913!--       Particle Schmidt number (Eq. 15.36)
3914          schmidt_num(ib) = kvis / mdiff
3915!
3916!--       Friction velocity for deposition on vegetation. Calculated following Prandtl (1925):
3917          ustar = SQRT( cdc ) * mag_u
3918          SELECT CASE ( depo_pcm_par_num )
3919
3920             CASE ( 1 )   ! Zhang et al. (2001)
3921                CALL depo_vel_Z01( vc(ib), ustar, schmidt_num(ib), paero(ib)%dwet, alpha,  gamma,  &
3922                                   par_a, depo )
3923             CASE ( 2 )   ! Petroff & Zhang (2010)
3924                CALL depo_vel_P10( vc(ib), mag_u, ustar, kvis, schmidt_num(ib), paero(ib)%dwet,    &
3925                                   par_l, c_brownian_diff, c_interception, c_impaction, beta_im,   &
3926                                   c_turb_impaction, depo )
3927          END SELECT
3928!
3929!--       Calculate the change in concentrations
3930          paero(ib)%numc = paero(ib)%numc - depo * lad * paero(ib)%numc * dt_salsa
3931          DO  ic = 1, maxspec+1
3932             paero(ib)%volc(ic) = paero(ib)%volc(ic) - depo * lad * paero(ib)%volc(ic) * dt_salsa
3933          ENDDO
3934       ENDDO
3935
3936    ENDIF
3937
3938 END SUBROUTINE deposition
3939
3940!------------------------------------------------------------------------------!
3941! Description:
3942! ------------
3943!> Calculate deposition velocity (m/s) based on Zhan et al. (2001, case 1).
3944!------------------------------------------------------------------------------!
3945
3946 SUBROUTINE depo_vel_Z01( vc, ustar, schmidt_num, diameter, alpha, gamma, par_a, depo )
3947
3948    IMPLICIT NONE
3949
3950    REAL(wp) ::  rs                !< overall quasi-laminar resistance for particles
3951    REAL(wp) ::  stokes_num        !< Stokes number for smooth or bluff surfaces
3952
3953    REAL(wp), INTENT(in) ::  alpha        !< parameter, Table 3 in Z01
3954    REAL(wp), INTENT(in) ::  gamma        !< parameter, Table 3 in Z01
3955    REAL(wp), INTENT(in) ::  par_a        !< parameter A for the characteristic diameter of
3956                                          !< collectors, Table 3 in Z01
3957    REAL(wp), INTENT(in) ::  diameter     !< particle diameter
3958    REAL(wp), INTENT(in) ::  schmidt_num  !< particle Schmidt number
3959    REAL(wp), INTENT(in) ::  ustar        !< friction velocity (m/s)
3960    REAL(wp), INTENT(in) ::  vc           !< terminal velocity (m/s)
3961
3962    REAL(wp), INTENT(inout)  ::  depo     !< deposition efficiency (m/s)
3963
3964    IF ( par_a > 0.0_wp )  THEN
3965!
3966!--    Initialise
3967       rs = 0.0_wp
3968!
3969!--    Stokes number for vegetated surfaces (Seinfeld & Pandis (2006): Eq.19.24)
3970       stokes_num = vc * ustar / ( g * par_a )
3971!
3972!--    The overall quasi-laminar resistance for particles (Zhang et al., Eq. 5)
3973       rs = MAX( EPSILON( 1.0_wp ), ( 3.0_wp * ustar * EXP( -stokes_num**0.5_wp ) *                &
3974                 ( schmidt_num**( -gamma ) + ( stokes_num / ( alpha + stokes_num ) )**2 +          &
3975                 0.5_wp * ( diameter / par_a )**2 ) ) )
3976
3977       depo = rs + vc
3978
3979    ELSE
3980       depo = 0.0_wp
3981    ENDIF
3982
3983 END SUBROUTINE depo_vel_Z01
3984
3985!------------------------------------------------------------------------------!
3986! Description:
3987! ------------
3988!> Calculate deposition velocity (m/s) based on Petroff & Zhang (2010, case 2).
3989!------------------------------------------------------------------------------!
3990
3991 SUBROUTINE depo_vel_P10( vc, mag_u, ustar, kvis_a, schmidt_num, diameter, par_l, c_brownian_diff, &
3992                          c_interception, c_impaction, beta_im, c_turb_impaction, depo )
3993
3994    IMPLICIT NONE
3995
3996    REAL(wp) ::  stokes_num        !< Stokes number for smooth or bluff surfaces
3997    REAL(wp) ::  tau_plus          !< dimensionless particle relaxation time
3998    REAL(wp) ::  v_bd              !< deposition velocity due to Brownian diffusion
3999    REAL(wp) ::  v_im              !< deposition velocity due to impaction
4000    REAL(wp) ::  v_in              !< deposition velocity due to interception
4001    REAL(wp) ::  v_it              !< deposition velocity due to turbulent impaction
4002
4003    REAL(wp), INTENT(in) ::  beta_im           !< parameter for turbulent impaction
4004    REAL(wp), INTENT(in) ::  c_brownian_diff   !< coefficient for Brownian diffusion
4005    REAL(wp), INTENT(in) ::  c_impaction       !< coefficient for inertial impaction
4006    REAL(wp), INTENT(in) ::  c_interception    !< coefficient for interception
4007    REAL(wp), INTENT(in) ::  c_turb_impaction  !< coefficient for turbulent impaction
4008    REAL(wp), INTENT(in) ::  kvis_a       !< kinematic viscosity of air (m2/s)
4009    REAL(wp), INTENT(in) ::  mag_u        !< wind velocity (m/s)
4010    REAL(wp), INTENT(in) ::  par_l        !< obstacle characteristic dimension in P10
4011    REAL(wp), INTENT(in) ::  diameter       !< particle diameter
4012    REAL(wp), INTENT(in) ::  schmidt_num  !< particle Schmidt number
4013    REAL(wp), INTENT(in) ::  ustar        !< friction velocity (m/s)
4014    REAL(wp), INTENT(in) ::  vc           !< terminal velocity (m/s)
4015
4016    REAL(wp), INTENT(inout)  ::  depo     !< deposition efficiency (m/s)
4017
4018    IF ( par_l > 0.0_wp )  THEN
4019!
4020!--    Initialise
4021       tau_plus = 0.0_wp
4022       v_bd     = 0.0_wp
4023       v_im     = 0.0_wp
4024       v_in     = 0.0_wp
4025       v_it     = 0.0_wp
4026!
4027!--    Stokes number for vegetated surfaces (Seinfeld & Pandis (2006): Eq.19.24)
4028       stokes_num = vc * ustar / ( g * par_l )
4029!
4030!--    Non-dimensional relexation time of the particle on top of canopy
4031       tau_plus = vc * ustar**2 / ( kvis_a * g )
4032!
4033!--    Brownian diffusion
4034       v_bd = mag_u * c_brownian_diff * schmidt_num**( -0.66666666_wp ) *                          &
4035              ( mag_u * par_l / kvis_a )**( -0.5_wp )
4036!
4037!--    Interception
4038       v_in = mag_u * c_interception * diameter / par_l *                                          &
4039              ( 2.0_wp + LOG( 2.0_wp * par_l / diameter ) )
4040!
4041!--    Impaction: Petroff (2009) Eq. 18
4042       v_im = mag_u * c_impaction * ( stokes_num / ( stokes_num + beta_im ) )**2
4043!
4044!--    Turbulent impaction
4045       IF ( tau_plus < 20.0_wp )  THEN
4046          v_it = 2.5E-3_wp * c_turb_impaction * tau_plus**2
4047       ELSE
4048          v_it = c_turb_impaction
4049       ENDIF
4050
4051       depo = ( v_bd + v_in + v_im + v_it + vc )
4052
4053    ELSE
4054       depo = 0.0_wp
4055    ENDIF
4056
4057 END SUBROUTINE depo_vel_P10
4058
4059!------------------------------------------------------------------------------!
4060! Description:
4061! ------------
4062!> Calculate the dry deposition on horizontal and vertical surfaces. Implement
4063!> as a surface flux.
4064!> @todo aerodynamic resistance ignored for now (not important for
4065!        high-resolution simulations)
4066!------------------------------------------------------------------------------!
4067 SUBROUTINE depo_surf( i, j, surf, vc, schmidt_num, kvis, mag_u, norm, match_array )
4068
4069    USE arrays_3d,                                                                                 &
4070        ONLY: rho_air_zw
4071
4072    USE surface_mod,                                                                               &
4073        ONLY:  ind_pav_green, ind_veg_wall, ind_wat_win, surf_type
4074
4075    IMPLICIT NONE
4076
4077    INTEGER(iwp) ::  ib      !< loop index
4078    INTEGER(iwp) ::  ic      !< loop index
4079    INTEGER(iwp) ::  icc     !< additional loop index
4080    INTEGER(iwp) ::  k       !< loop index
4081    INTEGER(iwp) ::  m       !< loop index
4082    INTEGER(iwp) ::  surf_e  !< End index of surface elements at (j,i)-gridpoint
4083    INTEGER(iwp) ::  surf_s  !< Start index of surface elements at (j,i)-gridpoint
4084
4085    INTEGER(iwp), INTENT(in) ::  i  !< loop index
4086    INTEGER(iwp), INTENT(in) ::  j  !< loop index
4087
4088    LOGICAL, INTENT(in) ::  norm   !< to normalise or not
4089
4090    REAL(wp) ::  alpha             !< parameter, Table 3 in Z01
4091    REAL(wp) ::  beta_im           !< parameter for turbulent impaction
4092    REAL(wp) ::  c_brownian_diff   !< coefficient for Brownian diffusion
4093    REAL(wp) ::  c_impaction       !< coefficient for inertial impaction
4094    REAL(wp) ::  c_interception    !< coefficient for interception
4095    REAL(wp) ::  c_turb_impaction  !< coefficient for turbulent impaction
4096    REAL(wp) ::  gamma             !< parameter, Table 3 in Z01
4097    REAL(wp) ::  norm_fac          !< normalisation factor (usually air density)
4098    REAL(wp) ::  par_a             !< parameter A for the characteristic radius of collectors,
4099                                   !< Table 3 in Z01
4100    REAL(wp) ::  par_l             !< obstacle characteristic dimension in P10
4101    REAL(wp) ::  rs                !< the overall quasi-laminar resistance for particles
4102    REAL(wp) ::  tau_plus          !< dimensionless particle relaxation time
4103    REAL(wp) ::  v_bd              !< deposition velocity due to Brownian diffusion
4104    REAL(wp) ::  v_im              !< deposition velocity due to impaction
4105    REAL(wp) ::  v_in              !< deposition velocity due to interception
4106    REAL(wp) ::  v_it              !< deposition velocity due to turbulent impaction
4107
4108    REAL(wp), DIMENSION(nbins_aerosol) ::  depo      !< deposition efficiency
4109    REAL(wp), DIMENSION(nbins_aerosol) ::  depo_sum  !< sum of deposition efficiencies
4110
4111    REAL(wp), DIMENSION(:), INTENT(in) ::  kvis   !< kinematic viscosity of air (m2/s)
4112    REAL(wp), DIMENSION(:), INTENT(in) ::  mag_u  !< wind velocity (m/s)
4113
4114    REAL(wp), DIMENSION(:,:), INTENT(in) ::  schmidt_num   !< particle Schmidt number
4115    REAL(wp), DIMENSION(:,:), INTENT(in) ::  vc            !< terminal velocity (m/s)
4116
4117    TYPE(match_surface), INTENT(in), OPTIONAL ::  match_array  !< match the deposition module and
4118                                                               !< LSM/USM surfaces
4119    TYPE(surf_type), INTENT(inout) :: surf                     !< respective surface type
4120!
4121!-- Initialise
4122    depo     = 0.0_wp
4123    depo_sum = 0.0_wp
4124    rs       = 0.0_wp
4125    surf_s   = surf%start_index(j,i)
4126    surf_e   = surf%end_index(j,i)
4127    tau_plus = 0.0_wp
4128    v_bd     = 0.0_wp
4129    v_im     = 0.0_wp
4130    v_in     = 0.0_wp
4131    v_it     = 0.0_wp
4132!
4133!-- Model parameters for the land use category. If LSM or USM is applied, import
4134!-- characteristics. Otherwise, apply surface type "urban".
4135    alpha   = alpha_z01(luc_urban)
4136    gamma   = gamma_z01(luc_urban)
4137    par_a   = A_z01(luc_urban, season_z01) * 1.0E-3_wp
4138
4139    par_l            = l_p10(luc_urban) * 0.01_wp
4140    c_brownian_diff  = c_b_p10(luc_urban)
4141    c_interception   = c_in_p10(luc_urban)
4142    c_impaction      = c_im_p10(luc_urban)
4143    beta_im          = beta_im_p10(luc_urban)
4144    c_turb_impaction = c_it_p10(luc_urban)
4145
4146
4147    IF ( PRESENT( match_array ) )  THEN  ! land or urban surface model
4148
4149       DO  m = surf_s, surf_e
4150
4151          k = surf%k(m)
4152          norm_fac = 1.0_wp
4153
4154          IF ( norm )  norm_fac = rho_air_zw(k)  ! normalise vertical fluxes by air density
4155
4156          IF ( match_array%match_lupg(m) > 0 )  THEN
4157             alpha = alpha_z01( match_array%match_lupg(m) )
4158             gamma = gamma_z01( match_array%match_lupg(m) )
4159             par_a = A_z01( match_array%match_lupg(m), season_z01 ) * 1.0E-3_wp
4160
4161             beta_im          = beta_im_p10( match_array%match_lupg(m) )
4162             c_brownian_diff  = c_b_p10( match_array%match_lupg(m) )
4163             c_impaction      = c_im_p10( match_array%match_lupg(m) )
4164             c_interception   = c_in_p10( match_array%match_lupg(m) )
4165             c_turb_impaction = c_it_p10( match_array%match_lupg(m) )
4166             par_l            = l_p10( match_array%match_lupg(m) ) * 0.01_wp
4167
4168             DO  ib = 1, nbins_aerosol
4169                IF ( aerosol_number(ib)%conc(k,j,i) < ( 2.0_wp * nclim )  .OR.                     &
4170                     schmidt_num(k+1,ib) < 1.0_wp )  CYCLE
4171
4172                SELECT CASE ( depo_surf_par_num )
4173
4174                   CASE ( 1 )
4175                      CALL depo_vel_Z01( vc(k+1,ib), surf%us(m), schmidt_num(k+1,ib),              &
4176                                         ra_dry(k,j,i,ib), alpha, gamma, par_a, depo(ib) )
4177                   CASE ( 2 )
4178                      CALL depo_vel_P10( vc(k+1,ib), mag_u(k+1), surf%us(m), kvis(k+1),            &
4179                                         schmidt_num(k+1,ib), ra_dry(k,j,i,ib), par_l,             &
4180                                         c_brownian_diff, c_interception, c_impaction, beta_im,    &
4181                                         c_turb_impaction, depo(ib) )
4182                END SELECT
4183             ENDDO
4184             depo_sum = depo_sum + surf%frac(ind_pav_green,m) * depo
4185          ENDIF
4186
4187          IF ( match_array%match_luvw(m) > 0 )  THEN
4188             alpha = alpha_z01( match_array%match_luvw(m) )
4189             gamma = gamma_z01( match_array%match_luvw(m) )
4190             par_a = A_z01( match_array%match_luvw(m), season_z01 ) * 1.0E-3_wp
4191
4192             beta_im          = beta_im_p10( match_array%match_luvw(m) )
4193             c_brownian_diff  = c_b_p10( match_array%match_luvw(m) )
4194             c_impaction      = c_im_p10( match_array%match_luvw(m) )
4195             c_interception   = c_in_p10( match_array%match_luvw(m) )
4196             c_turb_impaction = c_it_p10( match_array%match_luvw(m) )
4197             par_l            = l_p10( match_array%match_luvw(m) ) * 0.01_wp
4198
4199             DO  ib = 1, nbins_aerosol
4200                IF ( aerosol_number(ib)%conc(k,j,i) < ( 2.0_wp * nclim )  .OR.                     &
4201                     schmidt_num(k+1,ib) < 1.0_wp )  CYCLE
4202
4203                SELECT CASE ( depo_surf_par_num )
4204
4205                   CASE ( 1 )
4206                      CALL depo_vel_Z01( vc(k+1,ib), surf%us(m), schmidt_num(k+1,ib),              &
4207                                         ra_dry(k,j,i,ib), alpha, gamma, par_a, depo(ib) )
4208                   CASE ( 2 )
4209                      CALL depo_vel_P10( vc(k+1,ib), mag_u(k+1), surf%us(m), kvis(k+1),            &
4210                                         schmidt_num(k+1,ib), ra_dry(k,j,i,ib), par_l,             &
4211                                         c_brownian_diff, c_interception, c_impaction, beta_im,    &
4212                                         c_turb_impaction, depo(ib) )
4213                END SELECT
4214             ENDDO
4215             depo_sum = depo_sum + surf%frac(ind_veg_wall,m) * depo
4216          ENDIF
4217
4218          IF ( match_array%match_luww(m) > 0 )  THEN
4219             alpha = alpha_z01( match_array%match_luww(m) )
4220             gamma = gamma_z01( match_array%match_luww(m) )
4221             par_a = A_z01( match_array%match_luww(m), season_z01 ) * 1.0E-3_wp
4222
4223             beta_im          = beta_im_p10( match_array%match_luww(m) )
4224             c_brownian_diff  = c_b_p10( match_array%match_luww(m) )
4225             c_impaction      = c_im_p10( match_array%match_luww(m) )
4226             c_interception   = c_in_p10( match_array%match_luww(m) )
4227             c_turb_impaction = c_it_p10( match_array%match_luww(m) )
4228             par_l            = l_p10( match_array%match_luww(m) ) * 0.01_wp
4229
4230             DO  ib = 1, nbins_aerosol
4231                IF ( aerosol_number(ib)%conc(k,j,i) < ( 2.0_wp * nclim )  .OR.                     &
4232                     schmidt_num(k+1,ib) < 1.0_wp )  CYCLE
4233
4234                SELECT CASE ( depo_surf_par_num )
4235
4236                   CASE ( 1 )
4237                      CALL depo_vel_Z01( vc(k+1,ib), surf%us(m), schmidt_num(k+1,ib),              &
4238                                         ra_dry(k,j,i,ib), alpha, gamma, par_a, depo(ib) )
4239                   CASE ( 2 )
4240                      CALL depo_vel_P10( vc(k+1,ib), mag_u(k+1), surf%us(m), kvis(k+1),            &
4241                                         schmidt_num(k+1,ib), ra_dry(k,j,i,ib), par_l,             &
4242                                         c_brownian_diff, c_interception, c_impaction, beta_im,    &
4243                                         c_turb_impaction, depo(ib) )
4244                END SELECT
4245             ENDDO
4246             depo_sum = depo_sum + surf%frac(ind_wat_win,m) * depo
4247          ENDIF
4248
4249          DO  ib = 1, nbins_aerosol
4250             IF ( aerosol_number(ib)%conc(k,j,i) < ( 2.0_wp * nclim ) )  CYCLE
4251!
4252!--          Calculate changes in surface fluxes due to dry deposition
4253             IF ( include_emission )  THEN
4254                surf%answs(m,ib) = aerosol_number(ib)%source(j,i) - MAX( 0.0_wp,                   &
4255                                   depo_sum(ib) * norm_fac * aerosol_number(ib)%conc(k,j,i) )
4256                DO  ic = 1, ncomponents_mass
4257                   icc = ( ic - 1 ) * nbins_aerosol + ib
4258                   surf%amsws(m,icc) = aerosol_mass(icc)%source(j,i) - MAX( 0.0_wp,                &
4259                                       depo_sum(ib) *  norm_fac * aerosol_mass(icc)%conc(k,j,i) )
4260                ENDDO  ! ic
4261             ELSE
4262                surf%answs(m,ib) = -depo_sum(ib) * norm_fac * aerosol_number(ib)%conc(k,j,i)
4263                DO  ic = 1, ncomponents_mass
4264                   icc = ( ic - 1 ) * nbins_aerosol + ib
4265                   surf%amsws(m,icc) = -depo_sum(ib) *  norm_fac * aerosol_mass(icc)%conc(k,j,i)
4266                ENDDO  ! ic
4267             ENDIF
4268          ENDDO  ! ib
4269
4270       ENDDO
4271
4272    ELSE  ! default surfaces
4273
4274       DO  m = surf_s, surf_e
4275
4276          k = surf%k(m)
4277          norm_fac = 1.0_wp
4278
4279          IF ( norm )  norm_fac = rho_air_zw(k)  ! normalise vertical fluxes by air density
4280
4281          DO  ib = 1, nbins_aerosol
4282             IF ( aerosol_number(ib)%conc(k,j,i) < ( 2.0_wp * nclim )  .OR.                        &
4283                  schmidt_num(k+1,ib) < 1.0_wp )  CYCLE
4284
4285             SELECT CASE ( depo_surf_par_num )
4286
4287                CASE ( 1 )
4288                   CALL depo_vel_Z01( vc(k+1,ib), surf%us(m), schmidt_num(k+1,ib),                 &
4289                                      ra_dry(k,j,i,ib), alpha, gamma, par_a, depo(ib) )
4290                CASE ( 2 )
4291                   CALL depo_vel_P10( vc(k+1,ib), mag_u(k+1), surf%us(m), kvis(k+1),               &
4292                                      schmidt_num(k+1,ib), ra_dry(k,j,i,ib), par_l,                &
4293                                      c_brownian_diff, c_interception, c_impaction, beta_im,       &
4294                                      c_turb_impaction, depo(ib) )
4295             END SELECT
4296!
4297!--          Calculate changes in surface fluxes due to dry deposition
4298             IF ( include_emission )  THEN
4299                surf%answs(m,ib) = aerosol_number(ib)%source(j,i) - MAX( 0.0_wp,                   &
4300                                   depo(ib) * norm_fac * aerosol_number(ib)%conc(k,j,i) )
4301                DO  ic = 1, ncomponents_mass
4302                   icc = ( ic - 1 ) * nbins_aerosol + ib
4303                   surf%amsws(m,icc) = aerosol_mass(icc)%source(j,i) - MAX( 0.0_wp,                &
4304                                       depo(ib) *  norm_fac * aerosol_mass(icc)%conc(k,j,i) )
4305                ENDDO  ! ic
4306             ELSE
4307                surf%answs(m,ib) = -depo(ib) * norm_fac * aerosol_number(ib)%conc(k,j,i)
4308                DO  ic = 1, ncomponents_mass
4309                   icc = ( ic - 1 ) * nbins_aerosol + ib
4310                   surf%amsws(m,icc) = -depo(ib) *  norm_fac * aerosol_mass(icc)%conc(k,j,i)
4311                ENDDO  ! ic
4312             ENDIF
4313          ENDDO  ! ib
4314       ENDDO
4315
4316    ENDIF
4317
4318 END SUBROUTINE depo_surf
4319
4320!------------------------------------------------------------------------------!
4321! Description:
4322! ------------
4323!> Calculates particle loss and change in size distribution due to (Brownian)
4324!> coagulation. Only for particles with dwet < 30 micrometres.
4325!
4326!> Method:
4327!> Semi-implicit, non-iterative method: (Jacobson, 1994)
4328!> Volume concentrations of the smaller colliding particles added to the bin of
4329!> the larger colliding particles. Start from first bin and use the updated
4330!> number and volume for calculation of following bins. NB! Our bin numbering
4331!> does not follow particle size in subrange 2.
4332!
4333!> Schematic for bin numbers in different subranges:
4334!>             1                            2
4335!>    +-------------------------------------------+
4336!>  a | 1 | 2 | 3 || 4 | 5 | 6 | 7 |  8 |  9 | 10||
4337!>  b |           ||11 |12 |13 |14 | 15 | 16 | 17||
4338!>    +-------------------------------------------+
4339!
4340!> Exact coagulation coefficients for each pressure level are scaled according
4341!> to current particle wet size (linear scaling).
4342!> Bins are organized in terms of the dry size of the condensation nucleus,
4343!> while coagulation kernell is calculated with the actual hydrometeor
4344!> size.
4345!
4346!> Called from salsa_driver
4347!> fxm: Process selection should be made smarter - now just lots of IFs inside
4348!>      loops
4349!
4350!> Coded by:
4351!> Hannele Korhonen (FMI) 2005
4352!> Harri Kokkola (FMI) 2006
4353!> Tommi Bergman (FMI) 2012
4354!> Matti Niskanen(FMI) 2012
4355!> Anton Laakso  (FMI) 2013
4356!> Juha Tonttila (FMI) 2014
4357!------------------------------------------------------------------------------!
4358 SUBROUTINE coagulation( paero, ptstep, ptemp, ppres )
4359
4360    IMPLICIT NONE
4361
4362    INTEGER(iwp) ::  index_2a !< corresponding bin in subrange 2a
4363    INTEGER(iwp) ::  index_2b !< corresponding bin in subrange 2b
4364    INTEGER(iwp) ::  ib       !< loop index
4365    INTEGER(iwp) ::  ll       !< loop index
4366    INTEGER(iwp) ::  mm       !< loop index
4367    INTEGER(iwp) ::  nn       !< loop index
4368
4369    REAL(wp) ::  pressi          !< pressure
4370    REAL(wp) ::  temppi          !< temperature
4371    REAL(wp) ::  zdpart_mm       !< diameter of particle (m)
4372    REAL(wp) ::  zdpart_nn       !< diameter of particle (m)
4373    REAL(wp) ::  zminusterm      !< coagulation loss in a bin (1/s)
4374
4375    REAL(wp), INTENT(in) ::  ppres  !< ambient pressure (Pa)
4376    REAL(wp), INTENT(in) ::  ptemp  !< ambient temperature (K)
4377    REAL(wp), INTENT(in) ::  ptstep !< time step (s)
4378
4379    REAL(wp), DIMENSION(nbins_aerosol) ::  zmpart     !< approximate mass of particles (kg)
4380    REAL(wp), DIMENSION(maxspec+1)     ::  zplusterm  !< coagulation gain in a bin (for each
4381                                                      !< chemical compound)
4382    REAL(wp), DIMENSION(nbins_aerosol,nbins_aerosol) ::  zcc  !< updated coagulation coeff. (m3/s)
4383
4384    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< Aerosol properties
4385
4386    zdpart_mm = 0.0_wp
4387    zdpart_nn = 0.0_wp
4388!
4389!-- 1) Coagulation to coarse mode calculated in a simplified way:
4390!--    CoagSink ~ Dp in continuum subrange --> 'effective' number conc. of coarse particles
4391
4392!-- 2) Updating coagulation coefficients
4393!
4394!-- Aerosol mass (kg). Density of 1500 kg/m3 assumed
4395    zmpart(1:end_subrange_2b) = api6 * ( MIN( paero(1:end_subrange_2b)%dwet, 30.0E-6_wp )**3 )     &
4396                                * 1500.0_wp
4397    temppi = ptemp
4398    pressi = ppres
4399    zcc    = 0.0_wp
4400!
4401!-- Aero-aero coagulation
4402    DO  mm = 1, end_subrange_2b   ! smaller colliding particle
4403       IF ( paero(mm)%numc < ( 2.0_wp * nclim ) )  CYCLE
4404       DO  nn = mm, end_subrange_2b   ! larger colliding particle
4405          IF ( paero(nn)%numc < ( 2.0_wp * nclim ) )  CYCLE
4406
4407          zdpart_mm = MIN( paero(mm)%dwet, 30.0E-6_wp )     ! Limit to 30 um
4408          zdpart_nn = MIN( paero(nn)%dwet, 30.0E-6_wp )     ! Limit to 30 um
4409!
4410!--       Coagulation coefficient of particles (m3/s)
4411          zcc(mm,nn) = coagc( zdpart_mm, zdpart_nn, zmpart(mm), zmpart(nn), temppi, pressi )
4412          zcc(nn,mm) = zcc(mm,nn)
4413       ENDDO
4414    ENDDO
4415
4416!
4417!-- 3) New particle and volume concentrations after coagulation:
4418!--    Calculated according to Jacobson (2005) eq. 15.9
4419!
4420!-- Aerosols in subrange 1a:
4421    DO  ib = start_subrange_1a, end_subrange_1a
4422       IF ( paero(ib)%numc < ( 2.0_wp * nclim ) )  CYCLE
4423       zminusterm   = 0.0_wp
4424       zplusterm(:) = 0.0_wp
4425!
4426!--    Particles lost by coagulation with larger aerosols
4427       DO  ll = ib+1, end_subrange_2b
4428          zminusterm = zminusterm + zcc(ib,ll) * paero(ll)%numc
4429       ENDDO
4430!
4431!--    Coagulation gain in a bin: change in volume conc. (cm3/cm3):
4432       DO ll = start_subrange_1a, ib - 1
4433          zplusterm(1:2) = zplusterm(1:2) + zcc(ll,ib) * paero(ll)%volc(1:2)
4434          zplusterm(6:7) = zplusterm(6:7) + zcc(ll,ib) * paero(ll)%volc(6:7)
4435          zplusterm(8)   = zplusterm(8)   + zcc(ll,ib) * paero(ll)%volc(8)
4436       ENDDO
4437!
4438!--    Volume and number concentrations after coagulation update [fxm]
4439       paero(ib)%volc(1:2) = ( paero(ib)%volc(1:2) + ptstep * zplusterm(1:2) * paero(ib)%numc ) /  &
4440                            ( 1.0_wp + ptstep * zminusterm )
4441       paero(ib)%volc(6:8) = ( paero(ib)%volc(6:8) + ptstep * zplusterm(6:8) * paero(ib)%numc ) /  &
4442                            ( 1.0_wp + ptstep * zminusterm )
4443       paero(ib)%numc = paero(ib)%numc / ( 1.0_wp + ptstep * zminusterm + 0.5_wp * ptstep *        &
4444                        zcc(ib,ib) * paero(ib)%numc )
4445    ENDDO
4446!
4447!-- Aerosols in subrange 2a:
4448    DO  ib = start_subrange_2a, end_subrange_2a
4449       IF ( paero(ib)%numc < ( 2.0_wp * nclim ) )  CYCLE
4450       zminusterm   = 0.0_wp
4451       zplusterm(:) = 0.0_wp
4452!
4453!--    Find corresponding size bin in subrange 2b
4454       index_2b = ib - start_subrange_2a + start_subrange_2b
4455!
4456!--    Particles lost by larger particles in 2a
4457       DO  ll = ib+1, end_subrange_2a
4458          zminusterm = zminusterm + zcc(ib,ll) * paero(ll)%numc
4459       ENDDO
4460!
4461!--    Particles lost by larger particles in 2b
4462       IF ( .NOT. no_insoluble )  THEN
4463          DO  ll = index_2b+1, end_subrange_2b
4464             zminusterm = zminusterm + zcc(ib,ll) * paero(ll)%numc
4465          ENDDO
4466       ENDIF
4467!
4468!--    Particle volume gained from smaller particles in subranges 1, 2a and 2b
4469       DO  ll = start_subrange_1a, ib-1
4470          zplusterm(1:2) = zplusterm(1:2) + zcc(ll,ib) * paero(ll)%volc(1:2)
4471          zplusterm(6:8) = zplusterm(6:8) + zcc(ll,ib) * paero(ll)%volc(6:8)
4472       ENDDO
4473!
4474!--    Particle volume gained from smaller particles in 2a
4475!--    (Note, for components not included in the previous loop!)
4476       DO  ll = start_subrange_2a, ib-1
4477          zplusterm(3:5) = zplusterm(3:5) + zcc(ll,ib)*paero(ll)%volc(3:5)
4478       ENDDO
4479!
4480!--    Particle volume gained from smaller (and equal) particles in 2b
4481       IF ( .NOT. no_insoluble )  THEN
4482          DO  ll = start_subrange_2b, index_2b
4483             zplusterm(1:8) = zplusterm(1:8) + zcc(ll,ib) * paero(ll)%volc(1:8)
4484          ENDDO
4485       ENDIF
4486!
4487!--    Volume and number concentrations after coagulation update [fxm]
4488       paero(ib)%volc(1:8) = ( paero(ib)%volc(1:8) + ptstep * zplusterm(1:8) * paero(ib)%numc ) /  &
4489                            ( 1.0_wp + ptstep * zminusterm )
4490       paero(ib)%numc = paero(ib)%numc / ( 1.0_wp + ptstep * zminusterm + 0.5_wp * ptstep *        &
4491                        zcc(ib,ib) * paero(ib)%numc )
4492    ENDDO
4493!
4494!-- Aerosols in subrange 2b:
4495    IF ( .NOT. no_insoluble )  THEN
4496       DO  ib = start_subrange_2b, end_subrange_2b
4497          IF ( paero(ib)%numc < ( 2.0_wp * nclim ) )  CYCLE
4498          zminusterm   = 0.0_wp
4499          zplusterm(:) = 0.0_wp
4500!
4501!--       Find corresponding size bin in subsubrange 2a
4502          index_2a = ib - start_subrange_2b + start_subrange_2a
4503!
4504!--       Particles lost to larger particles in subranges 2b
4505          DO  ll = ib + 1, end_subrange_2b
4506             zminusterm = zminusterm + zcc(ib,ll) * paero(ll)%numc
4507          ENDDO
4508!
4509!--       Particles lost to larger and equal particles in 2a
4510          DO  ll = index_2a, end_subrange_2a
4511             zminusterm = zminusterm + zcc(ib,ll) * paero(ll)%numc
4512          ENDDO
4513!
4514!--       Particle volume gained from smaller particles in subranges 1 & 2a
4515          DO  ll = start_subrange_1a, index_2a - 1
4516             zplusterm(1:8) = zplusterm(1:8) + zcc(ll,ib) * paero(ll)%volc(1:8)
4517          ENDDO
4518!
4519!--       Particle volume gained from smaller particles in 2b
4520          DO  ll = start_subrange_2b, ib - 1
4521             zplusterm(1:8) = zplusterm(1:8) + zcc(ll,ib) * paero(ll)%volc(1:8)
4522          ENDDO
4523!
4524!--       Volume and number concentrations after coagulation update [fxm]
4525          paero(ib)%volc(1:8) = ( paero(ib)%volc(1:8) + ptstep * zplusterm(1:8) * paero(ib)%numc ) &
4526                                / ( 1.0_wp + ptstep * zminusterm )
4527          paero(ib)%numc = paero(ib)%numc / ( 1.0_wp + ptstep * zminusterm + 0.5_wp * ptstep *     &
4528                           zcc(ib,ib) * paero(ib)%numc )
4529       ENDDO
4530    ENDIF
4531
4532 END SUBROUTINE coagulation
4533
4534!------------------------------------------------------------------------------!
4535! Description:
4536! ------------
4537!> Calculation of coagulation coefficients. Extended version of the function
4538!> originally found in mo_salsa_init.
4539!
4540!> J. Tonttila, FMI, 05/2014
4541!------------------------------------------------------------------------------!
4542 REAL(wp) FUNCTION coagc( diam1, diam2, mass1, mass2, temp, pres )
4543
4544    IMPLICIT NONE
4545
4546    REAL(wp) ::  fmdist  !< distance of flux matching (m)
4547    REAL(wp) ::  knud_p  !< particle Knudsen number
4548    REAL(wp) ::  mdiam   !< mean diameter of colliding particles (m)
4549    REAL(wp) ::  mfp     !< mean free path of air molecules (m)
4550    REAL(wp) ::  visc    !< viscosity of air (kg/(m s))
4551
4552    REAL(wp), INTENT(in) ::  diam1  !< diameter of colliding particle 1 (m)
4553    REAL(wp), INTENT(in) ::  diam2  !< diameter of colliding particle 2 (m)
4554    REAL(wp), INTENT(in) ::  mass1  !< mass of colliding particle 1 (kg)
4555    REAL(wp), INTENT(in) ::  mass2  !< mass of colliding particle 2 (kg)
4556    REAL(wp), INTENT(in) ::  pres   !< ambient pressure (Pa?) [fxm]
4557    REAL(wp), INTENT(in) ::  temp   !< ambient temperature (K)
4558
4559    REAL(wp), DIMENSION (2) ::  beta    !< Cunningham correction factor
4560    REAL(wp), DIMENSION (2) ::  dfpart  !< particle diffusion coefficient (m2/s)
4561    REAL(wp), DIMENSION (2) ::  diam    !< diameters of particles (m)
4562    REAL(wp), DIMENSION (2) ::  flux    !< flux in continuum and free molec. regime (m/s)
4563    REAL(wp), DIMENSION (2) ::  knud    !< particle Knudsen number
4564    REAL(wp), DIMENSION (2) ::  mpart   !< masses of particles (kg)
4565    REAL(wp), DIMENSION (2) ::  mtvel   !< particle mean thermal velocity (m/s)
4566    REAL(wp), DIMENSION (2) ::  omega   !< particle mean free path
4567    REAL(wp), DIMENSION (2) ::  tva     !< temporary variable (m)
4568!
4569!-- Initialisation
4570    coagc   = 0.0_wp
4571!
4572!-- 1) Initializing particle and ambient air variables
4573    diam  = (/ diam1, diam2 /) !< particle diameters (m)
4574    mpart = (/ mass1, mass2 /) !< particle masses (kg)
4575!
4576!-- Viscosity of air (kg/(m s))
4577    visc = ( 7.44523E-3_wp * temp ** 1.5_wp ) / ( 5093.0_wp * ( temp + 110.4_wp ) )
4578!
4579!-- Mean free path of air (m)
4580    mfp = ( 1.656E-10_wp * temp + 1.828E-8_wp ) * ( p_0 + 1325.0_wp ) / pres
4581!
4582!-- 2) Slip correction factor for small particles
4583    knud = 2.0_wp * EXP( LOG(mfp) - LOG(diam) )! Knudsen number for air (15.23)
4584!
4585!-- Cunningham correction factor (Allen and Raabe, Aerosol Sci. Tech. 4, 269)
4586    beta = 1.0_wp + knud * ( 1.142_wp + 0.558_wp * EXP( -0.999_wp / knud ) )
4587!
4588!-- 3) Particle properties
4589!-- Diffusion coefficient (m2/s) (Jacobson (2005) eq. 15.29)
4590    dfpart = beta * abo * temp / ( 3.0_wp * pi * visc * diam )
4591!
4592!-- Mean thermal velocity (m/s) (Jacobson (2005) eq. 15.32)
4593    mtvel = SQRT( ( 8.0_wp * abo * temp ) / ( pi * mpart ) )
4594!
4595!-- Particle mean free path (m) (Jacobson (2005) eq. 15.34 )
4596    omega = 8.0_wp * dfpart / ( pi * mtvel )
4597!
4598!-- Mean diameter (m)
4599    mdiam = 0.5_wp * ( diam(1) + diam(2) )
4600!
4601!-- 4) Calculation of fluxes (Brownian collision kernels) and flux matching
4602!-- following Jacobson (2005):
4603!
4604!-- Flux in continuum regime (m3/s) (eq. 15.28)
4605    flux(1) = 4.0_wp * pi * mdiam * ( dfpart(1) + dfpart(2) )
4606!
4607!-- Flux in free molec. regime (m3/s) (eq. 15.31)
4608    flux(2) = pi * SQRT( ( mtvel(1)**2 ) + ( mtvel(2)**2 ) ) * ( mdiam**2 )
4609!
4610!-- temporary variables (m) to calculate flux matching distance (m)
4611    tva(1) = ( ( mdiam + omega(1) )**3 - ( mdiam**2 + omega(1)**2 ) * SQRT( ( mdiam**2 +           &
4612               omega(1)**2 ) ) ) / ( 3.0_wp * mdiam * omega(1) ) - mdiam
4613    tva(2) = ( ( mdiam + omega(2) )**3 - ( mdiam**2 + omega(2)**2 ) * SQRT( ( mdiam**2 +           &
4614               omega(2)**2 ) ) ) / ( 3.0_wp * mdiam * omega(2) ) - mdiam
4615!
4616!-- Flux matching distance (m): the mean distance from the centre of a sphere reached by particles
4617!-- that leave sphere's surface and travel a distance of particle mean free path (eq. 15.34)
4618    fmdist = SQRT( tva(1)**2 + tva(2)**2 )
4619!
4620!-- 5) Coagulation coefficient = coalescence efficiency * collision kernel (m3/s) (eq. 15.33).
4621!--    Here assumed coalescence efficiency 1!!
4622    coagc = flux(1) / ( mdiam / ( mdiam + fmdist) + flux(1) / flux(2) )
4623!
4624!-- Corrected collision kernel (Karl et al., 2016 (ACP)): Include van der Waals and viscous forces
4625    IF ( van_der_waals_coagc )  THEN
4626       knud_p = SQRT( omega(1)**2 + omega(2)**2 ) / mdiam
4627       IF ( knud_p >= 0.1_wp  .AND.  knud_p <= 10.0_wp )  THEN
4628          coagc = coagc * ( 2.0_wp + 0.4_wp * LOG( knud_p ) )
4629       ELSE
4630          coagc = coagc * 3.0_wp
4631       ENDIF
4632    ENDIF
4633
4634 END FUNCTION coagc
4635
4636!------------------------------------------------------------------------------!
4637! Description:
4638! ------------
4639!> Calculates the change in particle volume and gas phase
4640!> concentrations due to nucleation, condensation and dissolutional growth.
4641!
4642!> Sulphuric acid and organic vapour: only condensation and no evaporation.
4643!
4644!> New gas and aerosol phase concentrations calculated according to Jacobson
4645!> (1997): Numerical techniques to solve condensational and dissolutional growth
4646!> equations when growth is coupled to reversible reactions, Aerosol Sci. Tech.,
4647!> 27, pp 491-498.
4648!
4649!> Following parameterization has been used:
4650!> Molecular diffusion coefficient of condensing vapour (m2/s)
4651!> (Reid et al. (1987): Properties of gases and liquids, McGraw-Hill, New York.)
4652!> D = {1.d-7*sqrt(1/M_air + 1/M_gas)*T^1.75} / &
4653!      {p_atm/p_stand * (d_air^(1/3) + d_gas^(1/3))^2 }
4654!> M_air = 28.965 : molar mass of air (g/mol)
4655!> d_air = 19.70  : diffusion volume of air
4656!> M_h2so4 = 98.08 : molar mass of h2so4 (g/mol)
4657!> d_h2so4 = 51.96  : diffusion volume of h2so4
4658!
4659!> Called from main aerosol model
4660!> For equations, see Jacobson, Fundamentals of Atmospheric Modeling, 2nd Edition (2005)
4661!
4662!> Coded by:
4663!> Hannele Korhonen (FMI) 2005
4664!> Harri Kokkola (FMI) 2006
4665!> Juha Tonttila (FMI) 2014
4666!> Rewritten to PALM by Mona Kurppa (UHel) 2017
4667!------------------------------------------------------------------------------!
4668 SUBROUTINE condensation( paero, pc_sa, pc_ocnv, pcocsv, pchno3, pc_nh3, pcw, pcs, ptemp, ppres,   &
4669                          ptstep, prtcl )
4670
4671    IMPLICIT NONE
4672
4673    INTEGER(iwp) ::  ss      !< start index
4674    INTEGER(iwp) ::  ee      !< end index
4675
4676    REAL(wp) ::  zcs_ocnv    !< condensation sink of nonvolatile organics (1/s)
4677    REAL(wp) ::  zcs_ocsv    !< condensation sink of semivolatile organics (1/s)
4678    REAL(wp) ::  zcs_su      !< condensation sink of sulfate (1/s)
4679    REAL(wp) ::  zcs_tot     !< total condensation sink (1/s) (gases)
4680    REAL(wp) ::  zcvap_new1  !< vapour concentration after time step (#/m3): sulphuric acid
4681    REAL(wp) ::  zcvap_new2  !< nonvolatile organics
4682    REAL(wp) ::  zcvap_new3  !< semivolatile organics
4683    REAL(wp) ::  zdfvap      !< air diffusion coefficient (m2/s)
4684    REAL(wp) ::  zdvap1      !< change in vapour concentration (#/m3): sulphuric acid
4685    REAL(wp) ::  zdvap2      !< nonvolatile organics
4686    REAL(wp) ::  zdvap3      !< semivolatile organics
4687    REAL(wp) ::  zmfp        !< mean free path of condensing vapour (m)
4688    REAL(wp) ::  zrh         !< Relative humidity [0-1]
4689    REAL(wp) ::  zvisc       !< viscosity of air (kg/(m s))
4690    REAL(wp) ::  zn_vs_c     !< ratio of nucleation of all mass transfer in the smallest bin
4691    REAL(wp) ::  zxocnv      !< ratio of organic vapour in 3nm particles
4692    REAL(wp) ::  zxsa        !< Ratio in 3nm particles: sulphuric acid
4693
4694    REAL(wp), INTENT(in) ::  ppres   !< ambient pressure (Pa)
4695    REAL(wp), INTENT(in) ::  pcs     !< Water vapour saturation concentration (kg/m3)
4696    REAL(wp), INTENT(in) ::  ptemp   !< ambient temperature (K)
4697    REAL(wp), INTENT(in) ::  ptstep  !< timestep (s)
4698
4699    REAL(wp), INTENT(inout) ::  pchno3   !< Gas concentrations (#/m3): nitric acid HNO3
4700    REAL(wp), INTENT(inout) ::  pc_nh3   !< ammonia NH3
4701    REAL(wp), INTENT(inout) ::  pc_ocnv  !< non-volatile organics
4702    REAL(wp), INTENT(inout) ::  pcocsv   !< semi-volatile organics
4703    REAL(wp), INTENT(inout) ::  pc_sa    !< sulphuric acid H2SO4
4704    REAL(wp), INTENT(inout) ::  pcw      !< Water vapor concentration (kg/m3)
4705
4706    REAL(wp), DIMENSION(nbins_aerosol)       ::  zbeta          !< transitional correction factor
4707    REAL(wp), DIMENSION(nbins_aerosol)       ::  zcolrate       !< collision rate (1/s)
4708    REAL(wp), DIMENSION(nbins_aerosol)       ::  zcolrate_ocnv  !< collision rate of OCNV (1/s)
4709    REAL(wp), DIMENSION(start_subrange_1a+1) ::  zdfpart        !< particle diffusion coef. (m2/s)
4710    REAL(wp), DIMENSION(nbins_aerosol)       ::  zdvoloc        !< change of organics volume
4711    REAL(wp), DIMENSION(nbins_aerosol)       ::  zdvolsa        !< change of sulphate volume
4712    REAL(wp), DIMENSION(2)                   ::  zj3n3          !< Formation massrate of molecules
4713                                                                !< in nucleation, (molec/m3s),
4714                                                                !< 1: H2SO4 and 2: organic vapor
4715    REAL(wp), DIMENSION(nbins_aerosol)       ::  zknud          !< particle Knudsen number
4716
4717    TYPE(component_index), INTENT(in) :: prtcl  !< Keeps track which substances are used
4718
4719    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< Aerosol properties
4720
4721    zj3n3  = 0.0_wp
4722    zrh    = pcw / pcs
4723    zxocnv = 0.0_wp
4724    zxsa   = 0.0_wp
4725!
4726!-- Nucleation
4727    IF ( nsnucl > 0 )  THEN
4728       CALL nucleation( paero, ptemp, zrh, ppres, pc_sa, pc_ocnv, pc_nh3, ptstep, zj3n3, zxsa,     &
4729                        zxocnv )
4730    ENDIF
4731!
4732!-- Condensation on pre-existing particles
4733    IF ( lscndgas )  THEN
4734!
4735!--    Initialise:
4736       zdvolsa = 0.0_wp
4737       zdvoloc = 0.0_wp
4738       zcolrate = 0.0_wp
4739!
4740!--    1) Properties of air and condensing gases:
4741!--    Viscosity of air (kg/(m s)) (Eq. 4.54 in Jabonson (2005))
4742       zvisc = ( 7.44523E-3_wp * ptemp ** 1.5_wp ) / ( 5093.0_wp * ( ptemp + 110.4_wp ) )
4743!
4744!--    Diffusion coefficient of air (m2/s)
4745       zdfvap = 5.1111E-10_wp * ptemp ** 1.75_wp * ( p_0 + 1325.0_wp ) / ppres
4746!
4747!--    Mean free path (m): same for H2SO4 and organic compounds
4748       zmfp = 3.0_wp * zdfvap * SQRT( pi * amh2so4 / ( 8.0_wp * argas * ptemp ) )
4749!
4750!--    2) Transition regime correction factor zbeta for particles (Fuchs and Sutugin (1971)):
4751!--       Size of condensing molecule considered only for nucleation mode (3 - 20 nm).
4752!
4753!--    Particle Knudsen number: condensation of gases on aerosols
4754       ss = start_subrange_1a
4755       ee = start_subrange_1a+1
4756       zknud(ss:ee) = 2.0_wp * zmfp / ( paero(ss:ee)%dwet + d_sa )
4757       ss = start_subrange_1a+2
4758       ee = end_subrange_2b
4759       zknud(ss:ee) = 2.0_wp * zmfp / paero(ss:ee)%dwet
4760!
4761!--    Transitional correction factor: aerosol + gas (the semi-empirical Fuchs- Sutugin
4762!--    interpolation function (Fuchs and Sutugin, 1971))
4763       zbeta = ( zknud + 1.0_wp ) / ( 0.377_wp * zknud + 1.0_wp + 4.0_wp / ( 3.0_wp * massacc ) *  &
4764               ( zknud + zknud ** 2 ) )
4765!
4766!--    3) Collision rate of molecules to particles
4767!--       Particle diffusion coefficient considered only for nucleation mode (3 - 20 nm)
4768!
4769!--    Particle diffusion coefficient (m2/s) (e.g. Eq. 15.29 in Jacobson (2005))
4770       zdfpart = abo * ptemp * zbeta(start_subrange_1a:start_subrange_1a+1) / ( 3.0_wp * pi * zvisc&
4771                 * paero(start_subrange_1a:start_subrange_1a+1)%dwet)
4772!
4773!--    Collision rate (mass-transfer coefficient): gases on aerosols (1/s) (Eq. 16.64 in
4774!--    Jacobson (2005))
4775       ss = start_subrange_1a
4776       ee = start_subrange_1a+1
4777       zcolrate(ss:ee) = MERGE( 2.0_wp * pi * ( paero(ss:ee)%dwet + d_sa ) * ( zdfvap + zdfpart ) *&
4778                               zbeta(ss:ee) * paero(ss:ee)%numc, 0.0_wp, paero(ss:ee)%numc > nclim )
4779       ss = start_subrange_1a+2
4780       ee = end_subrange_2b
4781       zcolrate(ss:ee) = MERGE( 2.0_wp * pi * paero(ss:ee)%dwet * zdfvap * zbeta(ss:ee) *          &
4782                                paero(ss:ee)%numc, 0.0_wp, paero(ss:ee)%numc > nclim )
4783!
4784!-- 4) Condensation sink (1/s)
4785       zcs_tot = SUM( zcolrate )   ! total sink
4786!
4787!--    5) Changes in gas-phase concentrations and particle volume
4788!
4789!--    5.1) Organic vapours
4790!
4791!--    5.1.1) Non-volatile organic compound: condenses onto all bins
4792       IF ( pc_ocnv > 1.0E+10_wp  .AND.  zcs_tot > 1.0E-30_wp  .AND. index_oc > 0 )  &
4793       THEN
4794!--       Ratio of nucleation vs. condensation rates in the smallest bin
4795          zn_vs_c = 0.0_wp
4796          IF ( zj3n3(2) > 1.0_wp )  THEN
4797             zn_vs_c = ( zj3n3(2) ) / ( zj3n3(2) + pc_ocnv * zcolrate(start_subrange_1a) )
4798          ENDIF
4799!
4800!--       Collision rate in the smallest bin, including nucleation and condensation (see
4801!--       Jacobson (2005), eq. (16.73) )
4802          zcolrate_ocnv = zcolrate
4803          zcolrate_ocnv(start_subrange_1a) = zcolrate_ocnv(start_subrange_1a) + zj3n3(2) / pc_ocnv
4804!
4805!--       Total sink for organic vapor
4806          zcs_ocnv = zcs_tot + zj3n3(2) / pc_ocnv
4807!
4808!--       New gas phase concentration (#/m3)
4809          zcvap_new2 = pc_ocnv / ( 1.0_wp + ptstep * zcs_ocnv )
4810!
4811!--       Change in gas concentration (#/m3)
4812          zdvap2 = pc_ocnv - zcvap_new2
4813!
4814!--       Updated vapour concentration (#/m3)
4815          pc_ocnv = zcvap_new2
4816!
4817!--       Volume change of particles (m3(OC)/m3(air))
4818          zdvoloc = zcolrate_ocnv(start_subrange_1a:end_subrange_2b) / zcs_ocnv * amvoc * zdvap2
4819!
4820!--       Change of volume due to condensation in 1a-2b
4821          paero(start_subrange_1a:end_subrange_2b)%volc(2) =                                       &
4822                                          paero(start_subrange_1a:end_subrange_2b)%volc(2) + zdvoloc
4823!
4824!--       Change of number concentration in the smallest bin caused by nucleation (Jacobson (2005),
4825!--       eq. (16.75)). If zxocnv = 0, then the chosen nucleation mechanism doesn't take into
4826!--       account the non-volatile organic vapors and thus the paero doesn't have to be updated.
4827          IF ( zxocnv > 0.0_wp )  THEN
4828             paero(start_subrange_1a)%numc = paero(start_subrange_1a)%numc + zn_vs_c *             &
4829                                             zdvoloc(start_subrange_1a) / amvoc / ( n3 * zxocnv )
4830          ENDIF
4831       ENDIF
4832!
4833!--    5.1.2) Semivolatile organic compound: all bins except subrange 1
4834       zcs_ocsv = SUM( zcolrate(start_subrange_2a:end_subrange_2b) ) !< sink for semi-volatile org.
4835       IF ( pcocsv > 1.0E+10_wp  .AND.  zcs_ocsv > 1.0E-30  .AND. is_used( prtcl,'OC') )  THEN
4836!
4837!--       New gas phase concentration (#/m3)
4838          zcvap_new3 = pcocsv / ( 1.0_wp + ptstep * zcs_ocsv )
4839!
4840!--       Change in gas concentration (#/m3)
4841          zdvap3 = pcocsv - zcvap_new3 
4842!
4843!--       Updated gas concentration (#/m3)
4844          pcocsv = zcvap_new3
4845!
4846!--       Volume change of particles (m3(OC)/m3(air))
4847          ss = start_subrange_2a
4848          ee = end_subrange_2b
4849          zdvoloc(ss:ee) = zdvoloc(ss:ee) + zcolrate(ss:ee) / zcs_ocsv * amvoc * zdvap3
4850!
4851!--       Change of volume due to condensation in 1a-2b
4852          paero(start_subrange_1a:end_subrange_2b)%volc(2) =                                       &
4853                                          paero(start_subrange_1a:end_subrange_2b)%volc(2) + zdvoloc
4854       ENDIF
4855!
4856!--    5.2) Sulphate: condensed on all bins
4857       IF ( pc_sa > 1.0E+10_wp  .AND.  zcs_tot > 1.0E-30_wp  .AND.  index_so4 > 0 )  THEN
4858!
4859!--    Ratio of mass transfer between nucleation and condensation
4860          zn_vs_c = 0.0_wp
4861          IF ( zj3n3(1) > 1.0_wp )  THEN
4862             zn_vs_c = ( zj3n3(1) ) / ( zj3n3(1) + pc_sa * zcolrate(start_subrange_1a) )
4863          ENDIF
4864!
4865!--       Collision rate in the smallest bin, including nucleation and condensation (see
4866!--       Jacobson (2005), eq. (16.73))
4867          zcolrate(start_subrange_1a) = zcolrate(start_subrange_1a) + zj3n3(1) / pc_sa
4868!
4869!--       Total sink for sulfate (1/s)
4870          zcs_su = zcs_tot + zj3n3(1) / pc_sa
4871!
4872!--       Sulphuric acid:
4873!--       New gas phase concentration (#/m3)
4874          zcvap_new1 = pc_sa / ( 1.0_wp + ptstep * zcs_su )
4875!
4876!--       Change in gas concentration (#/m3)
4877          zdvap1 = pc_sa - zcvap_new1
4878!
4879!--       Updating vapour concentration (#/m3)
4880          pc_sa = zcvap_new1
4881!
4882!--       Volume change of particles (m3(SO4)/m3(air)) by condensation
4883          zdvolsa = zcolrate(start_subrange_1a:end_subrange_2b) / zcs_su * amvh2so4 * zdvap1
4884!
4885!--       Change of volume concentration of sulphate in aerosol [fxm]
4886          paero(start_subrange_1a:end_subrange_2b)%volc(1) =                                       &
4887                                          paero(start_subrange_1a:end_subrange_2b)%volc(1) + zdvolsa
4888!
4889!--       Change of number concentration in the smallest bin caused by nucleation
4890!--       (Jacobson (2005), equation (16.75))
4891          IF ( zxsa > 0.0_wp )  THEN
4892             paero(start_subrange_1a)%numc = paero(start_subrange_1a)%numc + zn_vs_c *             &
4893                                             zdvolsa(start_subrange_1a) / amvh2so4 / ( n3 * zxsa)
4894          ENDIF
4895       ENDIF
4896!
4897!--    Partitioning of H2O, HNO3, and NH3: Dissolutional growth
4898       IF ( lspartition  .AND.  ( pchno3 > 1.0E+10_wp  .OR.  pc_nh3 > 1.0E+10_wp ) )  THEN
4899          CALL gpparthno3( ppres, ptemp, paero, pchno3, pc_nh3, pcw, pcs, zbeta, ptstep )
4900       ENDIF
4901    ENDIF
4902!
4903!-- Condensation of water vapour
4904    IF ( lscndh2oae )  THEN
4905       CALL gpparth2o( paero, ptemp, ppres, pcs, pcw, ptstep )
4906    ENDIF
4907
4908 END SUBROUTINE condensation
4909
4910!------------------------------------------------------------------------------!
4911! Description:
4912! ------------
4913!> Calculates the particle number and volume increase, and gas-phase
4914!> concentration decrease due to nucleation subsequent growth to detectable size
4915!> of 3 nm.
4916!
4917!> Method:
4918!> When the formed clusters grow by condensation (possibly also by self-
4919!> coagulation), their number is reduced due to scavenging to pre-existing
4920!> particles. Thus, the apparent nucleation rate at 3 nm is significantly lower
4921!> than the real nucleation rate (at ~1 nm).
4922!
4923!> Calculation of the formation rate of detectable particles at 3 nm (i.e. J3):
4924!> nj3 = 1: Kerminen, V.-M. and Kulmala, M. (2002), J. Aerosol Sci.,33, 609-622.
4925!> nj3 = 2: Lehtinen et al. (2007), J. Aerosol Sci., 38(9), 988-994.
4926!> nj3 = 3: Anttila et al. (2010), J. Aerosol Sci., 41(7), 621-636.
4927!
4928!> c = aerosol of critical radius (1 nm)
4929!> x = aerosol with radius 3 nm
4930!> 2 = wet or mean droplet
4931!
4932!> Called from subroutine condensation (in module salsa_dynamics_mod.f90)
4933!
4934!> Calls one of the following subroutines:
4935!>  - binnucl
4936!>  - ternucl
4937!>  - kinnucl
4938!>  - actnucl
4939!
4940!> fxm: currently only sulphuric acid grows particles from 1 to 3 nm
4941!>  (if asked from Markku, this is terribly wrong!!!)
4942!
4943!> Coded by:
4944!> Hannele Korhonen (FMI) 2005
4945!> Harri Kokkola (FMI) 2006
4946!> Matti Niskanen(FMI) 2012
4947!> Anton Laakso  (FMI) 2013
4948!------------------------------------------------------------------------------!
4949
4950 SUBROUTINE nucleation( paero, ptemp, prh, ppres, pc_sa, pc_ocnv, pc_nh3, ptstep, pj3n3, pxsa,     &
4951                        pxocnv )
4952
4953    IMPLICIT NONE
4954
4955    INTEGER(iwp) ::  iteration
4956
4957    REAL(wp) ::  zc_h2so4     !< H2SO4 conc. (#/cm3) !UNITS!
4958    REAL(wp) ::  zc_org       !< organic vapour conc. (#/cm3)
4959    REAL(wp) ::  zcc_c        !< Cunningham correct factor for c = critical (1nm)
4960    REAL(wp) ::  zcc_x        !< Cunningham correct factor for x = 3nm
4961    REAL(wp) ::  zcoags_c     !< coagulation sink (1/s) for c = critical (1nm)
4962    REAL(wp) ::  zcoags_x     !< coagulation sink (1/s) for x = 3nm
4963    REAL(wp) ::  zcoagstot    !< total particle losses due to coagulation, including condensation
4964                              !< and self-coagulation
4965    REAL(wp) ::  zcocnv_local !< organic vapour conc. (#/m3)
4966    REAL(wp) ::  zcsink       !< condensational sink (#/m2)
4967    REAL(wp) ::  zcsa_local   !< H2SO4 conc. (#/m3)
4968    REAL(wp) ::  zcv_c        !< mean relative thermal velocity (m/s) for c = critical (1nm)
4969    REAL(wp) ::  zcv_x        !< mean relative thermal velocity (m/s) for x = 3nm
4970    REAL(wp) ::  zdcrit       !< diameter of critical cluster (m)
4971    REAL(wp) ::  zdelta_vap   !< change of H2SO4 and organic vapour concentration (#/m3)
4972    REAL(wp) ::  zdfvap       !< air diffusion coefficient (m2/s)
4973    REAL(wp) ::  zdmean       !< mean diameter of existing particles (m)
4974    REAL(wp) ::  zeta         !< constant: proportional to ratio of CS/GR (m)
4975                              !< (condensation sink / growth rate)
4976    REAL(wp) ::  zgamma       !< proportionality factor ((nm2*m2)/h)
4977    REAL(wp) ::  z_gr_clust   !< growth rate of formed clusters (nm/h)
4978    REAL(wp) ::  z_gr_tot     !< total growth rate
4979    REAL(wp) ::  zj3          !< number conc. of formed 3nm particles (#/m3)
4980    REAL(wp) ::  zjnuc        !< nucleation rate at ~1nm (#/m3s)
4981    REAL(wp) ::  z_k_eff      !< effective cogulation coefficient for freshly nucleated particles
4982    REAL(wp) ::  zknud_c      !< Knudsen number for c = critical (1nm)
4983    REAL(wp) ::  zknud_x      !< Knudsen number for x = 3nm
4984    REAL(wp) ::  zkocnv       !< lever: zkocnv=1 --> organic compounds involved in nucleation
4985    REAL(wp) ::  zksa         !< lever: zksa=1 --> H2SO4 involved in nucleation
4986    REAL(wp) ::  zlambda      !< parameter for adjusting the growth rate due to self-coagulation
4987    REAL(wp) ::  zm_c         !< particle mass (kg) for c = critical (1nm)
4988    REAL(wp) ::  zm_para      !< Parameter m for calculating the coagulation sink (Eq. 5&6 in
4989                              !< Lehtinen et al. 2007)
4990    REAL(wp) ::  zm_x         !< particle mass (kg) for x = 3nm
4991    REAL(wp) ::  zmfp         !< mean free path of condesing vapour(m)
4992    REAL(wp) ::  zmixnh3      !< ammonia mixing ratio (ppt)
4993    REAL(wp) ::  zmyy         !< gas dynamic viscosity (N*s/m2)
4994    REAL(wp) ::  z_n_nuc      !< number of clusters/particles at the size range d1-dx (#/m3)
4995    REAL(wp) ::  znoc         !< number of organic molecules in critical cluster
4996    REAL(wp) ::  znsa         !< number of H2SO4 molecules in critical cluster
4997
4998    REAL(wp), INTENT(in) ::  pc_nh3   !< ammonia concentration (#/m3)
4999    REAL(wp), INTENT(in) ::  pc_ocnv  !< conc. of non-volatile OC (#/m3)
5000    REAL(wp), INTENT(in) ::  pc_sa    !< sulphuric acid conc. (#/m3)
5001    REAL(wp), INTENT(in) ::  ppres    !< ambient air pressure (Pa)
5002    REAL(wp), INTENT(in) ::  prh      !< ambient rel. humidity [0-1]
5003    REAL(wp), INTENT(in) ::  ptemp    !< ambient temperature (K)
5004    REAL(wp), INTENT(in) ::  ptstep   !< time step (s) of SALSA
5005
5006    REAL(wp), INTENT(inout) ::  pj3n3(2) !< formation mass rate of molecules (molec/m3s) for
5007                                         !< 1: H2SO4 and 2: organic vapour
5008
5009    REAL(wp), INTENT(out) ::  pxocnv  !< ratio of non-volatile organic vapours in 3 nm particles
5010    REAL(wp), INTENT(out) ::  pxsa    !< ratio of H2SO4 in 3 nm aerosol particles
5011
5012    REAL(wp), DIMENSION(nbins_aerosol) ::  zbeta       !< transitional correction factor
5013    REAL(wp), DIMENSION(nbins_aerosol) ::  zcc_2       !< Cunningham correct factor:2
5014    REAL(wp), DIMENSION(nbins_aerosol) ::  zcv_2       !< mean relative thermal velocity (m/s): 2
5015    REAL(wp), DIMENSION(nbins_aerosol) ::  zcv_c2      !< average velocity after coagulation: c & 2
5016    REAL(wp), DIMENSION(nbins_aerosol) ::  zcv_x2      !< average velocity after coagulation: x & 2
5017    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_2       !< particle diffusion coefficient (m2/s): 2
5018    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_c       !< particle diffusion coefficient (m2/s): c
5019    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_c2      !< sum of diffusion coef. for c and 2
5020    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_x       !< particle diffusion coefficient (m2/s): x
5021    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_x2      !< sum of diffusion coef. for: x & 2
5022    REAL(wp), DIMENSION(nbins_aerosol) ::  zgamma_f_2  !< zgamma_f for calculating zomega
5023    REAL(wp), DIMENSION(nbins_aerosol) ::  zgamma_f_c  !< zgamma_f for calculating zomega
5024    REAL(wp), DIMENSION(nbins_aerosol) ::  zgamma_f_x  !< zgamma_f for calculating zomega
5025    REAL(wp), DIMENSION(nbins_aerosol) ::  z_k_c2      !< coagulation coef. in the continuum
5026                                                       !< regime: c & 2
5027    REAL(wp), DIMENSION(nbins_aerosol) ::  z_k_x2      !< coagulation coef. in the continuum
5028                                                       !< regime: x & 2
5029    REAL(wp), DIMENSION(nbins_aerosol) ::  zknud       !< particle Knudsen number
5030    REAL(wp), DIMENSION(nbins_aerosol) ::  zknud_2     !< particle Knudsen number: 2
5031    REAL(wp), DIMENSION(nbins_aerosol) ::  zm_2        !< particle mass (kg): 2
5032    REAL(wp), DIMENSION(nbins_aerosol) ::  zomega_2c   !< zomega (m) for calculating zsigma: c & 2
5033    REAL(wp), DIMENSION(nbins_aerosol) ::  zomega_2x   !< zomega (m) for calculating zsigma: x & 2
5034    REAL(wp), DIMENSION(nbins_aerosol) ::  zomega_c    !< zomega (m) for calculating zsigma: c
5035    REAL(wp), DIMENSION(nbins_aerosol) ::  zomega_x    !< zomega (m) for calculating zsigma: x
5036    REAL(wp), DIMENSION(nbins_aerosol) ::  z_r_c2      !< sum of the radii: c & 2
5037    REAL(wp), DIMENSION(nbins_aerosol) ::  z_r_x2      !< sum of the radii: x & 2
5038    REAL(wp), DIMENSION(nbins_aerosol) ::  zsigma_c2   !<
5039    REAL(wp), DIMENSION(nbins_aerosol) ::  zsigma_x2   !<
5040
5041    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< aerosol properties
5042!
5043!-- 1) Nucleation rate (zjnuc) and diameter of critical cluster (zdcrit)
5044    zjnuc  = 0.0_wp
5045    znsa   = 0.0_wp
5046    znoc   = 0.0_wp
5047    zdcrit = 0.0_wp
5048    zksa   = 0.0_wp
5049    zkocnv = 0.0_wp
5050
5051    zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
5052    zc_org   = pc_ocnv * 1.0E-6_wp   ! conc. of non-volatile OC to #/cm3
5053    zmixnh3  = pc_nh3 * ptemp * argas / ( ppres * avo )
5054
5055    SELECT CASE ( nsnucl )
5056!
5057!--    Binary H2SO4-H2O nucleation
5058       CASE(1)
5059
5060          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa, znoc, zdcrit,  zksa, zkocnv )
5061!
5062!--    Activation type nucleation (See Riipinen et al. (2007), Atmos. Chem. Phys., 7(8), 1899-1914)
5063       CASE(2)
5064!
5065!--       Nucleation rate (#/(m3 s))
5066          zc_h2so4  = MAX( zc_h2so4, 1.0E4_wp  )
5067          zc_h2so4  = MIN( zc_h2so4, 1.0E11_wp )
5068          zjnuc = act_coeff * pc_sa  ! (#/(m3 s))
5069!
5070!--       Organic compounds not involved when kinetic nucleation is assumed.
5071          zdcrit  = 7.9375E-10_wp   ! (m)
5072          zkocnv  = 0.0_wp
5073          zksa    = 1.0_wp
5074          znoc    = 0.0_wp
5075          znsa    = 2.0_wp
5076!
5077!--    Kinetically limited nucleation of (NH4)HSO4 clusters
5078!--    (See Sihto et al. (2006), Atmos. Chem. Phys., 6(12), 4079-4091.)
5079       CASE(3)
5080!
5081!--       Nucleation rate = coagcoeff*zpcsa**2 (#/(m3 s))
5082          zc_h2so4  = MAX( zc_h2so4, 1.0E4_wp  )
5083          zc_h2so4  = MIN( zc_h2so4, 1.0E11_wp )
5084          zjnuc = 5.0E-13_wp * zc_h2so4**2.0_wp * 1.0E+6_wp
5085!
5086!--       Organic compounds not involved when kinetic nucleation is assumed.
5087          zdcrit  = 7.9375E-10_wp   ! (m)
5088          zkocnv  = 0.0_wp
5089          zksa    = 1.0_wp
5090          znoc    = 0.0_wp
5091          znsa    = 2.0_wp
5092!
5093!--    Ternary H2SO4-H2O-NH3 nucleation
5094       CASE(4)
5095
5096          CALL ternucl( zc_h2so4, zmixnh3, ptemp, prh, zjnuc, znsa, znoc, zdcrit, zksa, zkocnv )
5097!
5098!--    Organic nucleation, J~[ORG] or J~[ORG]**2
5099!--    (See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.)
5100       CASE(5)
5101!
5102!--       Homomolecular nuleation rate
5103          zjnuc = 1.3E-7_wp * pc_ocnv   ! (1/s) (Paasonen et al. Table 4: median a_org)
5104!
5105!--       H2SO4 not involved when pure organic nucleation is assumed.
5106          zdcrit  = 1.5E-9  ! (m)
5107          zkocnv  = 1.0_wp
5108          zksa    = 0.0_wp
5109          znoc    = 1.0_wp
5110          znsa    = 0.0_wp
5111!
5112!--    Sum of H2SO4 and organic activation type nucleation, J~[H2SO4]+[ORG]
5113!--    (See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242)
5114       CASE(6)
5115!
5116!--       Nucleation rate  (#/m3/s)
5117          zjnuc = 6.1E-7_wp * pc_sa + 0.39E-7_wp * pc_ocnv   ! (Paasonen et al. Table 3.)
5118!
5119!--       Both organic compounds and H2SO4 are involved when sumnucleation is assumed.
5120          zdcrit  = 1.5E-9_wp   ! (m)
5121          zkocnv  = 1.0_wp
5122          zksa    = 1.0_wp
5123          znoc    = 1.0_wp
5124          znsa    = 1.0_wp
5125!
5126!--    Heteromolecular nucleation, J~[H2SO4]*[ORG]
5127!--    (See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.)
5128       CASE(7)
5129!
5130!--       Nucleation rate (#/m3/s)
5131          zjnuc = 4.1E-14_wp * pc_sa * pc_ocnv * 1.0E6_wp   ! (Paasonen et al. Table 4: median)
5132!
5133!--       Both organic compounds and H2SO4 are involved when heteromolecular nucleation is assumed
5134          zdcrit  = 1.5E-9_wp   ! (m)
5135          zkocnv  = 1.0_wp
5136          zksa    = 1.0_wp
5137          znoc    = 1.0_wp
5138          znsa    = 1.0_wp
5139!
5140!--    Homomolecular nucleation of H2SO4 and heteromolecular nucleation of H2SO4 and organic vapour,
5141!--    J~[H2SO4]**2 + [H2SO4]*[ORG] (EUCAARI project)
5142!--    (See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242)
5143       CASE(8)
5144!
5145!--       Nucleation rate (#/m3/s)
5146          zjnuc = ( 1.1E-14_wp * zc_h2so4**2 + 3.2E-14_wp * zc_h2so4 * zc_org ) * 1.0E+6_wp
5147!
5148!--       Both organic compounds and H2SO4 are involved when SAnucleation is assumed
5149          zdcrit  = 1.5E-9_wp   ! (m)
5150          zkocnv  = 1.0_wp
5151          zksa    = 1.0_wp
5152          znoc    = 1.0_wp
5153          znsa    = 3.0_wp
5154!
5155!--    Homomolecular nucleation of H2SO4 and organic vapour and heteromolecular nucleation of H2SO4
5156!--    and organic vapour, J~[H2SO4]**2 + [H2SO4]*[ORG]+[ORG]**2 (EUCAARI project)
5157       CASE(9)
5158!
5159!--       Nucleation rate (#/m3/s)
5160          zjnuc = ( 1.4E-14_wp * zc_h2so4**2 + 2.6E-14_wp * zc_h2so4 * zc_org + 0.037E-14_wp *     &
5161                    zc_org**2 ) * 1.0E+6_wp
5162!
5163!--       Both organic compounds and H2SO4 are involved when SAORGnucleation is assumed
5164          zdcrit  = 1.5E-9_wp   ! (m)
5165          zkocnv  = 1.0_wp
5166          zksa    = 1.0_wp
5167          znoc    = 3.0_wp
5168          znsa    = 3.0_wp
5169
5170    END SELECT
5171
5172    zcsa_local = pc_sa
5173    zcocnv_local = pc_ocnv
5174!
5175!-- 2) Change of particle and gas concentrations due to nucleation
5176!
5177!-- 2.1) Check that there is enough H2SO4 and organic vapour to produce the nucleation
5178    IF ( nsnucl <= 4 )  THEN 
5179!
5180!--    If the chosen nucleation scheme is 1-4, nucleation occurs only due to H2SO4. All of the total
5181!--    vapour concentration that is taking part to the nucleation is there for sulphuric acid
5182!--    (sa = H2SO4) and non-volatile organic vapour is zero.
5183       pxsa   = 1.0_wp   ! ratio of sulphuric acid in 3nm particles
5184       pxocnv = 0.0_wp   ! ratio of non-volatile origanic vapour
5185                                ! in 3nm particles
5186    ELSEIF ( nsnucl > 4 )  THEN
5187!
5188!--    If the chosen nucleation scheme is 5-9, nucleation occurs due to organic vapour or the
5189!--    combination of organic vapour and H2SO4. The number of needed molecules depends on the chosen
5190!--    nucleation type and it has an effect also on the minimum ratio of the molecules present.
5191       IF ( pc_sa * znsa + pc_ocnv * znoc < 1.E-14_wp )  THEN
5192          pxsa   = 0.0_wp
5193          pxocnv = 0.0_wp
5194       ELSE
5195          pxsa   = pc_sa * znsa / ( pc_sa * znsa + pc_ocnv * znoc ) 
5196          pxocnv = pc_ocnv * znoc / ( pc_sa * znsa + pc_ocnv * znoc )
5197       ENDIF
5198    ENDIF
5199!
5200!-- The change in total vapour concentration is the sum of the concentrations of the vapours taking
5201!-- part to the nucleation (depends on the chosen nucleation scheme)
5202    zdelta_vap = MIN( zjnuc * ( znoc + znsa ), ( pc_ocnv * zkocnv + pc_sa * zksa ) / ptstep )
5203!
5204!-- Nucleation rate J at ~1nm (#/m3s)
5205    zjnuc = zdelta_vap / ( znoc + znsa )
5206!
5207!-- H2SO4 concentration after nucleation (#/m3)
5208    zcsa_local = MAX( 1.0_wp, pc_sa - zdelta_vap * pxsa )
5209!
5210!-- Non-volative organic vapour concentration after nucleation (#/m3)
5211    zcocnv_local = MAX( 1.0_wp, pc_ocnv - zdelta_vap * pxocnv )
5212!
5213!-- 2.2) Formation rate of 3 nm particles (Kerminen & Kulmala, 2002)
5214!
5215!-- Growth rate by H2SO4 and organic vapour (nm/h, Eq. 21)
5216    z_gr_clust = 2.3623E-15_wp * SQRT( ptemp ) * ( zcsa_local + zcocnv_local )
5217!
5218!-- 2.2.2) Condensational sink of pre-existing particle population
5219!
5220!-- Diffusion coefficient (m2/s)
5221    zdfvap = 5.1111E-10_wp * ptemp**1.75_wp * ( p_0 + 1325.0_wp ) / ppres
5222!
5223!-- Mean free path of condensing vapour (m) (Jacobson (2005), Eq. 15.25 and 16.29)
5224    zmfp = 3.0_wp * zdfvap * SQRT( pi * amh2so4 / ( 8.0_wp * argas * ptemp ) )
5225!
5226!-- Knudsen number
5227    zknud = 2.0_wp * zmfp / ( paero(:)%dwet + d_sa )
5228!
5229!-- Transitional regime correction factor (zbeta) according to Fuchs and Sutugin (1971) (Eq. 4 in
5230!-- Kerminen and Kulmala, 2002)
5231    zbeta = ( zknud + 1.0_wp) / ( 0.377_wp * zknud + 1.0_wp + 4.0_wp / ( 3.0_wp * massacc ) *      &
5232            ( zknud + zknud**2 ) )
5233!
5234!-- Condensational sink (#/m2, Eq. 3)
5235    zcsink = SUM( paero(:)%dwet * zbeta * paero(:)%numc )
5236!
5237!-- 2.2.3) Parameterised formation rate of detectable 3 nm particles (i.e. J3)
5238    IF ( nj3 == 1 )  THEN   ! Kerminen and Kulmala (2002)
5239!
5240!--    Constants needed for the parameterisation: dapp = 3 nm and dens_nuc = 1830 kg/m3
5241       IF ( zcsink < 1.0E-30_wp )  THEN
5242          zeta = 0._dp
5243       ELSE
5244!
5245!--       Mean diameter of backgroud population (nm)
5246          zdmean = 1.0_wp / SUM( paero(:)%numc ) * SUM( paero(:)%numc * paero(:)%dwet ) * 1.0E+9_wp
5247!
5248!--       Proportionality factor (nm2*m2/h) (Eq. 22)
5249          zgamma = 0.23_wp * ( zdcrit * 1.0E+9_wp )**0.2_wp * ( zdmean / 150.0_wp )**0.048_wp *    &
5250                   ( ptemp / 293.0_wp )**( -0.75_wp ) * ( arhoh2so4 / 1000.0_wp )**( -0.33_wp )
5251!
5252!--       Factor eta (nm, Eq. 11)
5253          zeta = MIN( zgamma * zcsink / z_gr_clust, zdcrit * 1.0E11_wp )
5254       ENDIF
5255!
5256!--    Number conc. of clusters surviving to 3 nm in a time step (#/m3, Eq.14)
5257       zj3 = zjnuc * EXP( MIN( 0.0_wp, zeta / 3.0_wp - zeta / ( zdcrit * 1.0E9_wp ) ) )
5258
5259    ELSEIF ( nj3 > 1 )  THEN   ! Lehtinen et al. (2007) or Anttila et al. (2010)
5260!
5261!--    Defining the parameter m (zm_para) for calculating the coagulation sink onto background
5262!--    particles (Eq. 5&6 in Lehtinen et al. 2007). The growth is investigated between
5263!--    [d1,reglim(1)] = [zdcrit,3nm] and m = LOG( CoagS_dx / CoagX_zdcrit ) / LOG( reglim / zdcrit )
5264!--    (Lehtinen et al. 2007, Eq. 6).
5265!--    The steps for the coagulation sink for reglim = 3nm and zdcrit ~= 1nm are explained in
5266!--    Kulmala et al. (2001). The particles of diameter zdcrit ~1.14 nm  and reglim = 3nm are both
5267!--    in turn the "number 1" variables (Kulmala et al. 2001).
5268!--    c = critical (1nm), x = 3nm, 2 = wet or mean droplet
5269!
5270!--    Sum of the radii, R12 = R1 + R2 (m) of two particles 1 and 2
5271       z_r_c2 = zdcrit / 2.0_wp + paero(:)%dwet / 2.0_wp
5272       z_r_x2 = reglim(1) / 2.0_wp + paero(:)%dwet / 2.0_wp
5273!
5274!--    Particle mass (kg) (comes only from H2SO4)
5275       zm_c = 4.0_wp / 3.0_wp * pi * ( zdcrit / 2.0_wp )**3 * arhoh2so4
5276       zm_x = 4.0_wp / 3.0_wp * pi * ( reglim(1) / 2.0_wp )**3 * arhoh2so4
5277       zm_2 = 4.0_wp / 3.0_wp * pi * ( 0.5_wp * paero(:)%dwet )**3 * arhoh2so4
5278!
5279!--    Mean relative thermal velocity between the particles (m/s)
5280       zcv_c = SQRT( 8.0_wp * abo * ptemp / ( pi * zm_c ) )
5281       zcv_x = SQRT( 8.0_wp * abo * ptemp / ( pi * zm_x ) )
5282       zcv_2 = SQRT( 8.0_wp * abo * ptemp / ( pi * zm_2 ) )
5283!
5284!--    Average velocity after coagulation
5285       zcv_c2(:) = SQRT( zcv_c**2 + zcv_2**2 )
5286       zcv_x2(:) = SQRT( zcv_x**2 + zcv_2**2 )
5287!
5288!--    Knudsen number (zmfp = mean free path of condensing vapour)
5289       zknud_c = 2.0_wp * zmfp / zdcrit
5290       zknud_x = 2.0_wp * zmfp / reglim(1)
5291       zknud_2(:) = MAX( 0.0_wp, 2.0_wp * zmfp / paero(:)%dwet )
5292!
5293!--    Cunningham correction factors (Allen and Raabe, 1985)
5294       zcc_c    = 1.0_wp + zknud_c    * ( 1.142_wp + 0.558_wp * EXP( -0.999_wp / zknud_c ) )
5295       zcc_x    = 1.0_wp + zknud_x    * ( 1.142_wp + 0.558_wp * EXP( -0.999_wp / zknud_x ) )
5296       zcc_2(:) = 1.0_wp + zknud_2(:) * ( 1.142_wp + 0.558_wp * EXP( -0.999_wp / zknud_2(:) ) )
5297!
5298!--    Gas dynamic viscosity (N*s/m2). Here, viscocity(air @20C) = 1.81e-5_dp N/m2 *s (Hinds, p. 25)
5299       zmyy = 1.81E-5_wp * ( ptemp / 293.0_wp )**0.74_wp
5300!
5301!--    Particle diffusion coefficient (m2/s) (continuum regime)
5302       zdc_c(:) = abo * ptemp * zcc_c    / ( 3.0_wp * pi * zmyy * zdcrit )
5303       zdc_x(:) = abo * ptemp * zcc_x    / ( 3.0_wp * pi * zmyy * reglim(1) )
5304       zdc_2(:) = abo * ptemp * zcc_2(:) / ( 3.0_wp * pi * zmyy * paero(:)%dwet )
5305!
5306!--    D12 = D1+D2 (Seinfield and Pandis, 2nd ed. Eq. 13.38)
5307       zdc_c2 = zdc_c + zdc_2
5308       zdc_x2 = zdc_x + zdc_2
5309!
5310!--    zgamma_f = 8*D/pi/zcv (m) for calculating zomega (Fuchs, 1964)
5311       zgamma_f_c = 8.0_wp * zdc_c / pi / zcv_c
5312       zgamma_f_x = 8.0_wp * zdc_x / pi / zcv_x
5313       zgamma_f_2 = 8.0_wp * zdc_2 / pi / zcv_2
5314!
5315!--    zomega (m) for calculating zsigma
5316       zomega_c = ( ( z_r_c2 + zgamma_f_c )**3 - ( z_r_c2 ** 2 + zgamma_f_c )**1.5_wp ) /          &
5317                  ( 3.0_wp * z_r_c2 * zgamma_f_c ) - z_r_c2
5318       zomega_x = ( ( z_r_x2 + zgamma_f_x )**3 - ( z_r_x2**2 + zgamma_f_x )** 1.5_wp ) /           &
5319                  ( 3.0_wp * z_r_x2 * zgamma_f_x ) - z_r_x2
5320       zomega_2c = ( ( z_r_c2 + zgamma_f_2 )**3 - ( z_r_c2**2 + zgamma_f_2 )**1.5_wp ) /           &
5321                   ( 3.0_wp * z_r_c2 * zgamma_f_2 ) - z_r_c2
5322       zomega_2x = ( ( z_r_x2 + zgamma_f_2 )**3 - ( z_r_x2**2 + zgamma_f_2 )**1.5_wp ) /           &
5323                   ( 3.0_wp * z_r_x2 * zgamma_f_2 ) - z_r_x2 
5324!
5325!--    The distance (m) at which the two fluxes are matched (condensation and coagulation sinks)
5326       zsigma_c2 = SQRT( zomega_c**2 + zomega_2c**2 )
5327       zsigma_x2 = SQRT( zomega_x**2 + zomega_2x**2 )
5328!
5329!--    Coagulation coefficient in the continuum regime (m*m2/s, Eq. 17 in Kulmala et al., 2001)
5330       z_k_c2 = 4.0_wp * pi * z_r_c2 * zdc_c2 / ( z_r_c2 / ( z_r_c2 + zsigma_c2 ) +                &
5331               4.0_wp * zdc_c2 / ( zcv_c2 * z_r_c2 ) )
5332       z_k_x2 = 4.0_wp * pi * z_r_x2 * zdc_x2 / ( z_r_x2 / ( z_r_x2 + zsigma_x2 ) +                &
5333               4.0_wp * zdc_x2 / ( zcv_x2 * z_r_x2 ) )
5334!
5335!--    Coagulation sink (1/s, Eq. 16 in Kulmala et al., 2001)
5336       zcoags_c = MAX( 1.0E-20_wp, SUM( z_k_c2 * paero(:)%numc ) )
5337       zcoags_x = MAX( 1.0E-20_wp, SUM( z_k_x2 * paero(:)%numc ) )
5338!
5339!--    Parameter m for calculating the coagulation sink onto background particles (Eq. 5&6 in
5340!--    Lehtinen et al. 2007)
5341       zm_para = LOG( zcoags_x / zcoags_c ) / LOG( reglim(1) / zdcrit )
5342!
5343!--    Parameter gamma for calculating the formation rate J of particles having
5344!--    a diameter zdcrit < d < reglim(1) (Anttila et al. 2010, eq. 5 or Lehtinen et al.,2007, eq. 7)
5345       zgamma = ( ( ( reglim(1) / zdcrit )**( zm_para + 1.0_wp ) ) - 1.0_wp ) / ( zm_para + 1.0_wp )
5346
5347       IF ( nj3 == 2 )  THEN   ! Lehtinen et al. (2007): coagulation sink
5348!
5349!--       Formation rate J before iteration (#/m3s)
5350          zj3 = zjnuc * EXP( MIN( 0.0_wp, -zgamma * zdcrit * zcoags_c / ( z_gr_clust * 1.0E-9_wp / &
5351                60.0_wp**2 ) ) )
5352
5353       ELSEIF ( nj3 == 3 )  THEN  ! Anttila et al. (2010): coagulation sink and self-coag.
5354!
5355!--       If air is polluted, the self-coagulation becomes important. Self-coagulation of small
5356!--       particles < 3 nm.
5357!
5358!--       "Effective" coagulation coefficient between freshly-nucleated particles:
5359          z_k_eff = 5.0E-16_wp   ! m3/s
5360!
5361!--       zlambda parameter for "adjusting" the growth rate due to the self-coagulation
5362          zlambda = 6.0_wp
5363
5364          IF ( reglim(1) >= 10.0E-9_wp )  THEN   ! for particles >10 nm:
5365             z_k_eff   = 5.0E-17_wp
5366             zlambda = 3.0_wp
5367          ENDIF
5368!
5369!--       Initial values for coagulation sink and growth rate  (m/s)
5370          zcoagstot = zcoags_c
5371          z_gr_tot = z_gr_clust * 1.0E-9_wp / 60.0_wp**2
5372!
5373!--       Number of clusters/particles at the size range [d1,dx] (#/m3):
5374          z_n_nuc = zjnuc / zcoagstot !< Initial guess
5375!
5376!--       Coagulation sink and growth rate due to self-coagulation:
5377          DO  iteration = 1, 5
5378             zcoagstot = zcoags_c + z_k_eff * z_n_nuc * 1.0E-6_wp   ! (1/s, Anttila et al., eq. 1)
5379             z_gr_tot = z_gr_clust * 2.77777777E-7_wp +  1.5708E-6_wp * zlambda * zdcrit**3 *      &
5380                      ( z_n_nuc * 1.0E-6_wp ) * zcv_c * avo * 2.77777777E-7_wp ! (Eq. 3)
5381             zeta = - zcoagstot / ( ( zm_para + 1.0_wp ) * z_gr_tot * ( zdcrit**zm_para ) ) ! (Eq.7b)
5382!
5383!--          Calculate Eq. 7a (Taylor series for the number of particles between [d1,dx])
5384             z_n_nuc =  z_n_nuc_tayl( zdcrit, reglim(1), zm_para, zjnuc, zeta, z_gr_tot )
5385          ENDDO
5386!
5387!--       Calculate the final values with new z_n_nuc:
5388          zcoagstot = zcoags_c + z_k_eff * z_n_nuc * 1.0E-6_wp   ! (1/s)
5389          z_gr_tot = z_gr_clust * 1.0E-9_wp / 3600.0_wp + 1.5708E-6_wp *  zlambda * zdcrit**3 *    &
5390                   ( z_n_nuc * 1.0E-6_wp ) * zcv_c * avo * 1.0E-9_wp / 3600.0_wp !< (m/s)
5391          zj3 = zjnuc * EXP( MIN( 0.0_wp, -zgamma * zdcrit * zcoagstot / z_gr_tot ) ) ! (#/m3s, Eq.5a)
5392
5393       ENDIF
5394    ENDIF
5395!
5396!-- If J3 very small (< 1 #/cm3), neglect particle formation. In real atmosphere this would mean
5397!-- that clusters form but coagulate to pre-existing particles who gain sulphate. Since
5398!-- CoagS ~ CS (4piD*CS'), we do *not* update H2SO4 concentration here but let condensation take
5399!-- care of it. Formation mass rate of molecules (molec/m3s) for 1: H2SO4 and 2: organic vapour
5400    pj3n3(1) = zj3 * n3 * pxsa
5401    pj3n3(2) = zj3 * n3 * pxocnv
5402
5403 END SUBROUTINE nucleation
5404
5405!------------------------------------------------------------------------------!
5406! Description:
5407! ------------
5408!> Calculate the nucleation rate and the size of critical clusters assuming
5409!> binary nucleation.
5410!> Parametrisation according to Vehkamaki et al. (2002), J. Geophys. Res.,
5411!> 107(D22), 4622. Called from subroutine nucleation.
5412!------------------------------------------------------------------------------!
5413 SUBROUTINE binnucl( pc_sa, ptemp, prh, pnuc_rate, pn_crit_sa, pn_crit_ocnv, pd_crit, pk_sa,       &
5414                     pk_ocnv )
5415
5416    IMPLICIT NONE
5417
5418    REAL(wp) ::  za      !<
5419    REAL(wp) ::  zb      !<
5420    REAL(wp) ::  zc      !<
5421    REAL(wp) ::  zcoll   !<
5422    REAL(wp) ::  zlogsa  !<  LOG( zpcsa )
5423    REAL(wp) ::  zlogrh  !<  LOG( zrh )
5424    REAL(wp) ::  zm1     !<
5425    REAL(wp) ::  zm2     !<
5426    REAL(wp) ::  zma     !<
5427    REAL(wp) ::  zmw     !<
5428    REAL(wp) ::  zntot   !< number of molecules in critical cluster
5429    REAL(wp) ::  zpcsa   !< sulfuric acid concentration
5430    REAL(wp) ::  zrh     !< relative humidity
5431    REAL(wp) ::  zroo    !<
5432    REAL(wp) ::  zt      !< temperature
5433    REAL(wp) ::  zv1     !<
5434    REAL(wp) ::  zv2     !<
5435    REAL(wp) ::  zx      !< mole fraction of sulphate in critical cluster
5436    REAL(wp) ::  zxmass  !<
5437
5438    REAL(wp), INTENT(in) ::   pc_sa   !< H2SO4 conc. (#/cm3)
5439    REAL(wp), INTENT(in) ::   prh     !< relative humidity [0-1
5440    REAL(wp), INTENT(in) ::   ptemp   !< ambient temperature (K)
5441
5442    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucleation rate (#/(m3 s))
5443    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5444    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5445    REAL(wp), INTENT(out) ::  pd_crit       !< diameter of critical cluster (m)
5446    REAL(wp), INTENT(out) ::  pk_sa         !< Lever: if pk_sa = 1, H2SO4 is involved in nucleation.
5447    REAL(wp), INTENT(out) ::  pk_ocnv       !< Lever: if pk_ocnv = 1, organic compounds are involved
5448
5449    pnuc_rate = 0.0_wp
5450    pd_crit   = 1.0E-9_wp
5451!
5452!-- 1) Checking that we are in the validity range of the parameterization
5453    zpcsa  = MAX( pc_sa, 1.0E4_wp  )
5454    zpcsa  = MIN( zpcsa, 1.0E11_wp )
5455    zrh    = MAX( prh,   0.0001_wp )
5456    zrh    = MIN( zrh,   1.0_wp    )
5457    zt     = MAX( ptemp, 190.15_wp )
5458    zt     = MIN( zt,    300.15_wp )
5459
5460    zlogsa = LOG( zpcsa )
5461    zlogrh   = LOG( prh )
5462!
5463!-- 2) Mole fraction of sulphate in a critical cluster (Eq. 11)
5464    zx = 0.7409967177282139_wp                  - 0.002663785665140117_wp * zt +                   &
5465         0.002010478847383187_wp * zlogrh       - 0.0001832894131464668_wp* zt * zlogrh +          &
5466         0.001574072538464286_wp * zlogrh**2    - 0.00001790589121766952_wp * zt * zlogrh**2 +     &
5467         0.0001844027436573778_wp * zlogrh**3   - 1.503452308794887E-6_wp * zt * zlogrh**3 -       &
5468         0.003499978417957668_wp * zlogsa     + 0.0000504021689382576_wp * zt * zlogsa
5469!
5470!-- 3) Nucleation rate (Eq. 12)
5471    pnuc_rate = 0.1430901615568665_wp + 2.219563673425199_wp * zt -                                &
5472                0.02739106114964264_wp * zt**2 + 0.00007228107239317088_wp * zt**3 +               &
5473                5.91822263375044_wp / zx + 0.1174886643003278_wp * zlogrh +                        &
5474                0.4625315047693772_wp * zt * zlogrh - 0.01180591129059253_wp * zt**2 * zlogrh +    &
5475                0.0000404196487152575_wp * zt**3 * zlogrh +                                        &
5476                ( 15.79628615047088_wp * zlogrh ) / zx - 0.215553951893509_wp * zlogrh**2 -        &
5477                0.0810269192332194_wp * zt * zlogrh**2 +                                           &
5478                0.001435808434184642_wp * zt**2 * zlogrh**2 -                                      &
5479                4.775796947178588E-6_wp * zt**3 * zlogrh**2 -                                      &
5480                ( 2.912974063702185_wp * zlogrh**2 ) / zx - 3.588557942822751_wp * zlogrh**3 +     &
5481                0.04950795302831703_wp * zt * zlogrh**3 -                                          &
5482                0.0002138195118737068_wp * zt**2 * zlogrh**3 +                                     &
5483                3.108005107949533E-7_wp * zt**3 * zlogrh**3 -                                      &
5484                ( 0.02933332747098296_wp * zlogrh**3 ) / zx + 1.145983818561277_wp * zlogsa -      &
5485                0.6007956227856778_wp * zt * zlogsa + 0.00864244733283759_wp * zt**2 * zlogsa -    &
5486                0.00002289467254710888_wp * zt**3 * zlogsa -                                       &
5487                ( 8.44984513869014_wp * zlogsa ) / zx + 2.158548369286559_wp * zlogrh * zlogsa +   &
5488                0.0808121412840917_wp * zt * zlogrh * zlogsa -                                     &
5489                0.0004073815255395214_wp * zt**2 * zlogrh * zlogsa -                               &
5490                4.019572560156515E-7_wp * zt**3 * zlogrh * zlogsa +                                &
5491                ( 0.7213255852557236_wp * zlogrh * zlogsa ) / zx +                                 &
5492                1.62409850488771_wp * zlogrh**2 * zlogsa -                                         &
5493                0.01601062035325362_wp * zt * zlogrh**2 * zlogsa +                                 &
5494                0.00003771238979714162_wp*zt**2* zlogrh**2 * zlogsa +                              &
5495                3.217942606371182E-8_wp * zt**3 * zlogrh**2 * zlogsa -                             &
5496                ( 0.01132550810022116_wp * zlogrh**2 * zlogsa ) / zx +                             &
5497                9.71681713056504_wp * zlogsa**2 - 0.1150478558347306_wp * zt * zlogsa**2 +         &
5498                0.0001570982486038294_wp * zt**2 * zlogsa**2 +                                     &
5499                4.009144680125015E-7_wp * zt**3 * zlogsa**2 +                                      &
5500                ( 0.7118597859976135_wp * zlogsa**2 ) / zx -                                       &
5501                1.056105824379897_wp * zlogrh * zlogsa**2 +                                        &
5502                0.00903377584628419_wp * zt * zlogrh * zlogsa**2 -                                 &
5503                0.00001984167387090606_wp * zt**2 * zlogrh * zlogsa**2 +                           &
5504                2.460478196482179E-8_wp * zt**3 * zlogrh * zlogsa**2 -                             &
5505                ( 0.05790872906645181_wp * zlogrh * zlogsa**2 ) / zx -                             &
5506                0.1487119673397459_wp * zlogsa**3 + 0.002835082097822667_wp * zt * zlogsa**3 -     &
5507                9.24618825471694E-6_wp * zt**2 * zlogsa**3 +                                       &
5508                5.004267665960894E-9_wp * zt**3 * zlogsa**3 -                                      &
5509                ( 0.01270805101481648_wp * zlogsa**3 ) / zx
5510!
5511!-- Nucleation rate in #/(cm3 s)
5512    pnuc_rate = EXP( pnuc_rate ) 
5513!
5514!-- Check the validity of parameterization
5515    IF ( pnuc_rate < 1.0E-7_wp )  THEN
5516       pnuc_rate = 0.0_wp
5517       pd_crit   = 1.0E-9_wp
5518    ENDIF
5519!
5520!-- 4) Total number of molecules in the critical cluster (Eq. 13)
5521    zntot = - 0.002954125078716302_wp - 0.0976834264241286_wp * zt +                               &
5522              0.001024847927067835_wp * zt**2 - 2.186459697726116E-6_wp * zt**3 -                  &
5523              0.1017165718716887_wp / zx - 0.002050640345231486_wp * zlogrh -                      &
5524              0.007585041382707174_wp * zt * zlogrh + 0.0001926539658089536_wp * zt**2 * zlogrh -  &
5525              6.70429719683894E-7_wp * zt**3 * zlogrh - ( 0.2557744774673163_wp * zlogrh ) / zx +  &
5526              0.003223076552477191_wp * zlogrh**2 + 0.000852636632240633_wp * zt * zlogrh**2 -     &
5527              0.00001547571354871789_wp * zt**2 * zlogrh**2 +                                      &
5528              5.666608424980593E-8_wp * zt**3 * zlogrh**2 +                                        &
5529              ( 0.03384437400744206_wp * zlogrh**2 ) / zx +                                        &
5530              0.04743226764572505_wp * zlogrh**3 - 0.0006251042204583412_wp * zt * zlogrh**3 +     &
5531              2.650663328519478E-6_wp * zt**2 * zlogrh**3 -                                        &
5532              3.674710848763778E-9_wp * zt**3 * zlogrh**3 -                                        &
5533              ( 0.0002672510825259393_wp * zlogrh**3 ) / zx - 0.01252108546759328_wp * zlogsa +    &
5534              0.005806550506277202_wp * zt * zlogsa - 0.0001016735312443444_wp * zt**2 * zlogsa +  &
5535              2.881946187214505E-7_wp * zt**3 * zlogsa + ( 0.0942243379396279_wp * zlogsa ) / zx - &
5536              0.0385459592773097_wp * zlogrh * zlogsa -                                            &
5537              0.0006723156277391984_wp * zt * zlogrh * zlogsa  +                                   &
5538              2.602884877659698E-6_wp * zt**2 * zlogrh * zlogsa +                                  &
5539              1.194163699688297E-8_wp * zt**3 * zlogrh * zlogsa -                                  &
5540              ( 0.00851515345806281_wp * zlogrh * zlogsa ) / zx -                                  &
5541              0.01837488495738111_wp * zlogrh**2 * zlogsa +                                        &
5542              0.0001720723574407498_wp * zt * zlogrh**2 * zlogsa -                                 &
5543              3.717657974086814E-7_wp * zt**2 * zlogrh**2 * zlogsa -                               &
5544              5.148746022615196E-10_wp * zt**3 * zlogrh**2 * zlogsa +                              &
5545              ( 0.0002686602132926594_wp * zlogrh**2 * zlogsa ) / zx -                             &
5546              0.06199739728812199_wp * zlogsa**2 + 0.000906958053583576_wp * zt * zlogsa**2 -      &
5547              9.11727926129757E-7_wp * zt**2 * zlogsa**2 -                                         &
5548              5.367963396508457E-9_wp * zt**3 * zlogsa**2 -                                        &
5549              ( 0.007742343393937707_wp * zlogsa**2 ) / zx +                                       &
5550              0.0121827103101659_wp * zlogrh * zlogsa**2 -                                         &
5551              0.0001066499571188091_wp * zt * zlogrh * zlogsa**2 +                                 &
5552              2.534598655067518E-7_wp * zt**2 * zlogrh * zlogsa**2 -                               &
5553              3.635186504599571E-10_wp * zt**3 * zlogrh * zlogsa**2 +                              &
5554              ( 0.0006100650851863252_wp * zlogrh * zlogsa **2 ) / zx +                            &
5555              0.0003201836700403512_wp * zlogsa**3 - 0.0000174761713262546_wp * zt * zlogsa**3 +   &
5556              6.065037668052182E-8_wp * zt**2 * zlogsa**3 -                                        &
5557              1.421771723004557E-11_wp * zt**3 * zlogsa**3 +                                       &
5558              ( 0.0001357509859501723_wp * zlogsa**3 ) / zx
5559    zntot = EXP( zntot )  ! in #
5560!
5561!-- 5) Size of the critical cluster pd_crit (m) (diameter) (Eq. 14)
5562    pn_crit_sa = zx * zntot
5563    pd_crit = 2.0E-9_wp * EXP( -1.6524245_wp + 0.42316402_wp * zx + 0.33466487_wp * LOG( zntot ) )
5564!
5565!-- 6) Organic compounds not involved when binary nucleation is assumed
5566    pn_crit_ocnv = 0.0_wp   ! number of organic molecules
5567    pk_sa        = 1.0_wp   ! if = 1, H2SO4 involved in nucleation
5568    pk_ocnv      = 0.0_wp   ! if = 1, organic compounds involved
5569!
5570!-- Set nucleation rate to collision rate
5571    IF ( pn_crit_sa < 4.0_wp ) THEN
5572!
5573!--    Volumes of the colliding objects
5574       zma    = 96.0_wp   ! molar mass of SO4 in g/mol
5575       zmw    = 18.0_wp   ! molar mass of water in g/mol
5576       zxmass = 1.0_wp    ! mass fraction of H2SO4
5577       za = 0.7681724_wp + zxmass * ( 2.1847140_wp + zxmass *                                      &
5578                                      ( 7.1630022_wp + zxmass *                                    &
5579                                        ( -44.31447_wp + zxmass *                                  &
5580                                          ( 88.75606 + zxmass *                                    &
5581                                            ( -75.73729_wp + zxmass * 23.43228_wp ) ) ) ) )
5582       zb = 1.808225E-3_wp + zxmass * ( -9.294656E-3_wp + zxmass *                                 &
5583                                        ( -0.03742148_wp + zxmass *                                &
5584                                          ( 0.2565321_wp + zxmass *                                &
5585                                            ( -0.5362872_wp + zxmass *                             &
5586                                              ( 0.4857736 - zxmass * 0.1629592_wp ) ) ) ) )
5587       zc = - 3.478524E-6_wp + zxmass * ( 1.335867E-5_wp + zxmass *                                &
5588                                          ( 5.195706E-5_wp + zxmass *                              &
5589                                            ( -3.717636E-4_wp + zxmass *                           &
5590                                              ( 7.990811E-4_wp + zxmass *                          &
5591                                                ( -7.458060E-4_wp + zxmass * 2.58139E-4_wp ) ) ) ) )
5592!
5593!--    Density for the sulphuric acid solution (Eq. 10 in Vehkamaki)
5594       zroo = ( za + zt * ( zb + zc * zt ) ) * 1.0E+3_wp   ! (kg/m^3
5595       zm1  = 0.098_wp   ! molar mass of H2SO4 in kg/mol
5596       zm2  = zm1
5597       zv1  = zm1 / avo / zroo   ! volume
5598       zv2  = zv1
5599!
5600!--    Collision rate
5601       zcoll =  zpcsa * zpcsa * ( 3.0_wp * pi / 4.0_wp )**0.16666666_wp *                          &
5602                SQRT( 6.0_wp * argas * zt / zm1 + 6.0_wp * argas * zt / zm2 ) *                    &
5603                ( zv1**0.33333333_wp + zv2**0.33333333_wp )**2 * 1.0E+6_wp    ! m3 -> cm3
5604       zcoll = MIN( zcoll, 1.0E+10_wp )
5605       pnuc_rate  = zcoll   ! (#/(cm3 s))
5606
5607    ELSE
5608       pnuc_rate  = MIN( pnuc_rate, 1.0E+10_wp )
5609    ENDIF
5610    pnuc_rate = pnuc_rate * 1.0E+6_wp   ! (#/(m3 s))
5611
5612 END SUBROUTINE binnucl
5613 
5614!------------------------------------------------------------------------------!
5615! Description:
5616! ------------
5617!> Calculate the nucleation rate and the size of critical clusters assuming
5618!> ternary nucleation. Parametrisation according to:
5619!> Napari et al. (2002), J. Chem. Phys., 116, 4221-4227 and
5620!> Napari et al. (2002), J. Geophys. Res., 107(D19), AAC 6-1-ACC 6-6.
5621!------------------------------------------------------------------------------!
5622 SUBROUTINE ternucl( pc_sa, pc_nh3, ptemp, prh, pnuc_rate, pn_crit_sa, pn_crit_ocnv, pd_crit,      &
5623                     pk_sa, pk_ocnv )
5624
5625    IMPLICIT NONE
5626
5627    REAL(wp) ::  zlnj     !< logarithm of nucleation rate
5628    REAL(wp) ::  zlognh3  !< LOG( pc_nh3 )
5629    REAL(wp) ::  zlogrh   !< LOG( prh )
5630    REAL(wp) ::  zlogsa   !< LOG( pc_sa )
5631
5632    REAL(wp), INTENT(in) ::   pc_nh3  !< ammonia mixing ratio (ppt)
5633    REAL(wp), INTENT(in) ::   pc_sa   !< H2SO4 conc. (#/cm3)
5634    REAL(wp), INTENT(in) ::   prh     !< relative humidity [0-1]
5635    REAL(wp), INTENT(in) ::   ptemp   !< ambient temperature (K)
5636
5637    REAL(wp), INTENT(out) ::  pd_crit  !< diameter of critical cluster (m)
5638    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate in nucleation
5639    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 participate in nucleation
5640    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5641    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5642    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucleation rate (#/(m3 s))
5643!
5644!-- 1) Checking that we are in the validity range of the parameterization.
5645!--    Validity of parameterization : DO NOT REMOVE!
5646    IF ( ptemp < 240.0_wp  .OR.  ptemp > 300.0_wp )  THEN
5647       message_string = 'Invalid input value: ptemp'
5648       CALL message( 'salsa_mod: ternucl', 'PA0648', 1, 2, 0, 6, 0 )
5649    ENDIF
5650    IF ( prh < 0.05_wp  .OR.  prh > 0.95_wp )  THEN
5651       message_string = 'Invalid input value: prh'
5652       CALL message( 'salsa_mod: ternucl', 'PA0649', 1, 2, 0, 6, 0 )
5653    ENDIF
5654    IF ( pc_sa < 1.0E+4_wp  .OR.  pc_sa > 1.0E+9_wp )  THEN
5655       message_string = 'Invalid input value: pc_sa'
5656       CALL message( 'salsa_mod: ternucl', 'PA0650', 1, 2, 0, 6, 0 )
5657    ENDIF
5658    IF ( pc_nh3 < 0.1_wp  .OR.  pc_nh3 > 100.0_wp )  THEN
5659       message_string = 'Invalid input value: pc_nh3'
5660       CALL message( 'salsa_mod: ternucl', 'PA0651', 1, 2, 0, 6, 0 )
5661    ENDIF
5662
5663    zlognh3 = LOG( pc_nh3 )
5664    zlogrh  = LOG( prh )
5665    zlogsa  = LOG( pc_sa )
5666!
5667!-- 2) Nucleation rate (Eq. 7 in Napari et al., 2002: Parameterization of
5668!--    ternary nucleation of sulfuric acid - ammonia - water.
5669    zlnj = - 84.7551114741543_wp + 0.3117595133628944_wp * prh +                                   &
5670           1.640089605712946_wp * prh * ptemp - 0.003438516933381083_wp * prh * ptemp**2 -         &
5671           0.00001097530402419113_wp * prh * ptemp**3 - 0.3552967070274677_wp / zlogsa -           &
5672           ( 0.06651397829765026_wp * prh ) / zlogsa - ( 33.84493989762471_wp * ptemp ) / zlogsa - &
5673           ( 7.823815852128623_wp * prh * ptemp ) / zlogsa +                                       &
5674           ( 0.3453602302090915_wp * ptemp**2 ) / zlogsa +                                         &
5675           ( 0.01229375748100015_wp * prh * ptemp**2 ) / zlogsa -                                  &
5676           ( 0.000824007160514956_wp *ptemp**3 ) / zlogsa +                                        &
5677           ( 0.00006185539100670249_wp * prh * ptemp**3 ) / zlogsa +                               &
5678           3.137345238574998_wp * zlogsa + 3.680240980277051_wp * prh * zlogsa -                   &
5679           0.7728606202085936_wp * ptemp * zlogsa - 0.204098217156962_wp * prh * ptemp * zlogsa +  &
5680           0.005612037586790018_wp * ptemp**2 * zlogsa +                                           &
5681           0.001062588391907444_wp * prh * ptemp**2 * zlogsa -                                     &
5682           9.74575691760229E-6_wp * ptemp**3 * zlogsa -                                            &
5683           1.265595265137352E-6_wp * prh * ptemp**3 * zlogsa + 19.03593713032114_wp * zlogsa**2 -  &
5684           0.1709570721236754_wp * ptemp * zlogsa**2 +                                             &
5685           0.000479808018162089_wp * ptemp**2 * zlogsa**2 -                                        &
5686           4.146989369117246E-7_wp * ptemp**3 * zlogsa**2 + 1.076046750412183_wp * zlognh3 +       &
5687           0.6587399318567337_wp * prh * zlognh3 + 1.48932164750748_wp * ptemp * zlognh3 +         &
5688           0.1905424394695381_wp * prh * ptemp * zlognh3 -                                         &
5689           0.007960522921316015_wp * ptemp**2 * zlognh3 -                                          &
5690           0.001657184248661241_wp * prh * ptemp**2 * zlognh3 +                                    &
5691           7.612287245047392E-6_wp * ptemp**3 * zlognh3 +                                          &
5692           3.417436525881869E-6_wp * prh * ptemp**3 * zlognh3 +                                    &
5693           ( 0.1655358260404061_wp * zlognh3 ) / zlogsa +                                          &
5694           ( 0.05301667612522116_wp * prh * zlognh3 ) / zlogsa +                                   &
5695           ( 3.26622914116752_wp * ptemp * zlognh3 ) / zlogsa -                                    &
5696           ( 1.988145079742164_wp * prh * ptemp * zlognh3 ) / zlogsa -                             &
5697           ( 0.04897027401984064_wp * ptemp**2 * zlognh3 ) / zlogsa +                              &
5698           ( 0.01578269253599732_wp * prh * ptemp**2 * zlognh3 ) / zlogsa +                        &
5699           ( 0.0001469672236351303_wp * ptemp**3 * zlognh3 ) / zlogsa -                            &
5700           ( 0.00002935642836387197_wp * prh * ptemp**3 *zlognh3 ) / zlogsa +                      &
5701           6.526451177887659_wp * zlogsa * zlognh3 -                                               &
5702           0.2580021816722099_wp * ptemp * zlogsa * zlognh3 +                                      &
5703           0.001434563104474292_wp * ptemp**2 * zlogsa * zlognh3 -                                 &
5704           2.020361939304473E-6_wp * ptemp**3 * zlogsa * zlognh3 -                                 &
5705           0.160335824596627_wp * zlogsa**2 * zlognh3 +                                            &
5706           0.00889880721460806_wp * ptemp * zlogsa**2 * zlognh3 -                                  &
5707           0.00005395139051155007_wp * ptemp**2 * zlogsa**2 * zlognh3 +                            &
5708           8.39521718689596E-8_wp * ptemp**3 * zlogsa**2 * zlognh3 +                               &
5709           6.091597586754857_wp * zlognh3**2 + 8.5786763679309_wp * prh * zlognh3**2 -             &
5710           1.253783854872055_wp * ptemp * zlognh3**2 -                                             &
5711           0.1123577232346848_wp * prh * ptemp * zlognh3**2 +                                      &
5712           0.00939835595219825_wp * ptemp**2 * zlognh3**2 +                                        &
5713           0.0004726256283031513_wp * prh * ptemp**2 * zlognh3**2 -                                &
5714           0.00001749269360523252_wp * ptemp**3 * zlognh3**2 -                                     &
5715           6.483647863710339E-7_wp * prh * ptemp**3 * zlognh3**2 +                                 &
5716           ( 0.7284285726576598_wp * zlognh3**2 ) / zlogsa +                                       &
5717           ( 3.647355600846383_wp * ptemp * zlognh3**2 ) / zlogsa -                                &
5718           ( 0.02742195276078021_wp * ptemp**2 * zlognh3**2 ) / zlogsa +                           &
5719           ( 0.00004934777934047135_wp * ptemp**3 * zlognh3**2 ) / zlogsa +                        &
5720           41.30162491567873_wp * zlogsa * zlognh3**2 -                                            &
5721           0.357520416800604_wp * ptemp * zlogsa * zlognh3**2 +                                    &
5722           0.000904383005178356_wp * ptemp**2 * zlogsa * zlognh3**2 -                              &
5723           5.737876676408978E-7_wp * ptemp**3 * zlogsa * zlognh3**2 -                              &
5724           2.327363918851818_wp * zlogsa**2 * zlognh3**2 +                                         &
5725           0.02346464261919324_wp * ptemp * zlogsa**2 * zlognh3**2 -                               &
5726           0.000076518969516405_wp * ptemp**2 * zlogsa**2 * zlognh3**2 +                           &
5727           8.04589834836395E-8_wp * ptemp**3 * zlogsa**2 * zlognh3**2 -                            &
5728           0.02007379204248076_wp * zlogrh - 0.7521152446208771_wp * ptemp * zlogrh +              &
5729           0.005258130151226247_wp * ptemp**2 * zlogrh -                                           &
5730           8.98037634284419E-6_wp * ptemp**3 * zlogrh +                                            &
5731           ( 0.05993213079516759_wp * zlogrh ) / zlogsa +                                          &
5732           ( 5.964746463184173_wp * ptemp * zlogrh ) / zlogsa -                                    &
5733           ( 0.03624322255690942_wp * ptemp**2 * zlogrh ) / zlogsa +                               &
5734           ( 0.00004933369382462509_wp * ptemp**3 * zlogrh ) / zlogsa -                            &
5735           0.7327310805365114_wp * zlognh3 * zlogrh -                                              &
5736           0.01841792282958795_wp * ptemp * zlognh3 * zlogrh +                                     &
5737           0.0001471855981005184_wp * ptemp**2 * zlognh3 * zlogrh -                                &
5738           2.377113195631848E-7_wp * ptemp**3 * zlognh3 * zlogrh
5739    pnuc_rate = EXP( zlnj )   ! (#/(cm3 s))
5740!
5741!-- Check validity of parametrization
5742    IF ( pnuc_rate < 1.0E-5_wp )  THEN
5743       pnuc_rate = 0.0_wp
5744       pd_crit   = 1.0E-9_wp
5745    ELSEIF ( pnuc_rate > 1.0E6_wp )  THEN
5746       message_string = 'Invalid output value: nucleation rate > 10^6 1/cm3s'
5747       CALL message( 'salsa_mod: ternucl', 'PA0623', 1, 2, 0, 6, 0 )
5748    ENDIF
5749    pnuc_rate = pnuc_rate * 1.0E6_wp   ! (#/(m3 s))
5750!
5751!-- 3) Number of H2SO4 molecules in a critical cluster (Eq. 9)
5752    pn_crit_sa = 38.16448247950508_wp + 0.7741058259731187_wp * zlnj +                             &
5753                 0.002988789927230632_wp * zlnj**2 - 0.3576046920535017_wp * ptemp -               &
5754                 0.003663583011953248_wp * zlnj * ptemp + 0.000855300153372776_wp * ptemp**2
5755!
5756!-- Kinetic limit: at least 2 H2SO4 molecules in a cluster
5757    pn_crit_sa = MAX( pn_crit_sa, 2.0E0_wp )
5758!
5759!-- 4) Size of the critical cluster in nm (Eq. 12)
5760    pd_crit = 0.1410271086638381_wp - 0.001226253898894878_wp * zlnj -                             &
5761              7.822111731550752E-6_wp * zlnj**2 - 0.001567273351921166_wp * ptemp -                &
5762              0.00003075996088273962_wp * zlnj * ptemp + 0.00001083754117202233_wp * ptemp**2
5763    pd_crit = pd_crit * 2.0E-9_wp   ! Diameter in m
5764!
5765!-- 5) Organic compounds not involved when ternary nucleation assumed
5766    pn_crit_ocnv = 0.0_wp
5767    pk_sa   = 1.0_wp
5768    pk_ocnv = 0.0_wp
5769
5770 END SUBROUTINE ternucl
5771
5772!------------------------------------------------------------------------------!
5773! Description:
5774! ------------
5775!> Function z_n_nuc_tayl is connected to the calculation of self-coagualtion of
5776!> small particles. It calculates number of the particles in the size range
5777!> [zdcrit,dx] using Taylor-expansion (please note that the expansion is not
5778!> valid for certain rational numbers, e.g. -4/3 and -3/2)
5779!------------------------------------------------------------------------------!
5780 FUNCTION z_n_nuc_tayl( d1, dx, zm_para, zjnuc_t, zeta, z_gr_tot )
5781
5782    IMPLICIT NONE
5783
5784    INTEGER(iwp) ::  i !< running index
5785
5786    REAL(wp) ::  d1            !< lower diameter limit
5787    REAL(wp) ::  dx            !< upper diameter limit
5788    REAL(wp) ::  zjnuc_t       !< initial nucleation rate (1/s)
5789    REAL(wp) ::  zeta          !< ratio of CS/GR (m) (condensation sink / growth rate)
5790    REAL(wp) ::  term1         !<
5791    REAL(wp) ::  term2         !<
5792    REAL(wp) ::  term3         !<
5793    REAL(wp) ::  term4         !<
5794    REAL(wp) ::  term5         !<
5795    REAL(wp) ::  z_n_nuc_tayl  !< final nucleation rate (1/s)
5796    REAL(wp) ::  z_gr_tot      !< total growth rate (nm/h)
5797    REAL(wp) ::  zm_para       !< m parameter in Lehtinen et al. (2007), Eq. 6
5798
5799    z_n_nuc_tayl = 0.0_wp
5800
5801    DO  i = 0, 29
5802       IF ( i == 0  .OR.  i == 1 )  THEN
5803          term1 = 1.0_wp
5804       ELSE
5805          term1 = term1 * REAL( i, SELECTED_REAL_KIND(12,307) )
5806       END IF
5807       term2 = ( REAL( i, SELECTED_REAL_KIND(12,307) ) * ( zm_para + 1.0_wp ) + 1.0_wp ) * term1
5808       term3 = zeta**i
5809       term4 = term3 / term2
5810       term5 = REAL( i, SELECTED_REAL_KIND(12,307) ) * ( zm_para + 1.0_wp ) + 1.0_wp
5811       z_n_nuc_tayl = z_n_nuc_tayl + term4 * ( dx**term5 - d1**term5 )
5812    ENDDO
5813    z_n_nuc_tayl = z_n_nuc_tayl * zjnuc_t * EXP( -zeta * ( d1**( zm_para + 1 ) ) ) / z_gr_tot
5814
5815 END FUNCTION z_n_nuc_tayl
5816
5817!------------------------------------------------------------------------------!
5818! Description:
5819! ------------
5820!> Calculates the condensation of water vapour on aerosol particles. Follows the
5821!> analytical predictor method by Jacobson (2005).
5822!> For equations, see Jacobson (2005), Fundamentals of atmospheric modelling
5823!> (2nd edition).
5824!------------------------------------------------------------------------------!
5825 SUBROUTINE gpparth2o( paero, ptemp, ppres, pcs, pcw, ptstep )
5826
5827    IMPLICIT NONE
5828
5829    INTEGER(iwp) ::  ib   !< loop index
5830    INTEGER(iwp) ::  nstr !<
5831
5832    REAL(wp) ::  adt        !< internal timestep in this subroutine
5833    REAL(wp) ::  rhoair     !< air density (kg/m3)
5834    REAL(wp) ::  ttot       !< total time (s)
5835    REAL(wp) ::  zact       !< Water activity
5836    REAL(wp) ::  zaelwc1    !< Current aerosol water content (kg/m3)
5837    REAL(wp) ::  zaelwc2    !< New aerosol water content after equilibrium calculation (kg/m3)
5838    REAL(wp) ::  zbeta      !< Transitional correction factor
5839    REAL(wp) ::  zcwc       !< Current water vapour mole concentration in aerosols (mol/m3)
5840    REAL(wp) ::  zcwint     !< Current and new water vapour mole concentrations (mol/m3)
5841    REAL(wp) ::  zcwn       !< New water vapour mole concentration (mol/m3)
5842    REAL(wp) ::  zcwtot     !< Total water mole concentration (mol/m3)
5843    REAL(wp) ::  zdfh2o     !< molecular diffusion coefficient (cm2/s) for water
5844    REAL(wp) ::  zhlp1      !< intermediate variable to calculate the mass transfer coefficient
5845    REAL(wp) ::  zhlp2      !< intermediate variable to calculate the mass transfer coefficient
5846    REAL(wp) ::  zhlp3      !< intermediate variable to calculate the mass transfer coefficient
5847    REAL(wp) ::  zknud      !< Knudsen number
5848    REAL(wp) ::  zmfph2o    !< mean free path of H2O gas molecule
5849    REAL(wp) ::  zrh        !< relative humidity [0-1]
5850    REAL(wp) ::  zthcond    !< thermal conductivity of air (W/m/K)
5851
5852    REAL(wp), DIMENSION(nbins_aerosol) ::  zcwcae     !< Current water mole concentrations
5853    REAL(wp), DIMENSION(nbins_aerosol) ::  zcwintae   !< Current and new aerosol water mole concentration
5854    REAL(wp), DIMENSION(nbins_aerosol) ::  zcwnae     !< New water mole concentration in aerosols
5855    REAL(wp), DIMENSION(nbins_aerosol) ::  zcwsurfae  !< Surface mole concentration
5856    REAL(wp), DIMENSION(nbins_aerosol) ::  zkelvin    !< Kelvin effect
5857    REAL(wp), DIMENSION(nbins_aerosol) ::  zmtae      !< Mass transfer coefficients
5858    REAL(wp), DIMENSION(nbins_aerosol) ::  zwsatae    !< Water saturation ratio above aerosols
5859
5860    REAL(wp), INTENT(in) ::  ppres   !< Air pressure (Pa)
5861    REAL(wp), INTENT(in) ::  pcs     !< Water vapour saturation concentration (kg/m3)
5862    REAL(wp), INTENT(in) ::  ptemp   !< Ambient temperature (K)
5863    REAL(wp), INTENT(in) ::  ptstep  !< timestep (s)
5864
5865    REAL(wp), INTENT(inout) ::  pcw  !< Water vapour concentration (kg/m3)
5866
5867    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< Aerosol properties
5868!
5869!-- Relative humidity [0-1]
5870    zrh = pcw / pcs
5871!
5872!-- Calculate the condensation only for 2a/2b aerosol bins
5873    nstr = start_subrange_2a
5874!
5875!-- Save the current aerosol water content, 8 in paero is H2O
5876    zaelwc1 = SUM( paero(start_subrange_1a:end_subrange_2b)%volc(8) ) * arhoh2o
5877!
5878!-- Equilibration:
5879    IF ( advect_particle_water )  THEN
5880       IF ( zrh < 0.98_wp  .OR.  .NOT. lscndh2oae )  THEN
5881          CALL equilibration( zrh, ptemp, paero, .TRUE. )
5882       ELSE
5883          CALL equilibration( zrh, ptemp, paero, .FALSE. )
5884       ENDIF
5885    ENDIF
5886!
5887!-- The new aerosol water content after equilibrium calculation
5888    zaelwc2 = SUM( paero(start_subrange_1a:end_subrange_2b)%volc(8) ) * arhoh2o
5889!
5890!-- New water vapour mixing ratio (kg/m3)
5891    pcw = pcw - ( zaelwc2 - zaelwc1 ) * ppres * amdair / ( argas * ptemp )
5892!
5893!-- Initialise variables
5894    zcwsurfae(:) = 0.0_wp
5895    zhlp1        = 0.0_wp
5896    zhlp2        = 0.0_wp
5897    zhlp3        = 0.0_wp
5898    zmtae(:)     = 0.0_wp
5899    zwsatae(:)   = 0.0_wp
5900!
5901!-- Air:
5902!-- Density (kg/m3)
5903    rhoair = amdair * ppres / ( argas * ptemp )
5904!
5905!-- Thermal conductivity of air
5906    zthcond = 0.023807_wp + 7.1128E-5_wp * ( ptemp - 273.16_wp )
5907!
5908!-- Water vapour:
5909!-- Molecular diffusion coefficient (cm2/s) (eq.16.17)
5910    zdfh2o = ( 5.0_wp / ( 16.0_wp * avo * rhoair * 1.0E-3_wp * 3.11E-8_wp**2 ) ) * SQRT( argas *   &
5911               1.0E+7_wp * ptemp * amdair * 1.0E+3_wp * ( amh2o + amdair ) * 1.0E+3_wp /           &
5912               ( pi * amh2o * 2.0E+3_wp ) )
5913    zdfh2o = zdfh2o * 1.0E-4   ! Unit change to m^2/s
5914!
5915!-- Mean free path (eq. 15.25 & 16.29)
5916    zmfph2o = 3.0_wp * zdfh2o * SQRT( pi * amh2o / ( 8.0_wp * argas * ptemp ) )
5917!
5918!-- Kelvin effect (eq. 16.33)
5919    zkelvin(:) = EXP( 4.0_wp * surfw0 * amh2o / ( argas * ptemp * arhoh2o * paero(:)%dwet) )
5920
5921    DO  ib = 1, nbins_aerosol
5922       IF ( paero(ib)%numc > nclim  .AND.  zrh > 0.98_wp )  THEN
5923!
5924!--       Water activity
5925          zact = acth2o( paero(ib) )
5926!
5927!--       Saturation mole concentration over flat surface. Limit the super-
5928!--       saturation to max 1.01 for the mass transfer. Experimental!
5929          zcwsurfae(ib) = MAX( pcs, pcw / 1.01_wp ) * rhoair / amh2o
5930!
5931!--       Equilibrium saturation ratio
5932          zwsatae(ib) = zact * zkelvin(ib)
5933!
5934!--       Knudsen number (eq. 16.20)
5935          zknud = 2.0_wp * zmfph2o / paero(ib)%dwet
5936!
5937!--       Transitional correction factor (Fuks & Sutugin, 1971)
5938          zbeta = ( zknud + 1.0_wp ) / ( 0.377_wp * zknud + 1.0_wp + 4.0_wp /                      &
5939                  ( 3.0_wp * massacc(ib) ) * ( zknud + zknud**2 ) )
5940!
5941!--       Mass transfer of H2O: Eq. 16.64 but here D^eff =  zdfh2o * zbeta
5942          zhlp1 = paero(ib)%numc * 2.0_wp * pi * paero(ib)%dwet * zdfh2o * zbeta
5943!
5944!--       1st term on the left side of the denominator in eq. 16.55
5945          zhlp2 = amh2o * zdfh2o * alv * zwsatae(ib) * zcwsurfae(ib) / ( zthcond * ptemp )
5946!
5947!--       2nd term on the left side of the denominator in eq. 16.55
5948          zhlp3 = ( ( alv * amh2o ) / ( argas * ptemp ) ) - 1.0_wp
5949!
5950!--       Full eq. 16.64: Mass transfer coefficient (1/s)
5951          zmtae(ib) = zhlp1 / ( zhlp2 * zhlp3 + 1.0_wp )
5952       ENDIF
5953    ENDDO
5954!
5955!-- Current mole concentrations of water
5956    zcwc        = pcw * rhoair / amh2o   ! as vapour
5957    zcwcae(:)   = paero(:)%volc(8) * arhoh2o / amh2o   ! in aerosols
5958    zcwtot      = zcwc + SUM( zcwcae )   ! total water concentration
5959    zcwnae(:)   = 0.0_wp
5960    zcwintae(:) = zcwcae(:)
5961!
5962!-- Substepping loop
5963    zcwint = 0.0_wp
5964    ttot   = 0.0_wp
5965    DO  WHILE ( ttot < ptstep )
5966       adt = 2.0E-2_wp   ! internal timestep
5967!
5968!--    New vapour concentration: (eq. 16.71)
5969       zhlp1 = zcwc + adt * ( SUM( zmtae(nstr:nbins_aerosol) * zwsatae(nstr:nbins_aerosol) *       &
5970                                   zcwsurfae(nstr:nbins_aerosol) ) )   ! numerator
5971       zhlp2 = 1.0_wp + adt * ( SUM( zmtae(nstr:nbins_aerosol) ) )   ! denomin.
5972       zcwint = zhlp1 / zhlp2   ! new vapour concentration
5973       zcwint = MIN( zcwint, zcwtot )
5974       IF ( ANY( paero(:)%numc > nclim )  .AND. zrh > 0.98_wp )  THEN
5975          DO  ib = nstr, nbins_aerosol
5976             zcwintae(ib) = zcwcae(ib) + MIN( MAX( adt * zmtae(ib) * ( zcwint - zwsatae(ib) *      &
5977                                                   zcwsurfae(ib) ), -0.02_wp * zcwcae(ib) ),       &
5978                                            0.05_wp * zcwcae(ib) )
5979             zwsatae(ib) = acth2o( paero(ib), zcwintae(ib) ) * zkelvin(ib)
5980          ENDDO
5981       ENDIF
5982       zcwintae(nstr:nbins_aerosol) = MAX( zcwintae(nstr:nbins_aerosol), 0.0_wp )
5983!
5984!--    Update vapour concentration for consistency
5985       zcwint = zcwtot - SUM( zcwintae(1:nbins_aerosol) )
5986!
5987!--    Update "old" values for next cycle
5988       zcwcae = zcwintae
5989
5990       ttot = ttot + adt
5991
5992    ENDDO   ! ADT
5993
5994    zcwn      = zcwint
5995    zcwnae(:) = zcwintae(:)
5996    pcw       = zcwn * amh2o / rhoair
5997    paero(:)%volc(8) = MAX( 0.0_wp, zcwnae(:) * amh2o / arhoh2o )
5998
5999 END SUBROUTINE gpparth2o
6000
6001!------------------------------------------------------------------------------!
6002! Description:
6003! ------------
6004!> Calculates the activity coefficient of liquid water
6005!------------------------------------------------------------------------------!
6006 REAL(wp) FUNCTION acth2o( ppart, pcw )
6007
6008    IMPLICIT NONE
6009
6010    REAL(wp) ::  zns  !< molar concentration of solutes (mol/m3)
6011    REAL(wp) ::  znw  !< molar concentration of water (mol/m3)
6012
6013    REAL(wp), INTENT(in), OPTIONAL ::  pcw !< molar concentration of water (mol/m3)
6014
6015    TYPE(t_section), INTENT(in) ::  ppart !< Aerosol properties of a bin
6016
6017    zns = ( 3.0_wp * ( ppart%volc(1) * arhoh2so4 / amh2so4 ) + ( ppart%volc(2) * arhooc / amoc ) + &
6018            2.0_wp * ( ppart%volc(5) * arhoss / amss ) + ( ppart%volc(6) * arhohno3 / amhno3 ) +   &
6019            ( ppart%volc(7) * arhonh3 / amnh3 ) )
6020
6021    IF ( PRESENT(pcw) ) THEN
6022       znw = pcw
6023    ELSE
6024       znw = ppart%volc(8) * arhoh2o / amh2o
6025    ENDIF
6026!
6027!-- Activity = partial pressure of water vapour / sat. vapour pressure of water over a liquid surface
6028!--          = molality * activity coefficient (Jacobson, 2005: eq. 17.20-21)
6029!-- Assume activity coefficient of 1 for water
6030    acth2o = MAX( 0.1_wp, znw / MAX( EPSILON( 1.0_wp ),( znw + zns ) ) )
6031
6032 END FUNCTION acth2o
6033
6034!------------------------------------------------------------------------------!
6035! Description:
6036! ------------
6037!> Calculates the dissolutional growth of particles (i.e. gas transfers to a
6038!> particle surface and dissolves in liquid water on the surface). Treated here
6039!> as a non-equilibrium (time-dependent) process. Gases: HNO3 and NH3
6040!> (Chapter 17.14 in Jacobson, 2005).
6041!
6042!> Called from subroutine condensation.
6043!> Coded by:
6044!> Harri Kokkola (FMI)
6045!------------------------------------------------------------------------------!
6046 SUBROUTINE gpparthno3( ppres, ptemp, paero, pghno3, pgnh3, pcw, pcs, pbeta, ptstep )
6047
6048    IMPLICIT NONE
6049
6050    INTEGER(iwp) ::  ib  !< loop index
6051
6052    REAL(wp) ::  adt          !< timestep
6053    REAL(wp) ::  zc_nh3_c     !< Current NH3 gas concentration
6054    REAL(wp) ::  zc_nh3_int   !< Intermediate NH3 gas concentration
6055    REAL(wp) ::  zc_nh3_n     !< New NH3 gas concentration
6056    REAL(wp) ::  zc_nh3_tot   !< Total NH3 concentration
6057    REAL(wp) ::  zc_hno3_c    !< Current HNO3 gas concentration
6058    REAL(wp) ::  zc_hno3_int  !< Intermediate HNO3 gas concentration
6059    REAL(wp) ::  zc_hno3_n    !< New HNO3 gas concentration
6060    REAL(wp) ::  zc_hno3_tot  !< Total HNO3 concentration
6061    REAL(wp) ::  zdfvap       !< Diffusion coefficient for vapors
6062    REAL(wp) ::  zhlp1        !< intermediate variable
6063    REAL(wp) ::  zhlp2        !< intermediate variable
6064    REAL(wp) ::  zrh          !< relative humidity
6065
6066    REAL(wp), INTENT(in) ::  ppres      !< ambient pressure (Pa)
6067    REAL(wp), INTENT(in) ::  pcs        !< water vapour saturation
6068                                        !< concentration (kg/m3)
6069    REAL(wp), INTENT(in) ::  ptemp      !< ambient temperature (K)
6070    REAL(wp), INTENT(in) ::  ptstep     !< time step (s)
6071
6072    REAL(wp), INTENT(inout) ::  pghno3  !< nitric acid concentration (#/m3)
6073    REAL(wp), INTENT(inout) ::  pgnh3   !< ammonia conc. (#/m3)
6074    REAL(wp), INTENT(inout) ::  pcw     !< water vapour concentration (kg/m3)
6075
6076    REAL(wp), DIMENSION(nbins_aerosol) ::  zac_hno3_ae     !< Activity coefficients for HNO3
6077    REAL(wp), DIMENSION(nbins_aerosol) ::  zac_hhso4_ae    !< Activity coefficients for HHSO4
6078    REAL(wp), DIMENSION(nbins_aerosol) ::  zac_nh3_ae      !< Activity coefficients for NH3
6079    REAL(wp), DIMENSION(nbins_aerosol) ::  zac_nh4hso2_ae  !< Activity coefficients for NH4HSO2
6080    REAL(wp), DIMENSION(nbins_aerosol) ::  zcg_hno3_eq_ae  !< Equilibrium gas concentration: HNO3
6081    REAL(wp), DIMENSION(nbins_aerosol) ::  zcg_nh3_eq_ae   !< Equilibrium gas concentration: NH3
6082    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_hno3_int_ae  !< Intermediate HNO3 aerosol concentration
6083    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_hno3_c_ae    !< Current HNO3 in aerosols
6084    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_hno3_n_ae    !< New HNO3 in aerosols
6085    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_nh3_int_ae   !< Intermediate NH3 aerosol concentration
6086    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_nh3_c_ae     !< Current NH3 in aerosols
6087    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_nh3_n_ae     !< New NH3 in aerosols
6088    REAL(wp), DIMENSION(nbins_aerosol) ::  zkel_hno3_ae    !< Kelvin effect for HNO3
6089    REAL(wp), DIMENSION(nbins_aerosol) ::  zkel_nh3_ae     !< Kelvin effects for NH3
6090    REAL(wp), DIMENSION(nbins_aerosol) ::  zmt_hno3_ae     !< Mass transfer coefficients for HNO3
6091    REAL(wp), DIMENSION(nbins_aerosol) ::  zmt_nh3_ae      !< Mass transfer coefficients for NH3
6092    REAL(wp), DIMENSION(nbins_aerosol) ::  zsat_hno3_ae    !< HNO3 saturation ratio over a surface
6093    REAL(wp), DIMENSION(nbins_aerosol) ::  zsat_nh3_ae     !< NH3 saturation ratio over a surface
6094
6095    REAL(wp), DIMENSION(nbins_aerosol,maxspec) ::  zion_mols   !< Ion molalities from pdfite aerosols
6096
6097    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pbeta !< transitional correction factor for
6098
6099    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero !< Aerosol properties
6100!
6101!-- Initialise:
6102    adt            = ptstep
6103    zac_hhso4_ae   = 0.0_wp
6104    zac_nh3_ae     = 0.0_wp
6105    zac_nh4hso2_ae = 0.0_wp
6106    zac_hno3_ae    = 0.0_wp
6107    zcg_nh3_eq_ae  = 0.0_wp
6108    zcg_hno3_eq_ae = 0.0_wp
6109    zion_mols      = 0.0_wp
6110    zsat_nh3_ae    = 1.0_wp
6111    zsat_hno3_ae   = 1.0_wp
6112!
6113!-- Diffusion coefficient (m2/s)
6114    zdfvap = 5.1111E-10_wp * ptemp**1.75_wp * ( p_0 + 1325.0_wp ) / ppres
6115!
6116!-- Kelvin effects (Jacobson (2005), eq. 16.33)
6117    zkel_hno3_ae(1:nbins_aerosol) = EXP( 4.0_wp * surfw0 * amvhno3 /                               &
6118                                    ( abo * ptemp * paero(1:nbins_aerosol)%dwet ) )
6119    zkel_nh3_ae(1:nbins_aerosol) = EXP( 4.0_wp * surfw0 * amvnh3 /                                 &
6120                                   ( abo * ptemp * paero(1:nbins_aerosol)%dwet ) )
6121!
6122!-- Current vapour mole concentrations (mol/m3)
6123    zc_hno3_c = pghno3 / avo  ! HNO3
6124    zc_nh3_c = pgnh3 / avo   ! NH3
6125!
6126!-- Current particle mole concentrations (mol/m3)
6127    zc_hno3_c_ae(1:nbins_aerosol) = paero(1:nbins_aerosol)%volc(6) * arhohno3 / amhno3
6128    zc_nh3_c_ae(1:nbins_aerosol) = paero(1:nbins_aerosol)%volc(7) * arhonh3 / amnh3
6129!
6130!-- Total mole concentrations: gas and particle phase
6131    zc_hno3_tot = zc_hno3_c + SUM( zc_hno3_c_ae(1:nbins_aerosol) )
6132    zc_nh3_tot = zc_nh3_c + SUM( zc_nh3_c_ae(1:nbins_aerosol) )
6133!
6134!-- Relative humidity [0-1]
6135    zrh = pcw / pcs
6136!
6137!-- Mass transfer coefficients (Jacobson, Eq. 16.64)
6138    zmt_hno3_ae(:) = 2.0_wp * pi * paero(:)%dwet * zdfvap * paero(:)%numc * pbeta(:)
6139    zmt_nh3_ae(:)  = 2.0_wp * pi * paero(:)%dwet * zdfvap * paero(:)%numc * pbeta(:)
6140
6141!
6142!-- Get the equilibrium concentrations above aerosols
6143    CALL nitrate_ammonium_equilibrium( zrh, ptemp, paero, zcg_hno3_eq_ae, zcg_nh3_eq_ae,           &
6144                                       zac_hno3_ae, zac_nh3_ae, zac_nh4hso2_ae, zac_hhso4_ae,      &
6145                                       zion_mols )
6146!
6147!-- Calculate NH3 and HNO3 saturation ratios for aerosols
6148    CALL nitrate_ammonium_saturation( ptemp, paero, zac_hno3_ae, zac_nh4hso2_ae, zac_hhso4_ae,     &
6149                                      zcg_hno3_eq_ae, zc_hno3_c_ae, zc_nh3_c_ae, zkel_hno3_ae,     &
6150                                      zkel_nh3_ae, zsat_hno3_ae, zsat_nh3_ae )
6151!
6152!-- Intermediate gas concentrations of HNO3 and NH3
6153    zhlp1 = SUM( zc_hno3_c_ae(:) / ( 1.0_wp + adt * zmt_hno3_ae(:) * zsat_hno3_ae(:) ) )
6154    zhlp2 = SUM( zmt_hno3_ae(:) / ( 1.0_wp + adt * zmt_hno3_ae(:) * zsat_hno3_ae(:) ) )
6155    zc_hno3_int = ( zc_hno3_tot - zhlp1 ) / ( 1.0_wp + adt * zhlp2 )
6156
6157    zhlp1 = SUM( zc_nh3_c_ae(:) / ( 1.0_wp + adt * zmt_nh3_ae(:) * zsat_nh3_ae(:) ) )
6158    zhlp2 = SUM( zmt_nh3_ae(:) / ( 1.0_wp + adt * zmt_nh3_ae(:) * zsat_nh3_ae(:) ) )
6159    zc_nh3_int = ( zc_nh3_tot - zhlp1 )/( 1.0_wp + adt * zhlp2 )
6160
6161    zc_hno3_int = MIN( zc_hno3_int, zc_hno3_tot )
6162    zc_nh3_int = MIN( zc_nh3_int, zc_nh3_tot )
6163!
6164!-- Calculate the new concentration on aerosol particles
6165    zc_hno3_int_ae = zc_hno3_c_ae
6166    zc_nh3_int_ae = zc_nh3_c_ae
6167    DO  ib = 1, nbins_aerosol
6168       zc_hno3_int_ae(ib) = ( zc_hno3_c_ae(ib) + adt * zmt_hno3_ae(ib) * zc_hno3_int ) /           &
6169                            ( 1.0_wp + adt * zmt_hno3_ae(ib) * zsat_hno3_ae(ib) )
6170       zc_nh3_int_ae(ib) = ( zc_nh3_c_ae(ib) + adt * zmt_nh3_ae(ib) * zc_nh3_int ) /               &
6171                           ( 1.0_wp + adt * zmt_nh3_ae(ib) * zsat_nh3_ae(ib) )
6172    ENDDO
6173
6174    zc_hno3_int_ae(:) = MAX( zc_hno3_int_ae(:), 0.0_wp )
6175    zc_nh3_int_ae(:) = MAX( zc_nh3_int_ae(:), 0.0_wp )
6176!
6177!-- Final molar gas concentration and molar particle concentration of HNO3
6178    zc_hno3_n   = zc_hno3_int
6179    zc_hno3_n_ae = zc_hno3_int_ae
6180!
6181!-- Final molar gas concentration and molar particle concentration of NH3
6182    zc_nh3_n   = zc_nh3_int
6183    zc_nh3_n_ae = zc_nh3_int_ae
6184!
6185!-- Model timestep reached - update the gas concentrations
6186    pghno3 = zc_hno3_n * avo
6187    pgnh3  = zc_nh3_n * avo
6188!
6189!-- Update the particle concentrations
6190    DO  ib = start_subrange_1a, end_subrange_2b
6191       paero(ib)%volc(6) = zc_hno3_n_ae(ib) * amhno3 / arhohno3
6192       paero(ib)%volc(7) = zc_nh3_n_ae(ib) * amnh3 / arhonh3
6193    ENDDO
6194
6195 END SUBROUTINE gpparthno3
6196!------------------------------------------------------------------------------!
6197! Description:
6198! ------------
6199!> Calculate the equilibrium concentrations above aerosols (reference?)
6200!------------------------------------------------------------------------------!
6201 SUBROUTINE nitrate_ammonium_equilibrium( prh, ptemp, ppart, pcg_hno3_eq, pcg_nh3_eq, pgamma_hno3, &
6202                                          pgamma_nh4, pgamma_nh4hso2, pgamma_hhso4, pmols )
6203
6204    IMPLICIT NONE
6205
6206    INTEGER(iwp) ::  ib  !< loop index: aerosol bins
6207
6208    REAL(wp) ::  zhlp         !< intermediate variable
6209    REAL(wp) ::  zp_hcl       !< Equilibrium vapor pressures (Pa) of HCl
6210    REAL(wp) ::  zp_hno3      !< Equilibrium vapor pressures (Pa) of HNO3
6211    REAL(wp) ::  zp_nh3       !< Equilibrium vapor pressures (Pa) of NH3
6212    REAL(wp) ::  zwatertotal  !< Total water in particles (mol/m3)
6213
6214    REAL(wp), INTENT(in) ::  prh    !< relative humidity
6215    REAL(wp), INTENT(in) ::  ptemp  !< ambient temperature (K)
6216
6217    REAL(wp), DIMENSION(maxspec) ::  zgammas  !< Activity coefficients
6218    REAL(wp), DIMENSION(maxspec) ::  zions    !< molar concentration of ion (mol/m3)
6219
6220    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pcg_nh3_eq      !< equilibrium molar
6221                                                                          !< concentration: of NH3
6222    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pcg_hno3_eq     !< of HNO3
6223    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pgamma_hhso4    !< activity coeff. of HHSO4
6224    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pgamma_nh4      !< activity coeff. of NH3
6225    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pgamma_nh4hso2  !< activity coeff. of NH4HSO2
6226    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pgamma_hno3     !< activity coeff. of HNO3
6227
6228    REAL(wp), DIMENSION(nbins_aerosol,maxspec), INTENT(inout) ::  pmols  !< Ion molalities
6229
6230    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  ppart  !< Aerosol properties
6231
6232    zgammas     = 0.0_wp
6233    zhlp        = 0.0_wp
6234    zions       = 0.0_wp
6235    zp_hcl      = 0.0_wp
6236    zp_hno3     = 0.0_wp
6237    zp_nh3      = 0.0_wp
6238    zwatertotal = 0.0_wp
6239
6240    DO  ib = 1, nbins_aerosol
6241
6242       IF ( ppart(ib)%numc < nclim )  CYCLE
6243!
6244!--    Ion molar concentrations: 2*H2SO4 + CL + NO3 - Na - NH4
6245       zhlp = 2.0_wp * ppart(ib)%volc(1) * arhoh2so4 / amh2so4 + ppart(ib)%volc(5) * arhoss / amss &
6246              + ppart(ib)%volc(6) * arhohno3 / amhno3 - ppart(ib)%volc(5) * arhoss / amss -        &
6247              ppart(ib)%volc(7) * arhonh3 / amnh3
6248
6249       zions(1) = zhlp                                   ! H+
6250       zions(2) = ppart(ib)%volc(7) * arhonh3 / amnh3     ! NH4+
6251       zions(3) = ppart(ib)%volc(5) * arhoss / amss       ! Na+
6252       zions(4) = ppart(ib)%volc(1) * arhoh2so4 / amh2so4 ! SO4(2-)
6253       zions(5) = 0.0_wp                                 ! HSO4-
6254       zions(6) = ppart(ib)%volc(6) * arhohno3 / amhno3   ! NO3-
6255       zions(7) = ppart(ib)%volc(5) * arhoss / amss       ! Cl-
6256
6257       zwatertotal = ppart(ib)%volc(8) * arhoh2o / amh2o
6258       IF ( zwatertotal > 1.0E-30_wp )  THEN
6259          CALL inorganic_pdfite( prh, ptemp, zions, zwatertotal, zp_hno3, zp_hcl, zp_nh3, zgammas, &
6260                                 pmols(ib,:) )
6261       ENDIF
6262!
6263!--    Activity coefficients
6264       pgamma_hno3(ib)    = zgammas(1)  ! HNO3
6265       pgamma_nh4(ib)     = zgammas(3)  ! NH3
6266       pgamma_nh4hso2(ib) = zgammas(6)  ! NH4HSO2
6267       pgamma_hhso4(ib)   = zgammas(7)  ! HHSO4
6268!
6269!--    Equilibrium molar concentrations (mol/m3) from equlibrium pressures (Pa)
6270       pcg_hno3_eq(ib) = zp_hno3 / ( argas * ptemp )
6271       pcg_nh3_eq(ib) = zp_nh3 / ( argas * ptemp )
6272
6273    ENDDO
6274
6275  END SUBROUTINE nitrate_ammonium_equilibrium
6276
6277!------------------------------------------------------------------------------!
6278! Description:
6279! ------------
6280!> Calculate saturation ratios of NH4 and HNO3 for aerosols
6281!------------------------------------------------------------------------------!
6282 SUBROUTINE nitrate_ammonium_saturation( ptemp, ppart, pachno3, pacnh4hso2, pachhso4, pchno3eq,    &
6283                                         pchno3, pc_nh3, pkelhno3, pkelnh3, psathno3, psatnh3 )
6284
6285    IMPLICIT NONE
6286
6287    INTEGER(iwp) :: ib   !< running index for aerosol bins
6288
6289    REAL(wp) ::  k_ll_h2o   !< equilibrium constants of equilibrium reactions:
6290                            !< H2O(aq) <--> H+ + OH- (mol/kg)
6291    REAL(wp) ::  k_ll_nh3   !< NH3(aq) + H2O(aq) <--> NH4+ + OH- (mol/kg)
6292    REAL(wp) ::  k_gl_nh3   !< NH3(g) <--> NH3(aq) (mol/kg/atm)
6293    REAL(wp) ::  k_gl_hno3  !< HNO3(g) <--> H+ + NO3- (mol2/kg2/atm)
6294    REAL(wp) ::  zmol_no3   !< molality of NO3- (mol/kg)
6295    REAL(wp) ::  zmol_h     !< molality of H+ (mol/kg)
6296    REAL(wp) ::  zmol_so4   !< molality of SO4(2-) (mol/kg)
6297    REAL(wp) ::  zmol_cl    !< molality of Cl- (mol/kg)
6298    REAL(wp) ::  zmol_nh4   !< molality of NH4+ (mol/kg)
6299    REAL(wp) ::  zmol_na    !< molality of Na+ (mol/kg)
6300    REAL(wp) ::  zhlp1      !< intermediate variable
6301    REAL(wp) ::  zhlp2      !< intermediate variable
6302    REAL(wp) ::  zhlp3      !< intermediate variable
6303    REAL(wp) ::  zxi        !< particle mole concentration ratio: (NH3+SS)/H2SO4
6304    REAL(wp) ::  zt0        !< reference temp
6305
6306    REAL(wp), PARAMETER ::  a1 = -22.52_wp     !<
6307    REAL(wp), PARAMETER ::  a2 = -1.50_wp      !<
6308    REAL(wp), PARAMETER ::  a3 = 13.79_wp      !<
6309    REAL(wp), PARAMETER ::  a4 = 29.17_wp      !<
6310    REAL(wp), PARAMETER ::  b1 = 26.92_wp      !<
6311    REAL(wp), PARAMETER ::  b2 = 26.92_wp      !<
6312    REAL(wp), PARAMETER ::  b3 = -5.39_wp      !<
6313    REAL(wp), PARAMETER ::  b4 = 16.84_wp      !<
6314    REAL(wp), PARAMETER ::  K01 = 1.01E-14_wp  !<
6315    REAL(wp), PARAMETER ::  K02 = 1.81E-5_wp   !<
6316    REAL(wp), PARAMETER ::  K03 = 57.64_wp     !<
6317    REAL(wp), PARAMETER ::  K04 = 2.51E+6_wp   !<
6318
6319    REAL(wp), INTENT(in) ::  ptemp  !< ambient temperature (K)
6320
6321    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pachhso4    !< activity coeff. of HHSO4
6322    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pacnh4hso2  !< activity coeff. of NH4HSO2
6323    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pachno3     !< activity coeff. of HNO3
6324    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pchno3eq    !< eq. surface concentration: HNO3
6325    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pchno3      !< current particle mole
6326                                                                   !< concentration of HNO3 (mol/m3)
6327    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pc_nh3      !< of NH3 (mol/m3)
6328    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pkelhno3    !< Kelvin effect for HNO3
6329    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pkelnh3     !< Kelvin effect for NH3
6330
6331    REAL(wp), DIMENSION(nbins_aerosol), INTENT(out) ::  psathno3 !< saturation ratio of HNO3
6332    REAL(wp), DIMENSION(nbins_aerosol), INTENT(out) ::  psatnh3  !< saturation ratio of NH3
6333
6334    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  ppart  !< Aerosol properties
6335
6336    zmol_cl  = 0.0_wp
6337    zmol_h   = 0.0_wp
6338    zmol_na  = 0.0_wp
6339    zmol_nh4 = 0.0_wp
6340    zmol_no3 = 0.0_wp
6341    zmol_so4 = 0.0_wp
6342    zt0      = 298.15_wp
6343    zxi      = 0.0_wp
6344!
6345!-- Calculates equlibrium rate constants based on Table B.7 in Jacobson (2005):
6346!-- K^ll_H20, K^ll_NH3, K^gl_NH3, K^gl_HNO3
6347    zhlp1 = zt0 / ptemp
6348    zhlp2 = zhlp1 - 1.0_wp
6349    zhlp3 = 1.0_wp + LOG( zhlp1 ) - zhlp1
6350
6351    k_ll_h2o  = K01 * EXP( a1 * zhlp2 + b1 * zhlp3 )
6352    k_ll_nh3  = K02 * EXP( a2 * zhlp2 + b2 * zhlp3 )
6353    k_gl_nh3  = K03 * EXP( a3 * zhlp2 + b3 * zhlp3 )
6354    k_gl_hno3 = K04 * EXP( a4 * zhlp2 + b4 * zhlp3 )
6355
6356    DO  ib = 1, nbins_aerosol
6357
6358       IF ( ppart(ib)%numc > nclim  .AND.  ppart(ib)%volc(8) > 1.0E-30_wp  )  THEN
6359!
6360!--       Molality of H+ and NO3-
6361          zhlp1 = pc_nh3(ib) * amnh3 + ppart(ib)%volc(1) * arhoh2so4 + ppart(ib)%volc(2) * arhooc  &
6362                  + ppart(ib)%volc(5) * arhoss + ppart(ib)%volc(8) * arhoh2o
6363          zmol_no3 = pchno3(ib) / zhlp1  !< mol/kg
6364!
6365!--       Particle mole concentration ratio: (NH3+SS)/H2SO4
6366          zxi = ( pc_nh3(ib) + ppart(ib)%volc(5) * arhoss / amss ) / ( ppart(ib)%volc(1) *         &
6367                  arhoh2so4 / amh2so4 )
6368
6369          IF ( zxi <= 2.0_wp )  THEN
6370!
6371!--          Molality of SO4(2-)
6372             zhlp1 = pc_nh3(ib) * amnh3 + pchno3(ib) * amhno3 + ppart(ib)%volc(2) * arhooc +       &
6373                     ppart(ib)%volc(5) * arhoss + ppart(ib)%volc(8) * arhoh2o
6374             zmol_so4 = ( ppart(ib)%volc(1) * arhoh2so4 / amh2so4 ) / zhlp1
6375!
6376!--          Molality of Cl-
6377             zhlp1 = pc_nh3(ib) * amnh3 + pchno3(ib) * amhno3 + ppart(ib)%volc(2) * arhooc +       &
6378                     ppart(ib)%volc(1) * arhoh2so4 + ppart(ib)%volc(8) * arhoh2o
6379             zmol_cl = ( ppart(ib)%volc(5) * arhoss / amss ) / zhlp1
6380!
6381!--          Molality of NH4+
6382             zhlp1 =  pchno3(ib) * amhno3 + ppart(ib)%volc(1) * arhoh2so4 + ppart(ib)%volc(2) *    &
6383                      arhooc + ppart(ib)%volc(5) * arhoss + ppart(ib)%volc(8) * arhoh2o
6384             zmol_nh4 = pc_nh3(ib) / zhlp1
6385!
6386!--          Molality of Na+
6387             zmol_na = zmol_cl
6388!
6389!--          Molality of H+
6390             zmol_h = 2.0_wp * zmol_so4 + zmol_no3 + zmol_cl - ( zmol_nh4 + zmol_na )
6391
6392          ELSE
6393
6394             zhlp2 = pkelhno3(ib) * zmol_no3 * pachno3(ib)**2
6395
6396             IF ( zhlp2 > 1.0E-30_wp )  THEN
6397                zmol_h = k_gl_hno3 * pchno3eq(ib) / zhlp2 ! Eq. 17.38
6398             ELSE
6399                zmol_h = 0.0_wp
6400             ENDIF
6401
6402          ENDIF
6403
6404          zhlp1 = ppart(ib)%volc(8) * arhoh2o * argas * ptemp * k_gl_hno3
6405!
6406!--       Saturation ratio for NH3 and for HNO3
6407          IF ( zmol_h > 0.0_wp )  THEN
6408             zhlp2 = pkelnh3(ib) / ( zhlp1 * zmol_h )
6409             zhlp3 = k_ll_h2o / ( k_ll_nh3 + k_gl_nh3 )
6410             psatnh3(ib) = zhlp2 * ( ( pacnh4hso2(ib) / pachhso4(ib) )**2 ) * zhlp3
6411             psathno3(ib) = ( pkelhno3(ib) * zmol_h * pachno3(ib)**2 ) / zhlp1
6412          ELSE
6413             psatnh3(ib) = 1.0_wp
6414             psathno3(ib) = 1.0_wp
6415          ENDIF
6416       ELSE
6417          psatnh3(ib) = 1.0_wp
6418          psathno3(ib) = 1.0_wp
6419       ENDIF
6420
6421    ENDDO
6422
6423  END SUBROUTINE nitrate_ammonium_saturation
6424
6425!------------------------------------------------------------------------------!
6426! Description:
6427! ------------
6428!> Prototype module for calculating the water content of a mixed inorganic/
6429!> organic particle + equilibrium water vapour pressure above the solution
6430!> (HNO3, HCL, NH3 and representative organic compounds. Efficient calculation
6431!> of the partitioning of species between gas and aerosol. Based in a chamber
6432!> study.
6433!
6434!> Written by Dave Topping. Pure organic component properties predicted by Mark
6435!> Barley based on VOCs predicted in MCM simulations performed by Mike Jenkin.
6436!> Delivered by Gordon McFiggans as Deliverable D22 from WP1.4 in the EU FP6
6437!> EUCAARI Integrated Project.
6438!
6439!> REFERENCES
6440!> Clegg et al. (1998) A Thermodynamic Model of the System H+-NH4+-Na+-SO42- -NO3--Cl--H2O at
6441!>    298.15 K, J. Phys. Chem., 102A, 2155-2171.
6442!> Clegg et al. (2001) Thermodynamic modelling of aqueous aerosols containing electrolytes and
6443!>    dissolved organic compounds. Journal of Aerosol Science 2001;32(6):713-738.
6444!> Topping et al. (2005a) A curved multi-component aerosol hygroscopicity model framework: Part 1 -
6445!>    Inorganic compounds. Atmospheric Chemistry and Physics 2005;5:1205-1222.
6446!> Topping et al. (2005b) A curved multi-component aerosol hygroscopicity model framework: Part 2 -
6447!>    Including organic compounds. Atmospheric Chemistry and Physics 2005;5:1223-1242.
6448!> Wagman et al. (1982). The NBS tables of chemical thermodynamic properties: selected values for
6449!>    inorganic and C₁ and C₂ organic substances in SI units (book)
6450!> Zaveri et al. (2005). A new method for multicomponent activity coefficients of electrolytes in
6451!>    aqueous atmospheric aerosols, JGR, 110, D02201, 2005.
6452!
6453!> Queries concerning the use of this code through Gordon McFiggans,
6454!> g.mcfiggans@manchester.ac.uk,
6455!> Ownership: D. Topping, Centre for Atmospheric Sciences, University of
6456!> Manchester, 2007
6457!
6458!> Rewritten to PALM by Mona Kurppa, UHel, 2017
6459!------------------------------------------------------------------------------!
6460 SUBROUTINE inorganic_pdfite( rh, temp, ions, water_total, press_hno3, press_hcl, press_nh3,       &
6461                              gamma_out, mols_out )
6462
6463    IMPLICIT NONE
6464
6465    INTEGER(iwp) ::  binary_case
6466    INTEGER(iwp) ::  full_complexity
6467
6468    REAL(wp) ::  a                         !< auxiliary variable
6469    REAL(wp) ::  act_product               !< ionic activity coef. product:
6470                                           !< = (gamma_h2so4**3d0) / gamma_hhso4**2d0)
6471    REAL(wp) ::  ammonium_chloride         !<
6472    REAL(wp) ::  ammonium_chloride_eq_frac !<
6473    REAL(wp) ::  ammonium_nitrate          !<
6474    REAL(wp) ::  ammonium_nitrate_eq_frac  !<
6475    REAL(wp) ::  ammonium_sulphate         !<
6476    REAL(wp) ::  ammonium_sulphate_eq_frac !<
6477    REAL(wp) ::  b                         !< auxiliary variable
6478    REAL(wp) ::  binary_h2so4              !< binary H2SO4 activity coeff.
6479    REAL(wp) ::  binary_hcl                !< binary HCL activity coeff.
6480    REAL(wp) ::  binary_hhso4              !< binary HHSO4 activity coeff.
6481    REAL(wp) ::  binary_hno3               !< binary HNO3 activity coeff.
6482    REAL(wp) ::  binary_nh4hso4            !< binary NH4HSO4 activity coeff.
6483    REAL(wp) ::  c                         !< auxiliary variable
6484    REAL(wp) ::  charge_sum                !< sum of ionic charges
6485    REAL(wp) ::  gamma_h2so4               !< activity coefficient
6486    REAL(wp) ::  gamma_hcl                 !< activity coefficient
6487    REAL(wp) ::  gamma_hhso4               !< activity coeffient
6488    REAL(wp) ::  gamma_hno3                !< activity coefficient
6489    REAL(wp) ::  gamma_nh3                 !< activity coefficient
6490    REAL(wp) ::  gamma_nh4hso4             !< activity coefficient
6491    REAL(wp) ::  h_out                     !<
6492    REAL(wp) ::  h_real                    !< new hydrogen ion conc.
6493    REAL(wp) ::  h2so4_hcl                 !< contribution of H2SO4
6494    REAL(wp) ::  h2so4_hno3                !< contribution of H2SO4
6495    REAL(wp) ::  h2so4_nh3                 !< contribution of H2SO4
6496    REAL(wp) ::  h2so4_nh4hso4             !< contribution of H2SO4
6497    REAL(wp) ::  hcl_h2so4                 !< contribution of HCL
6498    REAL(wp) ::  hcl_hhso4                 !< contribution of HCL
6499    REAL(wp) ::  hcl_hno3                  !< contribution of HCL
6500    REAL(wp) ::  hcl_nh4hso4               !< contribution of HCL
6501    REAL(wp) ::  henrys_temp_dep           !< temperature dependence of Henry's Law
6502    REAL(wp) ::  hno3_h2so4                !< contribution of HNO3
6503    REAL(wp) ::  hno3_hcl                  !< contribution of HNO3
6504    REAL(wp) ::  hno3_hhso4                !< contribution of HNO3
6505    REAL(wp) ::  hno3_nh3                  !< contribution of HNO3
6506    REAL(wp) ::  hno3_nh4hso4              !< contribution of HNO3
6507    REAL(wp) ::  hso4_out                  !<
6508    REAL(wp) ::  hso4_real                 !< new bisulphate ion conc.
6509    REAL(wp) ::  hydrochloric_acid         !<
6510    REAL(wp) ::  hydrochloric_acid_eq_frac !<
6511    REAL(wp) ::  k_h                       !< equilibrium constant for H+
6512    REAL(wp) ::  k_hcl                     !< equilibrium constant of HCL
6513    REAL(wp) ::  k_hno3                    !< equilibrium constant of HNO3
6514    REAL(wp) ::  k_nh4                     !< equilibrium constant for NH4+
6515    REAL(wp) ::  k_h2o                     !< equil. const. for water_surface
6516    REAL(wp) ::  ln_h2so4_act              !< gamma_h2so4 = EXP(ln_h2so4_act)
6517    REAL(wp) ::  ln_HCL_act                !< gamma_hcl = EXP( ln_HCL_act )
6518    REAL(wp) ::  ln_hhso4_act              !< gamma_hhso4 = EXP(ln_hhso4_act)
6519    REAL(wp) ::  ln_hno3_act               !< gamma_hno3 = EXP( ln_hno3_act )
6520    REAL(wp) ::  ln_nh4hso4_act            !< gamma_nh4hso4 = EXP( ln_nh4hso4_act )
6521    REAL(wp) ::  molality_ratio_nh3        !< molality ratio of NH3 (NH4+ and H+)
6522    REAL(wp) ::  na2so4_h2so4              !< contribution of Na2SO4
6523    REAL(wp) ::  na2so4_hcl                !< contribution of Na2SO4
6524    REAL(wp) ::  na2so4_hhso4              !< contribution of Na2SO4
6525    REAL(wp) ::  na2so4_hno3               !< contribution of Na2SO4
6526    REAL(wp) ::  na2so4_nh3                !< contribution of Na2SO4
6527    REAL(wp) ::  na2so4_nh4hso4            !< contribution of Na2SO4
6528    REAL(wp) ::  nacl_h2so4                !< contribution of NaCl
6529    REAL(wp) ::  nacl_hcl                  !< contribution of NaCl
6530    REAL(wp) ::  nacl_hhso4                !< contribution of NaCl
6531    REAL(wp) ::  nacl_hno3                 !< contribution of NaCl
6532    REAL(wp) ::  nacl_nh3                  !< contribution of NaCl
6533    REAL(wp) ::  nacl_nh4hso4              !< contribution of NaCl
6534    REAL(wp) ::  nano3_h2so4               !< contribution of NaNO3
6535    REAL(wp) ::  nano3_hcl                 !< contribution of NaNO3
6536    REAL(wp) ::  nano3_hhso4               !< contribution of NaNO3
6537    REAL(wp) ::  nano3_hno3                !< contribution of NaNO3
6538    REAL(wp) ::  nano3_nh3                 !< contribution of NaNO3
6539    REAL(wp) ::  nano3_nh4hso4             !< contribution of NaNO3
6540    REAL(wp) ::  nh42so4_h2so4             !< contribution of NH42SO4
6541    REAL(wp) ::  nh42so4_hcl               !< contribution of NH42SO4
6542    REAL(wp) ::  nh42so4_hhso4             !< contribution of NH42SO4
6543    REAL(wp) ::  nh42so4_hno3              !< contribution of NH42SO4
6544    REAL(wp) ::  nh42so4_nh3               !< contribution of NH42SO4
6545    REAL(wp) ::  nh42so4_nh4hso4           !< contribution of NH42SO4
6546    REAL(wp) ::  nh4cl_h2so4               !< contribution of NH4Cl
6547    REAL(wp) ::  nh4cl_hcl                 !< contribution of NH4Cl
6548    REAL(wp) ::  nh4cl_hhso4               !< contribution of NH4Cl
6549    REAL(wp) ::  nh4cl_hno3                !< contribution of NH4Cl
6550    REAL(wp) ::  nh4cl_nh3                 !< contribution of NH4Cl
6551    REAL(wp) ::  nh4cl_nh4hso4             !< contribution of NH4Cl
6552    REAL(wp) ::  nh4no3_h2so4              !< contribution of NH4NO3
6553    REAL(wp) ::  nh4no3_hcl                !< contribution of NH4NO3
6554    REAL(wp) ::  nh4no3_hhso4              !< contribution of NH4NO3
6555    REAL(wp) ::  nh4no3_hno3               !< contribution of NH4NO3
6556    REAL(wp) ::  nh4no3_nh3                !< contribution of NH4NO3
6557    REAL(wp) ::  nh4no3_nh4hso4            !< contribution of NH4NO3
6558    REAL(wp) ::  nitric_acid               !<
6559    REAL(wp) ::  nitric_acid_eq_frac       !< Equivalent fractions
6560    REAL(wp) ::  press_hcl                 !< partial pressure of HCL
6561    REAL(wp) ::  press_hno3                !< partial pressure of HNO3
6562    REAL(wp) ::  press_nh3                 !< partial pressure of NH3
6563    REAL(wp) ::  rh                        !< relative humidity [0-1]
6564    REAL(wp) ::  root1                     !< auxiliary variable
6565    REAL(wp) ::  root2                     !< auxiliary variable
6566    REAL(wp) ::  so4_out                   !<
6567    REAL(wp) ::  so4_real                  !< new sulpate ion concentration
6568    REAL(wp) ::  sodium_chloride           !<
6569    REAL(wp) ::  sodium_chloride_eq_frac   !<
6570    REAL(wp) ::  sodium_nitrate            !<
6571    REAL(wp) ::  sodium_nitrate_eq_frac    !<
6572    REAL(wp) ::  sodium_sulphate           !<
6573    REAL(wp) ::  sodium_sulphate_eq_frac   !<
6574    REAL(wp) ::  solutes                   !<
6575    REAL(wp) ::  sulphuric_acid            !<
6576    REAL(wp) ::  sulphuric_acid_eq_frac    !<
6577    REAL(wp) ::  temp                      !< temperature
6578    REAL(wp) ::  water_total               !<
6579
6580    REAL(wp), DIMENSION(:) ::  gamma_out !< Activity coefficient for calculating the non-ideal
6581                                         !< dissociation constants
6582                                         !< 1: HNO3, 2: HCL, 3: NH4+/H+ (NH3), 4: HHSO4**2/H2SO4,
6583                                         !< 5: H2SO4**3/HHSO4**2, 6: NH4HSO2, 7: HHSO4
6584    REAL(wp), DIMENSION(:) ::  ions      !< ion molarities (mol/m3): 1: H+, 2: NH4+, 3: Na+,
6585                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
6586    REAL(wp), DIMENSION(7) ::  ions_mol  !< ion molalities (mol/kg): 1: H+, 2: NH4+, 3: Na+,
6587                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
6588    REAL(wp), DIMENSION(:) ::  mols_out  !< ion molality output (mol/kg): 1: H+, 2: NH4+, 3: Na+,
6589                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
6590!
6591!-- Value initialisation
6592    binary_h2so4    = 0.0_wp
6593    binary_hcl      = 0.0_wp
6594    binary_hhso4    = 0.0_wp
6595    binary_hno3     = 0.0_wp
6596    binary_nh4hso4  = 0.0_wp
6597    henrys_temp_dep = ( 1.0_wp / temp - 0.0033557_wp ) ! 1/T - 1/298 K
6598    hcl_hno3        = 1.0_wp
6599    h2so4_hno3      = 1.0_wp
6600    nh42so4_hno3    = 1.0_wp
6601    nh4no3_hno3     = 1.0_wp
6602    nh4cl_hno3      = 1.0_wp
6603    na2so4_hno3     = 1.0_wp
6604    nano3_hno3      = 1.0_wp
6605    nacl_hno3       = 1.0_wp
6606    hno3_hcl        = 1.0_wp
6607    h2so4_hcl       = 1.0_wp
6608    nh42so4_hcl     = 1.0_wp
6609    nh4no3_hcl      = 1.0_wp
6610    nh4cl_hcl       = 1.0_wp
6611    na2so4_hcl      = 1.0_wp
6612    nano3_hcl       = 1.0_wp
6613    nacl_hcl        = 1.0_wp
6614    hno3_nh3        = 1.0_wp
6615    h2so4_nh3       = 1.0_wp
6616    nh42so4_nh3     = 1.0_wp
6617    nh4no3_nh3      = 1.0_wp
6618    nh4cl_nh3       = 1.0_wp
6619    na2so4_nh3      = 1.0_wp
6620    nano3_nh3       = 1.0_wp
6621    nacl_nh3        = 1.0_wp
6622    hno3_hhso4      = 1.0_wp
6623    hcl_hhso4       = 1.0_wp
6624    nh42so4_hhso4   = 1.0_wp
6625    nh4no3_hhso4    = 1.0_wp
6626    nh4cl_hhso4     = 1.0_wp
6627    na2so4_hhso4    = 1.0_wp
6628    nano3_hhso4     = 1.0_wp
6629    nacl_hhso4      = 1.0_wp
6630    hno3_h2so4      = 1.0_wp
6631    hcl_h2so4       = 1.0_wp
6632    nh42so4_h2so4   = 1.0_wp
6633    nh4no3_h2so4    = 1.0_wp
6634    nh4cl_h2so4     = 1.0_wp
6635    na2so4_h2so4    = 1.0_wp
6636    nano3_h2so4     = 1.0_wp
6637    nacl_h2so4      = 1.0_wp
6638!
6639!-- New NH3 variables
6640    hno3_nh4hso4    = 1.0_wp
6641    hcl_nh4hso4     = 1.0_wp
6642    h2so4_nh4hso4   = 1.0_wp
6643    nh42so4_nh4hso4 = 1.0_wp
6644    nh4no3_nh4hso4  = 1.0_wp
6645    nh4cl_nh4hso4   = 1.0_wp
6646    na2so4_nh4hso4  = 1.0_wp
6647    nano3_nh4hso4   = 1.0_wp
6648    nacl_nh4hso4    = 1.0_wp
6649!
6650!-- Juha Tonttila added
6651    mols_out   = 0.0_wp
6652    press_hno3 = 0.0_wp  !< Initialising vapour pressures over the
6653    press_hcl  = 0.0_wp  !< multicomponent particle
6654    press_nh3  = 0.0_wp
6655    gamma_out  = 1.0_wp  !< i.e. don't alter the ideal mixing ratios if there's nothing there.
6656!
6657!-- 1) - COMPOSITION DEFINITIONS
6658!
6659!-- a) Inorganic ion pairing:
6660!-- In order to calculate the water content, which is also used in calculating vapour pressures, one
6661!-- needs to pair the anions and cations for use in the ZSR mixing rule. The equation provided by
6662!-- Clegg et al. (2001) is used for ion pairing. The solutes chosen comprise of 9 inorganic salts
6663!-- and acids which provide a pairing between each anion and cation: (NH4)2SO4, NH4NO3, NH4Cl,
6664!-- Na2SO4, NaNO3, NaCl, H2SO4, HNO3, HCL. The organic compound is treated as a seperate solute.
6665!-- Ions: 1: H+, 2: NH4+, 3: Na+, 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
6666!
6667    charge_sum = ions(1) + ions(2) + ions(3) + 2.0_wp * ions(4) + ions(5) + ions(6) + ions(7)
6668    nitric_acid       = ( 2.0_wp * ions(1) * ions(6) ) / charge_sum
6669    hydrochloric_acid = ( 2.0_wp * ions(1) * ions(7) ) / charge_sum
6670    sulphuric_acid    = ( 2.0_wp * ions(1) * ions(4) ) / charge_sum
6671    ammonium_sulphate = ( 2.0_wp * ions(2) * ions(4) ) / charge_sum
6672    ammonium_nitrate  = ( 2.0_wp * ions(2) * ions(6) ) / charge_sum
6673    ammonium_chloride = ( 2.0_wp * ions(2) * ions(7) ) / charge_sum
6674    sodium_sulphate   = ( 2.0_wp * ions(3) * ions(4) ) / charge_sum
6675    sodium_nitrate    = ( 2.0_wp * ions(3) * ions(6) ) / charge_sum
6676    sodium_chloride   = ( 2.0_wp * ions(3) * ions(7) ) / charge_sum
6677    solutes = 0.0_wp
6678    solutes = 3.0_wp * sulphuric_acid    + 2.0_wp * hydrochloric_acid + 2.0_wp * nitric_acid +     &
6679              3.0_wp * ammonium_sulphate + 2.0_wp * ammonium_nitrate + 2.0_wp * ammonium_chloride +&
6680              3.0_wp * sodium_sulphate   + 2.0_wp * sodium_nitrate   + 2.0_wp * sodium_chloride
6681!
6682!-- b) Inorganic equivalent fractions:
6683!-- These values are calculated so that activity coefficients can be expressed by a linear additive
6684!-- rule, thus allowing more efficient calculations and future expansion (see more detailed
6685!-- description below)
6686    nitric_acid_eq_frac       = 2.0_wp * nitric_acid / solutes
6687    hydrochloric_acid_eq_frac = 2.0_wp * hydrochloric_acid / solutes
6688    sulphuric_acid_eq_frac    = 3.0_wp * sulphuric_acid / solutes
6689    ammonium_sulphate_eq_frac = 3.0_wp * ammonium_sulphate / solutes
6690    ammonium_nitrate_eq_frac  = 2.0_wp * ammonium_nitrate / solutes
6691    ammonium_chloride_eq_frac = 2.0_wp * ammonium_chloride / solutes
6692    sodium_sulphate_eq_frac   = 3.0_wp * sodium_sulphate / solutes
6693    sodium_nitrate_eq_frac    = 2.0_wp * sodium_nitrate / solutes
6694    sodium_chloride_eq_frac   = 2.0_wp * sodium_chloride / solutes
6695!
6696!-- Inorganic ion molalities
6697    ions_mol(1) = ions(1) / ( water_total * 18.01528E-3_wp )   ! H+
6698    ions_mol(2) = ions(2) / ( water_total * 18.01528E-3_wp )   ! NH4+
6699    ions_mol(3) = ions(3) / ( water_total * 18.01528E-3_wp )   ! Na+
6700    ions_mol(4) = ions(4) / ( water_total * 18.01528E-3_wp )   ! SO4(2-)
6701    ions_mol(5) = ions(5) / ( water_total * 18.01528E-3_wp )   ! HSO4(2-)
6702    ions_mol(6) = ions(6) / ( water_total * 18.01528E-3_wp )   !  NO3-
6703    ions_mol(7) = ions(7) / ( water_total * 18.01528E-3_wp )   ! Cl-
6704
6705!-- ***
6706!-- At this point we may need to introduce a method for prescribing H+ when there is no 'real' value
6707!-- for H+..i.e. in the sulphate poor domain. This will give a value for solve quadratic proposed by
6708!-- Zaveri et al. 2005
6709!
6710!-- 2) - WATER CALCULATION
6711!
6712!-- a) The water content is calculated using the ZSR rule with solute concentrations calculated
6713!-- using 1a above. Whilst the usual approximation of ZSR relies on binary data consisting of 5th or
6714!-- higher order polynomials, in this code 4 different RH regimes are used, each housing cubic
6715!-- equations for the water associated with each solute listed above. Binary water contents for
6716!-- inorganic components were calculated using AIM online (Clegg et al 1998). The water associated
6717!-- with the organic compound is calculated assuming ideality and that aw = RH.
6718!
6719!-- b) Molality of each inorganic ion and organic solute (initial input) is calculated for use in
6720!-- vapour pressure calculation.
6721!
6722!-- 3) - BISULPHATE ION DISSOCIATION CALCULATION
6723!
6724!-- The dissociation of the bisulphate ion is calculated explicitly. A solution to the equilibrium
6725!-- equation between the bisulphate ion, hydrogen ion and sulphate ion is found using tabulated
6726!-- equilibrium constants (referenced). It is necessary to calculate the activity coefficients of
6727!-- HHSO4 and H2SO4 in a non-iterative manner. These are calculated using the same format as
6728!-- described in 4) below, where both activity coefficients were fit to the output from ADDEM
6729!-- (Topping et al 2005a,b) covering an extensive composition space, providing the activity
6730!-- coefficients and bisulphate ion dissociation as a function of equivalent mole fractions and
6731!-- relative humidity.
6732!
6733!-- NOTE: the flags "binary_case" and "full_complexity" are not used in this prototype. They are
6734!-- used for simplification of the fit expressions when using limited composition regions. This
6735!-- section of code calculates the bisulphate ion concentration.
6736!
6737    IF ( ions(1) > 0.0_wp .AND. ions(4) > 0.0_wp ) THEN
6738!
6739!--    HHSO4:
6740       binary_case = 1
6741       IF ( rh > 0.1_wp  .AND.  rh < 0.9_wp )  THEN
6742          binary_hhso4 = -4.9521_wp * rh**3 + 9.2881_wp * rh**2 - 10.777_wp * rh + 6.0534_wp
6743       ELSEIF ( rh >= 0.9_wp  .AND.  rh < 0.955_wp )  THEN
6744          binary_hhso4 = -6.3777_wp * rh + 5.962_wp
6745       ELSEIF ( rh >= 0.955_wp  .AND.  rh < 0.99_wp )  THEN
6746          binary_hhso4 = 2367.2_wp * rh**3 - 6849.7_wp * rh**2 + 6600.9_wp * rh - 2118.7_wp
6747       ELSEIF ( rh >= 0.99_wp  .AND.  rh < 0.9999_wp )  THEN
6748          binary_hhso4 = 3E-7_wp * rh**5 - 2E-5_wp * rh**4 + 0.0004_wp * rh**3 - 0.0035_wp * rh**2 &
6749                         + 0.0123_wp * rh - 0.3025_wp
6750       ENDIF
6751
6752       IF ( nitric_acid > 0.0_wp )  THEN
6753          hno3_hhso4 = -4.2204_wp * rh**4 + 12.193_wp * rh**3 - 12.481_wp * rh**2 + 6.459_wp * rh  &
6754                       - 1.9004_wp
6755       ENDIF
6756
6757       IF ( hydrochloric_acid > 0.0_wp )  THEN
6758          hcl_hhso4 = -54.845_wp * rh**7 + 209.54_wp * rh**6 - 336.59_wp * rh**5 + 294.21_wp *     &
6759                      rh**4 - 150.07_wp * rh**3 + 43.767_wp * rh**2 - 6.5495_wp * rh + 0.60048_wp
6760       ENDIF
6761
6762       IF ( ammonium_sulphate > 0.0_wp )  THEN
6763          nh42so4_hhso4 = 16.768_wp * rh**3 - 28.75_wp * rh**2 + 20.011_wp * rh - 8.3206_wp
6764       ENDIF
6765
6766       IF ( ammonium_nitrate > 0.0_wp )  THEN
6767          nh4no3_hhso4 = -17.184_wp * rh**4 + 56.834_wp * rh**3 - 65.765_wp * rh**2 +              &
6768                         35.321_wp * rh - 9.252_wp
6769       ENDIF
6770
6771       IF (ammonium_chloride > 0.0_wp )  THEN
6772          IF ( rh < 0.2_wp .AND. rh >= 0.1_wp )  THEN
6773             nh4cl_hhso4 = 3.2809_wp * rh - 2.0637_wp
6774          ELSEIF ( rh >= 0.2_wp .AND. rh < 0.99_wp )  THEN
6775             nh4cl_hhso4 = -1.2981_wp * rh**3 + 4.7461_wp * rh**2 - 2.3269_wp * rh - 1.1259_wp
6776          ENDIF
6777       ENDIF
6778
6779       IF ( sodium_sulphate > 0.0_wp )  THEN
6780          na2so4_hhso4 = 118.87_wp * rh**6 - 358.63_wp * rh**5 + 435.85_wp * rh**4 - 272.88_wp *   &
6781                         rh**3 + 94.411_wp * rh**2 - 18.21_wp * rh + 0.45935_wp
6782       ENDIF
6783
6784       IF ( sodium_nitrate > 0.0_wp )  THEN
6785          IF ( rh < 0.2_wp  .AND.  rh >= 0.1_wp )  THEN
6786             nano3_hhso4 = 4.8456_wp * rh - 2.5773_wp
6787          ELSEIF ( rh >= 0.2_wp  .AND.  rh < 0.99_wp )  THEN
6788             nano3_hhso4 = 0.5964_wp * rh**3 - 0.38967_wp * rh**2 + 1.7918_wp * rh - 1.9691_wp
6789          ENDIF
6790       ENDIF
6791
6792       IF ( sodium_chloride > 0.0_wp )  THEN
6793          IF ( rh < 0.2_wp )  THEN
6794             nacl_hhso4 = 0.51995_wp * rh - 1.3981_wp
6795          ELSEIF ( rh >= 0.2_wp  .AND.  rh < 0.99_wp )  THEN
6796             nacl_hhso4 = 1.6539_wp * rh - 1.6101_wp
6797          ENDIF
6798       ENDIF
6799
6800       ln_hhso4_act = binary_hhso4 + nitric_acid_eq_frac * hno3_hhso4 +                            &
6801                      hydrochloric_acid_eq_frac * hcl_hhso4 +                                      &
6802                      ammonium_sulphate_eq_frac * nh42so4_hhso4 +                                  &
6803                      ammonium_nitrate_eq_frac  * nh4no3_hhso4 +                                   &
6804                      ammonium_chloride_eq_frac * nh4cl_hhso4 +                                    &
6805                      sodium_sulphate_eq_frac   * na2so4_hhso4 +                                   &
6806                      sodium_nitrate_eq_frac * nano3_hhso4 + sodium_chloride_eq_frac   * nacl_hhso4
6807
6808       gamma_hhso4 = EXP( ln_hhso4_act )   ! molal activity coefficient of HHSO4
6809
6810!--    H2SO4 (sulphuric acid):
6811       IF ( rh >= 0.1_wp  .AND.  rh < 0.9_wp )  THEN
6812          binary_h2so4 = 2.4493_wp * rh**2 - 6.2326_wp * rh + 2.1763_wp
6813       ELSEIF ( rh >= 0.9_wp  .AND.  rh < 0.98 )  THEN
6814          binary_h2so4 = 914.68_wp * rh**3 - 2502.3_wp * rh**2 + 2281.9_wp * rh - 695.11_wp
6815       ELSEIF ( rh >= 0.98  .AND.  rh < 0.9999 )  THEN
6816          binary_h2so4 = 3.0E-8_wp * rh**4 - 5E-6_wp * rh**3 + 0.0003_wp * rh**2 - 0.0022_wp *     &
6817                         rh - 1.1305_wp
6818       ENDIF
6819
6820       IF ( nitric_acid > 0.0_wp )  THEN
6821          hno3_h2so4 = - 16.382_wp * rh**5 + 46.677_wp * rh**4 - 54.149_wp * rh**3 + 34.36_wp *    &
6822                         rh**2 - 12.54_wp * rh + 2.1368_wp
6823       ENDIF
6824
6825       IF ( hydrochloric_acid > 0.0_wp )  THEN
6826          hcl_h2so4 = - 14.409_wp * rh**5 + 42.804_wp * rh**4 - 47.24_wp * rh**3 + 24.668_wp *     &
6827                        rh**2 - 5.8015_wp * rh + 0.084627_wp
6828       ENDIF
6829
6830       IF ( ammonium_sulphate > 0.0_wp )  THEN
6831          nh42so4_h2so4 = 66.71_wp * rh**5 - 187.5_wp * rh**4 + 210.57_wp * rh**3 - 121.04_wp *    &
6832                          rh**2 + 39.182_wp * rh - 8.0606_wp
6833       ENDIF
6834
6835       IF ( ammonium_nitrate > 0.0_wp )  THEN
6836          nh4no3_h2so4 = - 22.532_wp * rh**4 + 66.615_wp * rh**3 - 74.647_wp * rh**2 + 37.638_wp * &
6837                         rh - 6.9711_wp
6838       ENDIF
6839
6840       IF ( ammonium_chloride > 0.0_wp )  THEN
6841          IF ( rh >= 0.1_wp  .AND.  rh < 0.2_wp )  THEN
6842             nh4cl_h2so4 = - 0.32089_wp * rh + 0.57738_wp
6843          ELSEIF ( rh >= 0.2_wp  .AND.  rh < 0.9_wp )  THEN
6844             nh4cl_h2so4 = 18.089_wp * rh**5 - 51.083_wp * rh**4 + 50.32_wp * rh**3 - 17.012_wp *  &
6845                           rh**2 - 0.93435_wp * rh + 1.0548_wp
6846          ELSEIF ( rh >= 0.9_wp  .AND.  rh < 0.99_wp )  THEN
6847             nh4cl_h2so4 = - 1.5749_wp * rh + 1.7002_wp
6848          ENDIF
6849       ENDIF
6850
6851       IF ( sodium_sulphate > 0.0_wp )  THEN
6852          na2so4_h2so4 = 29.843_wp * rh**4 - 69.417_wp * rh**3 + 61.507_wp * rh**2 - 29.874_wp *   &
6853                         rh + 7.7556_wp
6854       ENDIF
6855
6856       IF ( sodium_nitrate > 0.0_wp )  THEN
6857          nano3_h2so4 = - 122.37_wp * rh**6 + 427.43_wp * rh**5 - 604.68_wp * rh**4 + 443.08_wp *  &
6858                        rh**3 - 178.61_wp * rh**2 + 37.242_wp * rh - 1.9564_wp
6859       ENDIF
6860
6861       IF ( sodium_chloride > 0.0_wp )  THEN
6862          nacl_h2so4 = - 40.288_wp * rh**5 + 115.61_wp * rh**4 - 129.99_wp * rh**3 + 72.652_wp *   &
6863                       rh**2 - 22.124_wp * rh + 4.2676_wp
6864       ENDIF
6865
6866       ln_h2so4_act = binary_h2so4 + nitric_acid_eq_frac * hno3_h2so4 +                            &
6867                      hydrochloric_acid_eq_frac * hcl_h2so4 +                                      &
6868                      ammonium_sulphate_eq_frac * nh42so4_h2so4 +                                  &
6869                      ammonium_nitrate_eq_frac  * nh4no3_h2so4 +                                   &
6870                      ammonium_chloride_eq_frac * nh4cl_h2so4 +                                    &
6871                      sodium_sulphate_eq_frac * na2so4_h2so4 +                                     &
6872                      sodium_nitrate_eq_frac * nano3_h2so4 + sodium_chloride_eq_frac * nacl_h2so4
6873
6874       gamma_h2so4 = EXP( ln_h2so4_act )    ! molal activity coefficient
6875!
6876!--    Export activity coefficients
6877       IF ( gamma_h2so4 > 1.0E-10_wp )  THEN
6878          gamma_out(4) = gamma_hhso4**2 / gamma_h2so4
6879       ENDIF
6880       IF ( gamma_hhso4 > 1.0E-10_wp )  THEN
6881          gamma_out(5) = gamma_h2so4**3 / gamma_hhso4**2
6882       ENDIF
6883!
6884!--    Ionic activity coefficient product
6885       act_product = gamma_h2so4**3 / gamma_hhso4**2
6886!
6887!--    Solve the quadratic equation (i.e. x in ax**2 + bx + c = 0)
6888       a = 1.0_wp
6889       b = -1.0_wp * ( ions(4) + ions(1) + ( ( water_total * 18.0E-3_wp ) /                        &
6890           ( 99.0_wp * act_product ) ) )
6891       c = ions(4) * ions(1)
6892       root1 = ( ( -1.0_wp * b ) + ( ( ( b**2 ) - 4.0_wp * a * c )**0.5_wp ) ) / ( 2.0_wp * a )
6893       root2 = ( ( -1.0_wp * b ) - ( ( ( b**2 ) - 4.0_wp * a * c) **0.5_wp ) ) / ( 2.0_wp * a )
6894
6895       IF ( root1 > ions(1)  .OR.  root1 < 0.0_wp )  THEN
6896          root1 = 0.0_wp
6897       ENDIF
6898
6899       IF ( root2 > ions(1)  .OR.  root2 < 0.0_wp )  THEN
6900          root2 = 0.0_wp
6901       ENDIF
6902!
6903!--    Calculate the new hydrogen ion, bisulphate ion and sulphate ion
6904!--    concentration
6905       h_real    = ions(1)
6906       so4_real  = ions(4)
6907       hso4_real = MAX( root1, root2 )
6908       h_real   = ions(1) - hso4_real
6909       so4_real = ions(4) - hso4_real
6910!
6911!--    Recalculate ion molalities
6912       ions_mol(1) = h_real    / ( water_total * 18.01528E-3_wp )   ! H+
6913       ions_mol(4) = so4_real  / ( water_total * 18.01528E-3_wp )   ! SO4(2-)
6914       ions_mol(5) = hso4_real / ( water_total * 18.01528E-3_wp )   ! HSO4(2-)
6915
6916       h_out    = h_real
6917       hso4_out = hso4_real
6918       so4_out  = so4_real
6919
6920    ELSE
6921       h_out    = ions(1)
6922       hso4_out = 0.0_wp
6923       so4_out  = ions(4)
6924    ENDIF
6925
6926!
6927!-- 4) ACTIVITY COEFFICIENTS -for vapour pressures of HNO3,HCL and NH3
6928!
6929!-- This section evaluates activity coefficients and vapour pressures using the water content
6930!-- calculated above) for each inorganic condensing species: a - HNO3, b - NH3, c - HCL.
6931!-- The following procedure is used: Zaveri et al (2005) found that one could express the variation
6932!-- of activity coefficients linearly in log-space if equivalent mole fractions were used.
6933!-- So, by a taylor series expansion LOG( activity coefficient ) =
6934!--    LOG( binary activity coefficient at a given RH ) +
6935!--    (equivalent mole fraction compound A) *
6936!--    ('interaction' parameter between A and condensing species) +
6937!--    equivalent mole fraction compound B) *
6938!--    ('interaction' parameter between B and condensing species).
6939!-- Here, the interaction parameters have been fit to ADDEM by searching the whole compositon space
6940!-- and fit usign the Levenberg-Marquardt non-linear least squares algorithm.
6941!
6942!-- They are given as a function of RH and vary with complexity ranging from linear to 5th order
6943!-- polynomial expressions, the binary activity coefficients were calculated using AIM online.
6944!-- NOTE: for NH3, no binary activity coefficient was used and the data were fit to the ratio of the
6945!-- activity coefficients for the ammonium and hydrogen ions. Once the activity coefficients are
6946!-- obtained the vapour pressure can be easily calculated using tabulated equilibrium constants
6947!-- (referenced). This procedure differs from that of Zaveri et al (2005) in that it is not assumed
6948!-- one can carry behaviour from binary mixtures in multicomponent systems. To this end we have fit
6949!-- the 'interaction' parameters explicitly to a general inorganic equilibrium model
6950!-- (ADDEM - Topping et al. 2005a,b). Such parameters take into account bisulphate ion dissociation
6951!-- and water content. This also allows us to consider one regime for all composition space, rather
6952!-- than defining sulphate rich and sulphate poor regimes.
6953!-- NOTE: The flags "binary_case" and "full_complexity" are not used in this prototype. They are
6954!-- used for simplification of the fit expressions when using limited composition regions.
6955!
6956!-- a) - ACTIVITY COEFF/VAPOUR PRESSURE - HNO3
6957    IF ( ions(1) > 0.0_wp  .AND.  ions(6) > 0.0_wp )  THEN
6958       binary_case = 1
6959       IF ( rh > 0.1_wp  .AND.  rh < 0.98_wp )  THEN
6960          IF ( binary_case == 1 )  THEN
6961             binary_hno3 = 1.8514_wp * rh**3 - 4.6991_wp * rh**2 + 1.5514_wp * rh + 0.90236_wp
6962          ELSEIF ( binary_case == 2 )  THEN
6963             binary_hno3 = - 1.1751_wp * ( rh**2 ) - 0.53794_wp * rh + 1.2808_wp
6964          ENDIF
6965       ELSEIF ( rh >= 0.98_wp  .AND.  rh < 0.9999_wp )  THEN
6966          binary_hno3 = 1244.69635941351_wp * rh**3 - 2613.93941099991_wp * rh**2 +                &
6967                        1525.0684974546_wp * rh -155.946764059316_wp
6968       ENDIF
6969!
6970!--    Contributions from other solutes
6971       full_complexity = 1
6972       IF ( hydrochloric_acid > 0.0_wp )  THEN   ! HCL
6973          IF ( full_complexity == 1  .OR.  rh < 0.4_wp )  THEN
6974             hcl_hno3 = 16.051_wp * rh**4 - 44.357_wp * rh**3 + 45.141_wp * rh**2 - 21.638_wp *    &
6975                        rh + 4.8182_wp
6976          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6977             hcl_hno3 = - 1.5833_wp * rh + 1.5569_wp
6978          ENDIF
6979       ENDIF
6980
6981       IF ( sulphuric_acid > 0.0_wp )  THEN   ! H2SO4
6982          IF ( full_complexity == 1  .OR.  rh < 0.4_wp )  THEN
6983             h2so4_hno3 = - 3.0849_wp * rh**3 + 5.9609_wp * rh**2 - 4.468_wp * rh + 1.5658_wp
6984          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6985             h2so4_hno3 = - 0.93473_wp * rh + 0.9363_wp
6986          ENDIF
6987       ENDIF
6988
6989       IF ( ammonium_sulphate > 0.0_wp )  THEN   ! NH42SO4
6990          nh42so4_hno3 = 16.821_wp * rh**3 - 28.391_wp * rh**2 + 18.133_wp * rh - 6.7356_wp
6991       ENDIF
6992
6993       IF ( ammonium_nitrate > 0.0_wp )  THEN   ! NH4NO3
6994          nh4no3_hno3 = 11.01_wp * rh**3 - 21.578_wp * rh**2 + 14.808_wp * rh - 4.2593_wp
6995       ENDIF
6996
6997       IF ( ammonium_chloride > 0.0_wp )  THEN   ! NH4Cl
6998          IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
6999             nh4cl_hno3 = - 1.176_wp * rh**3 + 5.0828_wp * rh**2 - 3.8792_wp * rh - 0.05518_wp
7000          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
7001             nh4cl_hno3 = 2.6219_wp * rh**2 - 2.2609_wp * rh - 0.38436_wp
7002          ENDIF
7003       ENDIF
7004
7005       IF ( sodium_sulphate > 0.0_wp )  THEN   ! Na2SO4
7006          na2so4_hno3 = 35.504_wp * rh**4 - 80.101_wp * rh**3 + 67.326_wp * rh**2 - 28.461_wp *    &
7007                        rh + 5.6016_wp
7008       ENDIF
7009
7010       IF ( sodium_nitrate > 0.0_wp )  THEN   ! NaNO3
7011          IF ( full_complexity == 1 .OR. rh <= 0.4_wp ) THEN
7012             nano3_hno3 = 23.659_wp * rh**5 - 66.917_wp * rh**4 + 74.686_wp * rh**3 - 40.795_wp *  &
7013                          rh**2 + 10.831_wp * rh - 1.4701_wp
7014          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
7015             nano3_hno3 = 14.749_wp * rh**4 - 35.237_wp * rh**3 + 31.196_wp * rh**2 - 12.076_wp *  &
7016                          rh + 1.3605_wp
7017          ENDIF
7018       ENDIF
7019
7020       IF ( sodium_chloride > 0.0_wp )  THEN   ! NaCl
7021          IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
7022             nacl_hno3 = 13.682_wp * rh**4 - 35.122_wp * rh**3 + 33.397_wp * rh**2 - 14.586_wp *   &
7023                         rh + 2.6276_wp
7024          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
7025             nacl_hno3 = 1.1882_wp * rh**3 - 1.1037_wp * rh**2 - 0.7642_wp * rh + 0.6671_wp
7026          ENDIF
7027       ENDIF
7028
7029       ln_hno3_act = binary_hno3 + hydrochloric_acid_eq_frac * hcl_hno3 +                          &
7030                     sulphuric_acid_eq_frac    * h2so4_hno3 +                                      &
7031                     ammonium_sulphate_eq_frac * nh42so4_hno3 +                                    &
7032                     ammonium_nitrate_eq_frac  * nh4no3_hno3 +                                     &
7033                     ammonium_chloride_eq_frac * nh4cl_hno3 +                                      &
7034                     sodium_sulphate_eq_frac * na2so4_hno3 +                                       &
7035                     sodium_nitrate_eq_frac * nano3_hno3 + sodium_chloride_eq_frac   * nacl_hno3
7036
7037       gamma_hno3   = EXP( ln_hno3_act )   ! Molal activity coefficient of HNO3
7038       gamma_out(1) = gamma_hno3
7039!
7040!--    Partial pressure calculation
7041!--    k_hno3 = 2.51 * ( 10**6 )
7042!--    k_hno3 = 2.628145923d6 !< calculated by AIM online (Clegg et al 1998) after Chameides (1984)
7043       k_hno3     = 2.6E6_wp * EXP( 8700.0_wp * henrys_temp_dep )
7044       press_hno3 = ( ions_mol(1) * ions_mol(6) * ( gamma_hno3**2 ) ) / k_hno3
7045    ENDIF
7046!
7047!-- b) - ACTIVITY COEFF/VAPOUR PRESSURE - NH3
7048!-- Follow the two solute approach of Zaveri et al. (2005)
7049    IF ( ions(2) > 0.0_wp  .AND.  ions_mol(1) > 0.0_wp )  THEN
7050!
7051!--    NH4HSO4:
7052       binary_nh4hso4 = 56.907_wp * rh**6 - 155.32_wp * rh**5 + 142.94_wp * rh**4 - 32.298_wp *    &
7053                        rh**3 - 27.936_wp * rh**2 + 19.502_wp * rh - 4.2618_wp
7054       IF ( nitric_acid > 0.0_wp)  THEN   ! HNO3
7055          hno3_nh4hso4 = 104.8369_wp * rh**8 - 288.8923_wp * rh**7 + 129.3445_wp * rh**6 +         &
7056                         373.0471_wp * rh**5 - 571.0385_wp * rh**4 + 326.3528_wp * rh**3 -         &
7057                         74.169_wp * rh**2 - 2.4999_wp * rh + 3.17_wp
7058       ENDIF
7059
7060       IF ( hydrochloric_acid > 0.0_wp)  THEN   ! HCL
7061          hcl_nh4hso4 = - 7.9133_wp * rh**8 + 126.6648_wp * rh**7 - 460.7425_wp * rh**6 +          &
7062                         731.606_wp * rh**5 - 582.7467_wp * rh**4 + 216.7197_wp * rh**3 -          &
7063                         11.3934_wp * rh**2 - 17.7728_wp  * rh + 5.75_wp
7064       ENDIF
7065
7066       IF ( sulphuric_acid > 0.0_wp)  THEN   ! H2SO4
7067          h2so4_nh4hso4 = 195.981_wp * rh**8 - 779.2067_wp * rh**7 + 1226.3647_wp * rh**6 -        &
7068                         964.0261_wp * rh**5 + 391.7911_wp * rh**4 - 84.1409_wp  * rh**3 +         &
7069                          20.0602_wp * rh**2 - 10.2663_wp  * rh + 3.5817_wp
7070       ENDIF
7071
7072       IF ( ammonium_sulphate > 0.0_wp)  THEN   ! NH42SO4
7073          nh42so4_nh4hso4 = 617.777_wp * rh**8 -  2547.427_wp * rh**7 + 4361.6009_wp * rh**6 -     &
7074                           4003.162_wp * rh**5 + 2117.8281_wp * rh**4 - 640.0678_wp * rh**3 +      &
7075                            98.0902_wp * rh**2 -    2.2615_wp * rh - 2.3811_wp
7076       ENDIF
7077
7078       IF ( ammonium_nitrate > 0.0_wp)  THEN   ! NH4NO3
7079          nh4no3_nh4hso4 = - 104.4504_wp * rh**8 + 539.5921_wp * rh**7 - 1157.0498_wp * rh**6 +    &
7080                            1322.4507_wp * rh**5 - 852.2475_wp * rh**4 + 298.3734_wp * rh**3 -     &
7081                              47.0309_wp * rh**2 +    1.297_wp * rh - 0.8029_wp
7082       ENDIF
7083
7084       IF ( ammonium_chloride > 0.0_wp)  THEN   ! NH4Cl
7085          nh4cl_nh4hso4 = 258.1792_wp * rh**8 - 1019.3777_wp * rh**7 + 1592.8918_wp * rh**6 -      &
7086                         1221.0726_wp * rh**5 +  442.2548_wp * rh**4 -   43.6278_wp * rh**3 -      &
7087                            7.5282_wp * rh**2 -    3.8459_wp * rh + 2.2728_wp
7088       ENDIF
7089
7090       IF ( sodium_sulphate > 0.0_wp)  THEN   ! Na2SO4
7091          na2so4_nh4hso4 = 225.4238_wp * rh**8 - 732.4113_wp * rh**7 + 843.7291_wp * rh**6 -       &
7092                           322.7328_wp * rh**5 -  88.6252_wp * rh**4 +  72.4434_wp * rh**3 +       &
7093                            22.9252_wp * rh**2 -  25.3954_wp * rh + 4.6971_wp
7094       ENDIF
7095
7096       IF ( sodium_nitrate > 0.0_wp)  THEN   ! NaNO3
7097          nano3_nh4hso4 = 96.1348_wp * rh**8 - 341.6738_wp * rh**7 + 406.5314_wp * rh**6 -         &
7098                          98.5777_wp * rh**5 - 172.8286_wp * rh**4 + 149.3151_wp * rh**3 -         &
7099                          38.9998_wp * rh**2 -   0.2251_wp * rh + 0.4953_wp
7100       ENDIF
7101
7102       IF ( sodium_chloride > 0.0_wp)  THEN   ! NaCl
7103          nacl_nh4hso4 = 91.7856_wp * rh**8 - 316.6773_wp * rh**7 + 358.2703_wp * rh**6 -          &
7104                         68.9142_wp * rh**5 - 156.5031_wp * rh**4 + 116.9592_wp * rh**3 -          &
7105                         22.5271_wp * rh**2 - 3.7716_wp * rh + 1.56_wp
7106       ENDIF
7107
7108       ln_nh4hso4_act = binary_nh4hso4 + nitric_acid_eq_frac * hno3_nh4hso4 +                      &
7109                        hydrochloric_acid_eq_frac * hcl_nh4hso4 +                                  &
7110                        sulphuric_acid_eq_frac * h2so4_nh4hso4 +                                   &
7111                        ammonium_sulphate_eq_frac * nh42so4_nh4hso4 +                              &
7112                        ammonium_nitrate_eq_frac * nh4no3_nh4hso4 +                                &
7113                        ammonium_chloride_eq_frac * nh4cl_nh4hso4 +                                &
7114                        sodium_sulphate_eq_frac * na2so4_nh4hso4 +                                 &
7115                        sodium_nitrate_eq_frac * nano3_nh4hso4 +                                   &
7116                        sodium_chloride_eq_frac * nacl_nh4hso4
7117
7118       gamma_nh4hso4 = EXP( ln_nh4hso4_act ) ! molal act. coefficient of NH4HSO4
7119!
7120!--    Molal activity coefficient of NO3-
7121       gamma_out(6)  = gamma_nh4hso4
7122!
7123!--    Molal activity coefficient of NH4+
7124       gamma_nh3     = gamma_nh4hso4**2 / gamma_hhso4**2
7125       gamma_out(3)  = gamma_nh3
7126!
7127!--    This actually represents the ratio of the ammonium to hydrogen ion activity coefficients
7128!--    (see Zaveri paper) - multiply this by the ratio of the ammonium to hydrogen ion molality and
7129!--    the ratio of appropriate equilibrium constants
7130!
7131!--    Equilibrium constants
7132!--    k_h = 57.64d0    ! Zaveri et al. (2005)
7133       k_h = 5.8E1_wp * EXP( 4085.0_wp * henrys_temp_dep )   ! after Chameides (1984)
7134!--    k_nh4 = 1.81E-5_wp    ! Zaveri et al. (2005)
7135       k_nh4 = 1.7E-5_wp * EXP( -4325.0_wp * henrys_temp_dep )   ! Chameides (1984)
7136!--    k_h2o = 1.01E-14_wp    ! Zaveri et al (2005)
7137       k_h2o = 1.E-14_wp * EXP( -6716.0_wp * henrys_temp_dep )   ! Chameides (1984)
7138!
7139       molality_ratio_nh3 = ions_mol(2) / ions_mol(1)
7140!
7141!--    Partial pressure calculation
7142       press_nh3 = molality_ratio_nh3 * gamma_nh3 * ( k_h2o / ( k_h * k_nh4 ) )
7143
7144    ENDIF
7145!
7146!-- c) - ACTIVITY COEFF/VAPOUR PRESSURE - HCL
7147    IF ( ions(1) > 0.0_wp  .AND.  ions(7) > 0.0_wp )  THEN
7148       binary_case = 1
7149       IF ( rh > 0.1_wp  .AND.  rh < 0.98 )  THEN
7150          IF ( binary_case == 1 )  THEN
7151             binary_hcl = - 5.0179_wp * rh**3 + 9.8816_wp * rh**2 - 10.789_wp * rh + 5.4737_wp
7152          ELSEIF ( binary_case == 2 )  THEN
7153             binary_hcl = - 4.6221_wp * rh + 4.2633_wp
7154          ENDIF
7155       ELSEIF ( rh >= 0.98_wp  .AND.  rh < 0.9999_wp )  THEN
7156          binary_hcl = 775.6111008626_wp * rh**3 - 2146.01320888771_wp * rh**2 +                   &
7157                       1969.01979670259_wp *  rh - 598.878230033926_wp
7158       ENDIF
7159    ENDIF
7160
7161    IF ( nitric_acid > 0.0_wp )  THEN   ! HNO3
7162       IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
7163          hno3_hcl = 9.6256_wp * rh**4 - 26.507_wp * rh**3 + 27.622_wp * rh**2 - 12.958_wp * rh +  &
7164                     2.2193_wp
7165       ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
7166          hno3_hcl = 1.3242_wp * rh**2 - 1.8827_wp * rh + 0.55706_wp
7167       ENDIF
7168    ENDIF
7169
7170    IF ( sulphuric_acid > 0.0_wp )  THEN   ! H2SO4
7171       IF ( full_complexity == 1  .OR.  rh <= 0.4 )  THEN
7172          h2so4_hcl = 1.4406_wp * rh**3 - 2.7132_wp * rh**2 + 1.014_wp * rh + 0.25226_wp
7173       ELSEIF ( full_complexity == 0 .AND. rh > 0.4_wp ) THEN
7174          h2so4_hcl = 0.30993_wp * rh**2 - 0.99171_wp * rh + 0.66913_wp
7175       ENDIF
7176    ENDIF
7177
7178    IF ( ammonium_sulphate > 0.0_wp )  THEN   ! NH42SO4
7179       nh42so4_hcl = 22.071_wp * rh**3 - 40.678_wp * rh**2 + 27.893_wp * rh - 9.4338_wp
7180    ENDIF
7181
7182    IF ( ammonium_nitrate > 0.0_wp )  THEN   ! NH4NO3
7183       nh4no3_hcl = 19.935_wp * rh**3 - 42.335_wp * rh**2 + 31.275_wp * rh - 8.8675_wp
7184    ENDIF
7185
7186    IF ( ammonium_chloride > 0.0_wp )  THEN   ! NH4Cl
7187       IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
7188          nh4cl_hcl = 2.8048_wp * rh**3 - 4.3182_wp * rh**2 + 3.1971_wp * rh - 1.6824_wp
7189       ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
7190          nh4cl_hcl = 1.2304_wp * rh**2 - 0.18262_wp * rh - 1.0643_wp
7191       ENDIF
7192    ENDIF
7193
7194    IF ( sodium_sulphate > 0.0_wp )  THEN   ! Na2SO4
7195       na2so4_hcl = 36.104_wp * rh**4 - 78.658_wp * rh**3 + 63.441_wp * rh**2 - 26.727_wp * rh +   &
7196                    5.7007_wp
7197    ENDIF
7198
7199    IF ( sodium_nitrate > 0.0_wp )  THEN   ! NaNO3
7200       IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
7201          nano3_hcl = 54.471_wp * rh**5 - 159.42_wp * rh**4 + 180.25_wp * rh**3 - 98.176_wp * rh**2&
7202                      + 25.309_wp * rh - 2.4275_wp
7203       ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
7204          nano3_hcl = 21.632_wp * rh**4 - 53.088_wp * rh**3 + 47.285_wp * rh**2 - 18.519_wp * rh   &
7205                      + 2.6846_wp
7206       ENDIF
7207    ENDIF
7208
7209    IF ( sodium_chloride > 0.0_wp )  THEN   ! NaCl
7210       IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
7211          nacl_hcl = 5.4138_wp * rh**4 - 12.079_wp * rh**3 + 9.627_wp * rh**2 - 3.3164_wp * rh +   &
7212                     0.35224_wp
7213       ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
7214          nacl_hcl = 2.432_wp * rh**3 - 4.3453_wp * rh**2 + 2.3834_wp * rh - 0.4762_wp
7215       ENDIF
7216    ENDIF
7217
7218    ln_HCL_act = binary_hcl + nitric_acid_eq_frac * hno3_hcl + sulphuric_acid_eq_frac * h2so4_hcl +&
7219                 ammonium_sulphate_eq_frac * nh42so4_hcl + ammonium_nitrate_eq_frac * nh4no3_hcl + &
7220                 ammonium_chloride_eq_frac * nh4cl_hcl + sodium_sulphate_eq_frac * na2so4_hcl +    &
7221                 sodium_nitrate_eq_frac    * nano3_hcl + sodium_chloride_eq_frac   * nacl_hcl
7222
7223     gamma_hcl    = EXP( ln_HCL_act )   ! Molal activity coefficient
7224     gamma_out(2) = gamma_hcl
7225!
7226!--  Equilibrium constant after Wagman et al. (1982) (and NIST database)
7227     k_hcl = 2E6_wp * EXP( 9000.0_wp * henrys_temp_dep )
7228
7229     press_hcl = ( ions_mol(1) * ions_mol(7) * gamma_hcl**2 ) / k_hcl
7230!
7231!-- 5) Ion molility output
7232    mols_out = ions_mol
7233
7234 END SUBROUTINE inorganic_pdfite
7235
7236!------------------------------------------------------------------------------!
7237! Description:
7238! ------------
7239!> Update the particle size distribution. Put particles into corrects bins.
7240!>
7241!> Moving-centre method assumed, i.e. particles are allowed to grow to their
7242!> exact size as long as they are not crossing the fixed diameter bin limits.
7243!> If the particles in a size bin cross the lower or upper diameter limit, they
7244!> are all moved to the adjacent diameter bin and their volume is averaged with
7245!> the particles in the new bin, which then get a new diameter.
7246!
7247!> Moving-centre method minimises numerical diffusion.
7248!------------------------------------------------------------------------------!
7249 SUBROUTINE distr_update( paero )
7250
7251    IMPLICIT NONE
7252
7253    INTEGER(iwp) ::  ib      !< loop index
7254    INTEGER(iwp) ::  mm      !< loop index
7255    INTEGER(iwp) ::  counti  !< number of while loops
7256
7257    LOGICAL  ::  within_bins !< logical (particle belongs to the bin?)
7258
7259    REAL(wp) ::  znfrac  !< number fraction to be moved to the larger bin
7260    REAL(wp) ::  zvfrac  !< volume fraction to be moved to the larger bin
7261    REAL(wp) ::  zvexc   !< Volume in the grown bin which exceeds the bin upper limit
7262    REAL(wp) ::  zvihi   !< particle volume at the high end of the bin
7263    REAL(wp) ::  zvilo   !< particle volume at the low end of the bin
7264    REAL(wp) ::  zvpart  !< particle volume (m3)
7265    REAL(wp) ::  zvrat   !< volume ratio of a size bin
7266
7267    real(wp), dimension(nbins_aerosol) ::  dummy
7268
7269    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero !< aerosol properties
7270
7271    zvpart      = 0.0_wp
7272    zvfrac      = 0.0_wp
7273    within_bins = .FALSE.
7274
7275    dummy = paero(:)%numc
7276!
7277!-- Check if the volume of the bin is within bin limits after update
7278    counti = 0
7279    DO  WHILE ( .NOT. within_bins )
7280       within_bins = .TRUE.
7281!
7282!--    Loop from larger to smaller size bins
7283       DO  ib = end_subrange_2b-1, start_subrange_1a, -1
7284          mm = 0
7285          IF ( paero(ib)%numc > nclim )  THEN
7286             zvpart = 0.0_wp
7287             zvfrac = 0.0_wp
7288
7289             IF ( ib == end_subrange_2a )  CYCLE
7290!
7291!--          Dry volume
7292             zvpart = SUM( paero(ib)%volc(1:7) ) / paero(ib)%numc
7293!
7294!--          Smallest bin cannot decrease
7295             IF ( paero(ib)%vlolim > zvpart  .AND.  ib == start_subrange_1a ) CYCLE
7296!
7297!--          Decreasing bins
7298             IF ( paero(ib)%vlolim > zvpart )  THEN
7299                mm = ib - 1
7300                IF ( ib == start_subrange_2b )  mm = end_subrange_1a    ! 2b goes to 1a
7301
7302                paero(mm)%numc = paero(mm)%numc + paero(ib)%numc
7303                paero(ib)%numc = 0.0_wp
7304                paero(mm)%volc(:) = paero(mm)%volc(:) + paero(ib)%volc(:)
7305                paero(ib)%volc(:) = 0.0_wp
7306                CYCLE
7307             ENDIF
7308!
7309!--          If size bin has not grown, cycle.
7310!--          Changed by Mona: compare to the arithmetic mean volume, as done originally. Now
7311!--          particle volume is derived from the geometric mean diameter, not arithmetic (see
7312!--          SUBROUTINE set_sizebins).
7313             IF ( zvpart <= api6 * ( ( aero(ib)%vhilim + aero(ib)%vlolim ) / ( 2.0_wp * api6 ) ) ) &
7314             CYCLE
7315!
7316!--          Avoid precision problems
7317             IF ( ABS( zvpart - api6 * paero(ib)%dmid**3 ) < 1.0E-35_wp )  CYCLE
7318!
7319!--          Volume ratio of the size bin
7320             zvrat = paero(ib)%vhilim / paero(ib)%vlolim
7321!
7322!--          Particle volume at the low end of the bin
7323             zvilo = 2.0_wp * zvpart / ( 1.0_wp + zvrat )
7324!
7325!--          Particle volume at the high end of the bin
7326             zvihi = zvrat * zvilo
7327!
7328!--          Volume in the grown bin which exceeds the bin upper limit
7329             zvexc = 0.5_wp * ( zvihi + paero(ib)%vhilim )
7330!
7331!--          Number fraction to be moved to the larger bin
7332             znfrac = MIN( 1.0_wp, ( zvihi - paero(ib)%vhilim) / ( zvihi - zvilo ) )
7333!
7334!--          Volume fraction to be moved to the larger bin
7335             zvfrac = MIN( 0.99_wp, znfrac * zvexc / zvpart )
7336             IF ( zvfrac < 0.0_wp )  THEN
7337                message_string = 'Error: zvfrac < 0'
7338                CALL message( 'salsa_mod: distr_update', 'PA0624', 1, 2, 0, 6, 0 )
7339             ENDIF
7340!
7341!--          Update bin
7342             mm = ib + 1
7343!
7344!--          Volume (cm3/cm3)
7345             paero(mm)%volc(:) = paero(mm)%volc(:) + znfrac * paero(ib)%numc * zvexc *             &
7346                                 paero(ib)%volc(:) / SUM( paero(ib)%volc(1:7) )
7347             paero(ib)%volc(:) = paero(ib)%volc(:) - znfrac * paero(ib)%numc * zvexc *             &
7348                                 paero(ib)%volc(:) / SUM( paero(ib)%volc(1:7) )
7349
7350!--          Number concentration (#/m3)
7351             paero(mm)%numc = paero(mm)%numc + znfrac * paero(ib)%numc
7352             paero(ib)%numc = paero(ib)%numc * ( 1.0_wp - znfrac )
7353
7354          ENDIF     ! nclim
7355
7356          IF ( paero(ib)%numc > nclim )   THEN
7357             zvpart = SUM( paero(ib)%volc(1:7) ) / paero(ib)%numc  ! Note: dry volume!
7358             within_bins = ( paero(ib)%vlolim < zvpart  .AND. zvpart < paero(ib)%vhilim )
7359          ENDIF
7360
7361       ENDDO ! - ib
7362
7363       counti = counti + 1
7364       IF ( counti > 100 )  THEN
7365          message_string = 'Error: Aerosol bin update not converged'
7366          CALL message( 'salsa_mod: distr_update', 'PA0625', 1, 2, 0, 6, 0 )
7367       ENDIF
7368
7369    ENDDO ! - within bins
7370
7371 END SUBROUTINE distr_update
7372
7373!------------------------------------------------------------------------------!
7374! Description:
7375! ------------
7376!> salsa_diagnostics: Update properties for the current timestep:
7377!>
7378!> Juha Tonttila, FMI, 2014
7379!> Tomi Raatikainen, FMI, 2016
7380!------------------------------------------------------------------------------!
7381 SUBROUTINE salsa_diagnostics( i, j )
7382
7383    USE cpulog,                                                                &
7384        ONLY:  cpu_log, log_point_s
7385
7386    IMPLICIT NONE
7387
7388    INTEGER(iwp) ::  ib   !<
7389    INTEGER(iwp) ::  ic   !<
7390    INTEGER(iwp) ::  icc  !<
7391    INTEGER(iwp) ::  ig   !<
7392    INTEGER(iwp) ::  k    !<
7393
7394    INTEGER(iwp), INTENT(in) ::  i  !<
7395    INTEGER(iwp), INTENT(in) ::  j  !<
7396
7397    REAL(wp), DIMENSION(nzb:nzt+1) ::  flag          !< flag to mask topography
7398    REAL(wp), DIMENSION(nzb:nzt+1) ::  flag_zddry    !< flag to mask zddry
7399    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_adn        !< air density (kg/m3)
7400    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_p          !< pressure
7401    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_t          !< temperature (K)
7402    REAL(wp), DIMENSION(nzb:nzt+1) ::  mcsum         !< sum of mass concentration
7403    REAL(wp), DIMENSION(nzb:nzt+1) ::  ppm_to_nconc  !< Conversion factor: ppm to #/m3
7404    REAL(wp), DIMENSION(nzb:nzt+1) ::  zddry         !< particle dry diameter
7405    REAL(wp), DIMENSION(nzb:nzt+1) ::  zvol          !< particle volume
7406
7407    flag_zddry   = 0.0_wp
7408    in_adn       = 0.0_wp
7409    in_p         = 0.0_wp
7410    in_t         = 0.0_wp
7411    ppm_to_nconc = 1.0_wp
7412    zddry        = 0.0_wp
7413    zvol         = 0.0_wp
7414
7415    !$OMP MASTER
7416    CALL cpu_log( log_point_s(94), 'salsa diagnostics ', 'start' )
7417    !$OMP END MASTER
7418
7419!
7420!-- Calculate thermodynamic quantities needed in SALSA
7421    CALL salsa_thrm_ij( i, j, p_ij=in_p, temp_ij=in_t, adn_ij=in_adn )
7422!
7423!-- Calculate conversion factors for gas concentrations
7424    ppm_to_nconc = for_ppm_to_nconc * in_p / in_t
7425!
7426!-- Predetermine flag to mask topography
7427    flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(:,j,i), 0 ) )
7428
7429    DO  ib = 1, nbins_aerosol   ! aerosol size bins
7430!
7431!--    Remove negative values
7432       aerosol_number(ib)%conc(:,j,i) = MAX( nclim, aerosol_number(ib)%conc(:,j,i) ) * flag
7433!
7434!--    Calculate total mass concentration per bin
7435       mcsum = 0.0_wp
7436       DO  ic = 1, ncomponents_mass
7437          icc = ( ic - 1 ) * nbins_aerosol + ib
7438          mcsum = mcsum + aerosol_mass(icc)%conc(:,j,i) * flag
7439          aerosol_mass(icc)%conc(:,j,i) = MAX( mclim, aerosol_mass(icc)%conc(:,j,i) ) * flag
7440       ENDDO
7441!
7442!--    Check that number and mass concentration match qualitatively
7443       IF ( ANY( aerosol_number(ib)%conc(:,j,i) > nclim  .AND. mcsum <= 0.0_wp ) )  THEN
7444          DO  k = nzb+1, nzt
7445             IF ( aerosol_number(ib)%conc(k,j,i) >= nclim  .AND. mcsum(k) <= 0.0_wp )  THEN
7446                aerosol_number(ib)%conc(k,j,i) = nclim * flag(k)
7447                DO  ic = 1, ncomponents_mass
7448                   icc = ( ic - 1 ) * nbins_aerosol + ib
7449                   aerosol_mass(icc)%conc(k,j,i) = mclim * flag(k)
7450                ENDDO
7451             ENDIF
7452          ENDDO
7453       ENDIF
7454!
7455!--    Update aerosol particle radius
7456       CALL bin_mixrat( 'dry', ib, i, j, zvol )
7457       zvol = zvol / arhoh2so4    ! Why on sulphate?
7458!
7459!--    Particles smaller then 0.1 nm diameter are set to zero
7460       zddry = ( zvol / MAX( nclim, aerosol_number(ib)%conc(:,j,i) ) / api6 )**0.33333333_wp
7461       flag_zddry = MERGE( 1.0_wp, 0.0_wp, ( zddry < 1.0E-10_wp  .AND.                             &
7462                           aerosol_number(ib)%conc(:,j,i) > nclim ) )
7463!
7464!--    Volatile species to the gas phase
7465       IF ( index_so4 > 0 .AND. lscndgas )  THEN
7466          ic = ( index_so4 - 1 ) * nbins_aerosol + ib
7467          IF ( salsa_gases_from_chem )  THEN
7468             ig = gas_index_chem(1)
7469             chem_species(ig)%conc(:,j,i) = chem_species(ig)%conc(:,j,i) +                         &
7470                                            aerosol_mass(ic)%conc(:,j,i) * avo * flag_zddry /      &
7471                                            ( amh2so4 * ppm_to_nconc ) * flag
7472          ELSE
7473             salsa_gas(1)%conc(:,j,i) = salsa_gas(1)%conc(:,j,i) + aerosol_mass(ic)%conc(:,j,i) /  &
7474                                        amh2so4 * avo * flag_zddry * flag
7475          ENDIF
7476       ENDIF
7477       IF ( index_oc > 0  .AND.  lscndgas )  THEN
7478          ic = ( index_oc - 1 ) * nbins_aerosol + ib
7479          IF ( salsa_gases_from_chem )  THEN
7480             ig = gas_index_chem(5)
7481             chem_species(ig)%conc(:,j,i) = chem_species(ig)%conc(:,j,i) +                         &
7482                                            aerosol_mass(ic)%conc(:,j,i) * avo * flag_zddry /      &
7483                                            ( amoc * ppm_to_nconc ) * flag
7484          ELSE
7485             salsa_gas(5)%conc(:,j,i) = salsa_gas(5)%conc(:,j,i) + aerosol_mass(ic)%conc(:,j,i) /  &
7486                                        amoc * avo * flag_zddry * flag
7487          ENDIF
7488       ENDIF
7489       IF ( index_no > 0  .AND.  lscndgas )  THEN
7490          ic = ( index_no - 1 ) * nbins_aerosol + ib
7491          IF ( salsa_gases_from_chem )  THEN
7492             ig = gas_index_chem(2)
7493             chem_species(ig)%conc(:,j,i) = chem_species(ig)%conc(:,j,i) +                         &
7494                                            aerosol_mass(ic)%conc(:,j,i) * avo * flag_zddry /      &
7495                                            ( amhno3 * ppm_to_nconc ) *flag
7496          ELSE
7497             salsa_gas(2)%conc(:,j,i) = salsa_gas(2)%conc(:,j,i) + aerosol_mass(ic)%conc(:,j,i) /  &
7498                                        amhno3 * avo * flag_zddry * flag
7499          ENDIF
7500       ENDIF
7501       IF ( index_nh > 0  .AND.  lscndgas )  THEN
7502          ic = ( index_nh - 1 ) * nbins_aerosol + ib
7503          IF ( salsa_gases_from_chem )  THEN
7504             ig = gas_index_chem(3)
7505             chem_species(ig)%conc(:,j,i) = chem_species(ig)%conc(:,j,i) +                         &
7506                                            aerosol_mass(ic)%conc(:,j,i) * avo * flag_zddry /      &
7507                                            ( amnh3 * ppm_to_nconc ) *flag
7508          ELSE
7509             salsa_gas(3)%conc(:,j,i) = salsa_gas(3)%conc(:,j,i) + aerosol_mass(ic)%conc(:,j,i) /  &
7510                                        amnh3 * avo * flag_zddry *flag
7511          ENDIF
7512       ENDIF
7513!
7514!--    Mass and number to zero (insoluble species and water are lost)
7515       DO  ic = 1, ncomponents_mass
7516          icc = ( ic - 1 ) * nbins_aerosol + ib
7517          aerosol_mass(icc)%conc(:,j,i) = MERGE( mclim * flag, aerosol_mass(icc)%conc(:,j,i),      &
7518                                                 flag_zddry > 0.0_wp )
7519       ENDDO
7520       aerosol_number(ib)%conc(:,j,i) = MERGE( nclim * flag, aerosol_number(ib)%conc(:,j,i),       &
7521                                               flag_zddry > 0.0_wp )
7522       ra_dry(:,j,i,ib) = MAX( 1.0E-10_wp, 0.5_wp * zddry )
7523
7524    ENDDO
7525    IF ( .NOT. salsa_gases_from_chem )  THEN
7526       DO  ig = 1, ngases_salsa
7527          salsa_gas(ig)%conc(:,j,i) = MAX( nclim, salsa_gas(ig)%conc(:,j,i) ) * flag
7528       ENDDO
7529    ENDIF
7530
7531   !$OMP MASTER
7532    CALL cpu_log( log_point_s(94), 'salsa diagnostics ', 'stop' )
7533   !$OMP END MASTER
7534
7535 END SUBROUTINE salsa_diagnostics
7536
7537
7538!------------------------------------------------------------------------------!
7539! Description:
7540! ------------
7541!> Call for all grid points
7542!------------------------------------------------------------------------------!
7543 SUBROUTINE salsa_actions( location )
7544
7545
7546    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
7547
7548    SELECT CASE ( location )
7549
7550       CASE ( 'before_timestep' )
7551
7552          IF ( ws_scheme_sca )  sums_salsa_ws_l = 0.0_wp
7553
7554       CASE DEFAULT
7555          CONTINUE
7556
7557    END SELECT
7558
7559 END SUBROUTINE salsa_actions
7560
7561
7562!------------------------------------------------------------------------------!
7563! Description:
7564! ------------
7565!> Call for grid points i,j
7566!------------------------------------------------------------------------------!
7567
7568 SUBROUTINE salsa_actions_ij( i, j, location )
7569
7570
7571    INTEGER(iwp),      INTENT(IN) ::  i         !< grid index in x-direction
7572    INTEGER(iwp),      INTENT(IN) ::  j         !< grid index in y-direction
7573    CHARACTER (LEN=*), INTENT(IN) ::  location  !< call location string
7574    INTEGER(iwp)  ::  dummy  !< call location string
7575
7576    IF ( salsa    )   dummy = i + j
7577
7578    SELECT CASE ( location )
7579
7580       CASE ( 'before_timestep' )
7581
7582          IF ( ws_scheme_sca )  sums_salsa_ws_l = 0.0_wp
7583
7584       CASE DEFAULT
7585          CONTINUE
7586
7587    END SELECT
7588
7589
7590 END SUBROUTINE salsa_actions_ij
7591
7592!------------------------------------------------------------------------------!
7593! Description:
7594! ------------
7595!> Call for all grid points
7596!------------------------------------------------------------------------------!
7597 SUBROUTINE salsa_non_advective_processes
7598
7599    USE cpulog,                                                                                    &
7600        ONLY:  cpu_log, log_point_s
7601
7602    IMPLICIT NONE
7603
7604    INTEGER(iwp) ::  i  !<
7605    INTEGER(iwp) ::  j  !<
7606
7607    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
7608       IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  THEN
7609!
7610!--       Calculate aerosol dynamic processes. salsa_driver can be run with a longer time step.
7611          CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
7612          DO  i = nxl, nxr
7613             DO  j = nys, nyn
7614                CALL salsa_diagnostics( i, j )
7615                CALL salsa_driver( i, j, 3 )
7616                CALL salsa_diagnostics( i, j )
7617             ENDDO
7618          ENDDO
7619          CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
7620       ENDIF
7621    ENDIF
7622
7623 END SUBROUTINE salsa_non_advective_processes
7624
7625
7626!------------------------------------------------------------------------------!
7627! Description:
7628! ------------
7629!> Call for grid points i,j
7630!------------------------------------------------------------------------------!
7631 SUBROUTINE salsa_non_advective_processes_ij( i, j )
7632
7633    USE cpulog,                                                                &
7634        ONLY:  cpu_log, log_point_s
7635
7636    IMPLICIT NONE
7637
7638    INTEGER(iwp), INTENT(IN) ::  i  !< grid index in x-direction
7639    INTEGER(iwp), INTENT(IN) ::  j  !< grid index in y-direction
7640
7641    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
7642       IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  THEN
7643!
7644!--       Calculate aerosol dynamic processes. salsa_driver can be run with a longer time step.
7645          CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
7646          CALL salsa_diagnostics( i, j )
7647          CALL salsa_driver( i, j, 3 )
7648          CALL salsa_diagnostics( i, j )
7649          CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
7650       ENDIF
7651    ENDIF
7652
7653 END SUBROUTINE salsa_non_advective_processes_ij
7654
7655!------------------------------------------------------------------------------!
7656! Description:
7657! ------------
7658!> Routine for exchange horiz of salsa variables.
7659!------------------------------------------------------------------------------!
7660 SUBROUTINE salsa_exchange_horiz_bounds
7661
7662    USE cpulog,                                                                &
7663        ONLY:  cpu_log, log_point_s
7664
7665    IMPLICIT NONE
7666
7667    INTEGER(iwp) ::  ib   !<
7668    INTEGER(iwp) ::  ic   !<
7669    INTEGER(iwp) ::  icc  !<
7670    INTEGER(iwp) ::  ig   !<
7671
7672    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
7673       IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  THEN
7674
7675          CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
7676!
7677!--       Exchange ghost points and decycle if needed.
7678          DO  ib = 1, nbins_aerosol
7679             CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
7680             CALL salsa_boundary_conds( aerosol_number(ib)%conc, aerosol_number(ib)%init )
7681             DO  ic = 1, ncomponents_mass
7682                icc = ( ic - 1 ) * nbins_aerosol + ib
7683                CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
7684                CALL salsa_boundary_conds( aerosol_mass(icc)%conc, aerosol_mass(icc)%init )
7685             ENDDO
7686          ENDDO
7687          IF ( .NOT. salsa_gases_from_chem )  THEN
7688             DO  ig = 1, ngases_salsa
7689                CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
7690                CALL salsa_boundary_conds( salsa_gas(ig)%conc, salsa_gas(ig)%init )
7691             ENDDO
7692          ENDIF
7693          CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
7694!
7695!--       Update last_salsa_time
7696          last_salsa_time = time_since_reference_point
7697       ENDIF
7698    ENDIF
7699
7700 END SUBROUTINE salsa_exchange_horiz_bounds
7701
7702!------------------------------------------------------------------------------!
7703! Description:
7704! ------------
7705!> Calculate the prognostic equation for aerosol number and mass, and gas
7706!> concentrations. Cache-optimized.
7707!------------------------------------------------------------------------------!
7708 SUBROUTINE salsa_prognostic_equations_ij( i, j, i_omp_start, tn )
7709
7710    IMPLICIT NONE
7711
7712    INTEGER(iwp) ::  i            !<
7713    INTEGER(iwp) ::  i_omp_start  !<
7714    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
7715    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
7716    INTEGER(iwp) ::  icc          !< (c-1)*nbins_aerosol+b
7717    INTEGER(iwp) ::  ig           !< loop index for salsa gases
7718    INTEGER(iwp) ::  j            !<
7719    INTEGER(iwp) ::  tn           !<
7720
7721    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
7722!
7723!--    Aerosol number
7724       DO  ib = 1, nbins_aerosol
7725!kk          sums_salsa_ws_l = aerosol_number(ib)%sums_ws_l
7726          CALL salsa_tendency( 'aerosol_number', aerosol_number(ib)%conc_p, aerosol_number(ib)%conc,&
7727                               aerosol_number(ib)%tconc_m, i, j, i_omp_start, tn, ib, ib,          &
7728                               aerosol_number(ib)%flux_s, aerosol_number(ib)%diss_s,               &
7729                               aerosol_number(ib)%flux_l, aerosol_number(ib)%diss_l,               &
7730                               aerosol_number(ib)%init, .TRUE. )
7731!kk          aerosol_number(ib)%sums_ws_l = sums_salsa_ws_l
7732!
7733!--       Aerosol mass
7734          DO  ic = 1, ncomponents_mass
7735             icc = ( ic - 1 ) * nbins_aerosol + ib
7736!kk             sums_salsa_ws_l = aerosol_mass(icc)%sums_ws_l
7737             CALL salsa_tendency( 'aerosol_mass', aerosol_mass(icc)%conc_p, aerosol_mass(icc)%conc,&
7738                                  aerosol_mass(icc)%tconc_m, i, j, i_omp_start, tn, ib, ic,        &
7739                                  aerosol_mass(icc)%flux_s, aerosol_mass(icc)%diss_s,              &
7740                                  aerosol_mass(icc)%flux_l, aerosol_mass(icc)%diss_l,              &
7741                                  aerosol_mass(icc)%init, .TRUE. )
7742!kk             aerosol_mass(icc)%sums_ws_l = sums_salsa_ws_l
7743
7744          ENDDO  ! ic
7745       ENDDO  ! ib
7746!
7747!--    Gases
7748       IF ( .NOT. salsa_gases_from_chem )  THEN
7749
7750          DO  ig = 1, ngases_salsa
7751!kk             sums_salsa_ws_l = salsa_gas(ig)%sums_ws_l
7752             CALL salsa_tendency( 'salsa_gas', salsa_gas(ig)%conc_p, salsa_gas(ig)%conc,           &
7753                                  salsa_gas(ig)%tconc_m, i, j, i_omp_start, tn, ig, ig,            &
7754                                  salsa_gas(ig)%flux_s, salsa_gas(ig)%diss_s, salsa_gas(ig)%flux_l,&
7755                                  salsa_gas(ig)%diss_l, salsa_gas(ig)%init, .FALSE. )
7756!kk             salsa_gas(ig)%sums_ws_l = sums_salsa_ws_l
7757
7758          ENDDO  ! ig
7759
7760       ENDIF
7761
7762    ENDIF
7763
7764 END SUBROUTINE salsa_prognostic_equations_ij
7765!
7766!------------------------------------------------------------------------------!
7767! Description:
7768! ------------
7769!> Calculate the prognostic equation for aerosol number and mass, and gas
7770!> concentrations. For vector machines.
7771!------------------------------------------------------------------------------!
7772 SUBROUTINE salsa_prognostic_equations()
7773
7774    IMPLICIT NONE
7775
7776    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
7777    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
7778    INTEGER(iwp) ::  icc          !< (c-1)*nbins_aerosol+b
7779    INTEGER(iwp) ::  ig           !< loop index for salsa gases
7780
7781    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
7782!
7783!--    Aerosol number
7784       DO  ib = 1, nbins_aerosol
7785          sums_salsa_ws_l = aerosol_number(ib)%sums_ws_l
7786          CALL salsa_tendency( 'aerosol_number', aerosol_number(ib)%conc_p, aerosol_number(ib)%conc,&
7787                               aerosol_number(ib)%tconc_m, ib, ib, aerosol_number(ib)%init, .TRUE. )
7788          aerosol_number(ib)%sums_ws_l = sums_salsa_ws_l
7789!
7790!--       Aerosol mass
7791          DO  ic = 1, ncomponents_mass
7792             icc = ( ic - 1 ) * nbins_aerosol + ib
7793             sums_salsa_ws_l = aerosol_mass(icc)%sums_ws_l
7794             CALL salsa_tendency( 'aerosol_mass', aerosol_mass(icc)%conc_p, aerosol_mass(icc)%conc,&
7795                                  aerosol_mass(icc)%tconc_m, ib, ic, aerosol_mass(icc)%init, .TRUE. )
7796             aerosol_mass(icc)%sums_ws_l = sums_salsa_ws_l
7797
7798          ENDDO  ! ic
7799       ENDDO  ! ib
7800!
7801!--    Gases
7802       IF ( .NOT. salsa_gases_from_chem )  THEN
7803
7804          DO  ig = 1, ngases_salsa
7805             sums_salsa_ws_l = salsa_gas(ig)%sums_ws_l
7806             CALL salsa_tendency( 'salsa_gas', salsa_gas(ig)%conc_p, salsa_gas(ig)%conc,           &
7807                                  salsa_gas(ig)%tconc_m, ig, ig, salsa_gas(ig)%init, .FALSE. )
7808             salsa_gas(ig)%sums_ws_l = sums_salsa_ws_l
7809
7810          ENDDO  ! ig
7811
7812       ENDIF
7813
7814    ENDIF
7815
7816 END SUBROUTINE salsa_prognostic_equations
7817!
7818!------------------------------------------------------------------------------!
7819! Description:
7820! ------------
7821!> Tendencies for aerosol number and mass and gas concentrations.
7822!> Cache-optimized.
7823!------------------------------------------------------------------------------!
7824 SUBROUTINE salsa_tendency_ij( id, rs_p, rs, trs_m, i, j, i_omp_start, tn, ib, ic, flux_s, diss_s, &
7825                               flux_l, diss_l, rs_init, do_sedimentation )
7826
7827    USE advec_ws,                                                                                  &
7828        ONLY:  advec_s_ws
7829
7830    USE advec_s_pw_mod,                                                                            &
7831        ONLY:  advec_s_pw
7832
7833    USE advec_s_up_mod,                                                                            &
7834        ONLY:  advec_s_up
7835
7836    USE arrays_3d,                                                                                 &
7837        ONLY:  ddzu, rdf_sc, tend
7838
7839    USE diffusion_s_mod,                                                                           &
7840        ONLY:  diffusion_s
7841
7842    USE indices,                                                                                   &
7843        ONLY:  wall_flags_0
7844
7845    USE surface_mod,                                                                               &
7846        ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
7847
7848    IMPLICIT NONE
7849
7850    CHARACTER(LEN = *) ::  id  !<
7851
7852    INTEGER(iwp) ::  i            !<
7853    INTEGER(iwp) ::  i_omp_start  !<
7854    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
7855    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
7856    INTEGER(iwp) ::  icc          !< (c-1)*nbins_aerosol+b
7857    INTEGER(iwp) ::  j            !<
7858    INTEGER(iwp) ::  k            !<
7859    INTEGER(iwp) ::  tn           !<
7860
7861    LOGICAL ::  do_sedimentation  !<
7862
7863    REAL(wp), DIMENSION(nzb:nzt+1) ::  rs_init  !<
7864
7865    REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  diss_s  !<
7866    REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  flux_s  !<
7867
7868    REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  diss_l  !<
7869    REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  flux_l  !<
7870
7871    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  rs_p    !<
7872    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  rs      !<
7873    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  trs_m   !<
7874
7875    icc = ( ic - 1 ) * nbins_aerosol + ib
7876!
7877!-- Tendency-terms for reactive scalar
7878    tend(:,j,i) = 0.0_wp
7879!
7880!-- Advection terms
7881    IF ( timestep_scheme(1:5) == 'runge' )  THEN
7882       IF ( ws_scheme_sca )  THEN
7883          CALL advec_s_ws( salsa_advc_flags_s, i, j, rs, id, flux_s, diss_s, flux_l, diss_l,       &
7884                           i_omp_start, tn, bc_dirichlet_l  .OR.  bc_radiation_l,                  &
7885                           bc_dirichlet_n  .OR.  bc_radiation_n,                                   &
7886                           bc_dirichlet_r  .OR.  bc_radiation_r,                                   &
7887                           bc_dirichlet_s  .OR.  bc_radiation_s, monotonic_limiter_z )
7888       ELSE
7889          CALL advec_s_pw( i, j, rs )
7890       ENDIF
7891    ELSE
7892       CALL advec_s_up( i, j, rs )
7893    ENDIF
7894!
7895!-- Diffusion terms
7896    SELECT CASE ( id )
7897       CASE ( 'aerosol_number' )
7898          CALL diffusion_s( i, j, rs, surf_def_h(0)%answs(:,ib),                                   &
7899                                      surf_def_h(1)%answs(:,ib), surf_def_h(2)%answs(:,ib),        &
7900                                      surf_lsm_h%answs(:,ib),    surf_usm_h%answs(:,ib),           &
7901                                      surf_def_v(0)%answs(:,ib), surf_def_v(1)%answs(:,ib),        &
7902                                      surf_def_v(2)%answs(:,ib), surf_def_v(3)%answs(:,ib),        &
7903                                      surf_lsm_v(0)%answs(:,ib), surf_lsm_v(1)%answs(:,ib),        &
7904                                      surf_lsm_v(2)%answs(:,ib), surf_lsm_v(3)%answs(:,ib),        &
7905                                      surf_usm_v(0)%answs(:,ib), surf_usm_v(1)%answs(:,ib),        &
7906                                      surf_usm_v(2)%answs(:,ib), surf_usm_v(3)%answs(:,ib) )
7907       CASE ( 'aerosol_mass' )
7908          CALL diffusion_s( i, j, rs, surf_def_h(0)%amsws(:,icc),                                  &
7909                                      surf_def_h(1)%amsws(:,icc), surf_def_h(2)%amsws(:,icc),      &
7910                                      surf_lsm_h%amsws(:,icc),    surf_usm_h%amsws(:,icc),         &
7911                                      surf_def_v(0)%amsws(:,icc), surf_def_v(1)%amsws(:,icc),      &
7912                                      surf_def_v(2)%amsws(:,icc), surf_def_v(3)%amsws(:,icc),      &
7913                                      surf_lsm_v(0)%amsws(:,icc), surf_lsm_v(1)%amsws(:,icc),      &
7914                                      surf_lsm_v(2)%amsws(:,icc), surf_lsm_v(3)%amsws(:,icc),      &
7915                                      surf_usm_v(0)%amsws(:,icc), surf_usm_v(1)%amsws(:,icc),      &
7916                                      surf_usm_v(2)%amsws(:,icc), surf_usm_v(3)%amsws(:,icc) )
7917       CASE ( 'salsa_gas' )
7918          CALL diffusion_s( i, j, rs, surf_def_h(0)%gtsws(:,ib),                                   &
7919                                      surf_def_h(1)%gtsws(:,ib), surf_def_h(2)%gtsws(:,ib),        &
7920                                      surf_lsm_h%gtsws(:,ib), surf_usm_h%gtsws(:,ib),              &
7921                                      surf_def_v(0)%gtsws(:,ib), surf_def_v(1)%gtsws(:,ib),        &
7922                                      surf_def_v(2)%gtsws(:,ib), surf_def_v(3)%gtsws(:,ib),        &
7923                                      surf_lsm_v(0)%gtsws(:,ib), surf_lsm_v(1)%gtsws(:,ib),        &
7924                                      surf_lsm_v(2)%gtsws(:,ib), surf_lsm_v(3)%gtsws(:,ib),        &
7925                                      surf_usm_v(0)%gtsws(:,ib), surf_usm_v(1)%gtsws(:,ib),        &
7926                                      surf_usm_v(2)%gtsws(:,ib), surf_usm_v(3)%gtsws(:,ib) )
7927    END SELECT
7928!
7929!-- Sedimentation and prognostic equation for aerosol number and mass
7930    IF ( lsdepo  .AND.  do_sedimentation )  THEN
7931!DIR$ IVDEP
7932       DO  k = nzb+1, nzt
7933          tend(k,j,i) = tend(k,j,i) - MAX( 0.0_wp, ( rs(k+1,j,i) * sedim_vd(k+1,j,i,ib) -          &
7934                                                     rs(k,j,i) * sedim_vd(k,j,i,ib) ) * ddzu(k) )  &
7935                                    * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k-1,j,i), 0 ) )
7936          rs_p(k,j,i) = rs(k,j,i) + ( dt_3d * ( tsc(2) * tend(k,j,i) + tsc(3) * trs_m(k,j,i) )     &
7937                                      - tsc(5) * rdf_sc(k) * ( rs(k,j,i) - rs_init(k) ) )          &
7938                                  * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
7939          IF ( rs_p(k,j,i) < 0.0_wp )  rs_p(k,j,i) = 0.1_wp * rs(k,j,i)
7940       ENDDO
7941    ELSE
7942!
7943!--    Prognostic equation
7944!DIR$ IVDEP
7945       DO  k = nzb+1, nzt
7946          rs_p(k,j,i) = rs(k,j,i) + ( dt_3d * ( tsc(2) * tend(k,j,i) + tsc(3) * trs_m(k,j,i) )     &
7947                                                - tsc(5) * rdf_sc(k) * ( rs(k,j,i) - rs_init(k) ) )&
7948                                  * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
7949          IF ( rs_p(k,j,i) < 0.0_wp )  rs_p(k,j,i) = 0.1_wp * rs(k,j,i)
7950       ENDDO
7951    ENDIF
7952!
7953!-- Calculate tendencies for the next Runge-Kutta step
7954    IF ( timestep_scheme(1:5) == 'runge' )  THEN
7955       IF ( intermediate_timestep_count == 1 )  THEN
7956          DO  k = nzb+1, nzt
7957             trs_m(k,j,i) = tend(k,j,i)
7958          ENDDO
7959       ELSEIF ( intermediate_timestep_count < intermediate_timestep_count_max )  THEN
7960          DO  k = nzb+1, nzt
7961             trs_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * trs_m(k,j,i)
7962          ENDDO
7963       ENDIF
7964    ENDIF
7965
7966 END SUBROUTINE salsa_tendency_ij
7967!
7968!------------------------------------------------------------------------------!
7969! Description:
7970! ------------
7971!> Calculate the tendencies for aerosol number and mass concentrations.
7972!> For vector machines.
7973!------------------------------------------------------------------------------!
7974 SUBROUTINE salsa_tendency( id, rs_p, rs, trs_m, ib, ic, rs_init, do_sedimentation )
7975
7976    USE advec_ws,                                                                                  &
7977        ONLY:  advec_s_ws
7978    USE advec_s_pw_mod,                                                                            &
7979        ONLY:  advec_s_pw
7980    USE advec_s_up_mod,                                                                            &
7981        ONLY:  advec_s_up
7982    USE arrays_3d,                                                                                 &
7983        ONLY:  ddzu, rdf_sc, tend
7984    USE diffusion_s_mod,                                                                           &
7985        ONLY:  diffusion_s
7986    USE indices,                                                                                   &
7987        ONLY:  wall_flags_0
7988    USE surface_mod,                                                                               &
7989        ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
7990
7991    IMPLICIT NONE
7992
7993    CHARACTER(LEN = *) ::  id
7994
7995    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
7996    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
7997    INTEGER(iwp) ::  icc  !< (c-1)*nbins_aerosol+b
7998    INTEGER(iwp) ::  i    !<
7999    INTEGER(iwp) ::  j    !<
8000    INTEGER(iwp) ::  k    !<
8001
8002    LOGICAL ::  do_sedimentation  !<
8003
8004    REAL(wp), DIMENSION(nzb:nzt+1) ::  rs_init !<
8005
8006    REAL(wp), DIMENSION(:,:,:), POINTER ::  rs_p    !<
8007    REAL(wp), DIMENSION(:,:,:), POINTER ::  rs      !<
8008    REAL(wp), DIMENSION(:,:,:), POINTER ::  trs_m   !<
8009
8010    icc = ( ic - 1 ) * nbins_aerosol + ib
8011!
8012!-- Tendency-terms for reactive scalar
8013    tend = 0.0_wp
8014!
8015!-- Advection terms
8016    IF ( timestep_scheme(1:5) == 'runge' )  THEN
8017       IF ( ws_scheme_sca )  THEN
8018          CALL advec_s_ws( salsa_advc_flags_s, rs, id, bc_dirichlet_l  .OR.  bc_radiation_l,       &
8019                           bc_dirichlet_n  .OR.  bc_radiation_n,                                   &
8020                           bc_dirichlet_r  .OR.  bc_radiation_r,                                   &
8021                           bc_dirichlet_s  .OR.  bc_radiation_s )
8022       ELSE
8023          CALL advec_s_pw( rs )
8024       ENDIF
8025    ELSE
8026       CALL advec_s_up( rs )
8027    ENDIF
8028!
8029!-- Diffusion terms
8030    SELECT CASE ( id )
8031       CASE ( 'aerosol_number' )
8032          CALL diffusion_s( rs, surf_def_h(0)%answs(:,ib),                                         &
8033                                surf_def_h(1)%answs(:,ib), surf_def_h(2)%answs(:,ib),              &
8034                                surf_lsm_h%answs(:,ib),    surf_usm_h%answs(:,ib),                 &
8035                                surf_def_v(0)%answs(:,ib), surf_def_v(1)%answs(:,ib),              &
8036                                surf_def_v(2)%answs(:,ib), surf_def_v(3)%answs(:,ib),              &
8037                                surf_lsm_v(0)%answs(:,ib), surf_lsm_v(1)%answs(:,ib),              &
8038                                surf_lsm_v(2)%answs(:,ib), surf_lsm_v(3)%answs(:,ib),              &
8039                                surf_usm_v(0)%answs(:,ib), surf_usm_v(1)%answs(:,ib),              &
8040                                surf_usm_v(2)%answs(:,ib), surf_usm_v(3)%answs(:,ib) )
8041       CASE ( 'aerosol_mass' )
8042          CALL diffusion_s( rs, surf_def_h(0)%amsws(:,icc),                                        &
8043                                surf_def_h(1)%amsws(:,icc), surf_def_h(2)%amsws(:,icc),            &
8044                                surf_lsm_h%amsws(:,icc),    surf_usm_h%amsws(:,icc),               &
8045                                surf_def_v(0)%amsws(:,icc), surf_def_v(1)%amsws(:,icc),            &
8046                                surf_def_v(2)%amsws(:,icc), surf_def_v(3)%amsws(:,icc),            &
8047                                surf_lsm_v(0)%amsws(:,icc), surf_lsm_v(1)%amsws(:,icc),            &
8048                                surf_lsm_v(2)%amsws(:,icc), surf_lsm_v(3)%amsws(:,icc),            &
8049                                surf_usm_v(0)%amsws(:,icc), surf_usm_v(1)%amsws(:,icc),            &
8050                                surf_usm_v(2)%amsws(:,icc), surf_usm_v(3)%amsws(:,icc) )
8051       CASE ( 'salsa_gas' )
8052          CALL diffusion_s( rs, surf_def_h(0)%gtsws(:,ib),                                         &
8053                                surf_def_h(1)%gtsws(:,ib), surf_def_h(2)%gtsws(:,ib),              &
8054                                surf_lsm_h%gtsws(:,ib),    surf_usm_h%gtsws(:,ib),                 &
8055                                surf_def_v(0)%gtsws(:,ib), surf_def_v(1)%gtsws(:,ib),              &
8056                                surf_def_v(2)%gtsws(:,ib), surf_def_v(3)%gtsws(:,ib),              &
8057                                surf_lsm_v(0)%gtsws(:,ib), surf_lsm_v(1)%gtsws(:,ib),              &
8058                                surf_lsm_v(2)%gtsws(:,ib), surf_lsm_v(3)%gtsws(:,ib),              &
8059                                surf_usm_v(0)%gtsws(:,ib), surf_usm_v(1)%gtsws(:,ib),              &
8060                                surf_usm_v(2)%gtsws(:,ib), surf_usm_v(3)%gtsws(:,ib) )
8061    END SELECT
8062!
8063!-- Prognostic equation for a scalar
8064    DO  i = nxl, nxr
8065       DO  j = nys, nyn
8066!
8067!--       Sedimentation for aerosol number and mass
8068          IF ( lsdepo  .AND.  do_sedimentation )  THEN
8069             tend(nzb+1:nzt,j,i) = tend(nzb+1:nzt,j,i) - MAX( 0.0_wp, ( rs(nzb+2:nzt+1,j,i) *      &
8070                                   sedim_vd(nzb+2:nzt+1,j,i,ib) - rs(nzb+1:nzt,j,i) *              &
8071                                   sedim_vd(nzb+1:nzt,j,i,ib) ) * ddzu(nzb+1:nzt) ) *              &
8072                                   MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(nzb:nzt-1,j,i), 0 ) )
8073          ENDIF
8074          DO  k = nzb+1, nzt
8075             rs_p(k,j,i) = rs(k,j,i) +  ( dt_3d  * ( tsc(2) * tend(k,j,i) + tsc(3) * trs_m(k,j,i) )&
8076                                                  - tsc(5) * rdf_sc(k) * ( rs(k,j,i) - rs_init(k) )&
8077                                        ) * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
8078             IF ( rs_p(k,j,i) < 0.0_wp )  rs_p(k,j,i) = 0.1_wp * rs(k,j,i)
8079          ENDDO
8080       ENDDO
8081    ENDDO
8082!
8083!-- Calculate tendencies for the next Runge-Kutta step
8084    IF ( timestep_scheme(1:5) == 'runge' )  THEN
8085       IF ( intermediate_timestep_count == 1 )  THEN
8086          DO  i = nxl, nxr
8087             DO  j = nys, nyn
8088                DO  k = nzb+1, nzt
8089                   trs_m(k,j,i) = tend(k,j,i)
8090                ENDDO
8091             ENDDO
8092          ENDDO
8093       ELSEIF ( intermediate_timestep_count < intermediate_timestep_count_max )  THEN
8094          DO  i = nxl, nxr
8095             DO  j = nys, nyn
8096                DO  k = nzb+1, nzt
8097                   trs_m(k,j,i) =  -9.5625_wp * tend(k,j,i) + 5.3125_wp * trs_m(k,j,i)
8098                ENDDO
8099             ENDDO
8100          ENDDO
8101       ENDIF
8102    ENDIF
8103
8104 END SUBROUTINE salsa_tendency
8105
8106
8107!------------------------------------------------------------------------------!
8108! Description:
8109! ------------
8110!> Boundary conditions for prognostic variables in SALSA from module interface
8111!------------------------------------------------------------------------------!
8112 SUBROUTINE salsa_boundary_conditions
8113
8114    IMPLICIT NONE
8115
8116    INTEGER(iwp) ::  ib              !< index for aerosol size bins
8117    INTEGER(iwp) ::  ic              !< index for aerosol mass bins
8118    INTEGER(iwp) ::  icc             !< additional index for aerosol mass bins
8119    INTEGER(iwp) ::  ig              !< index for salsa gases
8120
8121
8122!
8123!-- moved from boundary_conds
8124    CALL salsa_boundary_conds
8125!
8126!-- Boundary conditions for prognostic quantitites of other modules:
8127!-- Here, only decycling is carried out
8128    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
8129
8130       DO  ib = 1, nbins_aerosol
8131          CALL salsa_boundary_conds( aerosol_number(ib)%conc_p, aerosol_number(ib)%init )
8132          DO  ic = 1, ncomponents_mass
8133             icc = ( ic - 1 ) * nbins_aerosol + ib
8134             CALL salsa_boundary_conds( aerosol_mass(icc)%conc_p, aerosol_mass(icc)%init )
8135          ENDDO
8136       ENDDO
8137       IF ( .NOT. salsa_gases_from_chem )  THEN
8138          DO  ig = 1, ngases_salsa
8139             CALL salsa_boundary_conds( salsa_gas(ig)%conc_p, salsa_gas(ig)%init )
8140          ENDDO
8141       ENDIF
8142
8143    ENDIF
8144
8145 END SUBROUTINE salsa_boundary_conditions
8146
8147!------------------------------------------------------------------------------!
8148! Description:
8149! ------------
8150!> Boundary conditions for prognostic variables in SALSA
8151!------------------------------------------------------------------------------!
8152 SUBROUTINE salsa_boundary_conds
8153
8154    USE arrays_3d,                                                                                 &
8155        ONLY:  dzu
8156
8157    USE surface_mod,                                                                               &
8158        ONLY :  bc_h
8159
8160    IMPLICIT NONE
8161
8162    INTEGER(iwp) ::  i    !< grid index x direction
8163    INTEGER(iwp) ::  ib   !< index for aerosol size bins
8164    INTEGER(iwp) ::  ic   !< index for chemical compounds in aerosols
8165    INTEGER(iwp) ::  icc  !< additional index for chemical compounds in aerosols
8166    INTEGER(iwp) ::  ig   !< idex for gaseous compounds
8167    INTEGER(iwp) ::  j    !< grid index y direction
8168    INTEGER(iwp) ::  k    !< grid index y direction
8169    INTEGER(iwp) ::  l    !< running index boundary type, for up- and downward-facing walls
8170    INTEGER(iwp) ::  m    !< running index surface elements
8171
8172    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
8173!
8174!--    Surface conditions:
8175       IF ( ibc_salsa_b == 0 )  THEN   ! Dirichlet
8176!
8177!--       Run loop over all non-natural and natural walls. Note, in wall-datatype the k coordinate
8178!--       belongs to the atmospheric grid point, therefore, set s_p at k-1
8179          DO  l = 0, 1
8180             !$OMP PARALLEL PRIVATE( ib, ic, icc, ig, i, j, k )
8181             !$OMP DO
8182             DO  m = 1, bc_h(l)%ns
8183
8184                i = bc_h(l)%i(m)
8185                j = bc_h(l)%j(m)
8186                k = bc_h(l)%k(m)
8187
8188                DO  ib = 1, nbins_aerosol
8189                   aerosol_number(ib)%conc_p(k+bc_h(l)%koff,j,i) =             &
8190                                    aerosol_number(ib)%conc(k+bc_h(l)%koff,j,i)
8191                   DO  ic = 1, ncomponents_mass
8192                      icc = ( ic - 1 ) * nbins_aerosol + ib
8193                      aerosol_mass(icc)%conc_p(k+bc_h(l)%koff,j,i) =           &
8194                                    aerosol_mass(icc)%conc(k+bc_h(l)%koff,j,i)
8195                   ENDDO
8196                ENDDO
8197                IF ( .NOT. salsa_gases_from_chem )  THEN
8198                   DO  ig = 1, ngases_salsa
8199                      salsa_gas(ig)%conc_p(k+bc_h(l)%koff,j,i) =               &
8200                                    salsa_gas(ig)%conc(k+bc_h(l)%koff,j,i)
8201                   ENDDO
8202                ENDIF
8203
8204             ENDDO
8205             !$OMP END PARALLEL
8206
8207          ENDDO
8208
8209       ELSE   ! Neumann
8210
8211          DO l = 0, 1
8212             !$OMP PARALLEL PRIVATE( ib, ic, icc, ig, i, j, k )
8213             !$OMP DO
8214             DO  m = 1, bc_h(l)%ns
8215
8216                i = bc_h(l)%i(m)
8217                j = bc_h(l)%j(m)
8218                k = bc_h(l)%k(m)
8219
8220                DO  ib = 1, nbins_aerosol
8221                   aerosol_number(ib)%conc_p(k+bc_h(l)%koff,j,i) =             &
8222                                               aerosol_number(ib)%conc_p(k,j,i)
8223                   DO  ic = 1, ncomponents_mass
8224                      icc = ( ic - 1 ) * nbins_aerosol + ib
8225                      aerosol_mass(icc)%conc_p(k+bc_h(l)%koff,j,i) =           &
8226                                               aerosol_mass(icc)%conc_p(k,j,i)
8227                   ENDDO
8228                ENDDO
8229                IF ( .NOT. salsa_gases_from_chem ) THEN
8230                   DO  ig = 1, ngases_salsa
8231                      salsa_gas(ig)%conc_p(k+bc_h(l)%koff,j,i) =               &
8232                                               salsa_gas(ig)%conc_p(k,j,i)
8233                   ENDDO
8234                ENDIF
8235
8236             ENDDO
8237             !$OMP END PARALLEL
8238          ENDDO
8239
8240       ENDIF
8241!
8242!--   Top boundary conditions:
8243       IF ( ibc_salsa_t == 0 )  THEN   ! Dirichlet
8244
8245          DO  ib = 1, nbins_aerosol
8246             aerosol_number(ib)%conc_p(nzt+1,:,:) = aerosol_number(ib)%conc(nzt+1,:,:)
8247             DO  ic = 1, ncomponents_mass
8248                icc = ( ic - 1 ) * nbins_aerosol + ib
8249                aerosol_mass(icc)%conc_p(nzt+1,:,:) = aerosol_mass(icc)%conc(nzt+1,:,:)
8250             ENDDO
8251          ENDDO
8252          IF ( .NOT. salsa_gases_from_chem )  THEN
8253             DO  ig = 1, ngases_salsa
8254                salsa_gas(ig)%conc_p(nzt+1,:,:) = salsa_gas(ig)%conc(nzt+1,:,:)
8255             ENDDO
8256          ENDIF
8257
8258       ELSEIF ( ibc_salsa_t == 1 )  THEN   ! Neumann
8259
8260          DO  ib = 1, nbins_aerosol
8261             aerosol_number(ib)%conc_p(nzt+1,:,:) = aerosol_number(ib)%conc_p(nzt,:,:)
8262             DO  ic = 1, ncomponents_mass
8263                icc = ( ic - 1 ) * nbins_aerosol + ib
8264                aerosol_mass(icc)%conc_p(nzt+1,:,:) = aerosol_mass(icc)%conc_p(nzt,:,:)
8265             ENDDO
8266          ENDDO
8267          IF ( .NOT. salsa_gases_from_chem )  THEN
8268             DO  ig = 1, ngases_salsa
8269                salsa_gas(ig)%conc_p(nzt+1,:,:) = salsa_gas(ig)%conc_p(nzt,:,:)
8270             ENDDO
8271          ENDIF
8272
8273       ELSEIF ( ibc_salsa_t == 2 )  THEN   ! Initial gradient
8274
8275          DO  ib = 1, nbins_aerosol
8276             aerosol_number(ib)%conc_p(nzt+1,:,:) = aerosol_number(ib)%conc_p(nzt,:,:) +           &
8277                                                    bc_an_t_val(ib) * dzu(nzt+1)
8278             DO  ic = 1, ncomponents_mass
8279                icc = ( ic - 1 ) * nbins_aerosol + ib
8280                aerosol_mass(icc)%conc_p(nzt+1,:,:) = aerosol_mass(icc)%conc_p(nzt,:,:) +          &
8281                                                      bc_am_t_val(icc) * dzu(nzt+1)
8282             ENDDO
8283          ENDDO
8284          IF ( .NOT. salsa_gases_from_chem )  THEN
8285             DO  ig = 1, ngases_salsa
8286                salsa_gas(ig)%conc_p(nzt+1,:,:) = salsa_gas(ig)%conc_p(nzt,:,:) +                  &
8287                                                  bc_gt_t_val(ig) * dzu(nzt+1)
8288             ENDDO
8289          ENDIF
8290
8291       ENDIF
8292!
8293!--    Lateral boundary conditions at the outflow
8294       IF ( bc_radiation_s )  THEN
8295          DO  ib = 1, nbins_aerosol
8296             aerosol_number(ib)%conc_p(:,nys-1,:) = aerosol_number(ib)%conc_p(:,nys,:)
8297             DO  ic = 1, ncomponents_mass
8298                icc = ( ic - 1 ) * nbins_aerosol + ib
8299                aerosol_mass(icc)%conc_p(:,nys-1,:) = aerosol_mass(icc)%conc_p(:,nys,:)
8300             ENDDO
8301          ENDDO
8302          IF ( .NOT. salsa_gases_from_chem )  THEN
8303             DO  ig = 1, ngases_salsa
8304                salsa_gas(ig)%conc_p(:,nys-1,:) = salsa_gas(ig)%conc_p(:,nys,:)
8305             ENDDO
8306          ENDIF
8307
8308       ELSEIF ( bc_radiation_n )  THEN
8309          DO  ib = 1, nbins_aerosol
8310             aerosol_number(ib)%conc_p(:,nyn+1,:) = aerosol_number(ib)%conc_p(:,nyn,:)
8311             DO  ic = 1, ncomponents_mass
8312                icc = ( ic - 1 ) * nbins_aerosol + ib
8313                aerosol_mass(icc)%conc_p(:,nyn+1,:) = aerosol_mass(icc)%conc_p(:,nyn,:)
8314             ENDDO
8315          ENDDO
8316          IF ( .NOT. salsa_gases_from_chem )  THEN
8317             DO  ig = 1, ngases_salsa
8318                salsa_gas(ig)%conc_p(:,nyn+1,:) = salsa_gas(ig)%conc_p(:,nyn,:)
8319             ENDDO
8320          ENDIF
8321
8322       ELSEIF ( bc_radiation_l )  THEN
8323          DO  ib = 1, nbins_aerosol
8324             aerosol_number(ib)%conc_p(:,:,nxl-1) = aerosol_number(ib)%conc_p(:,:,nxl)
8325             DO  ic = 1, ncomponents_mass
8326                icc = ( ic - 1 ) * nbins_aerosol + ib
8327                aerosol_mass(icc)%conc_p(:,:,nxl-1) = aerosol_mass(icc)%conc_p(:,:,nxl)
8328             ENDDO
8329          ENDDO
8330          IF ( .NOT. salsa_gases_from_chem )  THEN
8331             DO  ig = 1, ngases_salsa
8332                salsa_gas(ig)%conc_p(:,:,nxl-1) = salsa_gas(ig)%conc_p(:,:,nxl)
8333             ENDDO
8334          ENDIF
8335
8336       ELSEIF ( bc_radiation_r )  THEN
8337          DO  ib = 1, nbins_aerosol
8338             aerosol_number(ib)%conc_p(:,:,nxr+1) = aerosol_number(ib)%conc_p(:,:,nxr)
8339             DO  ic = 1, ncomponents_mass
8340                icc = ( ic - 1 ) * nbins_aerosol + ib
8341                aerosol_mass(icc)%conc_p(:,:,nxr+1) = aerosol_mass(icc)%conc_p(:,:,nxr)
8342             ENDDO
8343          ENDDO
8344          IF ( .NOT. salsa_gases_from_chem )  THEN
8345             DO  ig = 1, ngases_salsa
8346                salsa_gas(ig)%conc_p(:,:,nxr+1) = salsa_gas(ig)%conc_p(:,:,nxr)
8347             ENDDO
8348          ENDIF
8349
8350       ENDIF
8351
8352    ENDIF
8353
8354 END SUBROUTINE salsa_boundary_conds
8355
8356!------------------------------------------------------------------------------!
8357! Description:
8358! ------------
8359! Undoing of the previously done cyclic boundary conditions.
8360!------------------------------------------------------------------------------!
8361 SUBROUTINE salsa_boundary_conds_decycle ( sq, sq_init )
8362
8363    USE control_parameters,                                                                        &
8364        ONLY:  nesting_offline
8365
8366    IMPLICIT NONE
8367
8368    INTEGER(iwp) ::  boundary  !<
8369    INTEGER(iwp) ::  ee        !<
8370    INTEGER(iwp) ::  copied    !<
8371    INTEGER(iwp) ::  i         !<
8372    INTEGER(iwp) ::  j         !<
8373    INTEGER(iwp) ::  k         !<
8374    INTEGER(iwp) ::  ss        !<
8375
8376    REAL(wp) ::  flag  !< flag to mask topography grid points
8377
8378    REAL(wp), DIMENSION(nzb:nzt+1) ::  sq_init  !< initial concentration profile
8379
8380    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sq  !< concentration array
8381
8382    flag = 0.0_wp
8383!
8384!-- Skip input if forcing from a larger-scale models is applied.
8385    IF ( nesting_offline  .AND.  nesting_offline_salsa )  RETURN
8386!
8387!-- Left and right boundaries
8388    IF ( decycle_salsa_lr  .AND.  ( bc_lr_cyc  .OR. bc_lr == 'nested' ) )  THEN
8389
8390       DO  boundary = 1, 2
8391
8392          IF ( decycle_method_salsa(boundary) == 'dirichlet' )  THEN
8393!
8394!--          Initial profile is copied to ghost and first three layers
8395             ss = 1
8396             ee = 0
8397             IF ( boundary == 1  .AND.  nxl == 0 )  THEN
8398                ss = nxlg
8399                ee = nxl-1
8400             ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
8401                ss = nxr+1
8402                ee = nxrg
8403             ENDIF
8404
8405             DO  i = ss, ee
8406                DO  j = nysg, nyng
8407                   DO  k = nzb+1, nzt
8408                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
8409                      sq(k,j,i) = sq_init(k) * flag
8410                   ENDDO
8411                ENDDO
8412             ENDDO
8413
8414          ELSEIF ( decycle_method_salsa(boundary) == 'neumann' )  THEN
8415!
8416!--          The value at the boundary is copied to the ghost layers to simulate an outlet with
8417!--          zero gradient
8418             ss = 1
8419             ee = 0
8420             IF ( boundary == 1  .AND.  nxl == 0 )  THEN
8421                ss = nxlg
8422                ee = nxl-1
8423                copied = nxl
8424             ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
8425                ss = nxr+1
8426                ee = nxrg
8427                copied = nxr
8428             ENDIF
8429
8430              DO  i = ss, ee
8431                DO  j = nysg, nyng
8432                   DO  k = nzb+1, nzt
8433                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
8434                      sq(k,j,i) = sq(k,j,copied) * flag
8435                   ENDDO
8436                ENDDO
8437             ENDDO
8438
8439          ELSE
8440             WRITE(message_string,*) 'unknown decycling method: decycle_method_salsa (', boundary, &
8441                                     ') ="' // TRIM( decycle_method_salsa(boundary) ) // '"'
8442             CALL message( 'salsa_boundary_conds_decycle', 'PA0626', 1, 2, 0, 6, 0 )
8443          ENDIF
8444       ENDDO
8445    ENDIF
8446
8447!
8448!-- South and north boundaries
8449     IF ( decycle_salsa_ns  .AND.  ( bc_ns_cyc  .OR. bc_ns == 'nested' ) )  THEN
8450
8451       DO  boundary = 3, 4
8452
8453          IF ( decycle_method_salsa(boundary) == 'dirichlet' )  THEN
8454!
8455!--          Initial profile is copied to ghost and first three layers
8456             ss = 1
8457             ee = 0
8458             IF ( boundary == 3  .AND.  nys == 0 )  THEN
8459                ss = nysg
8460                ee = nys-1
8461             ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
8462                ss = nyn+1
8463                ee = nyng
8464             ENDIF
8465
8466             DO  i = nxlg, nxrg
8467                DO  j = ss, ee
8468                   DO  k = nzb+1, nzt
8469                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
8470                      sq(k,j,i) = sq_init(k) * flag
8471                   ENDDO
8472                ENDDO
8473             ENDDO
8474
8475          ELSEIF ( decycle_method_salsa(boundary) == 'neumann' )  THEN
8476!
8477!--          The value at the boundary is copied to the ghost layers to simulate an outlet with
8478!--          zero gradient
8479             ss = 1
8480             ee = 0
8481             IF ( boundary == 3  .AND.  nys == 0 )  THEN
8482                ss = nysg
8483                ee = nys-1
8484                copied = nys
8485             ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
8486                ss = nyn+1
8487                ee = nyng
8488                copied = nyn
8489             ENDIF
8490
8491              DO  i = nxlg, nxrg
8492                DO  j = ss, ee
8493                   DO  k = nzb+1, nzt
8494                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
8495                      sq(k,j,i) = sq(k,copied,i) * flag
8496                   ENDDO
8497                ENDDO
8498             ENDDO
8499
8500          ELSE
8501             WRITE(message_string,*) 'unknown decycling method: decycle_method_salsa (', boundary, &
8502                                     ') ="' // TRIM( decycle_method_salsa(boundary) ) // '"'
8503             CALL message( 'salsa_boundary_conds_decycle', 'PA0627', 1, 2, 0, 6, 0 )
8504          ENDIF
8505       ENDDO
8506    ENDIF
8507
8508 END SUBROUTINE salsa_boundary_conds_decycle
8509
8510!------------------------------------------------------------------------------!
8511! Description:
8512! ------------
8513!> Calculates the total dry or wet mass concentration for individual bins
8514!> Juha Tonttila (FMI) 2015
8515!> Tomi Raatikainen (FMI) 2016
8516!------------------------------------------------------------------------------!
8517 SUBROUTINE bin_mixrat( itype, ibin, i, j, mconc )
8518
8519    IMPLICIT NONE
8520
8521    CHARACTER(len=*), INTENT(in) ::  itype  !< 'dry' or 'wet'
8522
8523    INTEGER(iwp) ::  ic                 !< loop index for mass bin number
8524    INTEGER(iwp) ::  iend               !< end index: include water or not
8525
8526    INTEGER(iwp), INTENT(in) ::  ibin   !< index of the chemical component
8527    INTEGER(iwp), INTENT(in) ::  i      !< loop index for x-direction
8528    INTEGER(iwp), INTENT(in) ::  j      !< loop index for y-direction
8529
8530    REAL(wp), DIMENSION(:), INTENT(out) ::  mconc  !< total dry or wet mass concentration
8531
8532!-- Number of components
8533    IF ( itype == 'dry' )  THEN
8534       iend = prtcl%ncomp - 1 
8535    ELSE IF ( itype == 'wet' )  THEN
8536       iend = prtcl%ncomp
8537    ELSE
8538       message_string = 'Error in itype!'
8539       CALL message( 'bin_mixrat', 'PA0628', 2, 2, 0, 6, 0 )
8540    ENDIF
8541
8542    mconc = 0.0_wp
8543
8544    DO  ic = ibin, iend*nbins_aerosol+ibin, nbins_aerosol !< every nbins'th element
8545       mconc = mconc + aerosol_mass(ic)%conc(:,j,i)
8546    ENDDO
8547
8548 END SUBROUTINE bin_mixrat
8549
8550!------------------------------------------------------------------------------!
8551! Description:
8552! ------------
8553!> Sets surface fluxes
8554!------------------------------------------------------------------------------!
8555 SUBROUTINE salsa_emission_update
8556
8557    USE palm_date_time_mod,                                                                        &
8558        ONLY:  get_date_time
8559
8560    IMPLICIT NONE
8561
8562    IF ( include_emission )  THEN
8563
8564       IF ( time_since_reference_point >= skip_time_do_salsa  )  THEN
8565!
8566!--       Get time_utc_init from origin_date_time
8567          CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )
8568
8569          IF ( next_aero_emission_update <=                                                        &
8570               MAX( time_since_reference_point, 0.0_wp ) + time_utc_init )  THEN
8571             CALL salsa_emission_setup( .FALSE. )
8572          ENDIF
8573
8574          IF ( next_gas_emission_update <=                                                         &
8575               MAX( time_since_reference_point, 0.0_wp ) + time_utc_init )  THEN
8576             IF ( salsa_emission_mode == 'read_from_file'  .AND.  .NOT. salsa_gases_from_chem )    &
8577             THEN
8578                CALL salsa_gas_emission_setup( .FALSE. )
8579             ENDIF
8580          ENDIF
8581
8582       ENDIF
8583    ENDIF
8584
8585 END SUBROUTINE salsa_emission_update
8586
8587!------------------------------------------------------------------------------!
8588!> Description:
8589!> ------------
8590!> Define aerosol fluxes: constant or read from a from file
8591!> @todo - Emission stack height is not used yet. For default mode, emissions
8592!>         are assumed to occur on upward facing horizontal surfaces.
8593!------------------------------------------------------------------------------!
8594 SUBROUTINE salsa_emission_setup( init )
8595
8596    USE netcdf_data_input_mod,                                                                     &
8597        ONLY:  check_existence, close_input_file, get_attribute, get_variable,                     &
8598               inquire_num_variables, inquire_variable_names,                                      &
8599               get_dimension_length, open_read_file, street_type_f
8600
8601    USE palm_date_time_mod,                                                                        &
8602        ONLY:  days_per_week, get_date_time, hours_per_day, months_per_year, seconds_per_hour
8603
8604    USE surface_mod,                                                                               &
8605        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
8606
8607    IMPLICIT NONE
8608
8609    CHARACTER(LEN=80) ::  daytype = 'workday'  !< default day type
8610    CHARACTER(LEN=25) ::  in_name              !< name of a gas in the input file
8611    CHARACTER(LEN=25) ::  mod_name             !< name in the input file
8612
8613    INTEGER(iwp) ::  day_of_month   !< day of the month
8614    INTEGER(iwp) ::  day_of_week    !< day of the week
8615    INTEGER(iwp) ::  day_of_year    !< day of the year
8616    INTEGER(iwp) ::  hour_of_day    !< hour of the day
8617    INTEGER(iwp) ::  i              !< loop index
8618    INTEGER(iwp) ::  ib             !< loop index: aerosol number bins
8619    INTEGER(iwp) ::  ic             !< loop index: aerosol chemical components
8620    INTEGER(iwp) ::  id_salsa       !< NetCDF id of aerosol emission input file
8621    INTEGER(iwp) ::  in             !< loop index: emission category
8622    INTEGER(iwp) ::  index_dd       !< index day
8623    INTEGER(iwp) ::  index_hh       !< index hour
8624    INTEGER(iwp) ::  index_mm       !< index month
8625    INTEGER(iwp) ::  inn            !< loop index
8626    INTEGER(iwp) ::  j              !< loop index
8627    INTEGER(iwp) ::  month_of_year  !< month of the year
8628    INTEGER(iwp) ::  ss             !< loop index
8629
8630    INTEGER(iwp), DIMENSION(maxspec) ::  cc_i2m   !<
8631
8632    LOGICAL  ::  netcdf_extend = .FALSE.  !< NetCDF input file exists
8633
8634    LOGICAL, INTENT(in) ::  init  !< if .TRUE. --> initialisation call
8635
8636    REAL(wp) ::  second_of_day  !< second of the day
8637
8638    REAL(wp), DIMENSION(24) ::  par_emis_time_factor =  & !< time factors for the parameterized mode
8639                                                      (/ 0.009, 0.004, 0.004, 0.009, 0.029, 0.039, &
8640                                                         0.056, 0.053, 0.051, 0.051, 0.052, 0.055, &
8641                                                         0.059, 0.061, 0.064, 0.067, 0.069, 0.069, &
8642                                                         0.049, 0.039, 0.039, 0.029, 0.024, 0.019 /)
8643
8644    REAL(wp), DIMENSION(:), ALLOCATABLE ::  nsect_emission  !< sectional number emission
8645
8646    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  source_array  !< temporary source array
8647
8648!
8649!-- Define emissions:
8650    SELECT CASE ( salsa_emission_mode )
8651
8652       CASE ( 'uniform', 'parameterized' )
8653
8654          IF ( init )  THEN  ! Do only once
8655!
8656!-           Form a sectional size distribution for the emissions
8657             ALLOCATE( nsect_emission(1:nbins_aerosol),                                            &
8658                       source_array(nys:nyn,nxl:nxr,1:nbins_aerosol) )
8659!
8660!--          Precalculate a size distribution for the emission based on the mean diameter, standard
8661!--          deviation and number concentration per each log-normal mode
8662             CALL size_distribution( surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag,  &
8663                                     nsect_emission )
8664             IF ( salsa_emission_mode == 'uniform' )  THEN
8665                DO  ib = 1, nbins_aerosol
8666                   source_array(:,:,ib) = nsect_emission(ib)
8667                ENDDO
8668             ELSE
8669!
8670!--             Get a time factor for the specific hour
8671                IF ( .NOT.  ALLOCATED( aero_emission_att%time_factor ) )                           &
8672                   ALLOCATE( aero_emission_att%time_factor(1) )
8673                CALL get_date_time( MAX( time_since_reference_point, 0.0_wp ), hour=hour_of_day )
8674                index_hh = hour_of_day
8675                aero_emission_att%time_factor(1) = par_emis_time_factor(index_hh+1)
8676
8677                IF ( street_type_f%from_file )  THEN
8678                   DO  i = nxl, nxr
8679                      DO  j = nys, nyn
8680                         IF ( street_type_f%var(j,i) >= main_street_id  .AND.                      &
8681                              street_type_f%var(j,i) < max_street_id )  THEN
8682                            source_array(j,i,:) = nsect_emission(:) * emiss_factor_main *          &
8683                                                  aero_emission_att%time_factor(1)
8684                         ELSEIF ( street_type_f%var(j,i) >= side_street_id  .AND.                  &
8685                                  street_type_f%var(j,i) < main_street_id )  THEN
8686                            source_array(j,i,:) = nsect_emission(:) * emiss_factor_side *          &
8687                                                  aero_emission_att%time_factor(1)
8688                         ENDIF
8689                      ENDDO
8690                   ENDDO
8691                ELSE
8692                   WRITE( message_string, * ) 'salsa_emission_mode = "parameterized" but the '//  &
8693                                              'street_type data is missing.'
8694                   CALL message( 'salsa_emission_setup', 'PA0661', 1, 2, 0, 6, 0 )
8695                ENDIF
8696             ENDIF
8697!
8698!--          Check which chemical components are used
8699             cc_i2m = 0
8700             IF ( index_so4 > 0 ) cc_i2m(1) = index_so4
8701             IF ( index_oc > 0 )  cc_i2m(2) = index_oc
8702             IF ( index_bc > 0 )  cc_i2m(3) = index_bc
8703             IF ( index_du > 0 )  cc_i2m(4) = index_du
8704             IF ( index_ss > 0 )  cc_i2m(5) = index_ss
8705             IF ( index_no > 0 )  cc_i2m(6) = index_no
8706             IF ( index_nh > 0 )  cc_i2m(7) = index_nh
8707!
8708!--          Normalise mass fractions so that their sum is 1
8709             aerosol_flux_mass_fracs_a = aerosol_flux_mass_fracs_a /                               &
8710                                         SUM( aerosol_flux_mass_fracs_a(1:ncc ) )
8711             IF ( salsa_emission_mode ==  'uniform' )  THEN
8712!
8713!--             Set uniform fluxes of default horizontal surfaces
8714                CALL set_flux( surf_def_h(0), cc_i2m, aerosol_flux_mass_fracs_a, source_array )
8715             ELSE
8716!
8717!--             Set fluxes normalised based on the street type on land surfaces
8718                CALL set_flux( surf_lsm_h, cc_i2m, aerosol_flux_mass_fracs_a, source_array )
8719             ENDIF
8720
8721             DEALLOCATE( nsect_emission, source_array )
8722          ENDIF
8723
8724       CASE ( 'read_from_file' )
8725!
8726!--       Reset surface fluxes
8727          surf_def_h(0)%answs = 0.0_wp
8728          surf_def_h(0)%amsws = 0.0_wp
8729          surf_lsm_h%answs = 0.0_wp
8730          surf_lsm_h%amsws = 0.0_wp
8731          surf_usm_h%answs = 0.0_wp
8732          surf_usm_h%amsws = 0.0_wp
8733
8734!
8735!--       Reset source arrays:
8736          DO  ib = 1, nbins_aerosol
8737             aerosol_number(ib)%source = 0.0_wp
8738          ENDDO
8739
8740          DO  ic = 1, ncomponents_mass * nbins_aerosol
8741             aerosol_mass(ic)%source = 0.0_wp
8742          ENDDO
8743
8744#if defined( __netcdf )
8745!
8746!--       Check existence of PIDS_SALSA file
8747          INQUIRE( FILE = TRIM( input_file_salsa ) // TRIM( coupling_char ), EXIST = netcdf_extend )
8748          IF ( .NOT. netcdf_extend )  THEN
8749             message_string = 'Input file '// TRIM( input_file_salsa ) //  TRIM( coupling_char )&
8750                              // ' missing!'
8751             CALL message( 'salsa_emission_setup', 'PA0629', 1, 2, 0, 6, 0 )
8752          ENDIF
8753!
8754!--       Open file in read-only mode
8755          CALL open_read_file( TRIM( input_file_salsa ) // TRIM( coupling_char ), id_salsa )
8756
8757          IF ( init )  THEN
8758!
8759!--          Variable names
8760             CALL inquire_num_variables( id_salsa, aero_emission_att%num_vars )
8761             ALLOCATE( aero_emission_att%var_names(1:aero_emission_att%num_vars) )
8762             CALL inquire_variable_names( id_salsa, aero_emission_att%var_names )
8763!
8764!--          Read the index and name of chemical components
8765             CALL get_dimension_length( id_salsa, aero_emission_att%ncc, 'composition_index' )
8766             ALLOCATE( aero_emission_att%cc_index(1:aero_emission_att%ncc) )
8767             CALL get_variable( id_salsa, 'composition_index', aero_emission_att%cc_index )
8768
8769             IF ( check_existence( aero_emission_att%var_names, 'composition_name' ) )  THEN
8770                CALL get_variable( id_salsa, 'composition_name', aero_emission_att%cc_name,        &
8771                                   aero_emission_att%ncc )
8772             ELSE
8773                message_string = 'Missing composition_name in ' // TRIM( input_file_salsa )
8774                CALL message( 'salsa_emission_setup', 'PA0657', 1, 2, 0, 6, 0 )
8775             ENDIF
8776!
8777!--          Find the corresponding chemical components in the model
8778             aero_emission_att%cc_in2mod = 0
8779             DO  ic = 1, aero_emission_att%ncc
8780                in_name = aero_emission_att%cc_name(ic)
8781                SELECT CASE ( TRIM( in_name ) )
8782                   CASE ( 'H2SO4', 'h2so4', 'SO4', 'so4' )
8783                      aero_emission_att%cc_in2mod(1) = ic
8784                   CASE ( 'OC', 'oc', 'organics' )
8785                      aero_emission_att%cc_in2mod(2) = ic
8786                   CASE ( 'BC', 'bc' )
8787                      aero_emission_att%cc_in2mod(3) = ic
8788                   CASE ( 'DU', 'du' )
8789                      aero_emission_att%cc_in2mod(4) = ic
8790                   CASE ( 'SS', 'ss' )
8791                      aero_emission_att%cc_in2mod(5) = ic
8792                   CASE ( 'HNO3', 'hno3', 'NO', 'no', 'NO3', 'no3' )
8793                      aero_emission_att%cc_in2mod(6) = ic
8794                   CASE ( 'NH3', 'nh3', 'NH', 'nh', 'NH4', 'nh4' )
8795                      aero_emission_att%cc_in2mod(7) = ic
8796                END SELECT
8797
8798             ENDDO
8799
8800             IF ( SUM( aero_emission_att%cc_in2mod ) == 0 )  THEN
8801                message_string = 'None of the aerosol chemical components in ' // TRIM(            &
8802                                 input_file_salsa ) // ' correspond to the ones applied in SALSA.'
8803                CALL message( 'salsa_emission_setup', 'PA0630', 1, 2, 0, 6, 0 )
8804             ENDIF
8805!
8806!--          Get number of emission categories
8807             CALL get_dimension_length( id_salsa, aero_emission_att%ncat, 'ncat' )
8808!
8809!--          Get the chemical composition (i.e. mass fraction of different species) in aerosols
8810             IF ( check_existence( aero_emission_att%var_names, 'emission_mass_fracs' ) )  THEN
8811                ALLOCATE( aero_emission%mass_fracs(1:aero_emission_att%ncat,                       &
8812                                                   1:aero_emission_att%ncc) )
8813                CALL get_variable( id_salsa, 'emission_mass_fracs', aero_emission%mass_fracs,      &
8814                                   0, aero_emission_att%ncc-1, 0, aero_emission_att%ncat-1 )
8815             ELSE
8816                message_string = 'Missing emission_mass_fracs in ' //  TRIM( input_file_salsa )
8817                CALL message( 'salsa_emission_setup', 'PA0659', 1, 2, 0, 6, 0 )
8818             ENDIF
8819!
8820!--          If the chemical component is not activated, set its mass fraction to 0 to avoid
8821!--          inbalance between number and mass flux
8822             cc_i2m = aero_emission_att%cc_in2mod
8823             IF ( index_so4 < 0  .AND.  cc_i2m(1) > 0 )                                            &
8824                aero_emission%mass_fracs(:,cc_i2m(1)) = 0.0_wp
8825             IF ( index_oc  < 0  .AND.  cc_i2m(2) > 0 )                                            &
8826                aero_emission%mass_fracs(:,cc_i2m(2)) = 0.0_wp
8827             IF ( index_bc  < 0  .AND.  cc_i2m(3) > 0 )                                            &
8828                aero_emission%mass_fracs(:,cc_i2m(3)) = 0.0_wp
8829             IF ( index_du  < 0  .AND.  cc_i2m(4) > 0 )                                            &
8830                aero_emission%mass_fracs(:,cc_i2m(4)) = 0.0_wp
8831             IF ( index_ss  < 0  .AND.  cc_i2m(5) > 0 )                                            &
8832                aero_emission%mass_fracs(:,cc_i2m(5)) = 0.0_wp
8833             IF ( index_no  < 0  .AND.  cc_i2m(6) > 0 )                                            &
8834                aero_emission%mass_fracs(:,cc_i2m(6)) = 0.0_wp
8835             IF ( index_nh  < 0  .AND.  cc_i2m(7) > 0 )                                            &
8836                aero_emission%mass_fracs(:,cc_i2m(7)) = 0.0_wp
8837!
8838!--          Then normalise the mass fraction so that SUM = 1
8839             DO  in = 1, aero_emission_att%ncat
8840                aero_emission%mass_fracs(in,:) = aero_emission%mass_fracs(in,:) /                  &
8841                                                 SUM( aero_emission%mass_fracs(in,:) )
8842             ENDDO
8843!
8844!--          Inquire the fill value
8845             CALL get_attribute( id_salsa, '_FillValue', aero_emission%fill, .FALSE.,              &
8846                                 'aerosol_emission_values' )
8847!
8848!--          Inquire units of emissions
8849             CALL get_attribute( id_salsa, 'units', aero_emission_att%units, .FALSE.,              &
8850                                 'aerosol_emission_values' )
8851!
8852!--          Inquire the level of detail (lod)
8853             CALL get_attribute( id_salsa, 'lod', aero_emission_att%lod, .FALSE.,                  &
8854                                 'aerosol_emission_values' )
8855
8856!
8857!--          Read different emission information depending on the level of detail of emissions:
8858
8859!
8860!--          Default mode:
8861             IF ( aero_emission_att%lod == 1 )  THEN
8862!
8863!--             Unit conversion factor: convert to SI units (kg/m2/s)
8864                IF ( aero_emission_att%units == 'kg/m2/yr' )  THEN
8865                   aero_emission_att%conversion_factor = 1.0_wp / 3600.0_wp
8866                ELSEIF ( aero_emission_att%units == 'g/m2/yr' )  THEN
8867                   aero_emission_att%conversion_factor = 0.001_wp / 3600.0_wp
8868                ELSE
8869                   message_string = 'unknown unit for aerosol emissions: ' //                      &
8870                                    TRIM( aero_emission_att%units ) // ' (lod1)'
8871                   CALL message( 'salsa_emission_setup','PA0631', 1, 2, 0, 6, 0 )
8872                ENDIF
8873!
8874!--             Allocate emission arrays
8875                ALLOCATE( aero_emission_att%cat_index(1:aero_emission_att%ncat),                   &
8876                          aero_emission_att%rho(1:aero_emission_att%ncat),                         &
8877                          aero_emission_att%time_factor(1:aero_emission_att%ncat) )
8878!
8879!--             Get emission category names and indices
8880                IF ( check_existence( aero_emission_att%var_names, 'emission_category_name' ) )  THEN
8881                   CALL get_variable( id_salsa, 'emission_category_name',                          &
8882                                      aero_emission_att%cat_name,  aero_emission_att%ncat )
8883                ELSE
8884                   message_string = 'Missing emission_category_name in ' // TRIM( input_file_salsa )
8885                   CALL message( 'salsa_emission_setup', 'PA0658', 1, 2, 0, 6, 0 )
8886                ENDIF
8887                CALL get_variable( id_salsa, 'emission_category_index', aero_emission_att%cat_index )
8888!
8889!--             Find corresponding emission categories
8890                DO  in = 1, aero_emission_att%ncat
8891                   in_name = aero_emission_att%cat_name(in)
8892                   DO  ss = 1, def_modes%ndc
8893                      mod_name = def_modes%cat_name_table(ss)
8894                      IF ( TRIM( in_name(1:4) ) == TRIM( mod_name(1:4 ) ) )  THEN
8895                         def_modes%cat_input_to_model(ss) = in
8896                      ENDIF
8897                   ENDDO
8898                ENDDO
8899
8900                IF ( SUM( def_modes%cat_input_to_model ) == 0 )  THEN
8901                   message_string = 'None of the emission categories in ' //  TRIM(                &
8902                                    input_file_salsa ) // ' match with the ones in the model.'
8903                   CALL message( 'salsa_emission_setup', 'PA0632', 1, 2, 0, 6, 0 )
8904                ENDIF
8905!
8906!--             Emission time factors: Find check whether emission time factors are given for each
8907!--             hour of year OR based on month, day and hour
8908!
8909!--             For each hour of year:
8910                IF ( check_existence( aero_emission_att%var_names, 'nhoursyear' ) )  THEN
8911                   CALL get_dimension_length( id_salsa, aero_emission_att%nhoursyear, 'nhoursyear' )
8912                   ALLOCATE( aero_emission_att%etf(1:aero_emission_att%ncat,                       &
8913                                                   1:aero_emission_att%nhoursyear) )
8914                   CALL get_variable( id_salsa, 'emission_time_factors', aero_emission_att%etf,    &
8915                                    0, aero_emission_att%nhoursyear-1, 0, aero_emission_att%ncat-1 )
8916!
8917!--             Based on the month, day and hour:
8918                ELSEIF ( check_existence( aero_emission_att%var_names, 'nmonthdayhour' ) )  THEN
8919                   CALL get_dimension_length( id_salsa, aero_emission_att%nmonthdayhour,           &
8920                                              'nmonthdayhour' )
8921                   ALLOCATE( aero_emission_att%etf(1:aero_emission_att%ncat,                       &
8922                                                   1:aero_emission_att%nmonthdayhour) )
8923                   CALL get_variable( id_salsa, 'emission_time_factors', aero_emission_att%etf,    &
8924                                 0, aero_emission_att%nmonthdayhour-1, 0, aero_emission_att%ncat-1 )
8925                ELSE
8926                   message_string = 'emission_time_factors should be given for each nhoursyear ' //&
8927                                    'OR nmonthdayhour'
8928                   CALL message( 'salsa_emission_setup','PA0633', 1, 2, 0, 6, 0 )
8929                ENDIF
8930!
8931!--             Next emission update
8932                CALL get_date_time( time_since_reference_point, second_of_day=second_of_day )
8933                next_aero_emission_update = MOD( second_of_day, seconds_per_hour ) !- seconds_per_hour
8934!
8935!--             Calculate average mass density (kg/m3)
8936                aero_emission_att%rho = 0.0_wp
8937
8938                IF ( cc_i2m(1) /= 0 )  aero_emission_att%rho = aero_emission_att%rho +  arhoh2so4 *&
8939                                                               aero_emission%mass_fracs(:,cc_i2m(1))
8940                IF ( cc_i2m(2) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhooc *    &
8941                                                               aero_emission%mass_fracs(:,cc_i2m(2))
8942                IF ( cc_i2m(3) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhobc *    &
8943                                                               aero_emission%mass_fracs(:,cc_i2m(3))
8944                IF ( cc_i2m(4) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhodu *    &
8945                                                               aero_emission%mass_fracs(:,cc_i2m(4))
8946                IF ( cc_i2m(5) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhoss *    &
8947                                                               aero_emission%mass_fracs(:,cc_i2m(5))
8948                IF ( cc_i2m(6) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhohno3 *  &
8949                                                               aero_emission%mass_fracs(:,cc_i2m(6))
8950                IF ( cc_i2m(7) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhonh3 *   &
8951                                                               aero_emission%mass_fracs(:,cc_i2m(7))
8952!
8953!--             Allocate and read surface emission data (in total PM, get_variable_3d_real)
8954                ALLOCATE( aero_emission%def_data(nys:nyn,nxl:nxr,1:aero_emission_att%ncat) )
8955                CALL get_variable( id_salsa, 'aerosol_emission_values', aero_emission%def_data,    &
8956                                   0, aero_emission_att%ncat-1, nxl, nxr, nys, nyn )
8957
8958!
8959!--          Pre-processed mode
8960             ELSEIF ( aero_emission_att%lod == 2 )  THEN
8961!
8962!--             Unit conversion factor: convert to SI units (#/m2/s)
8963                IF ( aero_emission_att%units == '#/m2/s' )  THEN
8964                   aero_emission_att%conversion_factor = 1.0_wp
8965                ELSE
8966                   message_string = 'unknown unit for aerosol emissions: ' //                      &
8967                                    TRIM( aero_emission_att%units )
8968                   CALL message( 'salsa_emission_setup','PA0634', 1, 2, 0, 6, 0 )
8969                ENDIF
8970!
8971!--             Number of aerosol size bins in the emission data
8972                CALL get_dimension_length( id_salsa, aero_emission_att%nbins, 'Dmid' )
8973                IF ( aero_emission_att%nbins /= nbins_aerosol )  THEN
8974                   message_string = 'The number of size bins in aerosol input data does not ' //   &
8975                                    'correspond to the model set-up'
8976                   CALL message( 'salsa_emission_setup','PA0635', 1, 2, 0, 6, 0 )
8977                ENDIF
8978!
8979!--             Number of time steps in the emission data
8980                CALL get_dimension_length( id_salsa, aero_emission_att%nt, 'time')
8981!
8982!--             Allocate bin diameters, time and mass fraction array
8983                ALLOCATE( aero_emission_att%dmid(1:nbins_aerosol),                                 &
8984                          aero_emission_att%time(1:aero_emission_att%nt),                          &
8985                          aero_emission%num_fracs(1:aero_emission_att%ncat,1:nbins_aerosol) )
8986!
8987!--             Read mean diameters
8988                CALL get_variable( id_salsa, 'Dmid', aero_emission_att%dmid )
8989!
8990!--             Check whether the sectional representation of the aerosol size distribution conform
8991!--             to the one applied in the model
8992                IF ( ANY( ABS( ( aero(1:nbins_aerosol)%dmid - aero_emission_att%dmid ) /           &
8993                               aero(1:nbins_aerosol)%dmid ) > 0.1_wp )  )  THEN
8994                   message_string = 'Mean diameters of size bins in ' // TRIM( input_file_salsa )  &
8995                                    // ' do not match with the ones in the model.'
8996                   CALL message( 'salsa_emission_setup','PA0636', 1, 2, 0, 6, 0 )
8997                ENDIF
8998!
8999!--             Read time stamps:
9000                IF ( check_existence( aero_emission_att%var_names, 'time' ) )  THEN
9001                   CALL get_variable( id_salsa, 'time', aero_emission_att%time )
9002                ELSE
9003                   message_string = 'Missing time in ' //  TRIM( input_file_salsa )
9004                   CALL message( 'salsa_emission_setup', 'PA0660', 1, 2, 0, 6, 0 )
9005                ENDIF
9006!
9007!--             Read emission number fractions per category
9008                IF ( check_existence( aero_emission_att%var_names, 'emission_number_fracs' ) )  THEN
9009                   CALL get_variable( id_salsa, 'emission_number_fracs', aero_emission%num_fracs,  &
9010                                      0, nbins_aerosol-1, 0, aero_emission_att%ncat-1 )
9011                ELSE
9012                   message_string = 'Missing emission_number_fracs in ' //  TRIM( input_file_salsa )
9013                   CALL message( 'salsa_emission_setup', 'PA0659', 1, 2, 0, 6, 0 )
9014                ENDIF
9015
9016             ELSE
9017                message_string = 'Unknown lod for aerosol_emission_values.'
9018                CALL message( 'salsa_emission','PA0637', 1, 2, 0, 6, 0 )
9019
9020             ENDIF  ! lod
9021
9022          ENDIF  ! init
9023!
9024!--       Define and set current emission values:
9025!
9026!--       Default type emissions (aerosol emission given as total mass emission per year):
9027          IF ( aero_emission_att%lod == 1 )  THEN
9028!
9029!--          Emission time factors for each emission category at current time step
9030             IF ( aero_emission_att%nhoursyear > aero_emission_att%nmonthdayhour )  THEN
9031!
9032!--             Get the index of the current hour
9033                CALL get_date_time( MAX( 0.0_wp, time_since_reference_point ),                     &
9034                                    day_of_year=day_of_year, hour=hour_of_day )
9035                index_hh = ( day_of_year - 1_iwp ) * hours_per_day + hour_of_day
9036                aero_emission_att%time_factor = aero_emission_att%etf(:,index_hh+1)
9037
9038             ELSEIF ( aero_emission_att%nhoursyear < aero_emission_att%nmonthdayhour )  THEN
9039!
9040!--             Get the index of current hour (index_hh) (TODO: Now "workday" is always assumed.
9041!--             Needs to be calculated.)
9042                CALL get_date_time( MAX( 0.0_wp, time_since_reference_point ), month=month_of_year,&
9043                                    day=day_of_month, hour=hour_of_day, day_of_week=day_of_week )
9044                index_mm = month_of_year
9045                index_dd = months_per_year + day_of_week
9046                SELECT CASE(TRIM(daytype))
9047
9048                   CASE ("workday")
9049                      index_hh = months_per_year + days_per_week + hour_of_day
9050
9051                   CASE ("weekend")
9052                      index_hh = months_per_year + days_per_week + hours_per_day + hour_of_day
9053
9054                   CASE ("holiday")
9055                      index_hh = months_per_year + days_per_week + 2*hours_per_day + hour_of_day
9056
9057                END SELECT
9058                aero_emission_att%time_factor = aero_emission_att%etf(:,index_mm) *                &
9059                                                aero_emission_att%etf(:,index_dd) *                &
9060                                                aero_emission_att%etf(:,index_hh+1)
9061             ENDIF
9062
9063!
9064!--          Create a sectional number size distribution for emissions
9065             ALLOCATE( nsect_emission(1:nbins_aerosol),source_array(nys:nyn,nxl:nxr,1:nbins_aerosol) )
9066             DO  in = 1, aero_emission_att%ncat
9067
9068                inn = def_modes%cat_input_to_model(in)
9069!
9070!--             Calculate the number concentration (1/m3) of a log-normal size distribution
9071!--             following Jacobson (2005): Eq 13.25.
9072                def_modes%ntot_table = 6.0_wp * def_modes%pm_frac_table(:,inn) / ( pi *            &
9073                                       ( def_modes%dpg_table )**3 *  EXP( 4.5_wp *                 &
9074                                       LOG( def_modes%sigmag_table )**2 ) )
9075!
9076!--             Sectional size distibution (1/m3) from a log-normal one
9077                CALL size_distribution( def_modes%ntot_table, def_modes%dpg_table,                 &
9078                                        def_modes%sigmag_table, nsect_emission )
9079
9080                source_array = 0.0_wp
9081                DO  ib = 1, nbins_aerosol
9082                   source_array(:,:,ib) = aero_emission%def_data(:,:,in) *                         &
9083                                          aero_emission_att%conversion_factor /                    &
9084                                          aero_emission_att%rho(in) * nsect_emission(ib) *         &
9085                                          aero_emission_att%time_factor(in)
9086                ENDDO
9087!
9088!--             Set surface fluxes of aerosol number and mass on horizontal surfaces. Set fluxes
9089!--             only for either default, land or urban surface.
9090                IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
9091                   CALL set_flux( surf_def_h(0), aero_emission_att%cc_in2mod,                      &
9092                                  aero_emission%mass_fracs(in,:), source_array )
9093                ELSE
9094                   CALL set_flux( surf_usm_h, aero_emission_att%cc_in2mod,                         &
9095                                  aero_emission%mass_fracs(in,:), source_array )
9096                   CALL set_flux( surf_lsm_h, aero_emission_att%cc_in2mod,                         &
9097                                  aero_emission%mass_fracs(in,:), source_array )
9098                ENDIF
9099             ENDDO
9100!
9101!--          The next emission update is again after one hour
9102             next_aero_emission_update = next_aero_emission_update + 3600.0_wp
9103
9104
9105             DEALLOCATE( nsect_emission, source_array )
9106!
9107!--       Pre-processed:
9108          ELSEIF ( aero_emission_att%lod == 2 )  THEN
9109!
9110!--          Get time_utc_init from origin_date_time
9111             CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )
9112!
9113!--          Obtain time index for current point in time. Note, the time coordinate in the input
9114!--          file is relative to time_utc_init.
9115             aero_emission_att%tind = MINLOC( ABS( aero_emission_att%time - (                      &
9116                                                   time_utc_init + MAX( time_since_reference_point,&
9117                                                                        0.0_wp) ) ), DIM = 1 ) - 1
9118!
9119!--          Allocate the data input array always before reading in the data and deallocate after
9120             ALLOCATE( aero_emission%preproc_data(nys:nyn,nxl:nxr,1:aero_emission_att%ncat),       &
9121                       source_array(nys:nyn,nxl:nxr,1:nbins_aerosol) )
9122!
9123!--          Read in the next time step (get_variable_4d_to_3d_real)
9124             CALL get_variable( id_salsa, 'aerosol_emission_values', aero_emission%preproc_data,   &
9125                                aero_emission_att%tind, 0, aero_emission_att%ncat-1,               &
9126                                nxl, nxr, nys, nyn )
9127!
9128!--          Calculate the sources per category and set surface fluxes
9129             source_array = 0.0_wp
9130             DO  in = 1, aero_emission_att%ncat
9131                DO  ib = 1, nbins_aerosol
9132                   source_array(:,:,ib) = aero_emission%preproc_data(:,:,in) *                     &
9133                                          aero_emission%num_fracs(in,ib)
9134                ENDDO
9135!
9136!--             Set fluxes only for either default, land and urban surface.
9137                IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
9138                   CALL set_flux( surf_def_h(0), aero_emission_att%cc_in2mod,                      &
9139                                  aero_emission%mass_fracs(in,:), source_array )
9140                ELSE
9141                   CALL set_flux( surf_usm_h, aero_emission_att%cc_in2mod,                         &
9142                                  aero_emission%mass_fracs(in,:), source_array )
9143                   CALL set_flux( surf_lsm_h, aero_emission_att%cc_in2mod,                         &
9144                                  aero_emission%mass_fracs(in,:), source_array )
9145                ENDIF
9146             ENDDO
9147!
9148!--          Determine the next emission update
9149             next_aero_emission_update = aero_emission_att%time(aero_emission_att%tind+2)
9150
9151             DEALLOCATE( aero_emission%preproc_data, source_array )
9152
9153          ENDIF
9154!
9155!--       Close input file
9156          CALL close_input_file( id_salsa )
9157#else
9158          message_string = 'salsa_emission_mode = "read_from_file", but preprocessor directive ' //&
9159                           ' __netcdf is not used in compiling!'
9160          CALL message( 'salsa_emission_setup', 'PA0638', 1, 2, 0, 6, 0 )
9161
9162#endif
9163       CASE DEFAULT
9164          message_string = 'unknown salsa_emission_mode: ' // TRIM( salsa_emission_mode )
9165          CALL message( 'salsa_emission_setup', 'PA0639', 1, 2, 0, 6, 0 )
9166
9167    END SELECT
9168
9169    CONTAINS
9170
9171!------------------------------------------------------------------------------!
9172! Description:
9173! ------------
9174!> Sets the aerosol flux to aerosol arrays in 2a and 2b.
9175!------------------------------------------------------------------------------!
9176    SUBROUTINE set_flux( surface, cc_i_mod, mass_fracs, source_array )
9177
9178       USE arrays_3d,                                                                              &
9179           ONLY:  rho_air_zw
9180
9181       USE surface_mod,                                                                            &
9182           ONLY:  surf_type
9183
9184       IMPLICIT NONE
9185
9186       INTEGER(iwp) ::  i   !< loop index
9187       INTEGER(iwp) ::  ib  !< loop index
9188       INTEGER(iwp) ::  ic  !< loop index
9189       INTEGER(iwp) ::  j   !< loop index
9190       INTEGER(iwp) ::  k   !< loop index
9191       INTEGER(iwp) ::  m   !< running index for surface elements
9192
9193       INTEGER(iwp), DIMENSION(:) ::  cc_i_mod   !< index of chemical component in the input data
9194
9195       REAL(wp) ::  so4_oc  !< mass fraction between SO4 and OC in 1a
9196
9197       REAL(wp), DIMENSION(:), INTENT(in) ::  mass_fracs  !< mass fractions of chemical components
9198
9199       REAL(wp), DIMENSION(nys:nyn,nxl:nxr,1:nbins_aerosol), INTENT(inout) ::  source_array  !<
9200
9201       TYPE(surf_type), INTENT(inout) :: surface  !< respective surface type
9202
9203       so4_oc = 0.0_wp
9204
9205       DO  m = 1, surface%ns
9206!
9207!--       Get indices of respective grid point
9208          i = surface%i(m)
9209          j = surface%j(m)
9210          k = surface%k(m)
9211
9212          DO  ib = 1, nbins_aerosol
9213             IF ( source_array(j,i,ib) < nclim )  THEN
9214                source_array(j,i,ib) = 0.0_wp
9215             ENDIF
9216!
9217!--          Set mass fluxes.  First bins include only SO4 and/or OC.
9218             IF ( ib <= end_subrange_1a )  THEN
9219!
9220!--             Both sulphate and organic carbon
9221                IF ( index_so4 > 0  .AND.  index_oc > 0 )  THEN
9222
9223                   ic = ( index_so4 - 1 ) * nbins_aerosol + ib
9224                   so4_oc = mass_fracs(cc_i_mod(1)) / ( mass_fracs(cc_i_mod(1)) +                  &
9225                                                        mass_fracs(cc_i_mod(2)) )
9226                   surface%amsws(m,ic) = surface%amsws(m,ic) + so4_oc * source_array(j,i,ib)       &
9227                                         * api6 * aero(ib)%dmid**3 * arhoh2so4 * rho_air_zw(k-1)
9228                   aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(m,ic)
9229
9230                   ic = ( index_oc - 1 ) * nbins_aerosol + ib
9231                   surface%amsws(m,ic) = surface%amsws(m,ic) + ( 1-so4_oc ) * source_array(j,i,ib) &
9232                                         * api6 * aero(ib)%dmid**3 * arhooc * rho_air_zw(k-1)
9233                   aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(m,ic)
9234!
9235!--             Only sulphates
9236                ELSEIF ( index_so4 > 0  .AND.  index_oc < 0 )  THEN
9237                   ic = ( index_so4 - 1 ) * nbins_aerosol + ib
9238                   surface%amsws(m,ic) = surface%amsws(m,ic) + source_array(j,i,ib) * api6 *       &
9239                                         aero(ib)%dmid**3 * arhoh2so4 * rho_air_zw(k-1)
9240                   aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(m,ic)
9241!
9242!--             Only organic carbon
9243                ELSEIF ( index_so4 < 0  .AND.  index_oc > 0 )  THEN
9244                   ic = ( index_oc - 1 ) * nbins_aerosol + ib
9245                   surface%amsws(m,ic) = surface%amsws(m,ic) + source_array(j,i,ib) * api6 *       &
9246                                         aero(ib)%dmid**3 * arhooc * rho_air_zw(k-1)
9247                   aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(m,ic)
9248                ENDIF
9249
9250             ELSE
9251!
9252!--             Sulphate
9253                IF ( index_so4 > 0 )  THEN
9254                   ic = cc_i_mod(1)
9255                   CALL set_mass_flux( surface, m, ib, index_so4, mass_fracs(ic), arhoh2so4,       &
9256                                       source_array(j,i,ib) )
9257                ENDIF
9258!
9259!--             Organic carbon
9260                IF ( index_oc > 0 )  THEN
9261                   ic = cc_i_mod(2)
9262                   CALL set_mass_flux( surface, m, ib, index_oc, mass_fracs(ic),arhooc,            &
9263                                       source_array(j,i,ib) )
9264                ENDIF
9265!
9266!--             Black carbon
9267                IF ( index_bc > 0 )  THEN
9268                   ic = cc_i_mod(3)
9269                   CALL set_mass_flux( surface, m, ib, index_bc, mass_fracs(ic), arhobc,           &
9270                                       source_array(j,i,ib) )
9271                ENDIF
9272!
9273!--             Dust
9274                IF ( index_du > 0 )  THEN
9275                   ic = cc_i_mod(4)
9276                   CALL set_mass_flux( surface, m, ib, index_du, mass_fracs(ic), arhodu,           &
9277                                       source_array(j,i,ib) )
9278                ENDIF
9279!
9280!--             Sea salt
9281                IF ( index_ss > 0 )  THEN
9282                   ic = cc_i_mod(5)
9283                   CALL set_mass_flux( surface, m, ib, index_ss, mass_fracs(ic), arhoss,           &
9284                                       source_array(j,i,ib) )
9285                ENDIF
9286!
9287!--             Nitric acid
9288                IF ( index_no > 0 )  THEN
9289                    ic = cc_i_mod(6)
9290                   CALL set_mass_flux( surface, m, ib, index_no, mass_fracs(ic), arhohno3,         &
9291                                       source_array(j,i,ib) )
9292                ENDIF
9293!
9294!--             Ammonia
9295                IF ( index_nh > 0 )  THEN
9296                    ic = cc_i_mod(7)
9297                   CALL set_mass_flux( surface, m, ib, index_nh, mass_fracs(ic), arhonh3,          &
9298                                       source_array(j,i,ib) )
9299                ENDIF
9300
9301             ENDIF
9302!
9303!--          Save number fluxes in the end
9304             surface%answs(m,ib) = surface%answs(m,ib) + source_array(j,i,ib) * rho_air_zw(k-1)
9305             aerosol_number(ib)%source(j,i) = aerosol_number(ib)%source(j,i) + surface%answs(m,ib)
9306
9307          ENDDO  ! ib
9308       ENDDO  ! m
9309
9310    END SUBROUTINE set_flux
9311
9312!------------------------------------------------------------------------------!
9313! Description:
9314! ------------
9315!> Sets the mass emissions to aerosol arrays in 2a and 2b.
9316!------------------------------------------------------------------------------!
9317    SUBROUTINE set_mass_flux( surface, surf_num, ib, ispec, mass_frac, prho, nsource )
9318
9319       USE arrays_3d,                                                                              &
9320           ONLY:  rho_air_zw
9321
9322       USE surface_mod,                                                                            &
9323           ONLY:  surf_type
9324
9325       IMPLICIT NONE
9326
9327       INTEGER(iwp) ::  i   !< loop index
9328       INTEGER(iwp) ::  j   !< loop index
9329       INTEGER(iwp) ::  k   !< loop index
9330       INTEGER(iwp) ::  ic  !< loop index
9331
9332       INTEGER(iwp), INTENT(in) :: ib        !< Aerosol size bin index
9333       INTEGER(iwp), INTENT(in) :: ispec     !< Aerosol species index
9334       INTEGER(iwp), INTENT(in) :: surf_num  !< index surface elements
9335
9336       REAL(wp), INTENT(in) ::  mass_frac    !< mass fraction of a chemical compound in all bins
9337       REAL(wp), INTENT(in) ::  nsource      !< number source (#/m2/s)
9338       REAL(wp), INTENT(in) ::  prho         !< Aerosol density
9339
9340       TYPE(surf_type), INTENT(inout) ::  surface  !< respective surface type
9341!
9342!--    Get indices of respective grid point
9343       i = surface%i(surf_num)
9344       j = surface%j(surf_num)
9345       k = surface%k(surf_num)
9346!
9347!--    Subrange 2a:
9348       ic = ( ispec - 1 ) * nbins_aerosol + ib
9349       surface%amsws(surf_num,ic) = surface%amsws(surf_num,ic) + mass_frac * nsource *             &
9350                                    aero(ib)%core * prho * rho_air_zw(k-1)
9351       aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(surf_num,ic)
9352
9353    END SUBROUTINE set_mass_flux
9354
9355 END SUBROUTINE salsa_emission_setup
9356
9357!------------------------------------------------------------------------------!
9358! Description:
9359! ------------
9360!> Sets the gaseous fluxes
9361!------------------------------------------------------------------------------!
9362 SUBROUTINE salsa_gas_emission_setup( init )
9363
9364    USE netcdf_data_input_mod,                                                                     &
9365        ONLY:  check_existence, close_input_file, get_attribute, get_variable,                     &
9366               inquire_num_variables, inquire_variable_names,                                      &
9367               get_dimension_length, open_read_file
9368
9369    USE palm_date_time_mod,                                                                        &
9370        ONLY:  days_per_week, get_date_time, hours_per_day, months_per_year, seconds_per_hour
9371
9372    USE surface_mod,                                                                               &
9373        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
9374
9375    IMPLICIT NONE
9376
9377    CHARACTER(LEN=80) ::  daytype = 'workday'  !< default day type
9378    CHARACTER(LEN=25) ::  in_name              !< name of a gas in the input file
9379
9380    CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names   !<  variable names in input data
9381
9382
9383    INTEGER(iwp) ::  day_of_month   !< day of the month
9384    INTEGER(iwp) ::  day_of_week    !< day of the week
9385    INTEGER(iwp) ::  day_of_year    !< day of the year
9386    INTEGER(iwp) ::  hour_of_day    !< hour of the day
9387    INTEGER(iwp) ::  id_chem        !< NetCDF id of chemistry emission file
9388    INTEGER(iwp) ::  i              !< loop index
9389    INTEGER(iwp) ::  ig             !< loop index
9390    INTEGER(iwp) ::  in             !< running index for emission categories
9391    INTEGER(iwp) ::  index_dd       !< index day
9392    INTEGER(iwp) ::  index_hh       !< index hour
9393    INTEGER(iwp) ::  index_mm       !< index month
9394    INTEGER(iwp) ::  j              !< loop index
9395    INTEGER(iwp) ::  month_of_year  !< month of the year
9396    INTEGER(iwp) ::  num_vars       !< number of variables
9397
9398    LOGICAL  ::  netcdf_extend = .FALSE.  !< NetCDF input file exists
9399
9400    LOGICAL, INTENT(in) ::  init          !< if .TRUE. --> initialisation call
9401
9402    REAL(wp) ::  second_of_day    !< second of the day
9403
9404    REAL(wp), DIMENSION(:), ALLOCATABLE ::  time_factor  !< emission time factor
9405
9406    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  dum_var_3d  !<
9407
9408    REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE ::  dum_var_5d  !<
9409
9410!
9411!-- Reset surface fluxes
9412    surf_def_h(0)%gtsws = 0.0_wp
9413    surf_lsm_h%gtsws = 0.0_wp
9414    surf_usm_h%gtsws = 0.0_wp
9415
9416#if defined( __netcdf )
9417!
9418!-- Check existence of PIDS_CHEM file
9419    INQUIRE( FILE = 'PIDS_CHEM' // TRIM( coupling_char ), EXIST = netcdf_extend )
9420    IF ( .NOT. netcdf_extend )  THEN
9421       message_string = 'Input file PIDS_CHEM' //  TRIM( coupling_char ) // ' missing!'
9422       CALL message( 'salsa_gas_emission_setup', 'PA0640', 1, 2, 0, 6, 0 )
9423    ENDIF
9424!
9425!-- Open file in read-only mode
9426    CALL open_read_file( 'PIDS_CHEM' // TRIM( coupling_char ), id_chem )
9427
9428    IF ( init )  THEN
9429!
9430!--    Read the index and name of chemical components
9431       CALL get_dimension_length( id_chem, chem_emission_att%n_emiss_species, 'nspecies' )
9432       ALLOCATE( chem_emission_att%species_index(1:chem_emission_att%n_emiss_species) )
9433       CALL get_variable( id_chem, 'emission_index', chem_emission_att%species_index )
9434       CALL get_variable( id_chem, 'emission_name', chem_emission_att%species_name,                &
9435                          chem_emission_att%n_emiss_species )
9436!
9437!--    Allocate emission data
9438       ALLOCATE( chem_emission(1:chem_emission_att%n_emiss_species) )
9439!
9440!--    Find the corresponding indices in the model
9441       emission_index_chem = 0
9442       DO  ig = 1, chem_emission_att%n_emiss_species
9443          in_name = chem_emission_att%species_name(ig)
9444          SELECT CASE ( TRIM( in_name ) )
9445             CASE ( 'H2SO4', 'h2so4' )
9446                emission_index_chem(1) = ig
9447             CASE ( 'HNO3', 'hno3' )
9448                emission_index_chem(2) = ig
9449             CASE ( 'NH3', 'nh3' )
9450                emission_index_chem(3) = ig
9451             CASE ( 'OCNV', 'ocnv' )
9452                emission_index_chem(4) = ig
9453             CASE ( 'OCSV', 'ocsv' )
9454                emission_index_chem(5) = ig
9455          END SELECT
9456       ENDDO
9457!
9458!--    Inquire the fill value
9459       CALL get_attribute( id_chem, '_FillValue', aero_emission%fill, .FALSE., 'emission_values' )
9460!
9461!--    Inquire units of emissions
9462       CALL get_attribute( id_chem, 'units', chem_emission_att%units, .FALSE., 'emission_values' )
9463!
9464!--    Inquire the level of detail (lod)
9465       CALL get_attribute( id_chem, 'lod', lod_gas_emissions, .FALSE., 'emission_values' )
9466!
9467!--    Variable names
9468       CALL inquire_num_variables( id_chem, num_vars )
9469       ALLOCATE( var_names(1:num_vars) )
9470       CALL inquire_variable_names( id_chem, var_names )
9471!
9472!--    Default mode: as total emissions per year
9473       IF ( lod_gas_emissions == 1 )  THEN
9474
9475!
9476!--       Get number of emission categories and allocate emission arrays
9477          CALL get_dimension_length( id_chem, chem_emission_att%ncat, 'ncat' )
9478          ALLOCATE( chem_emission_att%cat_index(1:chem_emission_att%ncat),                         &
9479                    time_factor(1:chem_emission_att%ncat) )
9480!
9481!--       Get emission category names and indices
9482          CALL get_variable( id_chem, 'emission_category_name', chem_emission_att%cat_name,        &
9483                             chem_emission_att%ncat)
9484          CALL get_variable( id_chem, 'emission_category_index', chem_emission_att%cat_index )
9485!
9486!--       Emission time factors: Find check whether emission time factors are given for each hour
9487!--       of year OR based on month, day and hour
9488!
9489!--       For each hour of year:
9490          IF ( check_existence( var_names, 'nhoursyear' ) )  THEN
9491             CALL get_dimension_length( id_chem, chem_emission_att%nhoursyear, 'nhoursyear' )
9492             ALLOCATE( chem_emission_att%hourly_emis_time_factor(1:chem_emission_att%ncat,         &
9493                                                                 1:chem_emission_att%nhoursyear) )
9494             CALL get_variable( id_chem, 'emission_time_factors',                                  &
9495                                chem_emission_att%hourly_emis_time_factor,                         &
9496                                0, chem_emission_att%nhoursyear-1, 0, chem_emission_att%ncat-1 )
9497!
9498!--       Based on the month, day and hour:
9499          ELSEIF ( check_existence( var_names, 'nmonthdayhour' ) )  THEN
9500             CALL get_dimension_length( id_chem, chem_emission_att%nmonthdayhour, 'nmonthdayhour' )
9501             ALLOCATE( chem_emission_att%mdh_emis_time_factor(1:chem_emission_att%ncat,            &
9502                                                              1:chem_emission_att%nmonthdayhour) )
9503             CALL get_variable( id_chem, 'emission_time_factors',                                  &
9504                                chem_emission_att%mdh_emis_time_factor,                            &
9505                                0, chem_emission_att%nmonthdayhour-1, 0, chem_emission_att%ncat-1 )
9506          ELSE
9507             message_string = 'emission_time_factors should be given for each nhoursyear OR ' //   &
9508                              'nmonthdayhour'
9509             CALL message( 'salsa_gas_emission_setup','PA0641', 1, 2, 0, 6, 0 )
9510          ENDIF
9511!
9512!--       Next emission update
9513          CALL get_date_time( time_since_reference_point, second_of_day=second_of_day )
9514          next_gas_emission_update = MOD( second_of_day, seconds_per_hour ) !- seconds_per_hour
9515!
9516!--       Allocate and read surface emission data (in total PM) (NOTE that "preprocessed" input data
9517!--       array is applied now here)
9518          ALLOCATE( dum_var_5d(1,nys:nyn,nxl:nxr,1:chem_emission_att%n_emiss_species,              &
9519                               1:chem_emission_att%ncat) )
9520          CALL get_variable( id_chem, 'emission_values', dum_var_5d, 0, chem_emission_att%ncat-1,  &
9521                             0, chem_emission_att%n_emiss_species-1, nxl, nxr, nys, nyn, 0, 0 )
9522          DO  ig = 1, chem_emission_att%n_emiss_species
9523             ALLOCATE( chem_emission(ig)%default_emission_data(nys:nyn,nxl:nxr,                    &
9524                                                               1:chem_emission_att%ncat) )
9525             DO  in = 1, chem_emission_att%ncat
9526                DO  i = nxl, nxr
9527                   DO  j = nys, nyn
9528                      chem_emission(ig)%default_emission_data(j,i,in) = dum_var_5d(1,j,i,ig,in)
9529                   ENDDO
9530                ENDDO
9531             ENDDO
9532          ENDDO
9533          DEALLOCATE( dum_var_5d )
9534!
9535!--    Pre-processed mode:
9536       ELSEIF ( lod_gas_emissions == 2 )  THEN
9537!
9538!--       Number of time steps in the emission data
9539          CALL get_dimension_length( id_chem, chem_emission_att%dt_emission, 'time' )
9540!
9541!--       Allocate and read time
9542          ALLOCATE( gas_emission_time(1:chem_emission_att%dt_emission) )
9543          CALL get_variable( id_chem, 'time', gas_emission_time )
9544       ELSE
9545          message_string = 'Unknown lod for emission_values.'
9546          CALL message( 'salsa_gas_emission_setup','PA0642', 1, 2, 0, 6, 0 )
9547       ENDIF  ! lod
9548
9549    ENDIF  ! init
9550!
9551!-- Define and set current emission values:
9552
9553    IF ( lod_gas_emissions == 1 )  THEN
9554!
9555!--    Emission time factors for each emission category at current time step
9556       IF ( chem_emission_att%nhoursyear > chem_emission_att%nmonthdayhour )  THEN
9557!
9558!--       Get the index of the current hour
9559          CALL get_date_time( time_since_reference_point, &
9560                              day_of_year=day_of_year, hour=hour_of_day )
9561          index_hh = ( day_of_year - 1_iwp ) * hours_per_day + hour_of_day
9562          IF ( .NOT. ALLOCATED( time_factor ) )  ALLOCATE( time_factor(1:chem_emission_att%ncat) )
9563          time_factor = 0.0_wp
9564          time_factor = chem_emission_att%hourly_emis_time_factor(:,index_hh+1)
9565
9566       ELSEIF ( chem_emission_att%nhoursyear < chem_emission_att%nmonthdayhour )  THEN
9567!
9568!--       Get the index of current hour (index_hh) (TODO: Now "workday" is always assumed.
9569!--       Needs to be calculated.)
9570          CALL get_date_time( time_since_reference_point, &
9571                              month=month_of_year,        &
9572                              day=day_of_month,           &
9573                              hour=hour_of_day,           &
9574                              day_of_week=day_of_week     )
9575          index_mm = month_of_year
9576          index_dd = months_per_year + day_of_week
9577          SELECT CASE( TRIM( daytype ) )
9578
9579             CASE ("workday")
9580                index_hh = months_per_year + days_per_week + hour_of_day
9581
9582             CASE ("weekend")
9583                index_hh = months_per_year + days_per_week + hours_per_day + hour_of_day
9584
9585             CASE ("holiday")
9586                index_hh = months_per_year + days_per_week + 2*hours_per_day + hour_of_day
9587
9588          END SELECT
9589          time_factor = chem_emission_att%mdh_emis_time_factor(:,index_mm) *                       &
9590                        chem_emission_att%mdh_emis_time_factor(:,index_dd) *                       &
9591                        chem_emission_att%mdh_emis_time_factor(:,index_hh+1)
9592       ENDIF
9593!
9594!--    Set gas emissions for each emission category
9595       ALLOCATE( dum_var_3d(nys:nyn,nxl:nxr,1:chem_emission_att%n_emiss_species) )
9596
9597       DO  in = 1, chem_emission_att%ncat
9598          DO  ig = 1, chem_emission_att%n_emiss_species
9599             dum_var_3d(:,:,ig) = chem_emission(ig)%default_emission_data(:,:,in)
9600          ENDDO
9601!
9602!--       Set surface fluxes only for either default, land or urban surface
9603          IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
9604             CALL set_gas_flux( surf_def_h(0), emission_index_chem, chem_emission_att%units,    &
9605                                dum_var_3d, time_factor(in) )
9606          ELSE
9607             CALL set_gas_flux( surf_usm_h, emission_index_chem, chem_emission_att%units,       &
9608                                dum_var_3d, time_factor(in) )
9609             CALL set_gas_flux( surf_lsm_h, emission_index_chem, chem_emission_att%units,       &
9610                                dum_var_3d, time_factor(in) )
9611          ENDIF
9612       ENDDO
9613       DEALLOCATE( dum_var_3d )
9614!
9615!--    The next emission update is again after one hour
9616       next_gas_emission_update = next_gas_emission_update + 3600.0_wp
9617
9618    ELSEIF ( lod_gas_emissions == 2 )  THEN
9619!
9620!--    Get time_utc_init from origin_date_time
9621       CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )
9622!
9623!--    Obtain time index for current point in time. Note, the time coordinate in the input file is
9624!--    relative to time_utc_init.
9625       chem_emission_att%i_hour = MINLOC( ABS( gas_emission_time - ( time_utc_init +               &
9626                                         MAX( time_since_reference_point, 0.0_wp) ) ), DIM = 1 ) - 1
9627!
9628!--    Allocate the data input array always before reading in the data and deallocate after (NOTE
9629!--    that "preprocessed" input data array is applied now here)
9630       ALLOCATE( dum_var_5d(1,1,nys:nyn,nxl:nxr,1:chem_emission_att%n_emiss_species) )
9631!
9632!--    Read in the next time step
9633       CALL get_variable( id_chem, 'emission_values', dum_var_5d,                                  &
9634                          0, chem_emission_att%n_emiss_species-1, nxl, nxr, nys, nyn, 0, 0,        &
9635                          chem_emission_att%i_hour, chem_emission_att%i_hour )
9636!
9637!--    Set surface fluxes only for either default, land or urban surface
9638       IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
9639          CALL set_gas_flux( surf_def_h(0), emission_index_chem, chem_emission_att%units,          &
9640                             dum_var_5d(1,1,:,:,:) )
9641       ELSE
9642          CALL set_gas_flux( surf_usm_h, emission_index_chem, chem_emission_att%units,             &
9643                             dum_var_5d(1,1,:,:,:) )
9644          CALL set_gas_flux( surf_lsm_h, emission_index_chem, chem_emission_att%units,             &
9645                             dum_var_5d(1,1,:,:,:) )
9646       ENDIF
9647       DEALLOCATE ( dum_var_5d )
9648!
9649!--    Determine the next emission update
9650       next_gas_emission_update = gas_emission_time(chem_emission_att%i_hour+2)
9651
9652    ENDIF
9653!
9654!-- Close input file
9655    CALL close_input_file( id_chem )
9656
9657#else
9658    message_string = 'salsa_emission_mode = "read_from_file", but preprocessor directive ' //   &
9659                     ' __netcdf is not used in compiling!'
9660    CALL message( 'salsa_gas_emission_setup', 'PA0643', 1, 2, 0, 6, 0 )
9661
9662#endif
9663
9664    CONTAINS
9665!------------------------------------------------------------------------------!
9666! Description:
9667! ------------
9668!> Set gas fluxes for selected type of surfaces
9669!------------------------------------------------------------------------------!
9670    SUBROUTINE set_gas_flux( surface, cc_i_mod, unit, source_array, time_fac )
9671
9672       USE arrays_3d,                                                                              &
9673           ONLY: dzw, hyp, pt, rho_air_zw
9674
9675       USE grid_variables,                                                                         &
9676           ONLY:  dx, dy
9677
9678       USE surface_mod,                                                                            &
9679           ONLY:  surf_type
9680
9681       IMPLICIT NONE
9682
9683       CHARACTER(LEN=*), INTENT(in) ::  unit  !< flux unit in the input file
9684
9685       INTEGER(iwp) ::  ig  !< running index for gases
9686       INTEGER(iwp) ::  i   !< loop index
9687       INTEGER(iwp) ::  j   !< loop index
9688       INTEGER(iwp) ::  k   !< loop index
9689       INTEGER(iwp) ::  m   !< running index for surface elements
9690
9691       INTEGER(iwp), DIMENSION(:) ::  cc_i_mod   !< index of different gases in the input data
9692
9693       LOGICAL ::  use_time_fac  !< .TRUE. is time_fac present
9694
9695       REAL(wp), OPTIONAL ::  time_fac  !< emission time factor
9696
9697       REAL(wp), DIMENSION(ngases_salsa) ::  conv     !< unit conversion factor
9698
9699       REAL(wp), DIMENSION(nys:nyn,nxl:nxr,1:chem_emission_att%n_emiss_species), INTENT(in) ::  source_array  !<
9700
9701       TYPE(surf_type), INTENT(inout) :: surface  !< respective surface type
9702
9703       conv = 1.0_wp
9704       use_time_fac = PRESENT( time_fac )
9705
9706       DO  m = 1, surface%ns
9707!
9708!--       Get indices of respective grid point
9709          i = surface%i(m)
9710          j = surface%j(m)
9711          k = surface%k(m)
9712!
9713!--       Unit conversion factor: convert to SI units (#/m2/s)
9714          SELECT CASE ( TRIM( unit ) )
9715             CASE ( 'kg/m2/yr' )
9716                conv(1) = avo / ( amh2so4 * 3600.0_wp )
9717                conv(2) = avo / ( amhno3 * 3600.0_wp )
9718                conv(3) = avo / ( amnh3 * 3600.0_wp )
9719                conv(4) = avo / ( amoc * 3600.0_wp )
9720                conv(5) = avo / ( amoc * 3600.0_wp )
9721             CASE ( 'g/m2/yr' )
9722                conv(1) = avo / ( amh2so4 * 3.6E+6_wp )
9723                conv(2) = avo / ( amhno3 * 3.6E+6_wp )
9724                conv(3) = avo / ( amnh3 * 3.6E+6_wp )
9725                conv(4) = avo / ( amoc * 3.6E+6_wp )
9726                conv(5) = avo / ( amoc * 3.6E+6_wp )
9727             CASE ( 'g/m2/s' )
9728                conv(1) = avo / ( amh2so4 * 1000.0_wp )
9729                conv(2) = avo / ( amhno3 * 1000.0_wp )
9730                conv(3) = avo / ( amnh3 * 1000.0_wp )
9731                conv(4) = avo / ( amoc * 1000.0_wp )
9732                conv(5) = avo / ( amoc * 1000.0_wp )
9733             CASE ( '#/m2/s' )
9734                conv = 1.0_wp
9735             CASE ( 'ppm/m2/s' )
9736                conv = for_ppm_to_nconc * hyp(k) / pt(k,j,i) * ( 1.0E5_wp / hyp(k) )**0.286_wp *   &
9737                       dx * dy * dzw(k)
9738             CASE ( 'mumol/m2/s' )
9739                conv = 1.0E-6_wp * avo
9740             CASE DEFAULT
9741                message_string = 'unknown unit for gas emissions: ' // TRIM( chem_emission_att%units )
9742                CALL message( 'set_gas_flux','PA0644', 1, 2, 0, 6, 0 )
9743
9744          END SELECT
9745
9746          DO  ig = 1, ngases_salsa
9747             IF ( use_time_fac )  THEN
9748                surface%gtsws(m,ig) = surface%gtsws(m,ig) + rho_air_zw(k-1) * conv(ig) * time_fac  &
9749                                      * MAX( 0.0_wp, source_array(j,i,cc_i_mod(ig) ) )
9750             ELSE
9751                surface%gtsws(m,ig) = surface%gtsws(m,ig) + rho_air_zw(k-1) * conv(ig)             &
9752                                      * MAX( 0.0_wp, source_array(j,i,cc_i_mod(ig) ) )
9753             ENDIF
9754          ENDDO  ! ig
9755
9756       ENDDO  ! m
9757
9758    END SUBROUTINE set_gas_flux
9759
9760 END SUBROUTINE salsa_gas_emission_setup
9761
9762!------------------------------------------------------------------------------!
9763! Description:
9764! ------------
9765!> Check data output for salsa.
9766!------------------------------------------------------------------------------!
9767 SUBROUTINE salsa_check_data_output( var, unit )
9768
9769    IMPLICIT NONE
9770
9771    CHARACTER(LEN=*) ::  unit     !<
9772    CHARACTER(LEN=*) ::  var      !<
9773
9774    INTEGER(iwp) ::  char_to_int   !< for converting character to integer
9775
9776    IF ( var(1:6) /= 'salsa_' )  THEN
9777       unit = 'illegal'
9778       RETURN
9779    ENDIF
9780!
9781!-- Treat bin-specific outputs separately
9782    IF ( var(7:11) ==  'N_bin' )  THEN
9783       READ( var(12:),* ) char_to_int
9784       IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
9785          unit = '#/m3'
9786       ELSE
9787          unit = 'illegal'
9788          RETURN
9789       ENDIF
9790
9791    ELSEIF ( var(7:11) ==  'm_bin' )  THEN
9792       READ( var(12:),* ) char_to_int
9793       IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
9794          unit = 'kg/m3'
9795       ELSE
9796          unit = 'illegal'
9797          RETURN
9798       ENDIF
9799
9800    ELSE
9801       SELECT CASE ( TRIM( var(7:) ) )
9802
9803          CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV',  'g_OCSV' )
9804             IF (  air_chemistry )  THEN
9805                message_string = 'gases are imported from the chemistry module and thus output '// &
9806                                 'of "' // TRIM( var ) // '" is not allowed'
9807                CALL message( 'check_parameters', 'PA0653', 1, 2, 0, 6, 0 )
9808             ENDIF
9809             unit = '#/m3'
9810
9811          CASE ( 'LDSA' )
9812             unit = 'mum2/cm3'
9813
9814          CASE ( 'PM0.1', 'PM2.5', 'PM10', 's_BC', 's_DU', 's_H2O', 's_NH', 's_NO', 's_OC',        &
9815                 's_SO4', 's_SS' )
9816             unit = 'kg/m3'
9817
9818          CASE ( 'N_UFP', 'Ntot' )
9819             unit = '#/m3'
9820
9821          CASE DEFAULT
9822             unit = 'illegal'
9823
9824       END SELECT
9825    ENDIF
9826
9827 END SUBROUTINE salsa_check_data_output
9828
9829!------------------------------------------------------------------------------!
9830! Description:
9831! ------------
9832!> Check profile data output for salsa. Currently only for diagnostic variables
9833!> Ntot, N_UFP, PM0.1, PM2.5, PM10 and LDSA
9834!------------------------------------------------------------------------------!
9835 SUBROUTINE salsa_check_data_output_pr( var, var_count, unit, dopr_unit )
9836
9837    USE arrays_3d,                                                                                 &
9838        ONLY: zu
9839
9840    USE profil_parameter,                                                                          &
9841        ONLY:  dopr_index
9842
9843    USE statistics,                                                                                &
9844        ONLY:  hom, pr_palm, statistic_regions
9845
9846    IMPLICIT NONE
9847
9848    CHARACTER(LEN=*) ::  dopr_unit  !<
9849    CHARACTER(LEN=*) ::  unit       !<
9850    CHARACTER(LEN=*) ::  var        !<
9851
9852    INTEGER(iwp) ::  var_count     !<
9853
9854    IF ( var(1:6) /= 'salsa_' )  THEN
9855       unit = 'illegal'
9856       RETURN
9857    ENDIF
9858
9859    SELECT CASE ( TRIM( var(7:) ) )
9860
9861       CASE( 'LDSA' )
9862          salsa_pr_count = salsa_pr_count + 1
9863          salsa_pr_index(salsa_pr_count) = 1
9864          dopr_index(var_count) = pr_palm + salsa_pr_count
9865          dopr_unit = 'mum2/cm3'
9866          unit = dopr_unit
9867          hom(:,2,dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
9868
9869       CASE( 'N_UFP' )
9870          salsa_pr_count = salsa_pr_count + 1
9871          salsa_pr_index(salsa_pr_count) = 2
9872          dopr_index(var_count) = pr_palm + salsa_pr_count
9873          dopr_unit = '#/m3'
9874          unit = dopr_unit
9875          hom(:,2,dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
9876
9877       CASE( 'Ntot' )
9878          salsa_pr_count = salsa_pr_count + 1
9879          salsa_pr_index(salsa_pr_count) = 3
9880          dopr_index(var_count) = pr_palm + salsa_pr_count
9881          dopr_unit = '#/m3'
9882          unit = dopr_unit
9883          hom(:,2,dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
9884
9885       CASE( 'PM0.1' )
9886          salsa_pr_count = salsa_pr_count + 1
9887          salsa_pr_index(salsa_pr_count) = 4
9888          dopr_index(var_count) = pr_palm + salsa_pr_count
9889          dopr_unit = 'kg/m3'
9890          unit = dopr_unit
9891          hom(:,2,dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
9892
9893       CASE( 'PM2.5' )
9894          salsa_pr_count = salsa_pr_count + 1
9895          salsa_pr_index(salsa_pr_count) = 5
9896          dopr_index(var_count) = pr_palm + salsa_pr_count
9897          dopr_unit = 'kg/m3'
9898          unit = dopr_unit
9899          hom(:,2,dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
9900
9901       CASE( 'PM10' )
9902          salsa_pr_count = salsa_pr_count + 1
9903          salsa_pr_index(salsa_pr_count) = 6
9904          dopr_index(var_count) = pr_palm + salsa_pr_count
9905          dopr_unit = 'kg/m3'
9906          unit = dopr_unit
9907          hom(:,2,dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
9908
9909       CASE DEFAULT
9910          unit = 'illegal'
9911
9912    END SELECT
9913
9914
9915 END SUBROUTINE salsa_check_data_output_pr
9916
9917!-------------------------------------------------------------------------------!
9918!> Description:
9919!> Calculation of horizontally averaged profiles for salsa.
9920!-------------------------------------------------------------------------------!
9921 SUBROUTINE salsa_statistics( mode, sr, tn )
9922
9923    USE control_parameters,                                                                        &
9924        ONLY:  max_pr_user
9925
9926    USE chem_modules,                                                                              &
9927        ONLY:  max_pr_cs
9928
9929    USE statistics,                                                                                &
9930        ONLY:  pr_palm, rmask, sums_l
9931
9932    IMPLICIT NONE
9933
9934    CHARACTER(LEN=*) ::  mode  !<
9935
9936    INTEGER(iwp) ::  i    !< loop index
9937    INTEGER(iwp) ::  ib   !< loop index
9938    INTEGER(iwp) ::  ic   !< loop index
9939    INTEGER(iwp) ::  ii   !< loop index
9940    INTEGER(iwp) ::  ind  !< index in the statistical output
9941    INTEGER(iwp) ::  j    !< loop index
9942    INTEGER(iwp) ::  k    !< loop index
9943    INTEGER(iwp) ::  sr   !< statistical region
9944    INTEGER(iwp) ::  tn   !< thread number
9945
9946    REAL(wp) ::  df        !< For calculating LDSA: fraction of particles depositing in the alveolar
9947                           !< (or tracheobronchial) region of the lung. Depends on the particle size
9948    REAL(wp) ::  mean_d    !< Particle diameter in micrometres
9949    REAL(wp) ::  temp_bin  !< temporary variable
9950
9951    IF ( mode == 'profiles' )  THEN
9952       !$OMP DO
9953       DO  ii = 1, salsa_pr_count
9954
9955          ind = pr_palm + max_pr_user + max_pr_cs + ii
9956
9957          SELECT CASE( salsa_pr_index(ii) )
9958
9959             CASE( 1 )  ! LDSA
9960                DO  i = nxl, nxr
9961                   DO  j = nys, nyn
9962                      DO  k = nzb, nzt+1
9963                         temp_bin = 0.0_wp
9964                         DO  ib = 1, nbins_aerosol
9965   !
9966   !--                      Diameter in micrometres
9967                            mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
9968   !
9969   !--                      Deposition factor: alveolar
9970                            df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +    &
9971                                   2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -  &
9972                                   1.362_wp )**2 ) )
9973   !
9974   !--                      Lung-deposited surface area LDSA (units mum2/cm3)
9975                            temp_bin = temp_bin + pi * mean_d**2 * df * 1.0E-6_wp *                &
9976                                       aerosol_number(ib)%conc(k,j,i)
9977                         ENDDO
9978                         sums_l(k,ind,tn) = sums_l(k,ind,tn) + temp_bin * rmask(j,i,sr)  *         &
9979                                           MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 22 ) )
9980                      ENDDO
9981                   ENDDO
9982                ENDDO
9983
9984             CASE( 2 )  ! N_UFP
9985                DO  i = nxl, nxr
9986                   DO  j = nys, nyn
9987                      DO  k = nzb, nzt+1
9988                         temp_bin = 0.0_wp
9989                         DO  ib = 1, nbins_aerosol
9990                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )                          &
9991                               temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
9992                         ENDDO
9993                         sums_l(k,ind,tn) = sums_l(k,ind,tn) + temp_bin * rmask(j,i,sr)  *         &
9994                                           MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 22 ) )
9995                      ENDDO
9996                   ENDDO
9997                ENDDO
9998
9999             CASE( 3 )  ! Ntot
10000                DO  i = nxl, nxr
10001                   DO  j = nys, nyn
10002                      DO  k = nzb, nzt+1
10003                         temp_bin = 0.0_wp
10004                         DO  ib = 1, nbins_aerosol
10005                            temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
10006                         ENDDO
10007                         sums_l(k,ind,tn) = sums_l(k,ind,tn) + temp_bin * rmask(j,i,sr)  *         &
10008                                           MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 22 ) )
10009                      ENDDO
10010                   ENDDO
10011                ENDDO
10012
10013             CASE( 4 )  ! PM0.1
10014                DO  i = nxl, nxr
10015                   DO  j = nys, nyn
10016                      DO  k = nzb, nzt+1
10017                         temp_bin = 0.0_wp
10018                         DO  ib = 1, nbins_aerosol
10019                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
10020                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10021                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10022                               ENDDO
10023                            ENDIF
10024                         ENDDO
10025                         sums_l(k,ind,tn) = sums_l(k,ind,tn) + temp_bin * rmask(j,i,sr)  *         &
10026                                           MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 22 ) )
10027                      ENDDO
10028                   ENDDO
10029                ENDDO
10030
10031             CASE( 5 )  ! PM2.5
10032                DO  i = nxl, nxr
10033                   DO  j = nys, nyn
10034                      DO  k = nzb, nzt+1
10035                         temp_bin = 0.0_wp
10036                         DO  ib = 1, nbins_aerosol
10037                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
10038                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10039                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10040                               ENDDO
10041                            ENDIF
10042                         ENDDO
10043                         sums_l(k,ind,tn) = sums_l(k,ind,tn) + temp_bin * rmask(j,i,sr)  *         &
10044                                           MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 22 ) )
10045                      ENDDO
10046                   ENDDO
10047                ENDDO
10048
10049             CASE( 6 )  ! PM10
10050                DO  i = nxl, nxr
10051                   DO  j = nys, nyn
10052                      DO  k = nzb, nzt+1
10053                         temp_bin = 0.0_wp
10054                         DO  ib = 1, nbins_aerosol
10055                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
10056                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10057                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10058                               ENDDO
10059                            ENDIF
10060                         ENDDO
10061                         sums_l(k,ind,tn) = sums_l(k,ind,tn) + temp_bin * rmask(j,i,sr)  *         &
10062                                           MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 22 ) )
10063                      ENDDO
10064                   ENDDO
10065                ENDDO
10066
10067          END SELECT
10068       ENDDO
10069
10070    ELSEIF ( mode == 'time_series' )  THEN
10071!
10072!--    TODO
10073    ENDIF
10074
10075 END SUBROUTINE salsa_statistics
10076
10077
10078!------------------------------------------------------------------------------!
10079!
10080! Description:
10081! ------------
10082!> Subroutine for averaging 3D data
10083!------------------------------------------------------------------------------!
10084 SUBROUTINE salsa_3d_data_averaging( mode, variable )
10085
10086    USE control_parameters,                                                                        &
10087        ONLY:  average_count_3d
10088
10089    IMPLICIT NONE
10090
10091    CHARACTER(LEN=*)  ::  mode       !<
10092    CHARACTER(LEN=10) ::  vari       !<
10093    CHARACTER(LEN=*)  ::  variable   !<
10094
10095    INTEGER(iwp) ::  char_to_int  !< for converting character to integer
10096    INTEGER(iwp) ::  found_index  !<
10097    INTEGER(iwp) ::  i            !<
10098    INTEGER(iwp) ::  ib           !<
10099    INTEGER(iwp) ::  ic           !<
10100    INTEGER(iwp) ::  j            !<
10101    INTEGER(iwp) ::  k            !<
10102
10103    REAL(wp) ::  df       !< For calculating LDSA: fraction of particles depositing in the alveolar
10104                          !< (or tracheobronchial) region of the lung. Depends on the particle size
10105    REAL(wp) ::  mean_d   !< Particle diameter in micrometres
10106    REAL(wp) ::  temp_bin !< temporary variable
10107
10108    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !< points to selected output variable
10109
10110    temp_bin = 0.0_wp
10111
10112    IF ( mode == 'allocate' )  THEN
10113
10114       IF ( variable(7:11) ==  'N_bin' )  THEN
10115          IF ( .NOT. ALLOCATED( nbins_av ) )  THEN
10116             ALLOCATE( nbins_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
10117          ENDIF
10118          nbins_av = 0.0_wp
10119
10120       ELSEIF ( variable(7:11) ==  'm_bin' )  THEN
10121          IF ( .NOT. ALLOCATED( mbins_av ) )  THEN
10122             ALLOCATE( mbins_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
10123          ENDIF
10124          mbins_av = 0.0_wp
10125
10126       ELSE
10127
10128          SELECT CASE ( TRIM( variable(7:) ) )
10129
10130             CASE ( 'g_H2SO4' )
10131                IF ( .NOT. ALLOCATED( g_h2so4_av ) )  THEN
10132                   ALLOCATE( g_h2so4_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10133                ENDIF
10134                g_h2so4_av = 0.0_wp
10135
10136             CASE ( 'g_HNO3' )
10137                IF ( .NOT. ALLOCATED( g_hno3_av ) )  THEN
10138                   ALLOCATE( g_hno3_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10139                ENDIF
10140                g_hno3_av = 0.0_wp
10141
10142             CASE ( 'g_NH3' )
10143                IF ( .NOT. ALLOCATED( g_nh3_av ) )  THEN
10144                   ALLOCATE( g_nh3_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10145                ENDIF
10146                g_nh3_av = 0.0_wp
10147
10148             CASE ( 'g_OCNV' )
10149                IF ( .NOT. ALLOCATED( g_ocnv_av ) )  THEN
10150                   ALLOCATE( g_ocnv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10151                ENDIF
10152                g_ocnv_av = 0.0_wp
10153
10154             CASE ( 'g_OCSV' )
10155                IF ( .NOT. ALLOCATED( g_ocsv_av ) )  THEN
10156                   ALLOCATE( g_ocsv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10157                ENDIF
10158                g_ocsv_av = 0.0_wp
10159
10160             CASE ( 'LDSA' )
10161                IF ( .NOT. ALLOCATED( ldsa_av ) )  THEN
10162                   ALLOCATE( ldsa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10163                ENDIF
10164                ldsa_av = 0.0_wp
10165
10166             CASE ( 'N_UFP' )
10167                IF ( .NOT. ALLOCATED( nufp_av ) )  THEN
10168                   ALLOCATE( nufp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10169                ENDIF
10170                nufp_av = 0.0_wp
10171
10172             CASE ( 'Ntot' )
10173                IF ( .NOT. ALLOCATED( ntot_av ) )  THEN
10174                   ALLOCATE( ntot_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10175                ENDIF
10176                ntot_av = 0.0_wp
10177
10178             CASE ( 'PM0.1' )
10179                IF ( .NOT. ALLOCATED( pm01_av ) )  THEN
10180                   ALLOCATE( pm01_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10181                ENDIF
10182                pm01_av = 0.0_wp
10183
10184             CASE ( 'PM2.5' )
10185                IF ( .NOT. ALLOCATED( pm25_av ) )  THEN
10186                   ALLOCATE( pm25_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10187                ENDIF
10188                pm25_av = 0.0_wp
10189
10190             CASE ( 'PM10' )
10191                IF ( .NOT. ALLOCATED( pm10_av ) )  THEN
10192                   ALLOCATE( pm10_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10193                ENDIF
10194                pm10_av = 0.0_wp
10195
10196             CASE ( 's_BC' )
10197                IF ( .NOT. ALLOCATED( s_bc_av ) )  THEN
10198                   ALLOCATE( s_bc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10199                ENDIF
10200                s_bc_av = 0.0_wp
10201
10202             CASE ( 's_DU' )
10203                IF ( .NOT. ALLOCATED( s_du_av ) )  THEN
10204                   ALLOCATE( s_du_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10205                ENDIF
10206                s_du_av = 0.0_wp
10207
10208             CASE ( 's_H2O' )
10209                IF ( .NOT. ALLOCATED( s_h2o_av ) )  THEN
10210                   ALLOCATE( s_h2o_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10211                ENDIF
10212                s_h2o_av = 0.0_wp
10213
10214             CASE ( 's_NH' )
10215                IF ( .NOT. ALLOCATED( s_nh_av ) )  THEN
10216                   ALLOCATE( s_nh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10217                ENDIF
10218                s_nh_av = 0.0_wp
10219
10220             CASE ( 's_NO' )
10221                IF ( .NOT. ALLOCATED( s_no_av ) )  THEN
10222                   ALLOCATE( s_no_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10223                ENDIF
10224                s_no_av = 0.0_wp
10225
10226             CASE ( 's_OC' )
10227                IF ( .NOT. ALLOCATED( s_oc_av ) )  THEN
10228                   ALLOCATE( s_oc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10229                ENDIF
10230                s_oc_av = 0.0_wp
10231
10232             CASE ( 's_SO4' )
10233                IF ( .NOT. ALLOCATED( s_so4_av ) )  THEN
10234                   ALLOCATE( s_so4_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10235                ENDIF
10236                s_so4_av = 0.0_wp
10237
10238             CASE ( 's_SS' )
10239                IF ( .NOT. ALLOCATED( s_ss_av ) )  THEN
10240                   ALLOCATE( s_ss_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
10241                ENDIF
10242                s_ss_av = 0.0_wp
10243
10244             CASE DEFAULT
10245                CONTINUE
10246
10247          END SELECT
10248
10249       ENDIF
10250
10251    ELSEIF ( mode == 'sum' )  THEN
10252
10253       IF ( variable(7:11) ==  'N_bin' )  THEN
10254          READ( variable(12:),* ) char_to_int
10255          IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
10256             ib = char_to_int
10257             DO  i = nxlg, nxrg
10258                DO  j = nysg, nyng
10259                   DO  k = nzb, nzt+1
10260                      nbins_av(k,j,i,ib) = nbins_av(k,j,i,ib) + aerosol_number(ib)%conc(k,j,i)
10261                   ENDDO
10262                ENDDO
10263             ENDDO
10264          ENDIF
10265
10266       ELSEIF ( variable(7:11) ==  'm_bin' )  THEN
10267          READ( variable(12:),* ) char_to_int
10268          IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
10269             ib = char_to_int
10270             DO  i = nxlg, nxrg
10271                DO  j = nysg, nyng
10272                   DO  k = nzb, nzt+1
10273                      temp_bin = 0.0_wp
10274                      DO  ic = ib, nbins_aerosol * ncomponents_mass, nbins_aerosol
10275                         temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10276                      ENDDO
10277                      mbins_av(k,j,i,ib) = mbins_av(k,j,i,ib) + temp_bin
10278                   ENDDO
10279                ENDDO
10280             ENDDO
10281          ENDIF
10282       ELSE
10283
10284          SELECT CASE ( TRIM( variable(7:) ) )
10285
10286             CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV', 'g_OCSV' )
10287
10288                vari = TRIM( variable(9:) )  ! remove salsa_g_ from beginning
10289
10290                SELECT CASE( vari )
10291
10292                   CASE( 'H2SO4' )
10293                      found_index = 1
10294                      to_be_resorted => g_h2so4_av
10295
10296                   CASE( 'HNO3' )
10297                      found_index = 2
10298                      to_be_resorted => g_hno3_av
10299
10300                   CASE( 'NH3' )
10301                      found_index = 3
10302                      to_be_resorted => g_nh3_av
10303
10304                   CASE( 'OCNV' )
10305                      found_index = 4
10306                      to_be_resorted => g_ocnv_av
10307
10308                   CASE( 'OCSV' )
10309                      found_index = 5
10310                      to_be_resorted => g_ocsv_av
10311
10312                END SELECT
10313
10314                DO  i = nxlg, nxrg
10315                   DO  j = nysg, nyng
10316                      DO  k = nzb, nzt+1
10317                         to_be_resorted(k,j,i) = to_be_resorted(k,j,i) +                           &
10318                                                 salsa_gas(found_index)%conc(k,j,i)
10319                      ENDDO
10320                   ENDDO
10321                ENDDO
10322
10323             CASE ( 'LDSA' )
10324                DO  i = nxlg, nxrg
10325                   DO  j = nysg, nyng
10326                      DO  k = nzb, nzt+1
10327                         temp_bin = 0.0_wp
10328                         DO  ib = 1, nbins_aerosol
10329   !
10330   !--                      Diameter in micrometres
10331                            mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
10332   !
10333   !--                      Deposition factor: alveolar (use ra_dry)
10334                            df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +    &
10335                                   2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -  &
10336                                   1.362_wp )**2 ) )
10337   !
10338   !--                      Lung-deposited surface area LDSA (units mum2/cm3)
10339                            temp_bin = temp_bin + pi * mean_d**2 * df * 1.0E-6_wp *                &
10340                                       aerosol_number(ib)%conc(k,j,i)
10341                         ENDDO
10342                         ldsa_av(k,j,i) = ldsa_av(k,j,i) + temp_bin
10343                      ENDDO
10344                   ENDDO
10345                ENDDO
10346
10347             CASE ( 'N_UFP' )
10348                DO  i = nxlg, nxrg
10349                   DO  j = nysg, nyng
10350                      DO  k = nzb, nzt+1
10351                         temp_bin = 0.0_wp
10352                         DO  ib = 1, nbins_aerosol
10353                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
10354                               temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
10355                            ENDIF
10356                         ENDDO
10357                         nufp_av(k,j,i) = nufp_av(k,j,i) + temp_bin
10358                      ENDDO
10359                   ENDDO
10360                ENDDO
10361
10362             CASE ( 'Ntot' )
10363                DO  i = nxlg, nxrg
10364                   DO  j = nysg, nyng
10365                      DO  k = nzb, nzt+1
10366                         DO  ib = 1, nbins_aerosol
10367                            ntot_av(k,j,i) = ntot_av(k,j,i) + aerosol_number(ib)%conc(k,j,i)
10368                         ENDDO
10369                      ENDDO
10370                   ENDDO
10371                ENDDO
10372
10373             CASE ( 'PM0.1' )
10374                DO  i = nxlg, nxrg
10375                   DO  j = nysg, nyng
10376                      DO  k = nzb, nzt+1
10377                         temp_bin = 0.0_wp
10378                         DO  ib = 1, nbins_aerosol
10379                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
10380                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10381                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10382                               ENDDO
10383                            ENDIF
10384                         ENDDO
10385                         pm01_av(k,j,i) = pm01_av(k,j,i) + temp_bin
10386                      ENDDO
10387                   ENDDO
10388                ENDDO
10389
10390             CASE ( 'PM2.5' )
10391                DO  i = nxlg, nxrg
10392                   DO  j = nysg, nyng
10393                      DO  k = nzb, nzt+1
10394                         temp_bin = 0.0_wp
10395                         DO  ib = 1, nbins_aerosol
10396                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
10397                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10398                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10399                               ENDDO
10400                            ENDIF
10401                         ENDDO
10402                         pm25_av(k,j,i) = pm25_av(k,j,i) + temp_bin
10403                      ENDDO
10404                   ENDDO
10405                ENDDO
10406
10407             CASE ( 'PM10' )
10408                DO  i = nxlg, nxrg
10409                   DO  j = nysg, nyng
10410                      DO  k = nzb, nzt+1
10411                         temp_bin = 0.0_wp
10412                         DO  ib = 1, nbins_aerosol
10413                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
10414                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10415                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10416                               ENDDO
10417                            ENDIF
10418                         ENDDO
10419                         pm10_av(k,j,i) = pm10_av(k,j,i) + temp_bin
10420                      ENDDO
10421                   ENDDO
10422                ENDDO
10423
10424             CASE ( 's_BC', 's_DU', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
10425                IF ( is_used( prtcl, TRIM( variable(9:) ) ) )  THEN  ! 9: remove salsa_s_
10426                   found_index = get_index( prtcl, TRIM( variable(9:) ) )
10427                   IF ( TRIM( variable(9:) ) == 'BC' )   to_be_resorted => s_bc_av
10428                   IF ( TRIM( variable(9:) ) == 'DU' )   to_be_resorted => s_du_av
10429                   IF ( TRIM( variable(9:) ) == 'NH' )   to_be_resorted => s_nh_av
10430                   IF ( TRIM( variable(9:) ) == 'NO' )   to_be_resorted => s_no_av
10431                   IF ( TRIM( variable(9:) ) == 'OC' )   to_be_resorted => s_oc_av
10432                   IF ( TRIM( variable(9:) ) == 'SO4' )  to_be_resorted => s_so4_av
10433                   IF ( TRIM( variable(9:) ) == 'SS' )   to_be_resorted => s_ss_av
10434                   DO  i = nxlg, nxrg
10435                      DO  j = nysg, nyng
10436                         DO  k = nzb, nzt+1
10437                            DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
10438                               to_be_resorted(k,j,i) = to_be_resorted(k,j,i) +                     &
10439                                                       aerosol_mass(ic)%conc(k,j,i)
10440                            ENDDO
10441                         ENDDO
10442                      ENDDO
10443                   ENDDO
10444                ENDIF
10445
10446             CASE ( 's_H2O' )
10447                found_index = get_index( prtcl,'H2O' )
10448                to_be_resorted => s_h2o_av
10449                DO  i = nxlg, nxrg
10450                   DO  j = nysg, nyng
10451                      DO  k = nzb, nzt+1
10452                         DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
10453                            s_h2o_av(k,j,i) = s_h2o_av(k,j,i) + aerosol_mass(ic)%conc(k,j,i)
10454                         ENDDO
10455                      ENDDO
10456                   ENDDO
10457                ENDDO
10458
10459             CASE DEFAULT
10460                CONTINUE
10461
10462          END SELECT
10463
10464       ENDIF
10465
10466    ELSEIF ( mode == 'average' )  THEN
10467
10468       IF ( variable(7:11) ==  'N_bin' )  THEN
10469          READ( variable(12:),* ) char_to_int
10470          IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
10471             ib = char_to_int
10472             DO  i = nxlg, nxrg
10473                DO  j = nysg, nyng
10474                   DO  k = nzb, nzt+1
10475                      nbins_av(k,j,i,ib) = nbins_av(k,j,i,ib) / REAL( average_count_3d, KIND=wp )
10476                   ENDDO
10477                ENDDO
10478             ENDDO
10479          ENDIF
10480
10481       ELSEIF ( variable(7:11) ==  'm_bin' )  THEN
10482          READ( variable(12:),* ) char_to_int
10483          IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
10484             ib = char_to_int
10485             DO  i = nxlg, nxrg
10486                DO  j = nysg, nyng
10487                   DO  k = nzb, nzt+1
10488                      mbins_av(k,j,i,ib) = mbins_av(k,j,i,ib) / REAL( average_count_3d, KIND=wp)
10489                   ENDDO
10490                ENDDO
10491             ENDDO
10492          ENDIF
10493       ELSE
10494
10495          SELECT CASE ( TRIM( variable(7:) ) )
10496
10497             CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV', 'g_OCSV' )
10498                IF ( TRIM( variable(9:) ) == 'H2SO4' )  THEN  ! 9: remove salsa_g_ from beginning
10499                   found_index = 1
10500                   to_be_resorted => g_h2so4_av
10501                ELSEIF ( TRIM( variable(9:) ) == 'HNO3' )  THEN
10502                   found_index = 2
10503                   to_be_resorted => g_hno3_av
10504                ELSEIF ( TRIM( variable(9:) ) == 'NH3' )  THEN
10505                   found_index = 3
10506                   to_be_resorted => g_nh3_av
10507                ELSEIF ( TRIM( variable(9:) ) == 'OCNV' )  THEN
10508                   found_index = 4
10509                   to_be_resorted => g_ocnv_av
10510                ELSEIF ( TRIM( variable(9:) ) == 'OCSV' )  THEN
10511                   found_index = 5
10512                   to_be_resorted => g_ocsv_av
10513                ENDIF
10514                DO  i = nxlg, nxrg
10515                   DO  j = nysg, nyng
10516                      DO  k = nzb, nzt+1
10517                         to_be_resorted(k,j,i) = to_be_resorted(k,j,i) /                           &
10518                                                 REAL( average_count_3d, KIND=wp )
10519                      ENDDO
10520                   ENDDO
10521                ENDDO
10522
10523             CASE ( 'LDSA' )
10524                DO  i = nxlg, nxrg
10525                   DO  j = nysg, nyng
10526                      DO  k = nzb, nzt+1
10527                         ldsa_av(k,j,i) = ldsa_av(k,j,i) / REAL( average_count_3d, KIND=wp )
10528                      ENDDO
10529                   ENDDO
10530                ENDDO
10531
10532             CASE ( 'N_UFP' )
10533                DO  i = nxlg, nxrg
10534                   DO  j = nysg, nyng
10535                      DO  k = nzb, nzt+1
10536                         nufp_av(k,j,i) = nufp_av(k,j,i) / REAL( average_count_3d, KIND=wp )
10537                      ENDDO
10538                   ENDDO
10539                ENDDO
10540
10541             CASE ( 'Ntot' )
10542                DO  i = nxlg, nxrg
10543                   DO  j = nysg, nyng
10544                      DO  k = nzb, nzt+1
10545                         ntot_av(k,j,i) = ntot_av(k,j,i) / REAL( average_count_3d, KIND=wp )
10546                      ENDDO
10547                   ENDDO
10548                ENDDO
10549
10550
10551             CASE ( 'PM0.1' )
10552                DO  i = nxlg, nxrg
10553                   DO  j = nysg, nyng
10554                      DO  k = nzb, nzt+1
10555                         pm01_av(k,j,i) = pm01_av(k,j,i) / REAL( average_count_3d, KIND=wp )
10556                      ENDDO
10557                   ENDDO
10558                ENDDO
10559
10560             CASE ( 'PM2.5' )
10561                DO  i = nxlg, nxrg
10562                   DO  j = nysg, nyng
10563                      DO  k = nzb, nzt+1
10564                         pm25_av(k,j,i) = pm25_av(k,j,i) / REAL( average_count_3d, KIND=wp )
10565                      ENDDO
10566                   ENDDO
10567                ENDDO
10568
10569             CASE ( 'PM10' )
10570                DO  i = nxlg, nxrg
10571                   DO  j = nysg, nyng
10572                      DO  k = nzb, nzt+1
10573                         pm10_av(k,j,i) = pm10_av(k,j,i) / REAL( average_count_3d, KIND=wp )
10574                      ENDDO
10575                   ENDDO
10576                ENDDO
10577
10578             CASE ( 's_BC', 's_DU', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
10579                IF ( is_used( prtcl, TRIM( variable(9:) ) ) )  THEN  ! 9: remove salsa_s_
10580                   IF ( TRIM( variable(9:) ) == 'BC' )   to_be_resorted => s_bc_av
10581                   IF ( TRIM( variable(9:) ) == 'DU' )   to_be_resorted => s_du_av
10582                   IF ( TRIM( variable(9:) ) == 'NH' )   to_be_resorted => s_nh_av
10583                   IF ( TRIM( variable(9:) ) == 'NO' )   to_be_resorted => s_no_av
10584                   IF ( TRIM( variable(9:) ) == 'OC' )   to_be_resorted => s_oc_av
10585                   IF ( TRIM( variable(9:) ) == 'SO4' )  to_be_resorted => s_so4_av
10586                   IF ( TRIM( variable(9:) ) == 'SS' )   to_be_resorted => s_ss_av 
10587                   DO  i = nxlg, nxrg
10588                      DO  j = nysg, nyng
10589                         DO  k = nzb, nzt+1
10590                            to_be_resorted(k,j,i) = to_be_resorted(k,j,i) /                        &
10591                                                    REAL( average_count_3d, KIND=wp )
10592                         ENDDO
10593                      ENDDO
10594                   ENDDO
10595                ENDIF
10596
10597             CASE ( 's_H2O' )
10598                to_be_resorted => s_h2o_av
10599                DO  i = nxlg, nxrg
10600                   DO  j = nysg, nyng
10601                      DO  k = nzb, nzt+1
10602                         to_be_resorted(k,j,i) = to_be_resorted(k,j,i) /                           &
10603                                                 REAL( average_count_3d, KIND=wp )
10604                      ENDDO
10605                   ENDDO
10606                ENDDO
10607
10608          END SELECT
10609
10610       ENDIF
10611    ENDIF
10612
10613 END SUBROUTINE salsa_3d_data_averaging
10614
10615
10616!------------------------------------------------------------------------------!
10617!
10618! Description:
10619! ------------
10620!> Subroutine defining 2D output variables
10621!------------------------------------------------------------------------------!
10622 SUBROUTINE salsa_data_output_2d( av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do )
10623
10624    USE indices
10625
10626    USE kinds
10627
10628
10629    IMPLICIT NONE
10630
10631    CHARACTER(LEN=*) ::  grid       !<
10632    CHARACTER(LEN=*) ::  mode       !<
10633    CHARACTER(LEN=*) ::  variable   !<
10634    CHARACTER(LEN=5) ::  vari       !<  trimmed format of variable
10635
10636    INTEGER(iwp) ::  av           !<
10637    INTEGER(iwp) ::  char_to_int  !< for converting character to integer
10638    INTEGER(iwp) ::  found_index  !< index of a chemical compound
10639    INTEGER(iwp) ::  i            !<
10640    INTEGER(iwp) ::  ib           !< running index: size bins
10641    INTEGER(iwp) ::  ic           !< running index: mass bins
10642    INTEGER(iwp) ::  j            !<
10643    INTEGER(iwp) ::  k            !<
10644    INTEGER(iwp) ::  nzb_do       !<
10645    INTEGER(iwp) ::  nzt_do       !<
10646
10647    LOGICAL ::  found  !<
10648    LOGICAL ::  two_d  !< flag parameter to indicate 2D variables (horizontal cross sections)
10649
10650    REAL(wp) ::  df                       !< For calculating LDSA: fraction of particles
10651                                          !< depositing in the alveolar (or tracheobronchial)
10652                                          !< region of the lung. Depends on the particle size
10653    REAL(wp) ::  mean_d                   !< Particle diameter in micrometres
10654    REAL(wp) ::  temp_bin                 !< temporary array for calculating output variables
10655
10656    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !< output
10657
10658    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted           !< pointer
10659!
10660!-- Next statement is to avoid compiler warning about unused variable. May be removed in future.
10661    IF ( two_d )  CONTINUE
10662
10663    found = .TRUE.
10664    temp_bin  = 0.0_wp
10665
10666    IF ( variable(7:11)  == 'N_bin' )  THEN
10667
10668       READ( variable( 12:LEN( TRIM( variable ) ) - 3 ), * ) char_to_int
10669       IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
10670
10671          ib = char_to_int
10672          IF ( av == 0 )  THEN
10673             DO  i = nxl, nxr
10674                DO  j = nys, nyn
10675                   DO  k = nzb_do, nzt_do
10676                      local_pf(i,j,k) = MERGE( aerosol_number(ib)%conc(k,j,i), REAL( fill_value,   &
10677                                               KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
10678                   ENDDO
10679                ENDDO
10680             ENDDO
10681          ELSE
10682             DO  i = nxl, nxr
10683                DO  j = nys, nyn
10684                   DO  k = nzb_do, nzt_do
10685                      local_pf(i,j,k) = MERGE( nbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
10686                                               BTEST( wall_flags_0(k,j,i), 0 ) )
10687                   ENDDO
10688                ENDDO
10689             ENDDO
10690          ENDIF
10691          IF ( mode == 'xy' )  grid = 'zu'
10692       ENDIF
10693
10694    ELSEIF ( variable(7:11)  == 'm_bin' )  THEN
10695
10696       READ( variable( 12:LEN( TRIM( variable ) ) - 3 ), * ) char_to_int
10697       IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
10698
10699          ib = char_to_int
10700          IF ( av == 0 )  THEN
10701             DO  i = nxl, nxr
10702                DO  j = nys, nyn
10703                   DO  k = nzb_do, nzt_do
10704                      temp_bin = 0.0_wp
10705                      DO  ic = ib, ncomponents_mass * nbins_aerosol, nbins_aerosol
10706                         temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10707                      ENDDO
10708                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
10709                                               BTEST( wall_flags_0(k,j,i), 0 ) )
10710                   ENDDO
10711                ENDDO
10712             ENDDO
10713          ELSE
10714             DO  i = nxl, nxr
10715                DO  j = nys, nyn
10716                   DO  k = nzb_do, nzt_do
10717                      local_pf(i,j,k) = MERGE( mbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
10718                                               BTEST( wall_flags_0(k,j,i), 0 ) )
10719                   ENDDO
10720                ENDDO
10721             ENDDO
10722          ENDIF
10723          IF ( mode == 'xy' )  grid = 'zu'
10724       ENDIF
10725
10726    ELSE
10727
10728       SELECT CASE ( TRIM( variable( 7:LEN( TRIM( variable ) ) - 3 ) ) )  ! cut out _xy, _xz or _yz
10729
10730          CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV', 'g_OCSV' )
10731             vari = TRIM( variable( 9:LEN( TRIM( variable ) ) - 3 ) )  ! 9: remove salsa_g_
10732             IF ( av == 0 )  THEN
10733                IF ( vari == 'H2SO4')  found_index = 1
10734                IF ( vari == 'HNO3')   found_index = 2
10735                IF ( vari == 'NH3')    found_index = 3
10736                IF ( vari == 'OCNV')   found_index = 4
10737                IF ( vari == 'OCSV')   found_index = 5
10738                DO  i = nxl, nxr
10739                   DO  j = nys, nyn
10740                      DO  k = nzb_do, nzt_do
10741                         local_pf(i,j,k) = MERGE( salsa_gas(found_index)%conc(k,j,i),              &
10742                                                  REAL( fill_value,  KIND = wp ),                  &
10743                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10744                      ENDDO
10745                   ENDDO
10746                ENDDO
10747             ELSE
10748                IF ( vari == 'H2SO4' )  to_be_resorted => g_h2so4_av
10749                IF ( vari == 'HNO3' )   to_be_resorted => g_hno3_av
10750                IF ( vari == 'NH3' )    to_be_resorted => g_nh3_av
10751                IF ( vari == 'OCNV' )   to_be_resorted => g_ocnv_av
10752                IF ( vari == 'OCSV' )   to_be_resorted => g_ocsv_av
10753                DO  i = nxl, nxr
10754                   DO  j = nys, nyn
10755                      DO  k = nzb_do, nzt_do
10756                         local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,         &
10757                                                  KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
10758                      ENDDO
10759                   ENDDO
10760                ENDDO
10761             ENDIF
10762
10763             IF ( mode == 'xy' )  grid = 'zu'
10764
10765          CASE ( 'LDSA' )
10766             IF ( av == 0 )  THEN
10767                DO  i = nxl, nxr
10768                   DO  j = nys, nyn
10769                      DO  k = nzb_do, nzt_do
10770                         temp_bin = 0.0_wp
10771                         DO  ib = 1, nbins_aerosol
10772   !
10773   !--                      Diameter in micrometres
10774                            mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp 
10775   !
10776   !--                      Deposition factor: alveolar
10777                            df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +    &
10778                                   2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -  &
10779                                   1.362_wp )**2 ) )
10780   !
10781   !--                      Lung-deposited surface area LDSA (units mum2/cm3)
10782                            temp_bin = temp_bin + pi * mean_d**2 * df * 1.0E-6_wp *                &
10783                                       aerosol_number(ib)%conc(k,j,i)
10784                         ENDDO
10785
10786                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
10787                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10788                      ENDDO
10789                   ENDDO
10790                ENDDO
10791             ELSE
10792                DO  i = nxl, nxr
10793                   DO  j = nys, nyn
10794                      DO  k = nzb_do, nzt_do
10795                         local_pf(i,j,k) = MERGE( ldsa_av(k,j,i), REAL( fill_value, KIND = wp ),   &
10796                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10797                      ENDDO
10798                   ENDDO
10799                ENDDO
10800             ENDIF
10801
10802             IF ( mode == 'xy' )  grid = 'zu'
10803
10804          CASE ( 'N_UFP' )
10805
10806             IF ( av == 0 )  THEN
10807                DO  i = nxl, nxr
10808                   DO  j = nys, nyn
10809                      DO  k = nzb_do, nzt_do
10810                         temp_bin = 0.0_wp
10811                         DO  ib = 1, nbins_aerosol
10812                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
10813                               temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
10814                            ENDIF
10815                         ENDDO
10816                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
10817                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10818                      ENDDO
10819                   ENDDO
10820                ENDDO
10821             ELSE
10822                DO  i = nxl, nxr
10823                   DO  j = nys, nyn
10824                      DO  k = nzb_do, nzt_do
10825                         local_pf(i,j,k) = MERGE( nufp_av(k,j,i), REAL( fill_value, KIND = wp ),   &
10826                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10827                      ENDDO
10828                   ENDDO
10829                ENDDO
10830             ENDIF
10831
10832             IF ( mode == 'xy' )  grid = 'zu'
10833
10834          CASE ( 'Ntot' )
10835
10836             IF ( av == 0 )  THEN
10837                DO  i = nxl, nxr
10838                   DO  j = nys, nyn
10839                      DO  k = nzb_do, nzt_do
10840                         temp_bin = 0.0_wp
10841                         DO  ib = 1, nbins_aerosol
10842                            temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
10843                         ENDDO
10844                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
10845                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10846                      ENDDO
10847                   ENDDO
10848                ENDDO
10849             ELSE
10850                DO  i = nxl, nxr
10851                   DO  j = nys, nyn
10852                      DO  k = nzb_do, nzt_do
10853                         local_pf(i,j,k) = MERGE( ntot_av(k,j,i), REAL( fill_value, KIND = wp ),   &
10854                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10855                      ENDDO
10856                   ENDDO
10857                ENDDO
10858             ENDIF
10859
10860             IF ( mode == 'xy' )  grid = 'zu'
10861
10862          CASE ( 'PM0.1' )
10863             IF ( av == 0 )  THEN
10864                DO  i = nxl, nxr
10865                   DO  j = nys, nyn
10866                      DO  k = nzb_do, nzt_do
10867                         temp_bin = 0.0_wp
10868                         DO  ib = 1, nbins_aerosol
10869                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
10870                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10871                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10872                               ENDDO
10873                            ENDIF
10874                         ENDDO
10875                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
10876                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10877                      ENDDO
10878                   ENDDO
10879                ENDDO
10880             ELSE
10881                DO  i = nxl, nxr
10882                   DO  j = nys, nyn
10883                      DO  k = nzb_do, nzt_do
10884                         local_pf(i,j,k) = MERGE( pm01_av(k,j,i), REAL( fill_value, KIND = wp ),   &
10885                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10886                      ENDDO
10887                   ENDDO
10888                ENDDO
10889             ENDIF
10890
10891             IF ( mode == 'xy' )  grid = 'zu'
10892
10893          CASE ( 'PM2.5' )
10894             IF ( av == 0 )  THEN
10895                DO  i = nxl, nxr
10896                   DO  j = nys, nyn
10897                      DO  k = nzb_do, nzt_do
10898                         temp_bin = 0.0_wp
10899                         DO  ib = 1, nbins_aerosol
10900                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
10901                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10902                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10903                               ENDDO
10904                            ENDIF
10905                         ENDDO
10906                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
10907                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10908                      ENDDO
10909                   ENDDO
10910                ENDDO
10911             ELSE
10912                DO  i = nxl, nxr
10913                   DO  j = nys, nyn
10914                      DO  k = nzb_do, nzt_do
10915                         local_pf(i,j,k) = MERGE( pm25_av(k,j,i), REAL( fill_value, KIND = wp ),   &
10916                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10917                      ENDDO
10918                   ENDDO
10919                ENDDO
10920             ENDIF
10921
10922             IF ( mode == 'xy' )  grid = 'zu'
10923
10924          CASE ( 'PM10' )
10925             IF ( av == 0 )  THEN
10926                DO  i = nxl, nxr
10927                   DO  j = nys, nyn
10928                      DO  k = nzb_do, nzt_do
10929                         temp_bin = 0.0_wp
10930                         DO  ib = 1, nbins_aerosol
10931                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
10932                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10933                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10934                               ENDDO
10935                            ENDIF
10936                         ENDDO
10937                         local_pf(i,j,k) = MERGE( temp_bin,  REAL( fill_value, KIND = wp ),        &
10938                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10939                      ENDDO
10940                   ENDDO
10941                ENDDO
10942             ELSE
10943                DO  i = nxl, nxr
10944                   DO  j = nys, nyn
10945                      DO  k = nzb_do, nzt_do
10946                         local_pf(i,j,k) = MERGE( pm10_av(k,j,i), REAL( fill_value, KIND = wp ),   &
10947                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
10948                      ENDDO
10949                   ENDDO
10950                ENDDO
10951             ENDIF
10952
10953             IF ( mode == 'xy' )  grid = 'zu'
10954
10955          CASE ( 's_BC', 's_DU', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
10956             vari = TRIM( variable( 9:LEN( TRIM( variable ) ) - 3 ) )  ! 9: remove salsa_s_
10957             IF ( is_used( prtcl, vari ) )  THEN
10958                found_index = get_index( prtcl, vari )
10959                IF ( av == 0 )  THEN
10960                   DO  i = nxl, nxr
10961                      DO  j = nys, nyn
10962                         DO  k = nzb_do, nzt_do
10963                            temp_bin = 0.0_wp
10964                            DO  ic = ( found_index-1 ) * nbins_aerosol+1, found_index * nbins_aerosol
10965                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10966                            ENDDO
10967                            local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),      &
10968                                                     BTEST( wall_flags_0(k,j,i), 0 ) )
10969                         ENDDO
10970                      ENDDO
10971                   ENDDO
10972                ELSE
10973                   IF ( vari == 'BC' )   to_be_resorted => s_bc_av
10974                   IF ( vari == 'DU' )   to_be_resorted => s_du_av
10975                   IF ( vari == 'NH' )   to_be_resorted => s_nh_av
10976                   IF ( vari == 'NO' )   to_be_resorted => s_no_av
10977                   IF ( vari == 'OC' )   to_be_resorted => s_oc_av
10978                   IF ( vari == 'SO4' )  to_be_resorted => s_so4_av
10979                   IF ( vari == 'SS' )   to_be_resorted => s_ss_av
10980                   DO  i = nxl, nxr
10981                      DO  j = nys, nyn
10982                         DO  k = nzb_do, nzt_do
10983                            local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,      &
10984                                                     KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
10985                         ENDDO
10986                      ENDDO
10987                   ENDDO
10988                ENDIF
10989             ELSE
10990                local_pf = fill_value
10991             ENDIF
10992
10993             IF ( mode == 'xy' )  grid = 'zu'
10994
10995          CASE ( 's_H2O' )
10996             found_index = get_index( prtcl, 'H2O' )
10997             IF ( av == 0 )  THEN
10998                DO  i = nxl, nxr
10999                   DO  j = nys, nyn
11000                      DO  k = nzb_do, nzt_do
11001                         temp_bin = 0.0_wp
11002                         DO  ic = ( found_index-1 ) * nbins_aerosol+1, found_index * nbins_aerosol
11003                            temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11004                         ENDDO
11005                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
11006                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
11007                      ENDDO
11008                   ENDDO
11009                ENDDO
11010             ELSE
11011                to_be_resorted => s_h2o_av
11012                DO  i = nxl, nxr
11013                   DO  j = nys, nyn
11014                      DO  k = nzb_do, nzt_do
11015                         local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,         &
11016                                                  KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
11017                      ENDDO
11018                   ENDDO
11019                ENDDO
11020             ENDIF
11021
11022             IF ( mode == 'xy' )  grid = 'zu'
11023
11024          CASE DEFAULT
11025             found = .FALSE.
11026             grid  = 'none'
11027
11028       END SELECT
11029
11030    ENDIF
11031
11032 END SUBROUTINE salsa_data_output_2d
11033
11034!------------------------------------------------------------------------------!
11035!
11036! Description:
11037! ------------
11038!> Subroutine defining 3D output variables
11039!------------------------------------------------------------------------------!
11040 SUBROUTINE salsa_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
11041
11042    USE indices
11043
11044    USE kinds
11045
11046
11047    IMPLICIT NONE
11048
11049    CHARACTER(LEN=*), INTENT(in) ::  variable   !<
11050
11051    INTEGER(iwp) ::  av           !<
11052    INTEGER(iwp) ::  char_to_int  !< for converting character to integer
11053    INTEGER(iwp) ::  found_index  !< index of a chemical compound
11054    INTEGER(iwp) ::  ib           !< running index: size bins
11055    INTEGER(iwp) ::  ic           !< running index: mass bins
11056    INTEGER(iwp) ::  i            !<
11057    INTEGER(iwp) ::  j            !<
11058    INTEGER(iwp) ::  k            !<
11059    INTEGER(iwp) ::  nzb_do       !<
11060    INTEGER(iwp) ::  nzt_do       !<
11061
11062    LOGICAL ::  found      !<
11063
11064    REAL(wp) ::  df                       !< For calculating LDSA: fraction of particles
11065                                          !< depositing in the alveolar (or tracheobronchial)
11066                                          !< region of the lung. Depends on the particle size
11067    REAL(wp) ::  mean_d                   !< Particle diameter in micrometres
11068    REAL(wp) ::  temp_bin                 !< temporary array for calculating output variables
11069
11070    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !< local
11071
11072    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !< pointer
11073
11074    found     = .TRUE.
11075    temp_bin  = 0.0_wp
11076
11077    IF ( variable(7:11) == 'N_bin' )  THEN
11078       READ( variable(12:),* ) char_to_int
11079       IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
11080
11081          ib = char_to_int
11082          IF ( av == 0 )  THEN
11083             DO  i = nxl, nxr
11084                DO  j = nys, nyn
11085                   DO  k = nzb_do, nzt_do
11086                      local_pf(i,j,k) = MERGE( aerosol_number(ib)%conc(k,j,i), REAL( fill_value,   &
11087                                               KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
11088                   ENDDO
11089                ENDDO
11090             ENDDO
11091          ELSE
11092             DO  i = nxl, nxr
11093                DO  j = nys, nyn
11094                   DO  k = nzb_do, nzt_do
11095                      local_pf(i,j,k) = MERGE( nbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
11096                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
11097                   ENDDO
11098                ENDDO
11099             ENDDO
11100          ENDIF
11101       ENDIF
11102
11103    ELSEIF ( variable(7:11) == 'm_bin' )  THEN
11104       READ( variable(12:),* ) char_to_int
11105       IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
11106
11107          ib = char_to_int
11108          IF ( av == 0 )  THEN
11109             DO  i = nxl, nxr
11110                DO  j = nys, nyn
11111                   DO  k = nzb_do, nzt_do
11112                      temp_bin = 0.0_wp
11113                      DO  ic = ib, ncomponents_mass * nbins_aerosol, nbins_aerosol
11114                         temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11115                      ENDDO
11116                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
11117                                               BTEST( wall_flags_0(k,j,i), 0 ) )
11118                   ENDDO
11119                ENDDO
11120             ENDDO
11121          ELSE
11122             DO  i = nxl, nxr
11123                DO  j = nys, nyn
11124                   DO  k = nzb_do, nzt_do
11125                      local_pf(i,j,k) = MERGE( mbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
11126                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
11127                   ENDDO
11128                ENDDO
11129             ENDDO
11130          ENDIF
11131       ENDIF
11132
11133    ELSE
11134       SELECT CASE ( TRIM( variable(7:) ) )
11135
11136          CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV',  'g_OCSV' )
11137             IF ( av == 0 )  THEN
11138                IF ( TRIM( variable(7:) ) == 'g_H2SO4')  found_index = 1
11139                IF ( TRIM( variable(7:) ) == 'g_HNO3')   found_index = 2
11140                IF ( TRIM( variable(7:) ) == 'g_NH3')    found_index = 3
11141                IF ( TRIM( variable(7:) ) == 'g_OCNV')   found_index = 4
11142                IF ( TRIM( variable(7:) ) == 'g_OCSV')   found_index = 5
11143
11144                DO  i = nxl, nxr
11145                   DO  j = nys, nyn
11146                      DO  k = nzb_do, nzt_do
11147                         local_pf(i,j,k) = MERGE( salsa_gas(found_index)%conc(k,j,i),              &
11148                                                  REAL( fill_value, KIND = wp ),                   &
11149                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
11150                      ENDDO
11151                   ENDDO
11152                ENDDO
11153             ELSE
11154!
11155!--             9: remove salsa_g_ from the beginning
11156                IF ( TRIM( variable(9:) ) == 'H2SO4' ) to_be_resorted => g_h2so4_av
11157                IF ( TRIM( variable(9:) ) == 'HNO3' )  to_be_resorted => g_hno3_av
11158                IF ( TRIM( variable(9:) ) == 'NH3' )   to_be_resorted => g_nh3_av
11159                IF ( TRIM( variable(9:) ) == 'OCNV' )  to_be_resorted => g_ocnv_av
11160                IF ( TRIM( variable(9:) ) == 'OCSV' )  to_be_resorted => g_ocsv_av
11161                DO  i = nxl, nxr
11162                   DO  j = nys, nyn
11163                      DO  k = nzb_do, nzt_do
11164                         local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,         &
11165                                                  KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
11166                      ENDDO
11167                   ENDDO
11168                ENDDO
11169             ENDIF
11170
11171          CASE ( 'LDSA' )
11172             IF ( av == 0 )  THEN
11173                DO  i = nxl, nxr
11174                   DO  j = nys, nyn
11175                      DO  k = nzb_do, nzt_do
11176                         temp_bin = 0.0_wp
11177                         DO  ib = 1, nbins_aerosol
11178   !
11179   !--                      Diameter in micrometres
11180                            mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
11181   !
11182   !--                      Deposition factor: alveolar
11183                            df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +    &
11184                                   2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -  &
11185                                   1.362_wp )**2 ) )
11186   !
11187   !--                      Lung-deposited surface area LDSA (units mum2/cm3)
11188                            temp_bin = temp_bin + pi * mean_d**2 * df * 1.0E-6_wp *                &
11189                                       aerosol_number(ib)%conc(k,j,i)
11190                         ENDDO
11191                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
11192                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
11193                      ENDDO
11194                   ENDDO
11195                ENDDO
11196             ELSE
11197                DO  i = nxl, nxr
11198                   DO  j = nys, nyn
11199                      DO  k = nzb_do, nzt_do
11200                         local_pf(i,j,k) = MERGE( ldsa_av(k,j,i), REAL( fill_value, KIND = wp ),   &
11201                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11202                      ENDDO
11203                   ENDDO
11204                ENDDO
11205             ENDIF
11206
11207          CASE ( 'N_UFP' )
11208             IF ( av == 0 )  THEN
11209                DO  i = nxl, nxr
11210                   DO  j = nys, nyn
11211                      DO  k = nzb_do, nzt_do
11212                         temp_bin = 0.0_wp
11213                         DO  ib = 1, nbins_aerosol
11214                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
11215                               temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
11216                            ENDIF
11217                         ENDDO
11218                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
11219                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
11220                      ENDDO
11221                   ENDDO
11222                ENDDO
11223             ELSE
11224                DO  i = nxl, nxr
11225                   DO  j = nys, nyn
11226                      DO  k = nzb_do, nzt_do
11227                         local_pf(i,j,k) = MERGE( nufp_av(k,j,i), REAL( fill_value, KIND = wp ),   &
11228                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11229                      ENDDO
11230                   ENDDO
11231                ENDDO
11232             ENDIF
11233
11234          CASE ( 'Ntot' )
11235             IF ( av == 0 )  THEN
11236                DO  i = nxl, nxr
11237                   DO  j = nys, nyn
11238                      DO  k = nzb_do, nzt_do
11239                         temp_bin = 0.0_wp
11240                         DO  ib = 1, nbins_aerosol
11241                            temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
11242                         ENDDO
11243                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
11244                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
11245                      ENDDO
11246                   ENDDO
11247                ENDDO
11248             ELSE
11249                DO  i = nxl, nxr
11250                   DO  j = nys, nyn
11251                      DO  k = nzb_do, nzt_do
11252                         local_pf(i,j,k) = MERGE( ntot_av(k,j,i), REAL( fill_value, KIND = wp ),   &
11253                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11254                      ENDDO
11255                   ENDDO
11256                ENDDO
11257             ENDIF
11258
11259          CASE ( 'PM0.1' )
11260             IF ( av == 0 )  THEN
11261                DO  i = nxl, nxr
11262                   DO  j = nys, nyn
11263                      DO  k = nzb_do, nzt_do
11264                         temp_bin = 0.0_wp
11265                         DO  ib = 1, nbins_aerosol
11266                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
11267                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
11268                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11269                               ENDDO
11270                            ENDIF
11271                         ENDDO
11272                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
11273                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11274                      ENDDO
11275                   ENDDO
11276                ENDDO
11277             ELSE
11278                DO  i = nxl, nxr
11279                   DO  j = nys, nyn
11280                      DO  k = nzb_do, nzt_do
11281                         local_pf(i,j,k) = MERGE( pm01_av(k,j,i), REAL( fill_value, KIND = wp ),   &
11282                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11283                      ENDDO
11284                   ENDDO
11285                ENDDO
11286             ENDIF
11287
11288          CASE ( 'PM2.5' )
11289             IF ( av == 0 )  THEN
11290                DO  i = nxl, nxr
11291                   DO  j = nys, nyn
11292                      DO  k = nzb_do, nzt_do
11293                         temp_bin = 0.0_wp
11294                         DO  ib = 1, nbins_aerosol
11295                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
11296                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
11297                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11298                               ENDDO
11299                            ENDIF
11300                         ENDDO
11301                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
11302                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11303                      ENDDO
11304                   ENDDO
11305                ENDDO
11306             ELSE
11307                DO  i = nxl, nxr
11308                   DO  j = nys, nyn
11309                      DO  k = nzb_do, nzt_do
11310                         local_pf(i,j,k) = MERGE( pm25_av(k,j,i), REAL( fill_value, KIND = wp ),   &
11311                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11312                      ENDDO
11313                   ENDDO
11314                ENDDO
11315             ENDIF
11316
11317          CASE ( 'PM10' )
11318             IF ( av == 0 )  THEN
11319                DO  i = nxl, nxr
11320                   DO  j = nys, nyn
11321                      DO  k = nzb_do, nzt_do
11322                         temp_bin = 0.0_wp
11323                         DO  ib = 1, nbins_aerosol
11324                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
11325                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
11326                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11327                               ENDDO
11328                            ENDIF
11329                         ENDDO
11330                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
11331                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11332                      ENDDO
11333                   ENDDO
11334                ENDDO
11335             ELSE
11336                DO  i = nxl, nxr
11337                   DO  j = nys, nyn
11338                      DO  k = nzb_do, nzt_do
11339                         local_pf(i,j,k) = MERGE( pm10_av(k,j,i), REAL( fill_value, KIND = wp ),   &
11340                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
11341                      ENDDO
11342                   ENDDO
11343                ENDDO
11344             ENDIF
11345
11346          CASE ( 's_BC', 's_DU', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
11347             IF ( is_used( prtcl, TRIM( variable(9:) ) ) )  THEN  ! 9: remove salsa_s_
11348                found_index = get_index( prtcl, TRIM( variable(9:) ) )
11349                IF ( av == 0 )  THEN
11350                   DO  i = nxl, nxr
11351                      DO  j = nys, nyn
11352                         DO  k = nzb_do, nzt_do
11353                            temp_bin = 0.0_wp
11354                            DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
11355                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11356                            ENDDO
11357                            local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),      &
11358                                                     BTEST( wall_flags_0(k,j,i), 0 ) ) 
11359                         ENDDO
11360                      ENDDO
11361                   ENDDO
11362                ELSE
11363!
11364!--                9: remove salsa_s_ from the beginning
11365                   IF ( TRIM( variable(9:) ) == 'BC' )   to_be_resorted => s_bc_av
11366                   IF ( TRIM( variable(9:) ) == 'DU' )   to_be_resorted => s_du_av
11367                   IF ( TRIM( variable(9:) ) == 'NH' )   to_be_resorted => s_nh_av
11368                   IF ( TRIM( variable(9:) ) == 'NO' )   to_be_resorted => s_no_av
11369                   IF ( TRIM( variable(9:) ) == 'OC' )   to_be_resorted => s_oc_av
11370                   IF ( TRIM( variable(9:) ) == 'SO4' )  to_be_resorted => s_so4_av
11371                   IF ( TRIM( variable(9:) ) == 'SS' )   to_be_resorted => s_ss_av
11372                   DO  i = nxl, nxr
11373                      DO  j = nys, nyn
11374                         DO  k = nzb_do, nzt_do
11375                            local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,      &
11376                                                     KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
11377                         ENDDO
11378                      ENDDO
11379                   ENDDO
11380                ENDIF
11381             ENDIF
11382
11383          CASE ( 's_H2O' )
11384             found_index = get_index( prtcl, 'H2O' )
11385             IF ( av == 0 )  THEN
11386                DO  i = nxl, nxr
11387                   DO  j = nys, nyn
11388                      DO  k = nzb_do, nzt_do
11389                         temp_bin = 0.0_wp
11390                         DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
11391                            temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11392                         ENDDO
11393                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
11394                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
11395                      ENDDO
11396                   ENDDO
11397                ENDDO
11398             ELSE
11399                to_be_resorted => s_h2o_av
11400                DO  i = nxl, nxr
11401                   DO  j = nys, nyn
11402                      DO  k = nzb_do, nzt_do
11403                         local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,         &
11404                                                  KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
11405                      ENDDO
11406                   ENDDO
11407                ENDDO
11408             ENDIF
11409
11410          CASE DEFAULT
11411             found = .FALSE.
11412
11413       END SELECT
11414    ENDIF
11415
11416 END SUBROUTINE salsa_data_output_3d
11417
11418!------------------------------------------------------------------------------!
11419!
11420! Description:
11421! ------------
11422!> Subroutine defining mask output variables
11423!------------------------------------------------------------------------------!
11424 SUBROUTINE salsa_data_output_mask( av, variable, found, local_pf, mid )
11425
11426    USE arrays_3d,                                                                                 &
11427        ONLY:  tend
11428
11429    USE control_parameters,                                                                        &
11430        ONLY:  mask_i, mask_j, mask_k, mask_size_l, mask_surface, nz_do3d
11431
11432    IMPLICIT NONE
11433
11434    CHARACTER(LEN=5) ::  grid      !< flag to distinquish between staggered grid
11435    CHARACTER(LEN=*) ::  variable  !<
11436    CHARACTER(LEN=7) ::  vari      !< trimmed format of variable
11437
11438    INTEGER(iwp) ::  av             !<
11439    INTEGER(iwp) ::  char_to_int    !< for converting character to integer
11440    INTEGER(iwp) ::  found_index    !< index of a chemical compound
11441    INTEGER(iwp) ::  ib             !< loop index for aerosol size number bins
11442    INTEGER(iwp) ::  ic             !< loop index for chemical components
11443    INTEGER(iwp) ::  i              !< loop index in x-direction
11444    INTEGER(iwp) ::  j              !< loop index in y-direction
11445    INTEGER(iwp) ::  k              !< loop index in z-direction
11446    INTEGER(iwp) ::  im             !< loop index for masked variables
11447    INTEGER(iwp) ::  jm             !< loop index for masked variables
11448    INTEGER(iwp) ::  kk             !< loop index for masked output in z-direction
11449    INTEGER(iwp) ::  mid            !< masked output running index
11450    INTEGER(iwp) ::  ktt            !< k index of highest terrain surface
11451
11452    LOGICAL ::  found      !<
11453    LOGICAL ::  resorted   !<
11454
11455    REAL(wp) ::  df        !< For calculating LDSA: fraction of particles depositing in the alveolar
11456                           !< (or tracheobronchial) region of the lung. Depends on the particle size
11457    REAL(wp) ::  mean_d    !< Particle diameter in micrometres
11458    REAL(wp) ::  temp_bin  !< temporary array for calculating output variables
11459
11460    REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  local_pf   !<
11461
11462    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg), TARGET ::  temp_array  !< temporary array
11463
11464    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !< pointer
11465
11466    found      = .TRUE.
11467    resorted   = .FALSE.
11468    grid       = 's'
11469    temp_array = 0.0_wp
11470    temp_bin   = 0.0_wp
11471
11472    IF ( variable(7:11) == 'N_bin' )  THEN
11473       READ( variable(12:),* ) char_to_int
11474       IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
11475          ib = char_to_int
11476          IF ( av == 0 )  THEN
11477             IF ( .NOT. mask_surface(mid) )  THEN
11478                DO  i = 1, mask_size_l(mid,1)
11479                   DO  j = 1, mask_size_l(mid,2)
11480                      DO  k = 1, mask_size_l(mid,3)
11481                         local_pf(i,j,k) = aerosol_number(ib)%conc( mask_k(mid,k), mask_j(mid,j),  &
11482                                                                    mask_i(mid,i) )
11483                      ENDDO
11484                   ENDDO
11485                ENDDO
11486             ELSE
11487                DO  i = 1, mask_size_l(mid,1)
11488                   DO  j = 1, mask_size_l(mid,2)
11489!
11490!--                   Get k index of the highest terraing surface
11491                      im = mask_i(mid,i)
11492                      jm = mask_j(mid,j)
11493                      ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11494                      DO  k = 1, mask_size_l(mid,3)
11495                         kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11496!
11497!--                      Set value if not in building
11498                         IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11499                            local_pf(i,j,k) = fill_value
11500                         ELSE
11501                            local_pf(i,j,k) = aerosol_number(ib)%conc(kk,jm,im)
11502                         ENDIF
11503                      ENDDO
11504                   ENDDO
11505                ENDDO
11506             ENDIF
11507             resorted = .TRUE.
11508          ELSE
11509             temp_array = nbins_av(:,:,:,ib)
11510             to_be_resorted => temp_array
11511          ENDIF
11512       ENDIF
11513
11514    ELSEIF ( variable(7:11) == 'm_bin' )  THEN
11515
11516       READ( variable(12:),* ) char_to_int
11517       IF ( char_to_int >= 1  .AND. char_to_int <= SUM( nbin ) )  THEN
11518
11519          ib = char_to_int
11520          IF ( av == 0 )  THEN
11521             DO  i = nxl, nxr
11522                DO  j = nys, nyn
11523                   DO  k = nzb, nz_do3d
11524                      temp_bin = 0.0_wp
11525                      DO  ic = ib, ncomponents_mass * nbins_aerosol, nbins_aerosol
11526                         temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11527                      ENDDO
11528                      tend(k,j,i) = temp_bin
11529                   ENDDO
11530                ENDDO
11531             ENDDO
11532             IF ( .NOT. mask_surface(mid) )  THEN
11533                DO  i = 1, mask_size_l(mid,1)
11534                   DO  j = 1, mask_size_l(mid,2)
11535                      DO  k = 1, mask_size_l(mid,3)
11536                         local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
11537                      ENDDO
11538                   ENDDO
11539                ENDDO
11540             ELSE
11541                DO  i = 1, mask_size_l(mid,1)
11542                   DO  j = 1, mask_size_l(mid,2)
11543!
11544!--                   Get k index of the highest terraing surface
11545                      im = mask_i(mid,i)
11546                      jm = mask_j(mid,j)
11547                      ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11548                      DO  k = 1, mask_size_l(mid,3)
11549                         kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11550!
11551!--                      Set value if not in building
11552                         IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11553                            local_pf(i,j,k) = fill_value
11554                         ELSE
11555                            local_pf(i,j,k) = tend(kk,jm,im)
11556                         ENDIF
11557                      ENDDO
11558                   ENDDO
11559                ENDDO
11560             ENDIF
11561             resorted = .TRUE.
11562          ELSE
11563             temp_array = mbins_av(:,:,:,ib)
11564             to_be_resorted => temp_array
11565          ENDIF
11566       ENDIF
11567
11568    ELSE
11569       SELECT CASE ( TRIM( variable(7:) ) )
11570
11571          CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV',  'g_OCSV' )
11572             vari = TRIM( variable(7:) )
11573             IF ( av == 0 )  THEN
11574                IF ( vari == 'g_H2SO4')  to_be_resorted => salsa_gas(1)%conc
11575                IF ( vari == 'g_HNO3')   to_be_resorted => salsa_gas(2)%conc
11576                IF ( vari == 'g_NH3')    to_be_resorted => salsa_gas(3)%conc
11577                IF ( vari == 'g_OCNV')   to_be_resorted => salsa_gas(4)%conc
11578                IF ( vari == 'g_OCSV')   to_be_resorted => salsa_gas(5)%conc
11579             ELSE
11580                IF ( vari == 'g_H2SO4') to_be_resorted => g_h2so4_av
11581                IF ( vari == 'g_HNO3')  to_be_resorted => g_hno3_av
11582                IF ( vari == 'g_NH3')   to_be_resorted => g_nh3_av
11583                IF ( vari == 'g_OCNV')  to_be_resorted => g_ocnv_av
11584                IF ( vari == 'g_OCSV')  to_be_resorted => g_ocsv_av
11585             ENDIF
11586
11587          CASE ( 'LDSA' )
11588             IF ( av == 0 )  THEN
11589                DO  i = nxl, nxr
11590                   DO  j = nys, nyn
11591                      DO  k = nzb, nz_do3d
11592                         temp_bin = 0.0_wp
11593                         DO  ib = 1, nbins_aerosol
11594   !
11595   !--                      Diameter in micrometres
11596                            mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
11597   !
11598   !--                      Deposition factor: alveolar
11599                            df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +    &
11600                                   2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -  &
11601                                   1.362_wp )**2 ) )
11602   !
11603   !--                      Lung-deposited surface area LDSA (units mum2/cm3)
11604                            temp_bin = temp_bin + pi * mean_d**2 * df * 1.0E-6_wp *                &
11605                                       aerosol_number(ib)%conc(k,j,i)
11606                         ENDDO
11607                         tend(k,j,i) = temp_bin
11608                      ENDDO
11609                   ENDDO
11610                ENDDO
11611                IF ( .NOT. mask_surface(mid) )  THEN
11612                   DO  i = 1, mask_size_l(mid,1)
11613                      DO  j = 1, mask_size_l(mid,2)
11614                         DO  k = 1, mask_size_l(mid,3)
11615                            local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
11616                         ENDDO
11617                      ENDDO
11618                   ENDDO
11619                ELSE
11620                   DO  i = 1, mask_size_l(mid,1)
11621                      DO  j = 1, mask_size_l(mid,2)
11622!
11623!--                      Get k index of the highest terraing surface
11624                         im = mask_i(mid,i)
11625                         jm = mask_j(mid,j)
11626                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11627                         DO  k = 1, mask_size_l(mid,3)
11628                            kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11629!
11630!--                         Set value if not in building
11631                            IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11632                               local_pf(i,j,k) = fill_value
11633                            ELSE
11634                               local_pf(i,j,k) = tend(kk,jm,im)
11635                            ENDIF
11636                         ENDDO
11637                      ENDDO
11638                   ENDDO
11639                ENDIF
11640                resorted = .TRUE.
11641             ELSE
11642                to_be_resorted => ldsa_av
11643             ENDIF
11644
11645          CASE ( 'N_UFP' )
11646             IF ( av == 0 )  THEN
11647                DO  i = nxl, nxr
11648                   DO  j = nys, nyn
11649                      DO  k = nzb, nz_do3d
11650                         temp_bin = 0.0_wp
11651                         DO  ib = 1, nbins_aerosol
11652                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
11653                               temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
11654                            ENDIF
11655                         ENDDO
11656                         tend(k,j,i) = temp_bin
11657                      ENDDO
11658                   ENDDO
11659                ENDDO 
11660                IF ( .NOT. mask_surface(mid) )  THEN
11661                   DO  i = 1, mask_size_l(mid,1)
11662                      DO  j = 1, mask_size_l(mid,2)
11663                         DO  k = 1, mask_size_l(mid,3)
11664                            local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
11665                         ENDDO
11666                      ENDDO
11667                   ENDDO
11668                ELSE
11669                   DO  i = 1, mask_size_l(mid,1)
11670                      DO  j = 1, mask_size_l(mid,2)
11671!
11672!--                      Get k index of the highest terraing surface
11673                         im = mask_i(mid,i)
11674                         jm = mask_j(mid,j)
11675                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11676                         DO  k = 1, mask_size_l(mid,3)
11677                            kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11678!
11679!--                         Set value if not in building
11680                            IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11681                               local_pf(i,j,k) = fill_value
11682                            ELSE
11683                               local_pf(i,j,k) = tend(kk,jm,im)
11684                            ENDIF
11685                         ENDDO
11686                      ENDDO
11687                   ENDDO
11688                ENDIF
11689                resorted = .TRUE.
11690             ELSE
11691                to_be_resorted => nufp_av
11692             ENDIF
11693
11694          CASE ( 'Ntot' )
11695             IF ( av == 0 )  THEN
11696                DO  i = nxl, nxr
11697                   DO  j = nys, nyn
11698                      DO  k = nzb, nz_do3d
11699                         temp_bin = 0.0_wp
11700                         DO  ib = 1, nbins_aerosol
11701                            temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
11702                         ENDDO
11703                         tend(k,j,i) = temp_bin
11704                      ENDDO
11705                   ENDDO
11706                ENDDO 
11707                IF ( .NOT. mask_surface(mid) )  THEN
11708                   DO  i = 1, mask_size_l(mid,1)
11709                      DO  j = 1, mask_size_l(mid,2)
11710                         DO  k = 1, mask_size_l(mid,3)
11711                            local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
11712                         ENDDO
11713                      ENDDO
11714                   ENDDO
11715                ELSE
11716                   DO  i = 1, mask_size_l(mid,1)
11717                      DO  j = 1, mask_size_l(mid,2)
11718!
11719!--                      Get k index of the highest terraing surface
11720                         im = mask_i(mid,i)
11721                         jm = mask_j(mid,j)
11722                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11723                         DO  k = 1, mask_size_l(mid,3)
11724                            kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11725!
11726!--                         Set value if not in building
11727                            IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11728                               local_pf(i,j,k) = fill_value
11729                            ELSE
11730                               local_pf(i,j,k) = tend(kk,jm,im)
11731                            ENDIF
11732                         ENDDO
11733                      ENDDO
11734                   ENDDO
11735                ENDIF
11736                resorted = .TRUE.
11737             ELSE
11738                to_be_resorted => ntot_av
11739             ENDIF
11740
11741          CASE ( 'PM0.1' )
11742             IF ( av == 0 )  THEN
11743                DO  i = nxl, nxr
11744                   DO  j = nys, nyn
11745                      DO  k = nzb, nz_do3d
11746                         temp_bin = 0.0_wp
11747                         DO  ib = 1, nbins_aerosol
11748                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 0.1E-6_wp )  THEN
11749                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
11750                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11751                               ENDDO
11752                            ENDIF
11753                         ENDDO
11754                         tend(k,j,i) = temp_bin
11755                      ENDDO
11756                   ENDDO
11757                ENDDO 
11758                IF ( .NOT. mask_surface(mid) )  THEN
11759                   DO  i = 1, mask_size_l(mid,1)
11760                      DO  j = 1, mask_size_l(mid,2)
11761                         DO  k = 1, mask_size_l(mid,3)
11762                            local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
11763                         ENDDO
11764                      ENDDO
11765                   ENDDO
11766                ELSE
11767                   DO  i = 1, mask_size_l(mid,1)
11768                      DO  j = 1, mask_size_l(mid,2)
11769!
11770!--                      Get k index of the highest terraing surface
11771                         im = mask_i(mid,i)
11772                         jm = mask_j(mid,j)
11773                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11774                         DO  k = 1, mask_size_l(mid,3)
11775                            kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11776!
11777!--                         Set value if not in building
11778                            IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11779                               local_pf(i,j,k) = fill_value
11780                            ELSE
11781                               local_pf(i,j,k) = tend(kk,jm,im)
11782                            ENDIF
11783                         ENDDO
11784                      ENDDO
11785                   ENDDO
11786                ENDIF
11787                resorted = .TRUE.
11788             ELSE
11789                to_be_resorted => pm01_av
11790             ENDIF
11791
11792          CASE ( 'PM2.5' )
11793             IF ( av == 0 )  THEN
11794                DO  i = nxl, nxr
11795                   DO  j = nys, nyn
11796                      DO  k = nzb, nz_do3d
11797                         temp_bin = 0.0_wp
11798                         DO  ib = 1, nbins_aerosol
11799                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
11800                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
11801                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11802                               ENDDO
11803                            ENDIF
11804                         ENDDO
11805                         tend(k,j,i) = temp_bin
11806                      ENDDO
11807                   ENDDO
11808                ENDDO 
11809                IF ( .NOT. mask_surface(mid) )  THEN
11810                   DO  i = 1, mask_size_l(mid,1)
11811                      DO  j = 1, mask_size_l(mid,2)
11812                         DO  k = 1, mask_size_l(mid,3)
11813                            local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
11814                         ENDDO
11815                      ENDDO
11816                   ENDDO
11817                ELSE
11818                   DO  i = 1, mask_size_l(mid,1)
11819                      DO  j = 1, mask_size_l(mid,2)
11820!
11821!--                      Get k index of the highest terraing surface
11822                         im = mask_i(mid,i)
11823                         jm = mask_j(mid,j)
11824                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11825                         DO  k = 1, mask_size_l(mid,3)
11826                            kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11827!
11828!--                         Set value if not in building
11829                            IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11830                               local_pf(i,j,k) = fill_value
11831                            ELSE
11832                               local_pf(i,j,k) = tend(kk,jm,im)
11833                            ENDIF
11834                         ENDDO
11835                      ENDDO
11836                   ENDDO
11837                ENDIF
11838                resorted = .TRUE.
11839             ELSE
11840                to_be_resorted => pm25_av
11841             ENDIF
11842
11843          CASE ( 'PM10' )
11844             IF ( av == 0 )  THEN
11845                DO  i = nxl, nxr
11846                   DO  j = nys, nyn
11847                      DO  k = nzb, nz_do3d
11848                         temp_bin = 0.0_wp
11849                         DO  ib = 1, nbins_aerosol
11850                            IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
11851                               DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
11852                                  temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11853                               ENDDO
11854                            ENDIF
11855                         ENDDO
11856                         tend(k,j,i) = temp_bin
11857                      ENDDO
11858                   ENDDO
11859                ENDDO 
11860                IF ( .NOT. mask_surface(mid) )  THEN
11861                   DO  i = 1, mask_size_l(mid,1)
11862                      DO  j = 1, mask_size_l(mid,2)
11863                         DO  k = 1, mask_size_l(mid,3)
11864                            local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
11865                         ENDDO
11866                      ENDDO
11867                   ENDDO
11868                ELSE
11869                   DO  i = 1, mask_size_l(mid,1)
11870                      DO  j = 1, mask_size_l(mid,2)
11871!
11872!--                      Get k index of the highest terraing surface
11873                         im = mask_i(mid,i)
11874                         jm = mask_j(mid,j)
11875                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11876                         DO  k = 1, mask_size_l(mid,3)
11877                            kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11878!
11879!--                         Set value if not in building
11880                            IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11881                               local_pf(i,j,k) = fill_value
11882                            ELSE
11883                               local_pf(i,j,k) = tend(kk,jm,im)
11884                            ENDIF
11885                         ENDDO
11886                      ENDDO
11887                   ENDDO
11888                ENDIF
11889                resorted = .TRUE.
11890             ELSE
11891                to_be_resorted => pm10_av
11892             ENDIF
11893
11894          CASE ( 's_BC', 's_DU', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
11895             IF ( av == 0 )  THEN
11896                IF ( is_used( prtcl, TRIM( variable(3:) ) ) )  THEN
11897                   found_index = get_index( prtcl, TRIM( variable(3:) ) )
11898                   DO  i = nxl, nxr
11899                      DO  j = nys, nyn
11900                         DO  k = nzb, nz_do3d
11901                            temp_bin = 0.0_wp
11902                            DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
11903                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11904                            ENDDO
11905                            tend(k,j,i) = temp_bin
11906                         ENDDO
11907                      ENDDO
11908                   ENDDO
11909                ELSE
11910                   tend = 0.0_wp
11911                ENDIF
11912                IF ( .NOT. mask_surface(mid) )  THEN
11913                   DO  i = 1, mask_size_l(mid,1)
11914                      DO  j = 1, mask_size_l(mid,2)
11915                         DO  k = 1, mask_size_l(mid,3)
11916                            local_pf(i,j,k) = tend( mask_k(mid,k), mask_j(mid,j), mask_i(mid,i) )
11917                         ENDDO
11918                      ENDDO
11919                   ENDDO
11920                ELSE
11921                   DO  i = 1, mask_size_l(mid,1)
11922                      DO  j = 1, mask_size_l(mid,2)
11923!
11924!--                      Get k index of the highest terraing surface
11925                         im = mask_i(mid,i)
11926                         jm = mask_j(mid,j)
11927                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11928                         DO  k = 1, mask_size_l(mid,3)
11929                            kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11930!
11931!--                         Set value if not in building
11932                            IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11933                               local_pf(i,j,k) = fill_value
11934                            ELSE
11935                               local_pf(i,j,k) = tend(kk,jm,im)
11936                            ENDIF
11937                         ENDDO
11938                      ENDDO
11939                   ENDDO
11940                ENDIF
11941                resorted = .TRUE.
11942             ELSE
11943!
11944!--             9: remove salsa_s_ from the beginning
11945                IF ( TRIM( variable(9:) ) == 'BC' )   to_be_resorted => s_bc_av
11946                IF ( TRIM( variable(9:) ) == 'DU' )   to_be_resorted => s_du_av
11947                IF ( TRIM( variable(9:) ) == 'NH' )   to_be_resorted => s_nh_av
11948                IF ( TRIM( variable(9:) ) == 'NO' )   to_be_resorted => s_no_av
11949                IF ( TRIM( variable(9:) ) == 'OC' )   to_be_resorted => s_oc_av
11950                IF ( TRIM( variable(9:) ) == 'SO4' )  to_be_resorted => s_so4_av
11951                IF ( TRIM( variable(9:) ) == 'SS' )   to_be_resorted => s_ss_av
11952             ENDIF
11953
11954          CASE ( 's_H2O' )
11955             IF ( av == 0 )  THEN
11956                found_index = get_index( prtcl, 'H2O' )
11957                DO  i = nxl, nxr
11958                   DO  j = nys, nyn
11959                      DO  k = nzb, nz_do3d
11960                         temp_bin = 0.0_wp
11961                         DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
11962                            temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
11963                         ENDDO
11964                         tend(k,j,i) = temp_bin
11965                      ENDDO
11966                   ENDDO
11967                ENDDO
11968                IF ( .NOT. mask_surface(mid) )  THEN
11969                   DO  i = 1, mask_size_l(mid,1)
11970                      DO  j = 1, mask_size_l(mid,2)
11971                         DO  k = 1, mask_size_l(mid,3)
11972                            local_pf(i,j,k) = tend( mask_k(mid,k), mask_j(mid,j), mask_i(mid,i) )
11973                         ENDDO
11974                      ENDDO
11975                   ENDDO
11976                ELSE
11977                   DO  i = 1, mask_size_l(mid,1)
11978                      DO  j = 1, mask_size_l(mid,2)
11979!
11980!--                      Get k index of the highest terraing surface
11981                         im = mask_i(mid,i)
11982                         jm = mask_j(mid,j)
11983                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
11984                         DO  k = 1, mask_size_l(mid,3)
11985                            kk = MIN( ktt+mask_k(mid,k), nzt+1 )
11986!
11987!--                         Set value if not in building
11988                            IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
11989                               local_pf(i,j,k) = fill_value
11990                            ELSE
11991                               local_pf(i,j,k) =  tend(kk,jm,im)
11992                            ENDIF
11993                         ENDDO
11994                      ENDDO
11995                   ENDDO
11996                ENDIF
11997                resorted = .TRUE.
11998             ELSE
11999                to_be_resorted => s_h2o_av
12000             ENDIF
12001
12002          CASE DEFAULT
12003             found = .FALSE.
12004
12005       END SELECT
12006    ENDIF
12007
12008    IF ( found  .AND.  .NOT. resorted )  THEN
12009       IF ( .NOT. mask_surface(mid) )  THEN
12010!
12011!--       Default masked output
12012          DO  i = 1, mask_size_l(mid,1)
12013             DO  j = 1, mask_size_l(mid,2)
12014                DO  k = 1, mask_size_l(mid,3)
12015                   local_pf(i,j,k) = to_be_resorted( mask_k(mid,k), mask_j(mid,j), mask_i(mid,i) )
12016                ENDDO
12017             ENDDO
12018          ENDDO
12019       ELSE
12020!
12021!--       Terrain-following masked output
12022          DO  i = 1, mask_size_l(mid,1)
12023             DO  j = 1, mask_size_l(mid,2)
12024!--             Get k index of the highest terraing surface
12025                im = mask_i(mid,i)
12026                jm = mask_j(mid,j)
12027                ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_0(:,jm,im), 5 )), DIM = 1 ) - 1
12028                DO  k = 1, mask_size_l(mid,3)
12029                   kk = MIN( ktt+mask_k(mid,k), nzt+1 )
12030!--                Set value if not in building
12031                   IF ( BTEST( wall_flags_0(kk,jm,im), 6 ) )  THEN
12032                      local_pf(i,j,k) = fill_value
12033                   ELSE
12034                      local_pf(i,j,k) = to_be_resorted(kk,jm,im)
12035                   ENDIF
12036                ENDDO
12037             ENDDO
12038          ENDDO
12039       ENDIF
12040    ENDIF
12041
12042 END SUBROUTINE salsa_data_output_mask
12043
12044!------------------------------------------------------------------------------!
12045! Description:
12046! ------------
12047!> Creates index tables for different (aerosol) components
12048!------------------------------------------------------------------------------!
12049 SUBROUTINE component_index_constructor( self, ncomp, nlist, listcomp )
12050
12051    IMPLICIT NONE
12052
12053    INTEGER(iwp) ::  ii  !<
12054    INTEGER(iwp) ::  jj  !<
12055
12056    INTEGER(iwp), INTENT(in) ::  nlist ! < Maximum number of components
12057
12058    INTEGER(iwp), INTENT(inout) ::  ncomp  !< Number of components
12059
12060    CHARACTER(LEN=3), INTENT(in) ::  listcomp(nlist)  !< List cof component names
12061
12062    TYPE(component_index), INTENT(inout) ::  self  !< Object containing the indices of different
12063                                                   !< aerosol components
12064
12065    ncomp = 0
12066
12067    DO WHILE ( listcomp(ncomp+1) /= '  ' .AND. ncomp < nlist )
12068       ncomp = ncomp + 1
12069    ENDDO
12070
12071    self%ncomp = ncomp
12072    ALLOCATE( self%ind(ncomp), self%comp(ncomp) )
12073
12074    DO  ii = 1, ncomp
12075       self%ind(ii) = ii
12076    ENDDO
12077
12078    jj = 1
12079    DO  ii = 1, nlist
12080       IF ( listcomp(ii) == '') CYCLE
12081       self%comp(jj) = listcomp(ii)
12082       jj = jj + 1
12083    ENDDO
12084
12085 END SUBROUTINE component_index_constructor
12086
12087!------------------------------------------------------------------------------!
12088! Description:
12089! ------------
12090!> Gives the index of a component in the component list
12091!------------------------------------------------------------------------------!
12092 INTEGER FUNCTION get_index( self, incomp )
12093
12094    IMPLICIT NONE
12095
12096    CHARACTER(LEN=*), INTENT(in) ::  incomp !< Component name
12097
12098    INTEGER(iwp) ::  ii  !< index
12099
12100    TYPE(component_index), INTENT(in) ::  self  !< Object containing the indices of different
12101                                                !< aerosol components
12102    IF ( ANY( self%comp == incomp ) )  THEN
12103       ii = 1
12104       DO WHILE ( (self%comp(ii) /= incomp) )
12105          ii = ii + 1
12106       ENDDO
12107       get_index = ii
12108    ELSEIF ( incomp == 'H2O' )  THEN
12109       get_index = self%ncomp + 1
12110    ELSE
12111       WRITE( message_string, * ) 'Incorrect component name given!'
12112       CALL message( 'get_index', 'PA0591', 1, 2, 0, 6, 0 )
12113    ENDIF
12114
12115 END FUNCTION get_index
12116
12117!------------------------------------------------------------------------------!
12118! Description:
12119! ------------
12120!> Tells if the (aerosol) component is being used in the simulation
12121!------------------------------------------------------------------------------!
12122 LOGICAL FUNCTION is_used( self, icomp )
12123
12124    IMPLICIT NONE
12125
12126    CHARACTER(LEN=*), INTENT(in) ::  icomp !< Component name
12127
12128    TYPE(component_index), INTENT(in) ::  self  !< Object containing the indices of different
12129                                                !< aerosol components
12130
12131    IF ( ANY(self%comp == icomp) ) THEN
12132       is_used = .TRUE.
12133    ELSE
12134       is_used = .FALSE.
12135    ENDIF
12136
12137 END FUNCTION
12138
12139!------------------------------------------------------------------------------!
12140! Description:
12141! ------------
12142!> Set the lateral and top boundary conditions in case the PALM domain is
12143!> nested offline in a mesoscale model. Further, average boundary data and
12144!> determine mean profiles, further used for correct damping in the sponge
12145!> layer.
12146!------------------------------------------------------------------------------!
12147 SUBROUTINE salsa_nesting_offl_bc
12148
12149    USE control_parameters,                                                                        &
12150        ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r, bc_dirichlet_s, dt_3d,              &
12151               time_since_reference_point
12152
12153    USE indices,                                                                                   &
12154        ONLY:  nbgp, nxl, nxr, nyn, nys, nzb, nzt
12155
12156    IMPLICIT NONE
12157
12158    INTEGER(iwp) ::  i    !< running index x-direction
12159    INTEGER(iwp) ::  ib   !< running index for aerosol number bins
12160    INTEGER(iwp) ::  ic   !< running index for aerosol mass bins
12161    INTEGER(iwp) ::  icc  !< running index for aerosol mass bins
12162    INTEGER(iwp) ::  ig   !< running index for gaseous species
12163    INTEGER(iwp) ::  j    !< running index y-direction
12164    INTEGER(iwp) ::  k    !< running index z-direction
12165
12166    REAL(wp) ::  fac_dt  !< interpolation factor
12167
12168    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_mconc    !< reference profile for aerosol mass
12169    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_mconc_l  !< reference profile for aerosol mass: subdomain
12170    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_nconc    !< reference profile for aerosol number
12171    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_nconc_l  !< reference profile for aerosol_number: subdomain
12172    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_gconc    !< reference profile for gases
12173    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_gconc_l  !< reference profile for gases: subdomain
12174
12175!
12176!-- Skip input if no forcing from larger-scale models is applied.
12177    IF ( .NOT. nesting_offline_salsa )  RETURN
12178!
12179!-- Allocate temporary arrays to compute salsa mean profiles
12180    ALLOCATE( ref_gconc(nzb:nzt+1,1:ngases_salsa), ref_gconc_l(nzb:nzt+1,1:ngases_salsa),          &
12181              ref_mconc(nzb:nzt+1,1:nbins_aerosol*ncomponents_mass),                               &
12182              ref_mconc_l(nzb:nzt+1,1:nbins_aerosol*ncomponents_mass),                             &
12183              ref_nconc(nzb:nzt+1,1:nbins_aerosol), ref_nconc_l(nzb:nzt+1,1:nbins_aerosol) )
12184    ref_gconc   = 0.0_wp
12185    ref_gconc_l = 0.0_wp
12186    ref_mconc   = 0.0_wp
12187    ref_mconc_l = 0.0_wp
12188    ref_nconc   = 0.0_wp
12189    ref_nconc_l = 0.0_wp
12190
12191!
12192!-- Determine interpolation factor and limit it to 1. This is because t+dt can slightly exceed
12193!-- time(tind_p) before boundary data is updated again.
12194    fac_dt = ( time_utc_init + time_since_reference_point -                                        &
12195               salsa_nest_offl%time(salsa_nest_offl%tind) + dt_3d ) /                              &
12196             ( salsa_nest_offl%time(salsa_nest_offl%tind_p) -                                      &
12197               salsa_nest_offl%time(salsa_nest_offl%tind) )
12198    fac_dt = MIN( 1.0_wp, fac_dt )
12199
12200    IF ( bc_dirichlet_l )  THEN
12201       DO  ib = 1, nbins_aerosol
12202          DO  j = nys, nyn
12203             DO  k = nzb+1, nzt
12204                aerosol_number(ib)%conc(k,j,-1) = ( 1.0_wp - fac_dt ) *                            &
12205                                                  salsa_nest_offl%nconc_left(0,k,j,ib) + fac_dt *  &
12206                                                  salsa_nest_offl%nconc_left(1,k,j,ib)
12207             ENDDO
12208             ref_nconc_l(nzb+1:nzt,ib) = ref_nconc_l(nzb+1:nzt,ib) +                               &
12209                                         aerosol_number(ib)%conc(nzb+1:nzt,j,-1)
12210          ENDDO
12211          DO  ic = 1, ncomponents_mass
12212             icc = ( ic-1 ) * nbins_aerosol + ib
12213             DO  j = nys, nyn
12214                DO  k = nzb+1, nzt
12215                   aerosol_mass(icc)%conc(k,j,-1) = ( 1.0_wp - fac_dt ) *                          &
12216                                                    salsa_nest_offl%mconc_left(0,k,j,icc) + fac_dt &
12217                                                    * salsa_nest_offl%mconc_left(1,k,j,icc)
12218                ENDDO
12219                ref_mconc_l(nzb+1:nzt,icc) = ref_mconc_l(nzb+1:nzt,icc) +                          &
12220                                             aerosol_mass(icc)%conc(nzb+1:nzt,j,-1)
12221             ENDDO
12222          ENDDO
12223       ENDDO
12224       IF ( .NOT. salsa_gases_from_chem )  THEN
12225          DO  ig = 1, ngases_salsa
12226             DO  j = nys, nyn
12227                DO  k = nzb+1, nzt
12228                   salsa_gas(ig)%conc(k,j,-1) = ( 1.0_wp - fac_dt ) *                              &
12229                                                salsa_nest_offl%gconc_left(0,k,j,ig) + fac_dt *    &
12230                                                salsa_nest_offl%gconc_left(1,k,j,ig)
12231                ENDDO
12232                ref_gconc_l(nzb+1:nzt,ig) = ref_gconc_l(nzb+1:nzt,ig) +                            &
12233                                            salsa_gas(ig)%conc(nzb+1:nzt,j,-1)
12234             ENDDO
12235          ENDDO
12236       ENDIF
12237    ENDIF
12238
12239    IF ( bc_dirichlet_r )  THEN
12240       DO  ib = 1, nbins_aerosol
12241          DO  j = nys, nyn
12242             DO  k = nzb+1, nzt
12243                aerosol_number(ib)%conc(k,j,nxr+1) = ( 1.0_wp - fac_dt ) *                         &
12244                                                  salsa_nest_offl%nconc_right(0,k,j,ib) + fac_dt * &
12245                                                  salsa_nest_offl%nconc_right(1,k,j,ib)
12246             ENDDO
12247             ref_nconc_l(nzb+1:nzt,ib) = ref_nconc_l(nzb+1:nzt,ib) +                               &
12248                                         aerosol_number(ib)%conc(nzb+1:nzt,j,nxr+1)
12249          ENDDO
12250          DO  ic = 1, ncomponents_mass
12251             icc = ( ic-1 ) * nbins_aerosol + ib
12252             DO  j = nys, nyn
12253                DO  k = nzb+1, nzt
12254                   aerosol_mass(icc)%conc(k,j,nxr+1) = ( 1.0_wp - fac_dt ) *                       &
12255                                                    salsa_nest_offl%mconc_right(0,k,j,icc) + fac_dt&
12256                                                    * salsa_nest_offl%mconc_right(1,k,j,icc)
12257                ENDDO
12258                ref_mconc_l(nzb+1:nzt,icc) = ref_mconc_l(nzb+1:nzt,icc) +                          &
12259                                             aerosol_mass(icc)%conc(nzb+1:nzt,j,nxr+1)
12260             ENDDO
12261          ENDDO
12262       ENDDO
12263       IF ( .NOT. salsa_gases_from_chem )  THEN
12264          DO  ig = 1, ngases_salsa
12265             DO  j = nys, nyn
12266                DO  k = nzb+1, nzt
12267                   salsa_gas(ig)%conc(k,j,nxr+1) = ( 1.0_wp - fac_dt ) *                           &
12268                                                   salsa_nest_offl%gconc_right(0,k,j,ig) + fac_dt *&
12269                                                   salsa_nest_offl%gconc_right(1,k,j,ig)
12270                ENDDO
12271                ref_gconc_l(nzb+1:nzt,ig) = ref_gconc_l(nzb+1:nzt,ig) +                            &
12272                                            salsa_gas(ig)%conc(nzb+1:nzt,j,nxr+1)
12273             ENDDO
12274          ENDDO
12275       ENDIF
12276    ENDIF
12277
12278    IF ( bc_dirichlet_n )  THEN
12279       DO  ib = 1, nbins_aerosol
12280          DO  i = nxl, nxr
12281             DO  k = nzb+1, nzt
12282                aerosol_number(ib)%conc(k,nyn+1,i) = ( 1.0_wp - fac_dt ) *                         &
12283                                                  salsa_nest_offl%nconc_north(0,k,i,ib) + fac_dt * &
12284                                                  salsa_nest_offl%nconc_north(1,k,i,ib)
12285             ENDDO
12286             ref_nconc_l(nzb+1:nzt,ib) = ref_nconc_l(nzb+1:nzt,ib) +                               &
12287                                         aerosol_number(ib)%conc(nzb+1:nzt,nyn+1,i)
12288          ENDDO
12289          DO  ic = 1, ncomponents_mass
12290             icc = ( ic-1 ) * nbins_aerosol + ib
12291             DO  i = nxl, nxr
12292                DO  k = nzb+1, nzt
12293                   aerosol_mass(icc)%conc(k,nyn+1,i) = ( 1.0_wp - fac_dt ) *                       &
12294                                                    salsa_nest_offl%mconc_north(0,k,i,icc) + fac_dt&
12295                                                    * salsa_nest_offl%mconc_north(1,k,i,icc)
12296                ENDDO
12297                ref_mconc_l(nzb+1:nzt,icc) = ref_mconc_l(nzb+1:nzt,icc) +                          &
12298                                             aerosol_mass(icc)%conc(nzb+1:nzt,nyn+1,i)
12299             ENDDO
12300          ENDDO
12301       ENDDO
12302       IF ( .NOT. salsa_gases_from_chem )  THEN
12303          DO  ig = 1, ngases_salsa
12304             DO  i = nxl, nxr
12305                DO  k = nzb+1, nzt
12306                   salsa_gas(ig)%conc(k,nyn+1,i) = ( 1.0_wp - fac_dt ) *                           &
12307                                                   salsa_nest_offl%gconc_north(0,k,i,ig) + fac_dt *&
12308                                                   salsa_nest_offl%gconc_north(1,k,i,ig)
12309                ENDDO
12310                ref_gconc_l(nzb+1:nzt,ig) = ref_gconc_l(nzb+1:nzt,ig) +                            &
12311                                            salsa_gas(ig)%conc(nzb+1:nzt,nyn+1,i)
12312             ENDDO
12313          ENDDO
12314       ENDIF
12315    ENDIF
12316
12317    IF ( bc_dirichlet_s )  THEN
12318       DO  ib = 1, nbins_aerosol
12319          DO  i = nxl, nxr
12320             DO  k = nzb+1, nzt
12321                aerosol_number(ib)%conc(k,-1,i) = ( 1.0_wp - fac_dt ) *                            &
12322                                                  salsa_nest_offl%nconc_south(0,k,i,ib) + fac_dt * &
12323                                                  salsa_nest_offl%nconc_south(1,k,i,ib)
12324             ENDDO
12325             ref_nconc_l(nzb+1:nzt,ib) = ref_nconc_l(nzb+1:nzt,ib) +                               &
12326                                         aerosol_number(ib)%conc(nzb+1:nzt,-1,i)
12327          ENDDO
12328          DO  ic = 1, ncomponents_mass
12329             icc = ( ic-1 ) * nbins_aerosol + ib
12330             DO  i = nxl, nxr
12331                DO  k = nzb+1, nzt
12332                   aerosol_mass(icc)%conc(k,-1,i) = ( 1.0_wp - fac_dt ) *                          &
12333                                                    salsa_nest_offl%mconc_south(0,k,i,icc) + fac_dt&
12334                                                    * salsa_nest_offl%mconc_south(1,k,i,icc)
12335                ENDDO
12336                ref_mconc_l(nzb+1:nzt,icc) = ref_mconc_l(nzb+1:nzt,icc) +                          &
12337                                             aerosol_mass(icc)%conc(nzb+1:nzt,-1,i)
12338             ENDDO
12339          ENDDO
12340       ENDDO
12341       IF ( .NOT. salsa_gases_from_chem )  THEN
12342          DO  ig = 1, ngases_salsa
12343             DO  i = nxl, nxr
12344                DO  k = nzb+1, nzt
12345                   salsa_gas(ig)%conc(k,-1,i) = ( 1.0_wp - fac_dt ) *                              &
12346                                                salsa_nest_offl%gconc_south(0,k,i,ig) + fac_dt *   &
12347                                                salsa_nest_offl%gconc_south(1,k,i,ig)
12348                ENDDO
12349                ref_gconc_l(nzb+1:nzt,ig) = ref_gconc_l(nzb+1:nzt,ig) +                            &
12350                                            salsa_gas(ig)%conc(nzb+1:nzt,-1,i)
12351             ENDDO
12352          ENDDO
12353       ENDIF
12354    ENDIF
12355!
12356!-- Top boundary
12357    DO  ib = 1, nbins_aerosol
12358       DO  i = nxl, nxr
12359          DO  j = nys, nyn
12360             aerosol_number(ib)%conc(nzt+1,j,i) = ( 1.0_wp - fac_dt ) *                            &
12361                                                  salsa_nest_offl%nconc_top(0,j,i,ib) + fac_dt *   &
12362                                                  salsa_nest_offl%nconc_top(1,j,i,ib)
12363             ref_nconc_l(nzt+1,ib) = ref_nconc_l(nzt+1,ib) + aerosol_number(ib)%conc(nzt+1,j,i)
12364          ENDDO
12365       ENDDO
12366       DO  ic = 1, ncomponents_mass
12367          icc = ( ic-1 ) * nbins_aerosol + ib
12368          DO  i = nxl, nxr
12369             DO  j = nys, nyn
12370                aerosol_mass(icc)%conc(nzt+1,j,i) = ( 1.0_wp - fac_dt ) *                          &
12371                                                    salsa_nest_offl%mconc_top(0,j,i,icc) + fac_dt *&
12372                                                    salsa_nest_offl%mconc_top(1,j,i,icc)
12373                ref_mconc_l(nzt+1,icc) = ref_mconc_l(nzt+1,icc) + aerosol_mass(icc)%conc(nzt+1,j,i)
12374             ENDDO
12375          ENDDO
12376       ENDDO
12377    ENDDO
12378    IF ( .NOT. salsa_gases_from_chem )  THEN
12379       DO  ig = 1, ngases_salsa
12380          DO  i = nxl, nxr
12381             DO  j = nys, nyn
12382                salsa_gas(ig)%conc(nzt+1,j,i) = ( 1.0_wp - fac_dt ) *                              &
12383                                                salsa_nest_offl%gconc_top(0,j,i,ig) + fac_dt *     &
12384                                                salsa_nest_offl%gconc_top(1,j,i,ig)
12385                ref_gconc_l(nzt+1,ig) = ref_gconc_l(nzt+1,ig) + salsa_gas(ig)%conc(nzt+1,j,i)
12386             ENDDO
12387          ENDDO
12388       ENDDO
12389    ENDIF
12390!
12391!-- Do local exchange
12392    DO  ib = 1, nbins_aerosol
12393       CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
12394       DO  ic = 1, ncomponents_mass
12395          icc = ( ic-1 ) * nbins_aerosol + ib
12396          CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
12397       ENDDO
12398    ENDDO
12399    IF ( .NOT. salsa_gases_from_chem )  THEN
12400       DO  ig = 1, ngases_salsa
12401          CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
12402       ENDDO
12403    ENDIF
12404!
12405!-- In case of Rayleigh damping, where the initial profiles are still used, update these profiles
12406!-- from the averaged boundary data. But first, average these data.
12407#if defined( __parallel )
12408    IF ( .NOT. salsa_gases_from_chem )                                                             &
12409       CALL MPI_ALLREDUCE( ref_gconc_l, ref_gconc, ( nzt+1-nzb+1 ) * SIZE( ref_gconc(nzb,:) ),     &
12410                           MPI_REAL, MPI_SUM, comm2d, ierr )
12411    CALL MPI_ALLREDUCE( ref_mconc_l, ref_mconc, ( nzt+1-nzb+1 ) * SIZE( ref_mconc(nzb,:) ),        &
12412                        MPI_REAL, MPI_SUM, comm2d, ierr )
12413    CALL MPI_ALLREDUCE( ref_nconc_l, ref_nconc, ( nzt+1-nzb+1 ) * SIZE( ref_nconc(nzb,:) ),        &
12414                        MPI_REAL, MPI_SUM, comm2d, ierr )
12415#else
12416    IF ( .NOT. salsa_gases_from_chem )  ref_gconc = ref_gconc_l
12417    ref_mconc = ref_mconc_l
12418    ref_nconc = ref_nconc_l
12419#endif
12420!
12421!-- Average data. Note, reference profiles up to nzt are derived from lateral boundaries, at the
12422!-- model top it is derived from the top boundary. Thus, number of input data is different from
12423!-- nzb:nzt compared to nzt+1.
12424!-- Derived from lateral boundaries.
12425    IF ( .NOT. salsa_gases_from_chem )                                                             &
12426       ref_gconc(nzb:nzt,:) = ref_gconc(nzb:nzt,:) / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
12427    ref_mconc(nzb:nzt,:) = ref_mconc(nzb:nzt,:) / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
12428    ref_nconc(nzb:nzt,:) = ref_nconc(nzb:nzt,:) / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
12429!
12430!-- Derived from top boundary
12431    IF ( .NOT. salsa_gases_from_chem )                                                             &
12432       ref_gconc(nzt+1,:) = ref_gconc(nzt+1,:) / REAL( ( ny + 1 ) * ( nx + 1 ), KIND = wp )
12433    ref_mconc(nzt+1,:) = ref_mconc(nzt+1,:) / REAL( ( ny + 1 ) * ( nx + 1 ), KIND = wp )
12434    ref_nconc(nzt+1,:) = ref_nconc(nzt+1,:) / REAL( ( ny + 1 ) * ( nx + 1 ), KIND = wp )
12435!
12436!-- Write onto init profiles, which are used for damping. Also set lower boundary condition.
12437    DO  ib = 1, nbins_aerosol
12438       aerosol_number(ib)%init(:)   = ref_nconc(:,ib)
12439       aerosol_number(ib)%init(nzb) = aerosol_number(ib)%init(nzb+1)
12440       DO  ic = 1, ncomponents_mass
12441          icc = ( ic-1 ) * nbins_aerosol + ib
12442          aerosol_mass(icc)%init(:)   = ref_mconc(:,icc)
12443          aerosol_mass(icc)%init(nzb) = aerosol_mass(icc)%init(nzb+1)
12444       ENDDO
12445    ENDDO
12446    IF ( .NOT. salsa_gases_from_chem )  THEN
12447       DO  ig = 1, ngases_salsa
12448          salsa_gas(ig)%init(:)   = ref_gconc(:,ig)
12449          salsa_gas(ig)%init(nzb) = salsa_gas(ig)%init(nzb+1)
12450       ENDDO
12451    ENDIF
12452
12453    DEALLOCATE( ref_gconc, ref_gconc_l, ref_mconc, ref_mconc_l, ref_nconc, ref_nconc_l )
12454
12455 END SUBROUTINE salsa_nesting_offl_bc
12456
12457!------------------------------------------------------------------------------!
12458! Description:
12459! ------------
12460!> Allocate arrays used to read boundary data from NetCDF file and initialize
12461!> boundary data.
12462!------------------------------------------------------------------------------!
12463 SUBROUTINE salsa_nesting_offl_init
12464
12465    USE control_parameters,                                                                        &
12466        ONLY:  end_time, initializing_actions, spinup_time
12467
12468    USE palm_date_time_mod,                                                                        &
12469        ONLY:  get_date_time
12470
12471    IMPLICIT NONE
12472
12473    INTEGER(iwp) ::  ib          !< running index for aerosol number bins
12474    INTEGER(iwp) ::  ic          !< running index for aerosol mass bins
12475    INTEGER(iwp) ::  icc         !< additional running index for aerosol mass bins
12476    INTEGER(iwp) ::  ig          !< running index for gaseous species
12477    INTEGER(iwp) ::  nmass_bins  !< number of aerosol mass bins
12478
12479    nmass_bins = nbins_aerosol * ncomponents_mass
12480!
12481!-- Get time_utc_init from origin_date_time
12482    CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )
12483!
12484!-- Allocate arrays for reading boundary values. Arrays will incorporate 2 time levels in order to
12485!-- interpolate in between.
12486    IF ( nesting_offline_salsa )  THEN
12487       IF ( bc_dirichlet_l )  THEN
12488          ALLOCATE( salsa_nest_offl%nconc_left(0:1,nzb+1:nzt,nys:nyn,1:nbins_aerosol) )
12489          ALLOCATE( salsa_nest_offl%mconc_left(0:1,nzb+1:nzt,nys:nyn,1:nmass_bins) )
12490       ENDIF
12491       IF ( bc_dirichlet_r )  THEN
12492          ALLOCATE( salsa_nest_offl%nconc_right(0:1,nzb+1:nzt,nys:nyn,1:nbins_aerosol) )
12493          ALLOCATE( salsa_nest_offl%mconc_right(0:1,nzb+1:nzt,nys:nyn,1:nmass_bins) )
12494       ENDIF
12495       IF ( bc_dirichlet_n )  THEN
12496          ALLOCATE( salsa_nest_offl%nconc_north(0:1,nzb+1:nzt,nxl:nxr,1:nbins_aerosol) )
12497          ALLOCATE( salsa_nest_offl%mconc_north(0:1,nzb+1:nzt,nxl:nxr,1:nmass_bins) )
12498       ENDIF
12499       IF ( bc_dirichlet_s )  THEN
12500          ALLOCATE( salsa_nest_offl%nconc_south(0:1,nzb+1:nzt,nxl:nxr,1:nbins_aerosol) )
12501          ALLOCATE( salsa_nest_offl%mconc_south(0:1,nzb+1:nzt,nxl:nxr,1:nmass_bins) )
12502       ENDIF
12503       ALLOCATE( salsa_nest_offl%nconc_top(0:1,nys:nyn,nxl:nxr,1:nbins_aerosol) )
12504       ALLOCATE( salsa_nest_offl%mconc_top(0:1,nys:nyn,nxl:nxr,1:nmass_bins) )
12505
12506       IF ( .NOT. salsa_gases_from_chem )  THEN
12507          IF ( bc_dirichlet_l )  THEN
12508             ALLOCATE( salsa_nest_offl%gconc_left(0:1,nzb+1:nzt,nys:nyn,1:ngases_salsa) )
12509          ENDIF
12510          IF ( bc_dirichlet_r )  THEN
12511             ALLOCATE( salsa_nest_offl%gconc_right(0:1,nzb+1:nzt,nys:nyn,1:ngases_salsa) )
12512          ENDIF
12513          IF ( bc_dirichlet_n )  THEN
12514             ALLOCATE( salsa_nest_offl%gconc_north(0:1,nzb+1:nzt,nxl:nxr,1:ngases_salsa) )
12515          ENDIF
12516          IF ( bc_dirichlet_s )  THEN
12517             ALLOCATE( salsa_nest_offl%gconc_south(0:1,nzb+1:nzt,nxl:nxr,1:ngases_salsa) )
12518          ENDIF
12519          ALLOCATE( salsa_nest_offl%gconc_top(0:1,nys:nyn,nxl:nxr,1:ngases_salsa) )
12520       ENDIF
12521
12522!
12523!--    Read data at lateral and top boundaries from a larger-scale model
12524       CALL salsa_nesting_offl_input
12525!
12526!--    Check if sufficient time steps are provided to cover the entire simulation. Note, dynamic
12527!--    input is only required for the 3D simulation, not for the soil/wall spinup. However, as the
12528!--    spinup time is added to the end_time, this must be considered here.
12529       IF ( end_time - spinup_time >                                           &
12530            salsa_nest_offl%time(salsa_nest_offl%nt-1) - time_utc_init )  THEN
12531          message_string = 'end_time of the simulation exceeds the time dimension in the dynamic'//&
12532                           ' input file.'
12533          CALL message( 'salsa_nesting_offl_init', 'PA0681', 1, 2, 0, 6, 0 ) 
12534       ENDIF
12535
12536       IF ( salsa_nest_offl%time(0) /= time_utc_init )  THEN
12537          message_string = 'Offline nesting: time dimension must start at time_utc_init.'
12538          CALL message( 'salsa_nesting_offl_init', 'PA0682', 1, 2, 0, 6, 0 )
12539       ENDIF
12540!
12541!--    Initialize boundary data. Please note, do not initialize boundaries in case of restart runs.
12542       IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.  read_restart_data_salsa )  &
12543       THEN
12544          IF ( bc_dirichlet_l )  THEN
12545             DO  ib = 1, nbins_aerosol
12546                aerosol_number(ib)%conc(nzb+1:nzt,nys:nyn,-1) =                                    &
12547                                                 salsa_nest_offl%nconc_left(0,nzb+1:nzt,nys:nyn,ib)
12548                DO  ic = 1, ncomponents_mass
12549                   icc = ( ic - 1 ) * nbins_aerosol + ib
12550                   aerosol_mass(icc)%conc(nzb+1:nzt,nys:nyn,-1) =                                  &
12551                                                 salsa_nest_offl%mconc_left(0,nzb+1:nzt,nys:nyn,icc)
12552                ENDDO
12553             ENDDO
12554             DO  ig = 1, ngases_salsa
12555                salsa_gas(ig)%conc(nzb+1:nzt,nys:nyn,-1) =                                         &
12556                                                 salsa_nest_offl%gconc_left(0,nzb+1:nzt,nys:nyn,ig)
12557             ENDDO
12558          ENDIF
12559          IF ( bc_dirichlet_r )  THEN
12560             DO  ib = 1, nbins_aerosol
12561                aerosol_number(ib)%conc(nzb+1:nzt,nys:nyn,nxr+1) =                                 &
12562                                                salsa_nest_offl%nconc_right(0,nzb+1:nzt,nys:nyn,ib)
12563                DO  ic = 1, ncomponents_mass
12564                   icc = ( ic - 1 ) * nbins_aerosol + ib
12565                   aerosol_mass(icc)%conc(nzb+1:nzt,nys:nyn,nxr+1) =                               &
12566                                                salsa_nest_offl%mconc_right(0,nzb+1:nzt,nys:nyn,icc)
12567                ENDDO
12568             ENDDO
12569             DO  ig = 1, ngases_salsa
12570                salsa_gas(ig)%conc(nzb+1:nzt,nys:nyn,nxr+1) =                                      &
12571                                                 salsa_nest_offl%gconc_right(0,nzb+1:nzt,nys:nyn,ig)
12572             ENDDO
12573          ENDIF
12574          IF ( bc_dirichlet_n )  THEN
12575             DO  ib = 1, nbins_aerosol
12576                aerosol_number(ib)%conc(nzb+1:nzt,nyn+1,nxl:nxr) =                                 &
12577                                                salsa_nest_offl%nconc_north(0,nzb+1:nzt,nxl:nxr,ib)
12578                DO  ic = 1, ncomponents_mass
12579                   icc = ( ic - 1 ) * nbins_aerosol + ib
12580                   aerosol_mass(icc)%conc(nzb+1:nzt,nyn+1,nxl:nxr) =                               &
12581                                                salsa_nest_offl%mconc_north(0,nzb+1:nzt,nxl:nxr,icc)
12582                ENDDO
12583             ENDDO
12584             DO  ig = 1, ngases_salsa
12585                salsa_gas(ig)%conc(nzb+1:nzt,nyn+1,nxl:nxr) =                                      &
12586                                                 salsa_nest_offl%gconc_north(0,nzb+1:nzt,nxl:nxr,ig)
12587             ENDDO
12588          ENDIF
12589          IF ( bc_dirichlet_s )  THEN
12590             DO  ib = 1, nbins_aerosol
12591                aerosol_number(ib)%conc(nzb+1:nzt,-1,nxl:nxr) =                                    &
12592                                                salsa_nest_offl%nconc_south(0,nzb+1:nzt,nxl:nxr,ib)
12593                DO  ic = 1, ncomponents_mass
12594                   icc = ( ic - 1 ) * nbins_aerosol + ib
12595                   aerosol_mass(icc)%conc(nzb+1:nzt,-1,nxl:nxr) =                                  &
12596                                                salsa_nest_offl%mconc_south(0,nzb+1:nzt,nxl:nxr,icc)
12597                ENDDO
12598             ENDDO
12599             DO  ig = 1, ngases_salsa
12600                salsa_gas(ig)%conc(nzb+1:nzt,-1,nxl:nxr) =                                         &
12601                                                 salsa_nest_offl%gconc_south(0,nzb+1:nzt,nxl:nxr,ig)
12602             ENDDO
12603          ENDIF
12604       ENDIF
12605    ENDIF
12606
12607 END SUBROUTINE salsa_nesting_offl_init
12608
12609!------------------------------------------------------------------------------!
12610! Description:
12611! ------------
12612!> Set the lateral and top boundary conditions in case the PALM domain is
12613!> nested offline in a mesoscale model. Further, average boundary data and
12614!> determine mean profiles, further used for correct damping in the sponge
12615!> layer.
12616!------------------------------------------------------------------------------!
12617 SUBROUTINE salsa_nesting_offl_input
12618
12619    USE netcdf_data_input_mod,                                                                     &
12620        ONLY:  check_existence, close_input_file, get_attribute, get_variable,                     &
12621               inquire_num_variables, inquire_variable_names,                                      &
12622               get_dimension_length, open_read_file
12623
12624    IMPLICIT NONE
12625
12626    CHARACTER(LEN=25) ::  vname  !< variable name
12627
12628    INTEGER(iwp) ::  ic        !< running index for aerosol chemical components
12629    INTEGER(iwp) ::  ig        !< running index for gases
12630    INTEGER(iwp) ::  num_vars  !< number of variables in netcdf input file
12631
12632!
12633!-- Skip input if no forcing from larger-scale models is applied.
12634    IF ( .NOT. nesting_offline_salsa )  RETURN
12635!
12636!-- Initialise
12637    IF ( .NOT. salsa_nest_offl%init )  THEN
12638
12639#if defined ( __netcdf )
12640!
12641!--    Open file in read-only mode
12642       CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ),                   &
12643                            salsa_nest_offl%id_dynamic )
12644!
12645!--    At first, inquire all variable names.
12646       CALL inquire_num_variables( salsa_nest_offl%id_dynamic, num_vars )
12647!
12648!--    Allocate memory to store variable names.
12649       ALLOCATE( salsa_nest_offl%var_names(1:num_vars) )
12650       CALL inquire_variable_names( salsa_nest_offl%id_dynamic, salsa_nest_offl%var_names )
12651!
12652!--    Read time dimension, allocate memory and finally read time array
12653       CALL get_dimension_length( salsa_nest_offl%id_dynamic, salsa_nest_offl%nt,&
12654                                                    'time' )
12655
12656       IF ( check_existence( salsa_nest_offl%var_names, 'time' ) )  THEN
12657          ALLOCATE( salsa_nest_offl%time(0:salsa_nest_offl%nt-1) )
12658          CALL get_variable( salsa_nest_offl%id_dynamic, 'time', salsa_nest_offl%time )
12659       ENDIF
12660!
12661!--    Read the vertical dimension
12662       CALL get_dimension_length( salsa_nest_offl%id_dynamic,                    &
12663                                                    salsa_nest_offl%nzu, 'z' )
12664       ALLOCATE( salsa_nest_offl%zu_atmos(1:salsa_nest_offl%nzu) )
12665       CALL get_variable( salsa_nest_offl%id_dynamic, 'z', salsa_nest_offl%zu_atmos )
12666!
12667!--    Read the number of aerosol chemical components
12668       CALL get_dimension_length( salsa_nest_offl%id_dynamic,                    &
12669                                                    salsa_nest_offl%ncc, 'composition_index' )
12670!
12671!--    Read the names of aerosol chemical components
12672       CALL get_variable( salsa_nest_offl%id_dynamic, 'composition_name', salsa_nest_offl%cc_name, &
12673                          salsa_nest_offl%ncc )
12674!
12675!--    Define the index of each chemical component in the model
12676       DO  ic = 1, salsa_nest_offl%ncc
12677          SELECT CASE ( TRIM( salsa_nest_offl%cc_name(ic) ) )
12678             CASE ( 'H2SO4', 'SO4', 'h2so4', 'so4' )
12679                salsa_nest_offl%cc_in2mod(1) = ic
12680             CASE ( 'OC', 'oc' )
12681                salsa_nest_offl%cc_in2mod(2) = ic
12682             CASE ( 'BC', 'bc' )
12683                salsa_nest_offl%cc_in2mod(3) = ic
12684             CASE ( 'DU', 'du' )
12685                salsa_nest_offl%cc_in2mod(4) = ic
12686             CASE ( 'SS', 'ss' )
12687                salsa_nest_offl%cc_in2mod(5) = ic
12688             CASE ( 'HNO3', 'hno3', 'NO3', 'no3', 'NO', 'no' )
12689                salsa_nest_offl%cc_in2mod(6) = ic
12690             CASE ( 'NH3', 'nh3', 'NH4', 'nh4', 'NH', 'nh' )
12691                salsa_nest_offl%cc_in2mod(7) = ic
12692          END SELECT
12693       ENDDO
12694       IF ( SUM( salsa_nest_offl%cc_in2mod ) == 0 )  THEN
12695          message_string = 'None of the aerosol chemical components in ' //                        &
12696                           TRIM( input_file_dynamic ) // ' correspond to ones applied in SALSA.'
12697          CALL message( 'salsa_mod: salsa_nesting_offl_input',                      &
12698                        'PA0662', 2, 2, 0, 6, 0 )
12699       ENDIF
12700#endif
12701    ENDIF
12702!
12703!-- Check if dynamic driver data input is required.
12704    IF ( salsa_nest_offl%time(salsa_nest_offl%tind_p) <= MAX( time_since_reference_point, 0.0_wp)  &
12705         + time_utc_init  .OR.  .NOT.  salsa_nest_offl%init )  THEN
12706       CONTINUE
12707!
12708!-- Return otherwise
12709    ELSE
12710       RETURN
12711    ENDIF
12712!
12713!-- Obtain time index for current point in time.
12714    salsa_nest_offl%tind = MINLOC( ABS( salsa_nest_offl%time - ( time_utc_init +                   &
12715                                        MAX( time_since_reference_point, 0.0_wp) ) ), DIM = 1 ) - 1
12716    salsa_nest_offl%tind_p = salsa_nest_offl%tind + 1
12717!
12718!-- Open file in read-only mode
12719#if defined ( __netcdf )
12720
12721    CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ),                      &
12722                         salsa_nest_offl%id_dynamic )
12723!
12724!-- Read data at the western boundary
12725    CALL get_variable( salsa_nest_offl%id_dynamic, 'ls_forcing_left_aerosol',                      &
12726                       salsa_nest_offl%nconc_left,                                                 &
12727                       MERGE( 0, 1, bc_dirichlet_l ), MERGE( nbins_aerosol-1, 0, bc_dirichlet_l ), &
12728                       MERGE( nys, 1, bc_dirichlet_l ), MERGE( nyn, 0, bc_dirichlet_l ),           &
12729                       MERGE( nzb, 1, bc_dirichlet_l ), MERGE( nzt-1, 0, bc_dirichlet_l ),         &
12730                       MERGE( salsa_nest_offl%tind,   1, bc_dirichlet_l ),                         &
12731                       MERGE( salsa_nest_offl%tind_p, 0, bc_dirichlet_l  ) )
12732    IF ( bc_dirichlet_l )  THEN
12733       salsa_nest_offl%nconc_left = MAX( nclim, salsa_nest_offl%nconc_left )
12734       CALL nesting_offl_aero_mass( salsa_nest_offl%tind, salsa_nest_offl%tind_p, nzb+1, nzt, nys, &
12735                                    nyn, 'ls_forcing_left_mass_fracs_a', 1 )
12736    ENDIF
12737    IF ( .NOT. salsa_gases_from_chem )  THEN
12738       DO  ig = 1, ngases_salsa
12739          vname = salsa_nest_offl%char_l // salsa_nest_offl%gas_name(ig)
12740          CALL get_variable( salsa_nest_offl%id_dynamic, TRIM( vname ),                            &
12741                             salsa_nest_offl%gconc_left(:,:,:,ig),                                 &
12742                             MERGE( nys, 1, bc_dirichlet_l ), MERGE( nyn, 0, bc_dirichlet_l ),     &
12743                             MERGE( nzb, 1, bc_dirichlet_l ), MERGE( nzt-1, 0, bc_dirichlet_l ),   &
12744                             MERGE( salsa_nest_offl%tind,   1, bc_dirichlet_l ),                   &
12745                             MERGE( salsa_nest_offl%tind_p, 0, bc_dirichlet_l ) )
12746          IF ( bc_dirichlet_l )  salsa_nest_offl%gconc_left(:,:,:,ig) =                            &
12747                                                  MAX( nclim, salsa_nest_offl%gconc_left(:,:,:,ig) )
12748       ENDDO
12749    ENDIF
12750!
12751!-- Read data at the eastern boundary
12752    CALL get_variable( salsa_nest_offl%id_dynamic, 'ls_forcing_right_aerosol',                     &
12753                       salsa_nest_offl%nconc_right,                                                &
12754                       MERGE( 0, 1, bc_dirichlet_r ), MERGE( nbins_aerosol-1, 0, bc_dirichlet_r ), &
12755                       MERGE( nys, 1, bc_dirichlet_r ), MERGE( nyn, 0, bc_dirichlet_r ),           &
12756                       MERGE( nzb, 1, bc_dirichlet_r ), MERGE( nzt-1, 0, bc_dirichlet_r ),         &
12757                       MERGE( salsa_nest_offl%tind,   1, bc_dirichlet_r ),                         &
12758                       MERGE( salsa_nest_offl%tind_p, 0, bc_dirichlet_r ) )
12759    IF ( bc_dirichlet_r )  THEN
12760       salsa_nest_offl%nconc_right = MAX( nclim, salsa_nest_offl%nconc_right )
12761       CALL nesting_offl_aero_mass( salsa_nest_offl%tind, salsa_nest_offl%tind_p, nzb+1, nzt, nys, &
12762                                    nyn, 'ls_forcing_right_mass_fracs_a', 2 )
12763    ENDIF
12764    IF ( .NOT. salsa_gases_from_chem )  THEN
12765       DO  ig = 1, ngases_salsa
12766          vname = salsa_nest_offl%char_r // salsa_nest_offl%gas_name(ig)
12767          CALL get_variable( salsa_nest_offl%id_dynamic, TRIM( vname ),                            &
12768                             salsa_nest_offl%gconc_right(:,:,:,ig),                                &
12769                             MERGE( nys, 1, bc_dirichlet_r ), MERGE( nyn, 0, bc_dirichlet_r ),     &
12770                             MERGE( nzb, 1, bc_dirichlet_r ), MERGE( nzt-1, 0, bc_dirichlet_r ),   &
12771                             MERGE( salsa_nest_offl%tind,   1, bc_dirichlet_r ),                   &
12772                             MERGE( salsa_nest_offl%tind_p, 0, bc_dirichlet_r ) )
12773          IF ( bc_dirichlet_r )  salsa_nest_offl%gconc_right(:,:,:,ig) =                           &
12774                                                 MAX( nclim, salsa_nest_offl%gconc_right(:,:,:,ig) )
12775       ENDDO
12776    ENDIF
12777!
12778!-- Read data at the northern boundary
12779    CALL get_variable( salsa_nest_offl%id_dynamic, 'ls_forcing_north_aerosol',                     &
12780                       salsa_nest_offl%nconc_north,                                                &
12781                       MERGE( 0, 1, bc_dirichlet_n ), MERGE( nbins_aerosol-1, 0, bc_dirichlet_n ), &
12782                       MERGE( nxl, 1, bc_dirichlet_n ), MERGE( nxr, 0, bc_dirichlet_n ),           &
12783                       MERGE( nzb, 1, bc_dirichlet_n ), MERGE( nzt-1, 0, bc_dirichlet_n ),         &
12784                       MERGE( salsa_nest_offl%tind,   1, bc_dirichlet_n ),                         &
12785                       MERGE( salsa_nest_offl%tind_p, 0, bc_dirichlet_n ) )
12786    IF ( bc_dirichlet_n )  THEN
12787       salsa_nest_offl%nconc_north = MAX( nclim, salsa_nest_offl%nconc_north )
12788       CALL nesting_offl_aero_mass( salsa_nest_offl%tind, salsa_nest_offl%tind_p, nzb+1, nzt, nxl, &
12789                                    nxr, 'ls_forcing_north_mass_fracs_a', 3 )
12790    ENDIF
12791    IF ( .NOT. salsa_gases_from_chem )  THEN
12792       DO  ig = 1, ngases_salsa
12793          vname = salsa_nest_offl%char_n // salsa_nest_offl%gas_name(ig)
12794          CALL get_variable( salsa_nest_offl%id_dynamic, TRIM( vname ),                            &
12795                             salsa_nest_offl%gconc_north(:,:,:,ig),                                &
12796                             MERGE( nxl, 1, bc_dirichlet_n ), MERGE( nxr, 0, bc_dirichlet_n ),     &
12797                             MERGE( nzb, 1, bc_dirichlet_n ), MERGE( nzt-1, 0, bc_dirichlet_n ),   &
12798                             MERGE( salsa_nest_offl%tind,   1, bc_dirichlet_n ),                   &
12799                             MERGE( salsa_nest_offl%tind_p, 0, bc_dirichlet_n ) )
12800          IF ( bc_dirichlet_n )  salsa_nest_offl%gconc_north(:,:,:,ig) =                           &
12801                                                 MAX( nclim, salsa_nest_offl%gconc_north(:,:,:,ig) )
12802       ENDDO
12803    ENDIF
12804!
12805!-- Read data at the southern boundary
12806    CALL get_variable( salsa_nest_offl%id_dynamic, 'ls_forcing_south_aerosol',                     &
12807                       salsa_nest_offl%nconc_south,                                                &
12808                       MERGE( 0, 1, bc_dirichlet_s ), MERGE( nbins_aerosol-1, 0, bc_dirichlet_s ), &
12809                       MERGE( nxl, 1, bc_dirichlet_s ), MERGE( nxr, 0, bc_dirichlet_s ),           &
12810                       MERGE( nzb, 1, bc_dirichlet_s ), MERGE( nzt-1, 0, bc_dirichlet_s ),         &
12811                       MERGE( salsa_nest_offl%tind,   1, bc_dirichlet_s ),                         &
12812                       MERGE( salsa_nest_offl%tind_p, 0, bc_dirichlet_s ) )
12813    IF ( bc_dirichlet_s )  THEN
12814       salsa_nest_offl%nconc_south = MAX( nclim, salsa_nest_offl%nconc_south )
12815       CALL nesting_offl_aero_mass( salsa_nest_offl%tind, salsa_nest_offl%tind_p, nzb+1, nzt, nxl, &
12816                                    nxr, 'ls_forcing_south_mass_fracs_a', 4 )
12817    ENDIF
12818    IF ( .NOT. salsa_gases_from_chem )  THEN
12819       DO  ig = 1, ngases_salsa
12820          vname = salsa_nest_offl%char_s // salsa_nest_offl%gas_name(ig)
12821          CALL get_variable( salsa_nest_offl%id_dynamic, TRIM( vname ),                            &
12822                             salsa_nest_offl%gconc_south(:,:,:,ig),                                &
12823                             MERGE( nxl, 1, bc_dirichlet_s ), MERGE( nxr, 0, bc_dirichlet_s ),     &
12824                             MERGE( nzb, 1, bc_dirichlet_s ), MERGE( nzt-1, 0, bc_dirichlet_s ),   &
12825                             MERGE( salsa_nest_offl%tind,   1, bc_dirichlet_s ),                   &
12826                             MERGE( salsa_nest_offl%tind_p, 0, bc_dirichlet_s ) )
12827          IF ( bc_dirichlet_s )  salsa_nest_offl%gconc_south(:,:,:,ig) =                           &
12828                                                 MAX( nclim, salsa_nest_offl%gconc_south(:,:,:,ig) )
12829       ENDDO
12830    ENDIF
12831!
12832!-- Read data at the top boundary
12833    CALL get_variable( salsa_nest_offl%id_dynamic, 'ls_forcing_top_aerosol',                       &
12834                       salsa_nest_offl%nconc_top(0:1,nys:nyn,nxl:nxr,1:nbins_aerosol),             &
12835                       0, nbins_aerosol-1, nxl, nxr, nys, nyn, salsa_nest_offl%tind,               &
12836                       salsa_nest_offl%tind_p )
12837    salsa_nest_offl%nconc_top = MAX( nclim, salsa_nest_offl%nconc_top )
12838    CALL nesting_offl_aero_mass( salsa_nest_offl%tind, salsa_nest_offl%tind_p, nys, nyn, nxl, nxr, &
12839                                 'ls_forcing_top_mass_fracs_a', 5 )
12840    IF ( .NOT. salsa_gases_from_chem )  THEN
12841       DO  ig = 1, ngases_salsa
12842          vname = salsa_nest_offl%char_t // salsa_nest_offl%gas_name(ig)
12843          CALL get_variable( salsa_nest_offl%id_dynamic, TRIM( vname ),                            &
12844                             salsa_nest_offl%gconc_top(:,:,:,ig), nxl, nxr, nys, nyn,              &
12845                             salsa_nest_offl%tind, salsa_nest_offl%tind_p )
12846          salsa_nest_offl%gconc_top(:,:,:,ig) = MAX( nclim, salsa_nest_offl%gconc_top(:,:,:,ig) )
12847       ENDDO
12848    ENDIF
12849!
12850!-- Close input file
12851    CALL close_input_file( salsa_nest_offl%id_dynamic )
12852
12853#endif
12854!
12855!-- Set control flag to indicate that initialization is already done
12856    salsa_nest_offl%init = .TRUE.
12857
12858 END SUBROUTINE salsa_nesting_offl_input
12859
12860!------------------------------------------------------------------------------!
12861! Description:
12862! ------------
12863!> Sets the mass concentrations to aerosol arrays in 2a and 2b.
12864!------------------------------------------------------------------------------!
12865 SUBROUTINE nesting_offl_aero_mass( ts, te, ks, ke, is, ie, varname_a, ibound )
12866
12867    USE netcdf_data_input_mod,                                                                     &
12868        ONLY:  get_variable
12869
12870    IMPLICIT NONE
12871
12872    CHARACTER(LEN=25) ::  varname_b  !< name for bins b
12873
12874    CHARACTER(LEN=*), INTENT(in) ::  varname_a  !< name for bins a
12875
12876    INTEGER(iwp) ::  ee                !< loop index: end
12877    INTEGER(iwp) ::  i                 !< loop index
12878    INTEGER(iwp) ::  ib                !< loop index
12879    INTEGER(iwp) ::  ic                !< loop index
12880    INTEGER(iwp) ::  k                 !< loop index
12881    INTEGER(iwp) ::  ss                !< loop index: start
12882    INTEGER(iwp) ::  t                 !< loop index
12883    INTEGER(iwp) ::  type_so4_oc = -1  !<
12884
12885    INTEGER(iwp), INTENT(in) ::  ibound  !< index: 1=left, 2=right, 3=north, 4=south, 5=top
12886    INTEGER(iwp), INTENT(in) ::  ie      !< loop index
12887    INTEGER(iwp), INTENT(in) ::  is      !< loop index
12888    INTEGER(iwp), INTENT(in) ::  ks      !< loop index
12889    INTEGER(iwp), INTENT(in) ::  ke      !< loop index
12890    INTEGER(iwp), INTENT(in) ::  ts      !< loop index
12891    INTEGER(iwp), INTENT(in) ::  te      !< loop index
12892
12893    INTEGER(iwp), DIMENSION(maxspec) ::  cc_i2m   !<
12894
12895    REAL(wp) ::  pmf1a !< mass fraction in 1a
12896
12897    REAL(wp), DIMENSION(nbins_aerosol) ::  core   !< size of the bin mid aerosol particle
12898
12899    REAL(wp), DIMENSION(0:1,ks:ke,is:ie,1:nbins_aerosol) ::  to_nconc                   !<
12900    REAL(wp), DIMENSION(0:1,ks:ke,is:ie,1:nbins_aerosol*ncomponents_mass) ::  to_mconc  !<
12901
12902    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mf2a !< Mass distributions for a
12903    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mf2b !< and b bins
12904
12905!
12906!-- Variable name for insoluble mass fraction
12907    varname_b = varname_a(1:LEN( TRIM( varname_a ) ) - 1 ) // 'b'
12908!
12909!-- Bin mean aerosol particle volume (m3)
12910    core(1:nbins_aerosol) = api6 * aero(1:nbins_aerosol)%dmid**3
12911!
12912!-- Allocate and read mass fraction arrays
12913    ALLOCATE( mf2a(0:1,ks:ke,is:ie,1:salsa_nest_offl%ncc),                                         &
12914              mf2b(0:1,ks:ke,is:ie,1:salsa_nest_offl%ncc) )
12915    IF ( ibound == 5 )  THEN
12916       CALL get_variable( salsa_nest_offl%id_dynamic, varname_a,                                   &
12917                          mf2a(0:1,ks:ke,is:ie,1:salsa_nest_offl%ncc), 0, salsa_nest_offl%ncc-1,   &
12918                          is, ie, ks, ke, ts, te )
12919    ELSE
12920       CALL get_variable( salsa_nest_offl%id_dynamic, varname_a,                                   &
12921                          mf2a(0:1,ks:ke,is:ie,1:salsa_nest_offl%ncc), 0, salsa_nest_offl%ncc-1,   &
12922                          is, ie, ks-1, ke-1, ts, te )
12923    ENDIF
12924!
12925!-- If the chemical component is not activated, set its mass fraction to 0 to avoid mass inbalance
12926    cc_i2m = salsa_nest_offl%cc_in2mod
12927    IF ( index_so4 < 0  .AND. cc_i2m(1) > 0 )  mf2a(:,:,:,cc_i2m(1)) = 0.0_wp
12928    IF ( index_oc < 0   .AND. cc_i2m(2) > 0 )  mf2a(:,:,:,cc_i2m(2)) = 0.0_wp
12929    IF ( index_bc < 0   .AND. cc_i2m(3) > 0 )  mf2a(:,:,:,cc_i2m(3)) = 0.0_wp
12930    IF ( index_du < 0   .AND. cc_i2m(4) > 0 )  mf2a(:,:,:,cc_i2m(4)) = 0.0_wp
12931    IF ( index_ss < 0   .AND. cc_i2m(5) > 0 )  mf2a(:,:,:,cc_i2m(5)) = 0.0_wp
12932    IF ( index_no < 0   .AND. cc_i2m(6) > 0 )  mf2a(:,:,:,cc_i2m(6)) = 0.0_wp
12933    IF ( index_nh < 0   .AND. cc_i2m(7) > 0 )  mf2a(:,:,:,cc_i2m(7)) = 0.0_wp
12934    mf2b = 0.0_wp
12935!
12936!-- Initialise variable type_so4_oc to indicate whether SO4 and/OC is included in mass fraction data
12937    IF ( ( cc_i2m(1) > 0  .AND.  index_so4 > 0 )  .AND. ( cc_i2m(2) > 0  .AND.  index_oc > 0 ) )   &
12938    THEN
12939       type_so4_oc = 1
12940    ELSEIF ( cc_i2m(1) > 0  .AND.  index_so4 > 0 )  THEN
12941       type_so4_oc = 2
12942    ELSEIF ( cc_i2m(2) > 0  .AND.  index_oc > 0 )  THEN
12943       type_so4_oc = 3
12944    ENDIF
12945
12946    SELECT CASE ( ibound )
12947       CASE( 1 )
12948          to_nconc = salsa_nest_offl%nconc_left
12949          to_mconc = salsa_nest_offl%mconc_left
12950       CASE( 2 )
12951          to_nconc = salsa_nest_offl%nconc_right
12952          to_mconc = salsa_nest_offl%mconc_right
12953       CASE( 3 )
12954          to_nconc = salsa_nest_offl%nconc_north
12955          to_mconc = salsa_nest_offl%mconc_north
12956       CASE( 4 )
12957          to_nconc = salsa_nest_offl%nconc_south
12958          to_mconc = salsa_nest_offl%mconc_south
12959       CASE( 5 )
12960          to_nconc = salsa_nest_offl%nconc_top
12961          to_mconc = salsa_nest_offl%mconc_top
12962    END SELECT
12963!
12964!-- Set mass concentrations:
12965!
12966!-- Regime 1:
12967    SELECT CASE ( type_so4_oc )
12968       CASE ( 1 )  ! Both SO4 and OC given
12969
12970          ss = ( index_so4 - 1 ) * nbins_aerosol + start_subrange_1a  ! start
12971          ee = ( index_so4 - 1 ) * nbins_aerosol + end_subrange_1a    ! end
12972          ib = start_subrange_1a
12973          DO  ic = ss, ee
12974             DO i = is, ie
12975                DO k = ks, ke
12976                   DO t = 0, 1
12977                      pmf1a = mf2a(t,k,i,cc_i2m(1)) / ( mf2a(t,k,i,cc_i2m(1)) + mf2a(t,k,i,cc_i2m(2)) )
12978                      to_mconc(t,k,i,ic) = pmf1a * to_nconc(t,k,i,ib) * core(ib) * arhoh2so4
12979                   ENDDO
12980                ENDDO
12981             ENDDO
12982             ib = ib + 1
12983          ENDDO
12984          ss = ( index_oc - 1 ) * nbins_aerosol + start_subrange_1a ! start
12985          ee = ( index_oc - 1 ) * nbins_aerosol + end_subrange_1a   ! end
12986          ib = start_subrange_1a
12987          DO  ic = ss, ee
12988             DO i = is, ie
12989                DO k = ks, ke
12990                   DO t = 0, 1
12991                      pmf1a = mf2a(t,k,i,cc_i2m(2)) / ( mf2a(t,k,i,cc_i2m(1)) + mf2a(t,k,i,cc_i2m(2)) )
12992                      to_mconc(t,k,i,ic) = pmf1a * to_nconc(t,k,i,ib) * core(ib) * arhooc
12993                   ENDDO
12994                ENDDO
12995             ENDDO
12996             ib = ib + 1
12997          ENDDO
12998       CASE ( 2 )  ! Only SO4
12999          ss = ( index_so4 - 1 ) * nbins_aerosol + start_subrange_1a  ! start
13000          ee = ( index_so4 - 1 ) * nbins_aerosol + end_subrange_1a    ! end
13001          ib = start_subrange_1a
13002          DO  ic = ss, ee
13003             DO i = is, ie
13004                DO k = ks, ke
13005                   DO t = 0, 1
13006                      to_mconc(t,k,i,ic) = to_nconc(t,k,i,ib) * core(ib) * arhoh2so4
13007                   ENDDO
13008                ENDDO
13009             ENDDO
13010             ib = ib + 1
13011          ENDDO
13012       CASE ( 3 )  ! Only OC
13013          ss = ( index_oc - 1 ) * nbins_aerosol + start_subrange_1a ! start
13014          ee = ( index_oc - 1 ) * nbins_aerosol + end_subrange_1a   ! end
13015          ib = start_subrange_1a
13016          DO  ic = ss, ee
13017             DO i = is, ie
13018                DO k = ks, ke
13019                   DO t = 0, 1
13020                      to_mconc(t,k,i,ic) = to_nconc(t,k,i,ib) * core(ib) * arhooc
13021                   ENDDO
13022                ENDDO
13023             ENDDO
13024             ib = ib + 1
13025          ENDDO
13026    END SELECT
13027!
13028!-- Regimes 2a and 2b:
13029    IF ( index_so4 > 0 ) THEN
13030       CALL set_nest_mass( index_so4, 1, arhoh2so4 )
13031    ENDIF
13032    IF ( index_oc > 0 ) THEN
13033       CALL set_nest_mass( index_oc, 2, arhooc )
13034    ENDIF
13035    IF ( index_bc > 0 ) THEN
13036       CALL set_nest_mass( index_bc, 3, arhobc )
13037    ENDIF
13038    IF ( index_du > 0 ) THEN
13039       CALL set_nest_mass( index_du, 4, arhodu )
13040    ENDIF
13041    IF ( index_ss > 0 ) THEN
13042       CALL set_nest_mass( index_ss, 5, arhoss )
13043    ENDIF
13044    IF ( index_no > 0 ) THEN
13045       CALL set_nest_mass( index_no, 6, arhohno3 )
13046    ENDIF
13047    IF ( index_nh > 0 ) THEN
13048       CALL set_nest_mass( index_nh, 7, arhonh3 )
13049    ENDIF
13050
13051    DEALLOCATE( mf2a, mf2b )
13052
13053    SELECT CASE ( ibound )
13054       CASE( 1 )
13055          salsa_nest_offl%mconc_left = to_mconc
13056       CASE( 2 )
13057          salsa_nest_offl%mconc_right = to_mconc
13058       CASE( 3 )
13059          salsa_nest_offl%mconc_north = to_mconc
13060       CASE( 4 )
13061          salsa_nest_offl%mconc_south = to_mconc
13062       CASE( 5 )
13063          salsa_nest_offl%mconc_top = to_mconc
13064    END SELECT
13065
13066    CONTAINS
13067
13068!------------------------------------------------------------------------------!
13069! Description:
13070! ------------
13071!> Set nesting boundaries for aerosol mass.
13072!------------------------------------------------------------------------------!
13073    SUBROUTINE set_nest_mass( ispec, ispec_def, prho )
13074
13075       IMPLICIT NONE
13076
13077       INTEGER(iwp) ::  ic   !< chemical component index: default
13078       INTEGER(iwp) ::  icc  !< loop index: mass bin
13079
13080       INTEGER(iwp), INTENT(in) ::  ispec      !< aerosol species index
13081       INTEGER(iwp), INTENT(in) ::  ispec_def  !< default aerosol species index
13082
13083       REAL(wp), INTENT(in) ::  prho !< aerosol density
13084!
13085!--    Define the index of the chemical component in the input data
13086       ic = salsa_nest_offl%cc_in2mod(ispec_def)
13087
13088       DO i = is, ie
13089          DO k = ks, ke
13090             DO t = 0, 1
13091!
13092!--             Regime 2a:
13093                ss = ( ispec - 1 ) * nbins_aerosol + start_subrange_2a
13094                ee = ( ispec - 1 ) * nbins_aerosol + end_subrange_2a
13095                ib = start_subrange_2a
13096                DO icc = ss, ee
13097                   to_mconc(t,k,i,icc) = MAX( 0.0_wp, mf2a(t,k,i,ic) / SUM( mf2a(t,k,i,:) ) ) *    &
13098                                         to_nconc(t,k,i,ib) * core(ib) * prho
13099                   ib = ib + 1
13100                ENDDO
13101!
13102!--             Regime 2b:
13103                IF ( .NOT. no_insoluble )  THEN
13104!
13105!--                 TODO!
13106                    mf2b(t,k,i,ic) = mf2b(t,k,i,ic)
13107                ENDIF
13108             ENDDO   ! k
13109
13110          ENDDO   ! j
13111       ENDDO   ! i
13112
13113    END SUBROUTINE set_nest_mass
13114
13115 END SUBROUTINE nesting_offl_aero_mass
13116
13117
13118 END MODULE salsa_mod
Note: See TracBrowser for help on using the repository browser.