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

Last change on this file since 4416 was 4416, checked in by monakurppa, 4 years ago

Bug fixes in restart and reformatting av data output

  • add missing arrays (averaged data output) in salsa_wrd_local and salsa_rrd_local
  • set write_binary_salsa and read_restart_data_salsa to .T. by default
  • restructure the average arrays for gases and total mass concentrations of chemical components: set to 4d arrays instead of separate arrays
  • add allocation checks for averaged data output arrays
  • Property svn:keywords set to Id
File size: 601.4 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-2020 Leibniz Universitaet Hannover
19!--------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23! Bug fixes and reformatting for the restart data and averaged data output
24! - add missing arrays (averaged data output) in salsa_wrd_local and
25!   salsa_rrd_local
26! - set write_binary_salsa and read_restart_data_salsa to .T. by default
27! - restructure the average arrays for gases and total mass concentrations of
28!   chemical components: set to 4d arrays instead of separate arrays
29! - add allocation checks for averaged data output arrays
30!
31! Former revisions:
32! -----------------
33! $Id: salsa_mod.f90 4416 2020-02-20 17:53:57Z monakurppa $
34! Time index error in salsa_emission_setup
35!
36! 4380 2020-01-17 23:39:51Z monakurppa
37! - Error in saving the surface fluxes in an array that is applied in the
38!   deposition scheme
39! - Corrections in the header: aerosol bin diameters and lower bin limits not
40!   printed correctly
41!
42! 4364 2020-01-08 02:12:31Z monakurppa
43! Set time coordinate in the input data relative to origin_time rather than to
44! 00:00:00 UTC
45!
46! 4360 2020-01-07 11:25:50Z suehring
47! Introduction of wall_flags_total_0, which currently sets bits based on static
48! topography information used in wall_flags_static_0
49!
50! 4342 2019-12-16 13:49:14Z Giersch
51! cdc replaced by canopy_drag_coeff
52!
53! 4329 2019-12-10 15:46:36Z motisi
54! Renamed wall_flags_0 to wall_flags_static_0
55!
56! 4315 2019-12-02 09:20:07Z monakurppa
57! Add an additional check for the time dimension PIDS_SALSA in
58! salsa_emission_setup and correct some error message identifiers.
59!
60! 4298 2019-11-21 15:59:16Z suehring
61! Bugfix, close netcdf input files after reading
62!
63! 4295 2019-11-14 06:15:31Z monakurppa
64!
65!
66! 4280 2019-10-29 14:34:15Z monakurppa
67! Corrected a bug in boundary conditions and fac_dt in offline nesting
68!
69! 4273 2019-10-24 13:40:54Z monakurppa
70! - Rename nest_salsa to nesting_salsa
71! - Correct some errors in boundary condition flags
72! - Add a check for not trying to output gas concentrations in salsa if the
73!   chemistry module is applied
74! - Set the default value of nesting_salsa and nesting_offline_salsa to .TRUE.
75!
76! 4272 2019-10-23 15:18:57Z schwenkel
77! Further modularization of boundary conditions: moved boundary conditions to
78! respective modules
79!
80! 4270 2019-10-23 10:46:20Z monakurppa
81! - Implement offline nesting for salsa
82! - Alphabetic ordering for module interfaces
83! - Remove init_aerosol_type and init_gases_type from salsa_parin and define them
84!   based on the initializing_actions
85! - parameter definition removed from "season" and "season_z01" is added to parin
86! - bugfix in application of index_hh after implementing the new
87!   palm_date_time_mod
88! - Reformat salsa emission data with LOD=2: size distribution given for each
89!   emission category
90!
91! 4268 2019-10-17 11:29:38Z schwenkel
92! Moving module specific boundary conditions from time_integration to module
93!
94! 4256 2019-10-07 10:08:52Z monakurppa
95! Document previous changes: use global variables nx, ny and nz in salsa_header
96!
97! 4227 2019-09-10 18:04:34Z gronemeier
98! implement new palm_date_time_mod
99!
100! 4226 2019-09-10 17:03:24Z suehring
101! Netcdf input routine for dimension length renamed
102!
103! 4182 2019-08-22 15:20:23Z scharf
104! Corrected "Former revisions" section
105!
106! 4167 2019-08-16 11:01:48Z suehring
107! Changed behaviour of masked output over surface to follow terrain and ignore
108! buildings (J.Resler, T.Gronemeier)
109!
110! 4131 2019-08-02 11:06:18Z monakurppa
111! - Add "salsa_" before each salsa output variable
112! - Add a possibility to output the number (salsa_N_UFP) and mass concentration
113!   (salsa_PM0.1) of ultrafine particles, i.e. particles with a diameter smaller
114!   than 100 nm
115! - Implement aerosol emission mode "parameterized" which is based on the street
116!   type (similar to the chemistry module).
117! - Remove unnecessary nucleation subroutines.
118! - Add the z-dimension for gaseous emissions to correspond the implementation
119!   in the chemistry module
120!
121! 4118 2019-07-25 16:11:45Z suehring
122! - When Dirichlet condition is applied in decycling, the boundary conditions are
123!   only set at the ghost points and not at the prognostic grid points as done
124!   before
125! - Rename decycle_ns/lr to decycle_salsa_ns/lr and decycle_method to
126!   decycle_method_salsa
127! - Allocation and initialization of special advection flags salsa_advc_flags_s
128!   used for salsa. These are exclusively used for salsa variables to
129!   distinguish from the usually-used flags which might be different when
130!   decycling is applied in combination with cyclic boundary conditions.
131!   Moreover, salsa_advc_flags_s considers extended zones around buildings where
132!   the first-order upwind scheme is applied for the horizontal advection terms.
133!   This is done to overcome high concentration peaks due to stationary numerical
134!   oscillations caused by horizontal advection discretization.
135!
136! 4117 2019-07-25 08:54:02Z monakurppa
137! Pass integer flag array as well as boundary flags to WS scalar advection
138! routine
139!
140! 4109 2019-07-22 17:00:34Z suehring
141! Slightly revise setting of boundary conditions at horizontal walls, use
142! data-structure offset index instead of pre-calculate it for each facing
143!
144! 4079 2019-07-09 18:04:41Z suehring
145! Application of monotonic flux limiter for the vertical scalar advection
146! up to the topography top (only for the cache-optimized version at the
147! moment).
148!
149! 4069 2019-07-01 14:05:51Z Giersch
150! Masked output running index mid has been introduced as a local variable to
151! avoid runtime error (Loop variable has been modified) in time_integration
152!
153! 4058 2019-06-27 15:25:42Z knoop
154! Bugfix: to_be_resorted was uninitialized in case of s_H2O in 3d_data_averaging
155!
156! 4012 2019-05-31 15:19:05Z monakurppa
157! Merge salsa branch to trunk. List of changes:
158! - Error corrected in distr_update that resulted in the aerosol number size
159!   distribution not converging if the concentration was nclim.
160! - Added a separate output for aerosol liquid water (s_H2O)
161! - aerosol processes for a size bin are now calculated only if the aerosol
162!   number of concentration of that bin is > 2*nclim
163! - An initialisation error in the subroutine "deposition" corrected and the
164!   subroutine reformatted.
165! - stuff from salsa_util_mod.f90 moved into salsa_mod.f90
166! - calls for closing the netcdf input files added
167!
168! 3956 2019-05-07 12:32:52Z monakurppa
169! - Conceptual bug in depo_surf correct for urban and land surface model
170! - Subroutine salsa_tendency_ij optimized.
171! - Interfaces salsa_non_advective_processes and salsa_exchange_horiz_bounds
172!   created. These are now called in module_interface.
173!   salsa_exchange_horiz_bounds after calling salsa_driver only when needed
174!   (i.e. every dt_salsa).
175!
176! 3924 2019-04-23 09:33:06Z monakurppa
177! Correct a bug introduced by the previous update.
178!
179! 3899 2019-04-16 14:05:27Z monakurppa
180! - remove unnecessary error / location messages
181! - corrected some error message numbers
182! - allocate source arrays only if emissions or dry deposition is applied.
183!
184! 3885 2019-04-11 11:29:34Z kanani
185! Changes related to global restructuring of location messages and introduction
186! of additional debug messages
187!
188! 3876 2019-04-08 18:41:49Z knoop
189! Introduced salsa_actions module interface
190!
191! 3871 2019-04-08 14:38:39Z knoop
192! Major changes in formatting, performance and data input structure (see branch
193! the history for details)
194! - Time-dependent emissions enabled: lod=1 for yearly PM emissions that are
195!   normalised depending on the time, and lod=2 for preprocessed emissions
196!   (similar to the chemistry module).
197! - Additionally, 'uniform' emissions allowed. This emission is set constant on
198!   all horisontal upward facing surfaces and it is created based on parameters
199!   surface_aerosol_flux, aerosol_flux_dpg/sigmag/mass_fracs_a/mass_fracs_b.
200! - All emissions are now implemented as surface fluxes! No 3D sources anymore.
201! - Update the emission information by calling salsa_emission_update if
202!   skip_time_do_salsa >= time_since_reference_point and
203!   next_aero_emission_update <= time_since_reference_point
204! - Aerosol background concentrations read from PIDS_DYNAMIC. The vertical grid
205!   must match the one applied in the model.
206! - Gas emissions and background concentrations can be also read in in salsa_mod
207!   if the chemistry module is not applied.
208! - In deposition, information on the land use type can be now imported from
209!   the land use model
210! - Use SI units in PARIN, i.e. n_lognorm given in #/m3 and dpg in metres.
211! - Apply 100 character line limit
212! - Change all variable names from capital to lowercase letter
213! - Change real exponents to integer if possible. If not, precalculate the value
214!   value of exponent
215! - Rename in1a to start_subrange_1a, fn2a to end_subrange_1a etc.
216! - Rename nbins --> nbins_aerosol, ncc_tot --> ncomponents_mass and ngast -->
217!   ngases_salsa
218! - Rename ibc to index_bc, idu to index_du etc.
219! - Renamed loop indices b, c and sg to ib, ic and ig
220! - run_salsa subroutine removed
221! - Corrected a bud in salsa_driver: falsely applied ino instead of inh
222! - Call salsa_tendency within salsa_prognostic_equations which is called in
223!   module_interface_mod instead of prognostic_equations_mod
224! - Removed tailing white spaces and unused variables
225! - Change error message to start by PA instead of SA
226!
227! 3833 2019-03-28 15:04:04Z forkel
228! added USE chem_gasphase_mod for nvar, nspec and spc_names
229!
230! 3787 2019-03-07 08:43:54Z raasch
231! unused variables removed
232!
233! 3780 2019-03-05 11:19:45Z forkel
234! unused variable for file index removed from rrd-subroutines parameter list
235!
236! 3685 2019-01-21 01:02:11Z knoop
237! Some interface calls moved to module_interface + cleanup
238!
239! 3655 2019-01-07 16:51:22Z knoop
240! Implementation of the PALM module interface
241! 3412 2018-10-24 07:25:57Z monakurppa
242!
243! Authors:
244! --------
245! @author Mona Kurppa (University of Helsinki)
246!
247!
248! Description:
249! ------------
250!> Sectional aerosol module for large scale applications SALSA
251!> (Kokkola et al., 2008, ACP 8, 2469-2483). Solves the aerosol number and mass
252!> concentration as well as chemical composition. Includes aerosol dynamic
253!> processes: nucleation, condensation/evaporation of vapours, coagulation and
254!> deposition on tree leaves, ground and roofs.
255!> Implementation is based on formulations implemented in UCLALES-SALSA except
256!> for deposition which is based on parametrisations by Zhang et al. (2001,
257!> Atmos. Environ. 35, 549-560) or Petroff&Zhang (2010, Geosci. Model Dev. 3,
258!> 753-769)
259!>
260!> @todo Apply information from emission_stack_height to lift emission sources
261!> @todo Allow insoluble emissions
262!------------------------------------------------------------------------------!
263 MODULE salsa_mod
264
265    USE basic_constants_and_equations_mod,                                                         &
266        ONLY:  c_p, g, p_0, pi, r_d
267
268    USE chem_gasphase_mod,                                                                         &
269        ONLY:  nspec, nvar, spc_names
270
271    USE chem_modules,                                                                              &
272        ONLY:  call_chem_at_all_substeps, chem_gasphase_on, chem_species
273
274    USE control_parameters,                                                                        &
275        ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r, bc_dirichlet_s,      &
276               bc_lr, bc_lr_cyc, bc_ns, bc_ns_cyc, bc_radiation_l, bc_radiation_n, bc_radiation_r, &
277               bc_radiation_s, coupling_char, debug_output, dt_3d, intermediate_timestep_count,    &
278               intermediate_timestep_count_max, land_surface, max_pr_salsa, message_string,        &
279               monotonic_limiter_z, plant_canopy, pt_surface, salsa, scalar_advec,                 &
280               surface_pressure, time_since_reference_point, timestep_scheme, tsc, urban_surface,  &
281               ws_scheme_sca
282
283    USE indices,                                                                                   &
284        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzb, nz, nzt,             &
285               wall_flags_total_0
286
287    USE kinds
288
289    USE netcdf_data_input_mod,                                                                     &
290        ONLY:  chem_emis_att_type, chem_emis_val_type
291
292    USE pegrid
293
294    USE statistics,                                                                                &
295        ONLY:  sums_salsa_ws_l
296
297    IMPLICIT NONE
298!
299!-- SALSA constants:
300!
301!-- Local constants:
302    INTEGER(iwp), PARAMETER ::  luc_urban = 15     !< default landuse type for urban
303    INTEGER(iwp), PARAMETER ::  ngases_salsa  = 5  !< total number of gaseous tracers:
304                                                   !< 1 = H2SO4, 2 = HNO3, 3 = NH3, 4 = OCNV
305                                                   !< (non-volatile OC), 5 = OCSV (semi-volatile)
306    INTEGER(iwp), PARAMETER ::  nmod = 7     !< number of modes for initialising the aerosol size distribution
307    INTEGER(iwp), PARAMETER ::  nreg = 2     !< Number of main size subranges
308    INTEGER(iwp), PARAMETER ::  maxspec = 7  !< Max. number of aerosol species
309
310
311    REAL(wp), PARAMETER ::  fill_value = -9999.0_wp    !< value for the _FillValue attribute
312!
313!-- Universal constants
314    REAL(wp), PARAMETER ::  abo    = 1.380662E-23_wp   !< Boltzmann constant (J/K)
315    REAL(wp), PARAMETER ::  alv    = 2.260E+6_wp       !< latent heat for H2O vaporisation (J/kg)
316    REAL(wp), PARAMETER ::  alv_d_rv  = 4896.96865_wp  !< alv / rv
317    REAL(wp), PARAMETER ::  am_airmol = 4.8096E-26_wp  !< Average mass of an air molecule (Jacobson 2005, Eq.2.3)
318    REAL(wp), PARAMETER ::  api6   = 0.5235988_wp      !< pi / 6
319    REAL(wp), PARAMETER ::  argas  = 8.314409_wp       !< Gas constant (J/(mol K))
320    REAL(wp), PARAMETER ::  argas_d_cpd = 8.281283865E-3_wp  !< argas per cpd
321    REAL(wp), PARAMETER ::  avo    = 6.02214E+23_wp    !< Avogadro constant (1/mol)
322    REAL(wp), PARAMETER ::  d_sa   = 5.539376964394570E-10_wp  !< diameter of condensing H2SO4 molecule (m)
323    REAL(wp), PARAMETER ::  for_ppm_to_nconc =  7.243016311E+16_wp !< ppm * avo / R (K/(Pa*m3))
324    REAL(wp), PARAMETER ::  epsoc  = 0.15_wp          !< water uptake of organic material
325    REAL(wp), PARAMETER ::  mclim  = 1.0E-23_wp       !< mass concentration min limit (kg/m3)
326    REAL(wp), PARAMETER ::  n3     = 158.79_wp        !< Number of H2SO4 molecules in 3 nm cluster if d_sa=5.54e-10m
327    REAL(wp), PARAMETER ::  nclim  = 1.0_wp           !< number concentration min limit (#/m3)
328    REAL(wp), PARAMETER ::  surfw0 = 0.073_wp         !< surface tension of water at 293 K (J/m2)
329!
330!-- Molar masses in kg/mol
331    REAL(wp), PARAMETER ::  ambc     = 12.0E-3_wp     !< black carbon (BC)
332    REAL(wp), PARAMETER ::  amdair   = 28.970E-3_wp   !< dry air
333    REAL(wp), PARAMETER ::  amdu     = 100.0E-3_wp    !< mineral dust
334    REAL(wp), PARAMETER ::  amh2o    = 18.0154E-3_wp  !< H2O
335    REAL(wp), PARAMETER ::  amh2so4  = 98.06E-3_wp    !< H2SO4
336    REAL(wp), PARAMETER ::  amhno3   = 63.01E-3_wp    !< HNO3
337    REAL(wp), PARAMETER ::  amn2o    = 44.013E-3_wp   !< N2O
338    REAL(wp), PARAMETER ::  amnh3    = 17.031E-3_wp   !< NH3
339    REAL(wp), PARAMETER ::  amo2     = 31.9988E-3_wp  !< O2
340    REAL(wp), PARAMETER ::  amo3     = 47.998E-3_wp   !< O3
341    REAL(wp), PARAMETER ::  amoc     = 150.0E-3_wp    !< organic carbon (OC)
342    REAL(wp), PARAMETER ::  amss     = 58.44E-3_wp    !< sea salt (NaCl)
343!
344!-- Densities in kg/m3
345    REAL(wp), PARAMETER ::  arhobc     = 2000.0_wp  !< black carbon
346    REAL(wp), PARAMETER ::  arhodu     = 2650.0_wp  !< mineral dust
347    REAL(wp), PARAMETER ::  arhoh2o    = 1000.0_wp  !< H2O
348    REAL(wp), PARAMETER ::  arhoh2so4  = 1830.0_wp  !< SO4
349    REAL(wp), PARAMETER ::  arhohno3   = 1479.0_wp  !< HNO3
350    REAL(wp), PARAMETER ::  arhonh3    = 1530.0_wp  !< NH3
351    REAL(wp), PARAMETER ::  arhooc     = 2000.0_wp  !< organic carbon
352    REAL(wp), PARAMETER ::  arhoss     = 2165.0_wp  !< sea salt (NaCl)
353!
354!-- Volume of molecule in m3/#
355    REAL(wp), PARAMETER ::  amvh2o   = amh2o /avo / arhoh2o      !< H2O
356    REAL(wp), PARAMETER ::  amvh2so4 = amh2so4 / avo / arhoh2so4 !< SO4
357    REAL(wp), PARAMETER ::  amvhno3  = amhno3 / avo / arhohno3   !< HNO3
358    REAL(wp), PARAMETER ::  amvnh3   = amnh3 / avo / arhonh3     !< NH3
359    REAL(wp), PARAMETER ::  amvoc    = amoc / avo / arhooc       !< OC
360    REAL(wp), PARAMETER ::  amvss    = amss / avo / arhoss       !< sea salt
361!
362!-- Constants for the dry deposition model by Petroff and Zhang (2010):
363!-- obstacle characteristic dimension "L" (cm) (plane obstacle by default) and empirical constants
364!-- C_B, C_IN, C_IM, beta_IM and C_IT for each land use category (15, as in Zhang et al. (2001))
365    REAL(wp), DIMENSION(1:15), PARAMETER :: l_p10 = &
366        (/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/)
367    REAL(wp), DIMENSION(1:15), PARAMETER :: c_b_p10 = &
368        (/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/)
369    REAL(wp), DIMENSION(1:15), PARAMETER :: c_in_p10 = &
370        (/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/)
371    REAL(wp), DIMENSION(1:15), PARAMETER :: c_im_p10 = &
372        (/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/)
373    REAL(wp), DIMENSION(1:15), PARAMETER :: beta_im_p10 = &
374        (/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/)
375    REAL(wp), DIMENSION(1:15), PARAMETER :: c_it_p10 = &
376        (/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/)
377!
378!-- Constants for the dry deposition model by Zhang et al. (2001):
379!-- empirical constants "alpha" and "gamma" and characteristic radius "A" for
380!-- each land use category (15) and season (5)
381    REAL(wp), DIMENSION(1:15), PARAMETER :: alpha_z01 = &
382        (/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/)
383    REAL(wp), DIMENSION(1:15), PARAMETER :: gamma_z01 = &
384        (/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/)
385    REAL(wp), DIMENSION(1:15,1:5), PARAMETER :: A_z01 =  RESHAPE( (/& 
386         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
387         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
388         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
389         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
390         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
391                                                           /), (/ 15, 5 /) )
392!-- Land use categories (based on Z01 but the same applies here also for P10):
393!-- 1 = evergreen needleleaf trees,
394!-- 2 = evergreen broadleaf trees,
395!-- 3 = deciduous needleleaf trees,
396!-- 4 = deciduous broadleaf trees,
397!-- 5 = mixed broadleaf and needleleaf trees (deciduous broadleaf trees for P10),
398!-- 6 = grass (short grass for P10),
399!-- 7 = crops, mixed farming,
400!-- 8 = desert,
401!-- 9 = tundra,
402!-- 10 = shrubs and interrupted woodlands (thorn shrubs for P10),
403!-- 11 = wetland with plants (long grass for P10)
404!-- 12 = ice cap and glacier,
405!-- 13 = inland water (inland lake for P10)
406!-- 14 = ocean (water for P10),
407!-- 15 = urban
408!
409!-- SALSA variables:
410    CHARACTER(LEN=20)  ::  bc_salsa_b = 'neumann'                 !< bottom boundary condition
411    CHARACTER(LEN=20)  ::  bc_salsa_t = 'neumann'                 !< top boundary condition
412    CHARACTER(LEN=20)  ::  depo_pcm_par = 'zhang2001'             !< or 'petroff2010'
413    CHARACTER(LEN=20)  ::  depo_pcm_type = 'deciduous_broadleaf'  !< leaf type
414    CHARACTER(LEN=20)  ::  depo_surf_par = 'zhang2001'            !< or 'petroff2010'
415    CHARACTER(LEN=100) ::  input_file_dynamic = 'PIDS_DYNAMIC'    !< file name for dynamic input
416    CHARACTER(LEN=100) ::  input_file_salsa   = 'PIDS_SALSA'      !< file name for emission data
417    CHARACTER(LEN=20)  ::  salsa_emission_mode = 'no_emission'    !< 'no_emission', 'uniform',
418                                                                  !< 'parameterized', 'read_from_file'
419
420    CHARACTER(LEN=20), DIMENSION(4) ::  decycle_method_salsa =                                     &
421                                                 (/'dirichlet','dirichlet','dirichlet','dirichlet'/)
422                                     !< Decycling method at horizontal boundaries
423                                     !< 1=left, 2=right, 3=south, 4=north
424                                     !< dirichlet = initial profiles for the ghost and first 3 layers
425                                     !< neumann = zero gradient
426
427    CHARACTER(LEN=3), DIMENSION(maxspec) ::  listspec = &  !< Active aerosols
428                                   (/'SO4','   ','   ','   ','   ','   ','   '/)
429
430    INTEGER(iwp) ::  depo_pcm_par_num = 1   !< parametrisation type: 1=zhang2001, 2=petroff2010
431    INTEGER(iwp) ::  depo_pcm_type_num = 0  !< index for the dry deposition type on the plant canopy
432    INTEGER(iwp) ::  depo_surf_par_num = 1  !< parametrisation type: 1=zhang2001, 2=petroff2010
433    INTEGER(iwp) ::  end_subrange_1a = 1    !< last index for bin subrange 1a
434    INTEGER(iwp) ::  end_subrange_2a = 1    !< last index for bin subrange 2a
435    INTEGER(iwp) ::  end_subrange_2b = 1    !< last index for bin subrange 2b
436    INTEGER(iwp) ::  ibc_salsa_b            !< index for the bottom boundary condition
437    INTEGER(iwp) ::  ibc_salsa_t            !< index for the top boundary condition
438    INTEGER(iwp) ::  index_bc  = -1         !< index for black carbon (BC)
439    INTEGER(iwp) ::  index_du  = -1         !< index for dust
440    INTEGER(iwp) ::  index_nh  = -1         !< index for NH3
441    INTEGER(iwp) ::  index_no  = -1         !< index for HNO3
442    INTEGER(iwp) ::  index_oc  = -1         !< index for organic carbon (OC)
443    INTEGER(iwp) ::  index_so4 = -1         !< index for SO4 or H2SO4
444    INTEGER(iwp) ::  index_ss  = -1         !< index for sea salt
445    INTEGER(iwp) ::  init_aerosol_type = 0  !< Initial size distribution type
446                                            !< 0 = uniform (read from PARIN)
447                                            !< 1 = read vertical profiles from an input file
448    INTEGER(iwp) ::  init_gases_type = 0    !< Initial gas concentration type
449                                            !< 0 = uniform (read from PARIN)
450                                            !< 1 = read vertical profiles from an input file
451    INTEGER(iwp) ::  lod_gas_emissions = 0  !< level of detail of the gaseous emission data
452    INTEGER(iwp) ::  main_street_id = 0     !< lower bound of main street IDs for parameterized emission mode
453    INTEGER(iwp) ::  max_street_id = 0      !< upper bound of main street IDs for parameterized emission mode
454    INTEGER(iwp) ::  nbins_aerosol = 1      !< total number of size bins
455    INTEGER(iwp) ::  ncc   = 1              !< number of chemical components used
456    INTEGER(iwp) ::  ncomponents_mass = 1   !< total number of chemical compounds (ncc+1)
457                                            !< if particle water is advected)
458    INTEGER(iwp) ::  nj3 = 1                !< J3 parametrization (nucleation)
459                                            !< 1 = condensational sink (Kerminen&Kulmala, 2002)
460                                            !< 2 = coagulational sink (Lehtinen et al. 2007)
461                                            !< 3 = coagS+self-coagulation (Anttila et al. 2010)
462    INTEGER(iwp) ::  nsnucl = 0             !< Choice of the nucleation scheme:
463                                            !< 0 = off
464                                            !< 1 = binary nucleation
465                                            !< 2 = activation type nucleation
466                                            !< 3 = kinetic nucleation
467                                            !< 4 = ternary nucleation
468                                            !< 5 = nucleation with ORGANICs
469                                            !< 6 = activation type of nucleation with H2SO4+ORG
470                                            !< 7 = heteromolecular nucleation with H2SO4*ORG
471                                            !< 8 = homomolecular nucleation of H2SO4
472                                            !<     + heteromolecular nucleation with H2SO4*ORG
473                                            !< 9 = homomolecular nucleation of H2SO4 and ORG
474                                            !<     + heteromolecular nucleation with H2SO4*ORG
475    INTEGER(iwp) ::  salsa_pr_count = 0     !< counter for salsa variable profiles
476    INTEGER(iwp) ::  season_z01 = 1         !< For dry deposition by Zhang et al.: 1 = summer,
477                                            !< 2 = autumn (no harvest yet), 3 = late autumn
478                                            !< (already frost), 4 = winter, 5 = transitional spring
479    INTEGER(iwp) ::  side_street_id = 0     !< lower bound of side street IDs for parameterized emission mode
480    INTEGER(iwp) ::  start_subrange_1a = 1  !< start index for bin subranges: subrange 1a
481    INTEGER(iwp) ::  start_subrange_2a = 1  !<                                subrange 2a
482    INTEGER(iwp) ::  start_subrange_2b = 1  !<                                subrange 2b
483
484    INTEGER(iwp), DIMENSION(nreg) ::  nbin = (/ 3, 7/)  !< Number of size bins per subrange: 1 & 2
485
486    INTEGER(iwp), DIMENSION(ngases_salsa) ::  gas_index_chem = (/ 1, 1, 1, 1, 1/)  !< gas indices in chemistry_model_mod
487                                                                                   !< 1 = H2SO4, 2 = HNO3,
488                                                                                   !< 3 = NH3,   4 = OCNV, 5 = OCSV
489    INTEGER(iwp), DIMENSION(ngases_salsa) ::  emission_index_chem  !< gas indices in the gas emission file
490    INTEGER(iwp), DIMENSION(99) ::  salsa_pr_index  = 0            !< index for salsa profiles
491
492    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  k_topo_top  !< vertical index of the topography top
493
494    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE  ::  salsa_advc_flags_s !< flags used to degrade order of advection
495                                                                        !< scheme for salsa variables near walls and
496                                                                        !< lateral boundaries
497!
498!-- SALSA switches:
499    LOGICAL ::  advect_particle_water   = .TRUE.   !< Advect water concentration of particles
500    LOGICAL ::  decycle_salsa_lr        = .FALSE.  !< Undo cyclic boundaries: left and right
501    LOGICAL ::  decycle_salsa_ns        = .FALSE.  !< Undo cyclic boundaries: north and south
502    LOGICAL ::  include_emission        = .FALSE.  !< Include or not emissions
503    LOGICAL ::  feedback_to_palm        = .FALSE.  !< Allow feedback due to condensation of H2O
504    LOGICAL ::  nesting_salsa           = .TRUE.   !< Apply nesting for salsa
505    LOGICAL ::  nesting_offline_salsa   = .TRUE.   !< Apply offline nesting for salsa
506    LOGICAL ::  no_insoluble            = .FALSE.  !< Exclude insoluble chemical components
507    LOGICAL ::  read_restart_data_salsa = .TRUE.   !< Read restart data for salsa
508    LOGICAL ::  salsa_gases_from_chem   = .FALSE.  !< Transfer the gaseous components to SALSA
509    LOGICAL ::  van_der_waals_coagc     = .FALSE.  !< Include van der Waals and viscous forces in coagulation
510    LOGICAL ::  write_binary_salsa      = .TRUE.   !< read binary for salsa
511!
512!-- Process switches: nl* is read from the NAMELIST and is NOT changed.
513!--                   ls* is the switch used and will get the value of nl*
514!--                       except for special circumstances (spinup period etc.)
515    LOGICAL ::  nlcoag       = .FALSE.  !< Coagulation master switch
516    LOGICAL ::  lscoag       = .FALSE.  !<
517    LOGICAL ::  nlcnd        = .FALSE.  !< Condensation master switch
518    LOGICAL ::  lscnd        = .FALSE.  !<
519    LOGICAL ::  nlcndgas     = .FALSE.  !< Condensation of precursor gases
520    LOGICAL ::  lscndgas     = .FALSE.  !<
521    LOGICAL ::  nlcndh2oae   = .FALSE.  !< Condensation of H2O on aerosol
522    LOGICAL ::  lscndh2oae   = .FALSE.  !< particles (FALSE -> equilibrium calc.)
523    LOGICAL ::  nldepo       = .FALSE.  !< Deposition master switch
524    LOGICAL ::  lsdepo       = .FALSE.  !<
525    LOGICAL ::  nldepo_surf  = .FALSE.  !< Deposition on vegetation master switch
526    LOGICAL ::  lsdepo_surf  = .FALSE.  !<
527    LOGICAL ::  nldepo_pcm   = .FALSE.  !< Deposition on walls master switch
528    LOGICAL ::  lsdepo_pcm   = .FALSE.  !<
529    LOGICAL ::  nldistupdate = .TRUE.   !< Size distribution update master switch
530    LOGICAL ::  lsdistupdate = .FALSE.  !<
531    LOGICAL ::  lspartition  = .FALSE.  !< Partition of HNO3 and NH3
532
533    REAL(wp) ::  act_coeff = 1.0E-7_wp               !< Activation coefficient (1/s)
534    REAL(wp) ::  dt_salsa  = 0.00001_wp              !< Time step of SALSA
535    REAL(wp) ::  emiss_factor_main = 0.0_wp          !< relative emission factor for main streets
536    REAL(wp) ::  emiss_factor_side = 0.0_wp          !< relative emission factor for side streets
537    REAL(wp) ::  h2so4_init = nclim                  !< Init value for sulphuric acid gas
538    REAL(wp) ::  hno3_init  = nclim                  !< Init value for nitric acid gas
539    REAL(wp) ::  last_salsa_time = 0.0_wp            !< previous salsa call
540    REAL(wp) ::  next_aero_emission_update = 0.0_wp  !< previous emission update
541    REAL(wp) ::  next_gas_emission_update = 0.0_wp   !< previous emission update
542    REAL(wp) ::  nf2a = 1.0_wp                       !< Number fraction allocated to 2a-bins
543    REAL(wp) ::  nh3_init  = nclim                   !< Init value for ammonia gas
544    REAL(wp) ::  ocnv_init = nclim                   !< Init value for non-volatile organic gases
545    REAL(wp) ::  ocsv_init = nclim                   !< Init value for semi-volatile organic gases
546    REAL(wp) ::  rhlim = 1.20_wp                     !< RH limit in %/100. Prevents unrealistical RH
547    REAL(wp) ::  skip_time_do_salsa = 0.0_wp         !< Starting time of SALSA (s)
548!
549!-- Initial log-normal size distribution: mode diameter (dpg, metres),
550!-- standard deviation (sigmag) and concentration (n_lognorm, #/m3)
551    REAL(wp), DIMENSION(nmod) ::  dpg   = &
552                     (/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/)
553    REAL(wp), DIMENSION(nmod) ::  sigmag  = &
554                                        (/1.8_wp, 2.16_wp, 2.21_wp, 2.0_wp, 2.0_wp, 2.0_wp, 2.0_wp/)
555    REAL(wp), DIMENSION(nmod) ::  n_lognorm = &
556                             (/1.04e+11_wp, 3.23E+10_wp, 5.4E+6_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp/)
557!
558!-- Initial mass fractions / chemical composition of the size distribution
559    REAL(wp), DIMENSION(maxspec) ::  mass_fracs_a = &  !< mass fractions between
560             (/1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)     !< aerosol species for A bins
561    REAL(wp), DIMENSION(maxspec) ::  mass_fracs_b = &  !< mass fractions between
562             (/0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)     !< aerosol species for B bins
563    REAL(wp), DIMENSION(nreg+1) ::  reglim = &         !< Min&max diameters of size subranges
564                                 (/ 3.0E-9_wp, 5.0E-8_wp, 1.0E-5_wp/)
565!
566!-- Initial log-normal size distribution: mode diameter (dpg, metres), standard deviation (sigmag)
567!-- concentration (n_lognorm, #/m3) and mass fractions of all chemical components (listed in
568!-- listspec) for both a (soluble) and b (insoluble) bins.
569    REAL(wp), DIMENSION(nmod) ::  aerosol_flux_dpg   = &
570                     (/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/)
571    REAL(wp), DIMENSION(nmod) ::  aerosol_flux_sigmag  = &
572                                        (/1.8_wp, 2.16_wp, 2.21_wp, 2.0_wp, 2.0_wp, 2.0_wp, 2.0_wp/)
573    REAL(wp), DIMENSION(maxspec) ::  aerosol_flux_mass_fracs_a = &
574                                                               (/1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)
575    REAL(wp), DIMENSION(maxspec) ::  aerosol_flux_mass_fracs_b = &
576                                                               (/0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)
577    REAL(wp), DIMENSION(nmod) ::  surface_aerosol_flux = &
578                                 (/1.0E+8_wp, 1.0E+9_wp, 1.0E+5_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp/)
579
580    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bin_low_limits     !< to deliver information about
581                                                               !< the lower diameters per bin
582    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_am_t_val        !< vertical gradient of: aerosol mass
583    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_an_t_val        !< of: aerosol number
584    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_gt_t_val        !< salsa gases near domain top
585    REAL(wp), DIMENSION(:), ALLOCATABLE ::  gas_emission_time  !< Time array in gas emission data (s)
586    REAL(wp), DIMENSION(:), ALLOCATABLE ::  nsect              !< Background number concentrations
587    REAL(wp), DIMENSION(:), ALLOCATABLE ::  massacc            !< Mass accomodation coefficients
588!
589!-- SALSA derived datatypes:
590!
591!-- Component index
592    TYPE component_index
593       CHARACTER(len=3), ALLOCATABLE ::  comp(:)  !< Component name
594       INTEGER(iwp) ::  ncomp  !< Number of components
595       INTEGER(iwp), ALLOCATABLE ::  ind(:)  !< Component index
596    END TYPE component_index
597!
598!-- For matching LSM and USM surface types and the deposition module surface types
599    TYPE match_surface
600       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_lupg  !< index for pavement / green roofs
601       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_luvw  !< index for vegetation / walls
602       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_luww  !< index for water / windows
603    END TYPE match_surface
604!
605!-- Aerosol emission data attributes
606    TYPE salsa_emission_attribute_type
607
608       CHARACTER(LEN=25) ::   units
609
610       CHARACTER(LEN=25), DIMENSION(:), ALLOCATABLE ::   cat_name    !<
611       CHARACTER(LEN=25), DIMENSION(:), ALLOCATABLE ::   cc_name     !<
612       CHARACTER(LEN=25), DIMENSION(:), ALLOCATABLE ::   unit_time   !<
613       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names   !<
614
615       INTEGER(iwp) ::  lod = 0            !< level of detail
616       INTEGER(iwp) ::  nbins = 10         !< number of aerosol size bins
617       INTEGER(iwp) ::  ncat  = 0          !< number of emission categories
618       INTEGER(iwp) ::  ncc   = 7          !< number of aerosol chemical components
619       INTEGER(iwp) ::  nhoursyear = 0     !< number of hours: HOURLY mode
620       INTEGER(iwp) ::  nmonthdayhour = 0  !< number of month days and hours: MDH mode
621       INTEGER(iwp) ::  num_vars           !< number of variables
622       INTEGER(iwp) ::  nt  = 0            !< number of time steps
623       INTEGER(iwp) ::  nz  = 0            !< number of vertical levels
624       INTEGER(iwp) ::  tind               !< time index for reference time in salsa emission data
625
626       INTEGER(iwp), DIMENSION(maxspec) ::  cc_in2mod = 0   !<
627
628       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  cat_index  !< Index of emission categories
629       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  cc_index   !< Index of chemical components
630
631       REAL(wp) ::  conversion_factor  !< unit conversion factor for aerosol emissions
632
633       REAL(wp), DIMENSION(:), ALLOCATABLE ::  dmid         !< mean diameters of size bins (m)
634       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rho          !< average density (kg/m3)
635       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time         !< time (s)
636       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time_factor  !< emission time factor
637       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z            !< height (m)
638
639       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  etf  !< emission time factor
640       REAL(wp), DIMENSION(:,:), ALLOCATABLE :: stack_height
641
642    END TYPE salsa_emission_attribute_type
643!
644!-- The default size distribution and mass composition per emission category:
645!-- 1 = traffic, 2 = road dust, 3 = wood combustion, 4 = other
646!-- Mass fractions: H2SO4, OC, BC, DU, SS, HNO3, NH3
647    TYPE salsa_emission_mode_type
648
649       INTEGER(iwp) ::  ndm = 3  !< number of default modes
650       INTEGER(iwp) ::  ndc = 4  !< number of default categories
651
652       CHARACTER(LEN=25), DIMENSION(1:4) ::  cat_name_table = (/'traffic exhaust', &
653                                                                'road dust      ', &
654                                                                'wood combustion', &
655                                                                'other          '/)
656
657       INTEGER(iwp), DIMENSION(1:4) ::  cat_input_to_model   !<
658
659       REAL(wp), DIMENSION(1:3) ::  dpg_table = (/ 13.5E-9_wp, 1.4E-6_wp, 5.4E-8_wp/)  !<
660       REAL(wp), DIMENSION(1:3) ::  ntot_table  !<
661       REAL(wp), DIMENSION(1:3) ::  sigmag_table = (/ 1.6_wp, 1.4_wp, 1.7_wp /)  !<
662
663       REAL(wp), DIMENSION(1:maxspec,1:4) ::  mass_frac_table = &  !<
664          RESHAPE( (/ 0.04_wp, 0.48_wp, 0.48_wp, 0.0_wp,  0.0_wp, 0.0_wp, 0.0_wp, &
665                      0.0_wp,  0.05_wp, 0.0_wp,  0.95_wp, 0.0_wp, 0.0_wp, 0.0_wp, &
666                      0.0_wp,  0.5_wp,  0.5_wp,  0.0_wp,  0.0_wp, 0.0_wp, 0.0_wp, &
667                      0.0_wp,  0.5_wp,  0.5_wp,  0.0_wp,  0.0_wp, 0.0_wp, 0.0_wp  &
668                   /), (/maxspec,4/) )
669
670       REAL(wp), DIMENSION(1:3,1:4) ::  pm_frac_table = & !< rel. mass
671                                     RESHAPE( (/ 0.016_wp, 0.000_wp, 0.984_wp, &
672                                                 0.000_wp, 1.000_wp, 0.000_wp, &
673                                                 0.000_wp, 0.000_wp, 1.000_wp, &
674                                                 1.000_wp, 0.000_wp, 1.000_wp  &
675                                              /), (/3,4/) )
676
677    END TYPE salsa_emission_mode_type
678!
679!-- Aerosol emission data values
680    TYPE salsa_emission_value_type
681
682       REAL(wp) ::  fill  !< fill value
683
684       REAL(wp), DIMENSION(:,:), ALLOCATABLE :: mass_fracs  !< mass fractions per emis. category
685       REAL(wp), DIMENSION(:,:), ALLOCATABLE :: num_fracs   !< number fractions per emis. category
686
687       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: def_data      !< surface emission in PM
688       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: preproc_data  !< surface emission per category
689
690    END TYPE salsa_emission_value_type
691!
692!-- Offline nesting data type
693    TYPE salsa_nest_offl_type
694
695       CHARACTER(LEN=16) ::  char_l = 'ls_forcing_left_'  !< leading substring at left boundary
696       CHARACTER(LEN=17) ::  char_n = 'ls_forcing_north_' !< leading substring at north boundary
697       CHARACTER(LEN=17) ::  char_r = 'ls_forcing_right_' !< leading substring at right boundary
698       CHARACTER(LEN=17) ::  char_s = 'ls_forcing_south_' !< leading substring at south boundary
699       CHARACTER(LEN=15) ::  char_t = 'ls_forcing_top_'   !< leading substring at top boundary
700
701       CHARACTER(LEN=5), DIMENSION(1:ngases_salsa) ::  gas_name = (/'H2SO4','HNO3 ','NH3  ','OCNV ','OCSV '/)
702
703       CHARACTER(LEN=25),  DIMENSION(:), ALLOCATABLE ::  cc_name    !< chemical component name
704       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< list of variable names
705
706       INTEGER(iwp) ::  id_dynamic  !< NetCDF id of dynamic input file
707       INTEGER(iwp) ::  ncc         !< number of aerosol chemical components
708       INTEGER(iwp) ::  nt          !< number of time levels in dynamic input file
709       INTEGER(iwp) ::  nzu         !< number of vertical levels on scalar grid in dynamic input file
710       INTEGER(iwp) ::  tind        !< time index for reference time in mesoscale-offline nesting
711       INTEGER(iwp) ::  tind_p      !< time index for following time in mesoscale-offline nesting
712
713       INTEGER(iwp), DIMENSION(maxspec) ::  cc_in2mod = 0  !< to transfer chemical composition from input to model
714
715       LOGICAL ::  init  = .FALSE. !< flag indicating the initialisation of offline nesting
716
717       REAL(wp), DIMENSION(:), ALLOCATABLE ::  dmid      !< vertical profile of aerosol bin diameters
718       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time      !< time in dynamic input file
719       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos  !< zu in dynamic input file
720
721       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_left   !< gas conc. at left boundary
722       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_north  !< gas conc. at north boundary
723       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_right  !< gas conc. at right boundary
724       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_south  !< gas conc. at south boundary
725       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  gconc_top    !< gas conc.at top boundary
726       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_left   !< aerosol mass conc. at left boundary
727       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_north  !< aerosol mass conc. at north boundary
728       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_right  !< aerosol mass conc. at right boundary
729       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_south  !< aerosol mass conc. at south boundary
730       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  mconc_top    !< aerosol mass conc. at top boundary
731       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_left   !< aerosol number conc. at left boundary
732       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_north  !< aerosol number conc. at north boundary
733       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_right  !< aerosol number conc. at right boundary
734       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_south  !< aerosol number conc. at south boundary
735       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  nconc_top    !< aerosol number conc. at top boundary
736
737    END TYPE salsa_nest_offl_type
738!
739!-- Prognostic variable: Aerosol size bin information (number (#/m3) and mass (kg/m3) concentration)
740!-- and the concentration of gaseous tracers (#/m3). Gas tracers are contained sequentially in
741!-- dimension 4 as:
742!-- 1. H2SO4, 2. HNO3, 3. NH3, 4. OCNV (non-volatile organics), 5. OCSV (semi-volatile)
743    TYPE salsa_variable
744
745       REAL(wp), DIMENSION(:), ALLOCATABLE     ::  init  !<
746
747       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s     !<
748       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s     !<
749       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  source     !<
750       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ws_l  !<
751
752       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l  !<
753       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l  !<
754
755       REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  conc     !<
756       REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  conc_p   !<
757       REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tconc_m  !<
758
759    END TYPE salsa_variable
760!
761!-- Datatype used to store information about the binned size distributions of aerosols
762    TYPE t_section
763
764       REAL(wp) ::  dmid     !< bin middle diameter (m)
765       REAL(wp) ::  vhilim   !< bin volume at the high limit
766       REAL(wp) ::  vlolim   !< bin volume at the low limit
767       REAL(wp) ::  vratiohi !< volume ratio between the center and high limit
768       REAL(wp) ::  vratiolo !< volume ratio between the center and low limit
769       !******************************************************
770       ! ^ Do NOT change the stuff above after initialization !
771       !******************************************************
772       REAL(wp) ::  core    !< Volume of dry particle
773       REAL(wp) ::  dwet    !< Wet diameter or mean droplet diameter (m)
774       REAL(wp) ::  numc    !< Number concentration of particles/droplets (#/m3)
775       REAL(wp) ::  veqh2o  !< Equilibrium H2O concentration for each particle
776
777       REAL(wp), DIMENSION(maxspec+1) ::  volc !< Volume concentrations (m^3/m^3) of aerosols +
778                                               !< water. Since most of the stuff in SALSA is hard
779                                               !< coded, these *have to be* in the order
780                                               !< 1:SO4, 2:OC, 3:BC, 4:DU, 5:SS, 6:NO, 7:NH, 8:H2O
781    END TYPE t_section
782
783    TYPE(salsa_emission_attribute_type) ::  aero_emission_att  !< emission attributes
784    TYPE(salsa_emission_value_type)     ::  aero_emission      !< emission values
785    TYPE(salsa_emission_mode_type)      ::  def_modes          !< default emission modes
786
787    TYPE(chem_emis_att_type) ::  chem_emission_att  !< chemistry emission attributes
788
789    TYPE(chem_emis_val_type), DIMENSION(:), ALLOCATABLE ::  chem_emission  !< chemistry emissions
790
791    TYPE(t_section), DIMENSION(:), ALLOCATABLE ::  aero  !< local aerosol properties
792
793    TYPE(match_surface) ::  lsm_to_depo_h  !< to match the deposition module and horizontal LSM surfaces
794    TYPE(match_surface) ::  usm_to_depo_h  !< to match the deposition module and horizontal USM surfaces
795
796    TYPE(match_surface), DIMENSION(0:3) ::  lsm_to_depo_v  !< to match the deposition mod. and vertical LSM surfaces
797    TYPE(match_surface), DIMENSION(0:3) ::  usm_to_depo_v  !< to match the deposition mod. and vertical USM surfaces
798!
799!-- SALSA variables: as x = x(k,j,i,bin).
800!-- The 4th dimension contains all the size bins sequentially for each aerosol species  + water.
801!
802!-- Prognostic variables:
803!
804!-- Number concentration (#/m3)
805    TYPE(salsa_variable), DIMENSION(:), ALLOCATABLE, TARGET ::  aerosol_number  !<
806    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  nconc_1  !<
807    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  nconc_2  !<
808    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  nconc_3  !<
809!
810!-- Mass concentration (kg/m3)
811    TYPE(salsa_variable), DIMENSION(:), ALLOCATABLE, TARGET ::  aerosol_mass  !<
812    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  mconc_1  !<
813    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  mconc_2  !<
814    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  mconc_3  !<
815!
816!-- Gaseous concentrations (#/m3)
817    TYPE(salsa_variable), DIMENSION(:), ALLOCATABLE, TARGET ::  salsa_gas  !<
818    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  gconc_1  !<
819    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  gconc_2  !<
820    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  gconc_3  !<
821!
822!-- Diagnostic tracers
823    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  sedim_vd  !< sedimentation velocity per bin (m/s)
824    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  ra_dry    !< aerosol dry radius (m)
825
826!-- Particle component index tables
827    TYPE(component_index) :: prtcl  !< Contains "getIndex" which gives the index for a given aerosol
828                                    !< component name: 1:SO4, 2:OC, 3:BC, 4:DU, 5:SS, 6:NO, 7:NH, 8:H2O
829!
830!-- Offline nesting:
831    TYPE(salsa_nest_offl_type) ::  salsa_nest_offl  !< data structure for offline nesting
832!
833!-- Data output arrays:
834!
835!-- Integrated:
836    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ldsa_av  !< lung-deposited surface area
837    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ntot_av  !< total number concentration
838    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nufp_av  !< ultrafine particles (UFP)
839    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pm01_av  !< PM0.1
840    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pm25_av  !< PM2.5
841    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pm10_av  !< PM10
842!
843!-- Bin specific mass and number concentrations:
844    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  mbins_av  !< bin mas
845    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  nbins_av  !< bin number
846!
847!-- Gases:
848    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  salsa_gases_av  !< gases
849!
850!-- In the particle phase:
851    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_h2o_av  !< liquid water
852    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  s_mass_av  !< mass components
853
854!
855!-- PALM interfaces:
856
857    INTERFACE salsa_actions
858       MODULE PROCEDURE salsa_actions
859       MODULE PROCEDURE salsa_actions_ij
860    END INTERFACE salsa_actions
861
862    INTERFACE salsa_3d_data_averaging
863       MODULE PROCEDURE salsa_3d_data_averaging
864    END INTERFACE salsa_3d_data_averaging
865
866    INTERFACE salsa_boundary_conds
867       MODULE PROCEDURE salsa_boundary_conds
868       MODULE PROCEDURE salsa_boundary_conds_decycle
869    END INTERFACE salsa_boundary_conds
870
871    INTERFACE salsa_boundary_conditions
872       MODULE PROCEDURE salsa_boundary_conditions
873    END INTERFACE salsa_boundary_conditions
874
875    INTERFACE salsa_check_data_output
876       MODULE PROCEDURE salsa_check_data_output
877    END INTERFACE salsa_check_data_output
878
879    INTERFACE salsa_check_data_output_pr
880       MODULE PROCEDURE salsa_check_data_output_pr
881    END INTERFACE salsa_check_data_output_pr
882
883    INTERFACE salsa_check_parameters
884       MODULE PROCEDURE salsa_check_parameters
885    END INTERFACE salsa_check_parameters
886
887    INTERFACE salsa_data_output_2d
888       MODULE PROCEDURE salsa_data_output_2d
889    END INTERFACE salsa_data_output_2d
890
891    INTERFACE salsa_data_output_3d
892       MODULE PROCEDURE salsa_data_output_3d
893    END INTERFACE salsa_data_output_3d
894
895    INTERFACE salsa_data_output_mask
896       MODULE PROCEDURE salsa_data_output_mask
897    END INTERFACE salsa_data_output_mask
898
899    INTERFACE salsa_define_netcdf_grid
900       MODULE PROCEDURE salsa_define_netcdf_grid
901    END INTERFACE salsa_define_netcdf_grid
902
903    INTERFACE salsa_emission_update
904       MODULE PROCEDURE salsa_emission_update
905    END INTERFACE salsa_emission_update
906
907    INTERFACE salsa_exchange_horiz_bounds
908       MODULE PROCEDURE salsa_exchange_horiz_bounds
909    END INTERFACE salsa_exchange_horiz_bounds
910
911    INTERFACE salsa_header
912       MODULE PROCEDURE salsa_header
913    END INTERFACE salsa_header
914
915    INTERFACE salsa_init
916       MODULE PROCEDURE salsa_init
917    END INTERFACE salsa_init
918
919    INTERFACE salsa_init_arrays
920       MODULE PROCEDURE salsa_init_arrays
921    END INTERFACE salsa_init_arrays
922
923    INTERFACE salsa_nesting_offl_bc
924       MODULE PROCEDURE salsa_nesting_offl_bc
925    END INTERFACE salsa_nesting_offl_bc
926
927    INTERFACE salsa_nesting_offl_init
928       MODULE PROCEDURE salsa_nesting_offl_init
929    END INTERFACE salsa_nesting_offl_init
930
931    INTERFACE salsa_nesting_offl_input
932       MODULE PROCEDURE salsa_nesting_offl_input
933    END INTERFACE salsa_nesting_offl_input
934
935    INTERFACE salsa_non_advective_processes
936       MODULE PROCEDURE salsa_non_advective_processes
937       MODULE PROCEDURE salsa_non_advective_processes_ij
938    END INTERFACE salsa_non_advective_processes
939
940    INTERFACE salsa_parin
941       MODULE PROCEDURE salsa_parin
942    END INTERFACE salsa_parin
943
944    INTERFACE salsa_prognostic_equations
945       MODULE PROCEDURE salsa_prognostic_equations
946       MODULE PROCEDURE salsa_prognostic_equations_ij
947    END INTERFACE salsa_prognostic_equations
948
949    INTERFACE salsa_rrd_local
950       MODULE PROCEDURE salsa_rrd_local
951    END INTERFACE salsa_rrd_local
952
953    INTERFACE salsa_statistics
954       MODULE PROCEDURE salsa_statistics
955    END INTERFACE salsa_statistics
956
957    INTERFACE salsa_swap_timelevel
958       MODULE PROCEDURE salsa_swap_timelevel
959    END INTERFACE salsa_swap_timelevel
960
961    INTERFACE salsa_tendency
962       MODULE PROCEDURE salsa_tendency
963       MODULE PROCEDURE salsa_tendency_ij
964    END INTERFACE salsa_tendency
965
966    INTERFACE salsa_wrd_local
967       MODULE PROCEDURE salsa_wrd_local
968    END INTERFACE salsa_wrd_local
969
970
971    SAVE
972
973    PRIVATE
974!
975!-- Public functions:
976    PUBLIC salsa_3d_data_averaging,       &
977           salsa_actions,                 &
978           salsa_boundary_conds,          &
979           salsa_boundary_conditions,     &
980           salsa_check_data_output,       &
981           salsa_check_data_output_pr,    &
982           salsa_check_parameters,        &
983           salsa_data_output_2d,          &
984           salsa_data_output_3d,          &
985           salsa_data_output_mask,        &
986           salsa_define_netcdf_grid,      &
987           salsa_diagnostics,             &
988           salsa_emission_update,         &
989           salsa_exchange_horiz_bounds,   &
990           salsa_header,                  &
991           salsa_init,                    &
992           salsa_init_arrays,             &
993           salsa_nesting_offl_bc,         &
994           salsa_nesting_offl_init,       &
995           salsa_nesting_offl_input,      &
996           salsa_non_advective_processes, &
997           salsa_parin,                   &
998           salsa_prognostic_equations,    &
999           salsa_rrd_local,               &
1000           salsa_statistics,              &
1001           salsa_swap_timelevel,          &
1002           salsa_wrd_local
1003
1004!
1005!-- Public parameters, constants and initial values
1006    PUBLIC bc_am_t_val,           &
1007           bc_an_t_val,           &
1008           bc_gt_t_val,           &
1009           ibc_salsa_b,           &
1010           init_aerosol_type,     &
1011           init_gases_type,       &
1012           nesting_salsa,         &
1013           nesting_offline_salsa, &
1014           salsa_gases_from_chem, &
1015           skip_time_do_salsa
1016!
1017!-- Public variables
1018    PUBLIC aerosol_mass,     &
1019           aerosol_number,   &
1020           gconc_2,          &
1021           mconc_2,          &
1022           nbins_aerosol,    &
1023           ncomponents_mass, &
1024           nconc_2,          &
1025           ngases_salsa,     &
1026           salsa_gas,        &
1027           salsa_nest_offl
1028
1029
1030 CONTAINS
1031
1032!------------------------------------------------------------------------------!
1033! Description:
1034! ------------
1035!> Parin for &salsa_par for new modules
1036!------------------------------------------------------------------------------!
1037 SUBROUTINE salsa_parin
1038
1039    USE control_parameters,                                                                        &
1040        ONLY:  data_output_pr
1041
1042    IMPLICIT NONE
1043
1044    CHARACTER(LEN=80) ::  line   !< dummy string that contains the current line of parameter file
1045
1046    INTEGER(iwp) ::  i                 !< loop index
1047    INTEGER(iwp) ::  max_pr_salsa_tmp  !< dummy variable
1048
1049    NAMELIST /salsa_parameters/      aerosol_flux_dpg,                         &
1050                                     aerosol_flux_mass_fracs_a,                &
1051                                     aerosol_flux_mass_fracs_b,                &
1052                                     aerosol_flux_sigmag,                      &
1053                                     advect_particle_water,                    &
1054                                     bc_salsa_b,                               &
1055                                     bc_salsa_t,                               &
1056                                     decycle_salsa_lr,                         &
1057                                     decycle_method_salsa,                     &
1058                                     decycle_salsa_ns,                         &
1059                                     depo_pcm_par,                             &
1060                                     depo_pcm_type,                            &
1061                                     depo_surf_par,                            &
1062                                     dpg,                                      &
1063                                     dt_salsa,                                 &
1064                                     emiss_factor_main,                        &
1065                                     emiss_factor_side,                        &
1066                                     feedback_to_palm,                         &
1067                                     h2so4_init,                               &
1068                                     hno3_init,                                &
1069                                     listspec,                                 &
1070                                     main_street_id,                           &
1071                                     mass_fracs_a,                             &
1072                                     mass_fracs_b,                             &
1073                                     max_street_id,                            &
1074                                     n_lognorm,                                &
1075                                     nbin,                                     &
1076                                     nesting_salsa,                            &
1077                                     nesting_offline_salsa,                    &
1078                                     nf2a,                                     &
1079                                     nh3_init,                                 &
1080                                     nj3,                                      &
1081                                     nlcnd,                                    &
1082                                     nlcndgas,                                 &
1083                                     nlcndh2oae,                               &
1084                                     nlcoag,                                   &
1085                                     nldepo,                                   &
1086                                     nldepo_pcm,                               &
1087                                     nldepo_surf,                              &
1088                                     nldistupdate,                             &
1089                                     nsnucl,                                   &
1090                                     ocnv_init,                                &
1091                                     ocsv_init,                                &
1092                                     read_restart_data_salsa,                  &
1093                                     reglim,                                   &
1094                                     salsa,                                    &
1095                                     salsa_emission_mode,                      &
1096                                     season_z01,                               &
1097                                     sigmag,                                   &
1098                                     side_street_id,                           &
1099                                     skip_time_do_salsa,                       &
1100                                     surface_aerosol_flux,                     &
1101                                     van_der_waals_coagc,                      &
1102                                     write_binary_salsa
1103
1104    line = ' '
1105!
1106!-- Try to find salsa package
1107    REWIND ( 11 )
1108    line = ' '
1109    DO WHILE ( INDEX( line, '&salsa_parameters' ) == 0 )
1110       READ ( 11, '(A)', END=10 )  line
1111    ENDDO
1112    BACKSPACE ( 11 )
1113!
1114!-- Read user-defined namelist
1115    READ ( 11, salsa_parameters )
1116!
1117!-- Enable salsa (salsa switch in modules.f90)
1118    salsa = .TRUE.
1119
1120 10 CONTINUE
1121!
1122!-- Update the number of output profiles
1123    max_pr_salsa_tmp = 0
1124    i = 1
1125    DO WHILE ( data_output_pr(i) /= ' '  .AND.  i <= 100 )
1126       IF ( TRIM( data_output_pr(i)(1:6) ) == 'salsa_' )  max_pr_salsa_tmp = max_pr_salsa_tmp + 1
1127       i = i + 1
1128    ENDDO
1129    IF ( max_pr_salsa_tmp > 0 )  max_pr_salsa = max_pr_salsa_tmp
1130
1131 END SUBROUTINE salsa_parin
1132
1133!------------------------------------------------------------------------------!
1134! Description:
1135! ------------
1136!> Check parameters routine for salsa.
1137!------------------------------------------------------------------------------!
1138 SUBROUTINE salsa_check_parameters
1139
1140    USE control_parameters,                                                                        &
1141        ONLY:  child_domain, humidity, initializing_actions, nesting_offline
1142
1143    IMPLICIT NONE
1144
1145!
1146!-- Check that humidity is switched on
1147    IF ( salsa  .AND.  .NOT.  humidity )  THEN
1148       WRITE( message_string, * ) 'salsa = ', salsa, ' is not allowed with humidity = ', humidity
1149       CALL message( 'salsa_check_parameters', 'PA0594', 1, 2, 0, 6, 0 )
1150    ENDIF
1151!
1152!-- For nested runs, explicitly set nesting boundary conditions.
1153    IF ( child_domain )  THEN
1154       IF ( nesting_salsa )  THEN
1155          bc_salsa_t = 'nested'
1156       ELSE
1157          bc_salsa_t = 'neumann'
1158       ENDIF
1159    ENDIF
1160!
1161!-- Set boundary conditions also in case the model is offline-nested in larger-scale models.
1162    IF ( nesting_offline )  THEN
1163       IF ( nesting_offline_salsa )  THEN
1164          bc_salsa_t = 'nesting_offline'
1165       ELSE
1166          bc_salsa_t = 'neumann'
1167       ENDIF
1168    ENDIF
1169!
1170!-- Set bottom boundary condition flag
1171    IF ( bc_salsa_b == 'dirichlet' )  THEN
1172       ibc_salsa_b = 0
1173    ELSEIF ( bc_salsa_b == 'neumann' )  THEN
1174       ibc_salsa_b = 1
1175    ELSE
1176       message_string = 'unknown boundary condition: bc_salsa_b = "' // TRIM( bc_salsa_t ) // '"'
1177       CALL message( 'salsa_check_parameters', 'PA0595', 1, 2, 0, 6, 0 )
1178    ENDIF
1179!
1180!-- Set top boundary conditions flag
1181    IF ( bc_salsa_t == 'dirichlet' )  THEN
1182       ibc_salsa_t = 0
1183    ELSEIF ( bc_salsa_t == 'neumann' )  THEN
1184       ibc_salsa_t = 1
1185    ELSEIF ( bc_salsa_t == 'initial_gradient' )  THEN
1186       ibc_salsa_t = 2
1187    ELSEIF ( bc_salsa_t == 'nested'  .OR.  bc_salsa_t == 'nesting_offline' )  THEN
1188       ibc_salsa_t = 3
1189    ELSE
1190       message_string = 'unknown boundary condition: bc_salsa_t = "' // TRIM( bc_salsa_t ) // '"'
1191       CALL message( 'salsa_check_parameters', 'PA0596', 1, 2, 0, 6, 0 )
1192    ENDIF
1193!
1194!-- Check J3 parametrisation
1195    IF ( nj3 < 1  .OR.  nj3 > 3 )  THEN
1196       message_string = 'unknown nj3 (must be 1-3)'
1197       CALL message( 'salsa_check_parameters', 'PA0597', 1, 2, 0, 6, 0 )
1198    ENDIF
1199!
1200!-- Check bottom boundary condition in case of surface emissions
1201    IF ( salsa_emission_mode /= 'no_emission'  .AND.  ibc_salsa_b  == 0 ) THEN
1202       message_string = 'salsa_emission_mode /= "no_emission" requires bc_salsa_b = "Neumann"'
1203       CALL message( 'salsa_check_parameters','PA0598', 1, 2, 0, 6, 0 )
1204    ENDIF
1205!
1206!-- Check whether emissions are applied
1207    IF ( salsa_emission_mode /= 'no_emission' )  include_emission = .TRUE.
1208!
1209!-- Set the initialisation type: background concentration are read from PIDS_DYNAMIC if
1210!-- initializing_actions = 'inifor set_constant_profiles'
1211    IF ( INDEX( initializing_actions, 'inifor' ) /= 0 )  THEN
1212       init_aerosol_type = 1
1213       init_gases_type = 1
1214    ENDIF
1215!
1216!-- If the run is not a restart run, set read_restart_data to .FALSE.
1217    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
1218       read_restart_data_salsa = .FALSE.
1219    ENDIF
1220
1221 END SUBROUTINE salsa_check_parameters
1222
1223!------------------------------------------------------------------------------!
1224!
1225! Description:
1226! ------------
1227!> Subroutine defining appropriate grid for netcdf variables.
1228!> It is called out from subroutine netcdf.
1229!> Same grid as for other scalars (see netcdf_interface_mod.f90)
1230!------------------------------------------------------------------------------!
1231 SUBROUTINE salsa_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
1232
1233    IMPLICIT NONE
1234
1235    CHARACTER(LEN=*), INTENT(OUT) ::  grid_x   !<
1236    CHARACTER(LEN=*), INTENT(OUT) ::  grid_y   !<
1237    CHARACTER(LEN=*), INTENT(OUT) ::  grid_z   !<
1238    CHARACTER(LEN=*), INTENT(IN)  ::  var      !<
1239
1240    LOGICAL, INTENT(OUT) ::  found   !<
1241
1242    found  = .TRUE.
1243!
1244!-- Check for the grid
1245
1246    IF ( var(1:6) == 'salsa_' )  THEN  ! same grid for all salsa output variables
1247       grid_x = 'x'
1248       grid_y = 'y'
1249       grid_z = 'zu'
1250    ELSE
1251       found  = .FALSE.
1252       grid_x = 'none'
1253       grid_y = 'none'
1254       grid_z = 'none'
1255    ENDIF
1256
1257 END SUBROUTINE salsa_define_netcdf_grid
1258
1259!------------------------------------------------------------------------------!
1260! Description:
1261! ------------
1262!> Header output for new module
1263!------------------------------------------------------------------------------!
1264 SUBROUTINE salsa_header( io )
1265
1266    USE indices,                                                                                   &
1267        ONLY:  nx, ny, nz
1268
1269    IMPLICIT NONE
1270 
1271    INTEGER(iwp), INTENT(IN) ::  io   !< Unit of the output file
1272!
1273!-- Write SALSA header
1274    WRITE( io, 1 )
1275    WRITE( io, 2 ) skip_time_do_salsa
1276    WRITE( io, 3 ) dt_salsa
1277    WRITE( io, 4 )  nz, ny, nx, nbins_aerosol
1278    IF ( advect_particle_water )  THEN
1279       WRITE( io, 5 )  nz, ny, nx, ncomponents_mass*nbins_aerosol, advect_particle_water
1280    ELSE
1281       WRITE( io, 5 )  nz, ny, nx, ncc*nbins_aerosol, advect_particle_water
1282    ENDIF
1283    IF ( .NOT. salsa_gases_from_chem )  THEN
1284       WRITE( io, 6 )  nz, ny, nx, ngases_salsa, salsa_gases_from_chem
1285    ENDIF
1286    WRITE( io, 7 )
1287    IF ( nsnucl > 0 )   WRITE( io, 8 ) nsnucl, nj3
1288    IF ( nlcoag )       WRITE( io, 9 )
1289    IF ( nlcnd )        WRITE( io, 10 ) nlcndgas, nlcndh2oae
1290    IF ( lspartition )  WRITE( io, 11 )
1291    IF ( nldepo )       WRITE( io, 12 ) nldepo_pcm, nldepo_surf
1292    WRITE( io, 13 )  reglim, nbin, ( aero(:)%vlolim / api6 )**0.33333333_wp
1293    WRITE( io, 25 )  aero(:)%dmid
1294    IF ( init_aerosol_type == 0 )  WRITE( io, 14 ) nsect
1295    WRITE( io, 15 ) ncc, listspec, mass_fracs_a, mass_fracs_b
1296    IF ( .NOT. salsa_gases_from_chem )  THEN
1297       WRITE( io, 16 ) ngases_salsa, h2so4_init, hno3_init, nh3_init, ocnv_init, ocsv_init
1298    ENDIF
1299    WRITE( io, 17 )  init_aerosol_type, init_gases_type
1300    IF ( init_aerosol_type == 0 )  THEN
1301       WRITE( io, 18 )  dpg, sigmag, n_lognorm
1302    ELSE
1303       WRITE( io, 19 )
1304    ENDIF
1305    IF ( nesting_salsa )  WRITE( io, 20 )  nesting_salsa
1306    IF ( nesting_offline_salsa )  WRITE( io, 21 )  nesting_offline_salsa
1307    WRITE( io, 22 ) salsa_emission_mode
1308    IF ( salsa_emission_mode == 'uniform' )  THEN
1309       WRITE( io, 23 ) surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag,                &
1310                       aerosol_flux_mass_fracs_a
1311    ENDIF
1312    IF ( SUM( aerosol_flux_mass_fracs_b ) > 0.0_wp  .OR. salsa_emission_mode == 'read_from_file' ) &
1313    THEN
1314       WRITE( io, 24 )
1315    ENDIF
1316
13171   FORMAT (//' SALSA information:'/                                                               &
1318              ' ------------------------------'/)
13192   FORMAT   ('    Starts at: skip_time_do_salsa = ', F10.2, '  s')
13203   FORMAT  (/'    Timestep: dt_salsa = ', F6.2, '  s')
13214   FORMAT  (/'    Array shape (z,y,x,bins):'/                                                     &
1322              '       aerosol_number:  ', 4(I5)) 
13235   FORMAT  (/'       aerosol_mass:    ', 4(I5),/                                                  &
1324              '       (advect_particle_water = ', L1, ')')
13256   FORMAT   ('       salsa_gas: ', 4(I5),/                                                        &
1326              '       (salsa_gases_from_chem = ', L1, ')')
13277   FORMAT  (/'    Aerosol dynamic processes included: ')
13288   FORMAT  (/'       nucleation (scheme = ', I1, ' and J3 parametrization = ', I1, ')')
13299   FORMAT  (/'       coagulation')
133010  FORMAT  (/'       condensation (of precursor gases = ', L1, ' and water vapour = ', L1, ')' )
133111  FORMAT  (/'       dissolutional growth by HNO3 and NH3')
133212  FORMAT  (/'       dry deposition (on vegetation = ', L1, ' and on topography = ', L1, ')')
133313  FORMAT  (/'    Aerosol bin subrange limits (in metres): ',  3(ES10.2E3), /                     &
1334              '    Number of size bins for each aerosol subrange: ', 2I3,/                         &
1335              '    Aerosol bin lower limits (in metres): ', 12(ES10.2E3))
133625  FORMAT  (/'    Bin geometric mean diameters (in metres): ', 12(ES10.2E3))
133714  FORMAT   ('    Initial number concentration in bins at the lowest level (#/m**3):', 9(ES10.2E3))
133815  FORMAT  (/'    Number of chemical components used: ', I1,/                                     &
1339              '       Species: ',7(A6),/                                                           &
1340              '    Initial relative contribution of each species to particle volume in:',/         &
1341              '       a-bins: ', 7(F6.3),/                                                         &
1342              '       b-bins: ', 7(F6.3))
134316  FORMAT  (/'    Number of gaseous tracers used: ', I1,/                                         &
1344              '    Initial gas concentrations:',/                                                  &
1345              '       H2SO4: ',ES12.4E3, ' #/m**3',/                                               &
1346              '       HNO3:  ',ES12.4E3, ' #/m**3',/                                               &
1347              '       NH3:   ',ES12.4E3, ' #/m**3',/                                               &
1348              '       OCNV:  ',ES12.4E3, ' #/m**3',/                                               &
1349              '       OCSV:  ',ES12.4E3, ' #/m**3')
135017   FORMAT (/'   Initialising concentrations: ', /                                                &
1351              '      Aerosol size distribution: init_aerosol_type = ', I1,/                        &
1352              '      Gas concentrations: init_gases_type = ', I1 )
135318   FORMAT ( '      Mode diametres: dpg(nmod) = ', 7(F7.3), ' (m)', /                             &
1354              '      Standard deviation: sigmag(nmod) = ', 7(F7.2),/                               &
1355              '      Number concentration: n_lognorm(nmod) = ', 7(ES12.4E3), ' (#/m3)' )
135619   FORMAT (/'      Size distribution read from a file.')
135720   FORMAT (/'   Nesting for salsa variables: ', L1 )
135821   FORMAT (/'   Offline nesting for salsa variables: ', L1 )
135922   FORMAT (/'   Emissions: salsa_emission_mode = ', A )
136023   FORMAT (/'      surface_aerosol_flux = ', ES12.4E3, ' #/m**2/s', /                            &
1361              '      aerosol_flux_dpg     =  ', 7(F7.3), ' (m)', /                                 &
1362              '      aerosol_flux_sigmag  =  ', 7(F7.2), /                                         &
1363              '      aerosol_mass_fracs_a =  ', 7(ES12.4E3) )
136424   FORMAT (/'      (currently all emissions are soluble!)')
1365
1366 END SUBROUTINE salsa_header
1367
1368!------------------------------------------------------------------------------!
1369! Description:
1370! ------------
1371!> Allocate SALSA arrays and define pointers if required
1372!------------------------------------------------------------------------------!
1373 SUBROUTINE salsa_init_arrays
1374
1375    USE advec_ws,                                                                                  &
1376        ONLY: ws_init_flags_scalar
1377
1378    USE surface_mod,                                                                               &
1379        ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
1380
1381    IMPLICIT NONE
1382
1383    INTEGER(iwp) ::  gases_available !< Number of available gas components in the chemistry model
1384    INTEGER(iwp) ::  i               !< loop index for allocating
1385    INTEGER(iwp) ::  ii              !< index for indexing chemical components
1386    INTEGER(iwp) ::  l               !< loop index for allocating: surfaces
1387    INTEGER(iwp) ::  lsp             !< loop index for chem species in the chemistry model
1388
1389    gases_available = 0
1390!
1391!-- Allocate prognostic variables (see salsa_swap_timelevel)
1392!
1393!-- Set derived indices:
1394!-- (This does the same as the subroutine salsa_initialize in SALSA/UCLALES-SALSA)
1395    start_subrange_1a = 1  ! 1st index of subrange 1a
1396    start_subrange_2a = start_subrange_1a + nbin(1)  ! 1st index of subrange 2a
1397    end_subrange_1a   = start_subrange_2a - 1        ! last index of subrange 1a
1398    end_subrange_2a   = end_subrange_1a + nbin(2)    ! last index of subrange 2a
1399
1400!
1401!-- If the fraction of insoluble aerosols in subrange 2 is zero: do not allocate arrays for them
1402    IF ( nf2a > 0.999999_wp  .AND.  SUM( mass_fracs_b ) < 0.00001_wp )  THEN
1403       no_insoluble = .TRUE.
1404       start_subrange_2b = end_subrange_2a+1  ! 1st index of subrange 2b
1405       end_subrange_2b   = end_subrange_2a    ! last index of subrange 2b
1406    ELSE
1407       start_subrange_2b = start_subrange_2a + nbin(2)  ! 1st index of subrange 2b
1408       end_subrange_2b   = end_subrange_2a + nbin(2)    ! last index of subrange 2b
1409    ENDIF
1410
1411    nbins_aerosol = end_subrange_2b   ! total number of aerosol size bins
1412!
1413!-- Create index tables for different aerosol components
1414    CALL component_index_constructor( prtcl, ncc, maxspec, listspec )
1415
1416    ncomponents_mass = ncc
1417    IF ( advect_particle_water )  ncomponents_mass = ncc + 1  ! Add water
1418!
1419!-- Indices for chemical components used (-1 = not used)
1420    ii = 0
1421    IF ( is_used( prtcl, 'SO4' ) )  THEN
1422       index_so4 = get_index( prtcl,'SO4' )
1423       ii = ii + 1
1424    ENDIF
1425    IF ( is_used( prtcl,'OC' ) )  THEN
1426       index_oc = get_index(prtcl, 'OC')
1427       ii = ii + 1
1428    ENDIF
1429    IF ( is_used( prtcl, 'BC' ) )  THEN
1430       index_bc = get_index( prtcl, 'BC' )
1431       ii = ii + 1
1432    ENDIF
1433    IF ( is_used( prtcl, 'DU' ) )  THEN
1434       index_du = get_index( prtcl, 'DU' )
1435       ii = ii + 1
1436    ENDIF
1437    IF ( is_used( prtcl, 'SS' ) )  THEN
1438       index_ss = get_index( prtcl, 'SS' )
1439       ii = ii + 1
1440    ENDIF
1441    IF ( is_used( prtcl, 'NO' ) )  THEN
1442       index_no = get_index( prtcl, 'NO' )
1443       ii = ii + 1
1444    ENDIF
1445    IF ( is_used( prtcl, 'NH' ) )  THEN
1446       index_nh = get_index( prtcl, 'NH' )
1447       ii = ii + 1
1448    ENDIF
1449!
1450!-- All species must be known
1451    IF ( ii /= ncc )  THEN
1452       message_string = 'Unknown aerosol species/component(s) given in the initialization'
1453       CALL message( 'salsa_mod: salsa_init', 'PA0600', 1, 2, 0, 6, 0 )
1454    ENDIF
1455!
1456!-- Allocate:
1457    ALLOCATE( aero(nbins_aerosol), bc_am_t_val(nbins_aerosol*ncomponents_mass),                    &
1458              bc_an_t_val(nbins_aerosol), bc_gt_t_val(ngases_salsa), bin_low_limits(nbins_aerosol),&
1459              nsect(nbins_aerosol), massacc(nbins_aerosol) )
1460    ALLOCATE( k_topo_top(nysg:nyng,nxlg:nxrg) )
1461    IF ( nldepo ) ALLOCATE( sedim_vd(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
1462    ALLOCATE( ra_dry(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
1463!
1464!-- Initialise the sectional particle size distribution
1465    CALL set_sizebins
1466!
1467!-- Aerosol number concentration
1468    ALLOCATE( aerosol_number(nbins_aerosol) )
1469    ALLOCATE( nconc_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol),                                &
1470              nconc_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol),                                &
1471              nconc_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
1472    nconc_1 = 0.0_wp
1473    nconc_2 = 0.0_wp
1474    nconc_3 = 0.0_wp
1475
1476    DO i = 1, nbins_aerosol
1477       aerosol_number(i)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    => nconc_1(:,:,:,i)
1478       aerosol_number(i)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => nconc_2(:,:,:,i)
1479       aerosol_number(i)%tconc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => nconc_3(:,:,:,i)
1480       ALLOCATE( aerosol_number(i)%flux_s(nzb+1:nzt,0:threads_per_task-1),                         &
1481                 aerosol_number(i)%diss_s(nzb+1:nzt,0:threads_per_task-1),                         &
1482                 aerosol_number(i)%flux_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                 &
1483                 aerosol_number(i)%diss_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                 &
1484                 aerosol_number(i)%init(nzb:nzt+1),                                                &
1485                 aerosol_number(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1) )
1486       aerosol_number(i)%init = nclim
1487       IF ( include_emission  .OR.  ( nldepo  .AND.  nldepo_surf ) )  THEN
1488          ALLOCATE( aerosol_number(i)%source(nys:nyn,nxl:nxr) )
1489          aerosol_number(i)%source = 0.0_wp
1490       ENDIF
1491    ENDDO
1492
1493!
1494!-- Aerosol mass concentration
1495    ALLOCATE( aerosol_mass(ncomponents_mass*nbins_aerosol) )
1496    ALLOCATE( mconc_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ncomponents_mass*nbins_aerosol),               &
1497              mconc_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ncomponents_mass*nbins_aerosol),               &
1498              mconc_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ncomponents_mass*nbins_aerosol) )
1499    mconc_1 = 0.0_wp
1500    mconc_2 = 0.0_wp
1501    mconc_3 = 0.0_wp
1502
1503    DO i = 1, ncomponents_mass*nbins_aerosol
1504       aerosol_mass(i)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    => mconc_1(:,:,:,i)
1505       aerosol_mass(i)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => mconc_2(:,:,:,i)
1506       aerosol_mass(i)%tconc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => mconc_3(:,:,:,i)
1507       ALLOCATE( aerosol_mass(i)%flux_s(nzb+1:nzt,0:threads_per_task-1),                           &
1508                 aerosol_mass(i)%diss_s(nzb+1:nzt,0:threads_per_task-1),                           &
1509                 aerosol_mass(i)%flux_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                   &
1510                 aerosol_mass(i)%diss_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                   &
1511                 aerosol_mass(i)%init(nzb:nzt+1),                                                  &
1512                 aerosol_mass(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1)  )
1513       aerosol_mass(i)%init = mclim
1514       IF ( include_emission  .OR.  ( nldepo  .AND.  nldepo_surf ) )  THEN
1515          ALLOCATE( aerosol_mass(i)%source(nys:nyn,nxl:nxr) )
1516          aerosol_mass(i)%source = 0.0_wp
1517       ENDIF
1518    ENDDO
1519
1520!
1521!-- Surface fluxes: answs = aerosol number, amsws = aerosol mass
1522!
1523!-- Horizontal surfaces: default type
1524    DO  l = 0, 2   ! upward (l=0), downward (l=1) and model top (l=2)
1525       ALLOCATE( surf_def_h(l)%answs( 1:surf_def_h(l)%ns, nbins_aerosol ) )
1526       ALLOCATE( surf_def_h(l)%amsws( 1:surf_def_h(l)%ns, nbins_aerosol*ncomponents_mass ) )
1527       surf_def_h(l)%answs = 0.0_wp
1528       surf_def_h(l)%amsws = 0.0_wp
1529    ENDDO
1530!
1531!-- Horizontal surfaces: natural type
1532    ALLOCATE( surf_lsm_h%answs( 1:surf_lsm_h%ns, nbins_aerosol ) )
1533    ALLOCATE( surf_lsm_h%amsws( 1:surf_lsm_h%ns, nbins_aerosol*ncomponents_mass ) )
1534    surf_lsm_h%answs = 0.0_wp
1535    surf_lsm_h%amsws = 0.0_wp
1536!
1537!-- Horizontal surfaces: urban type
1538    ALLOCATE( surf_usm_h%answs( 1:surf_usm_h%ns, nbins_aerosol ) )
1539    ALLOCATE( surf_usm_h%amsws( 1:surf_usm_h%ns, nbins_aerosol*ncomponents_mass ) )
1540    surf_usm_h%answs = 0.0_wp
1541    surf_usm_h%amsws = 0.0_wp
1542
1543!
1544!-- Vertical surfaces: northward (l=0), southward (l=1), eastward (l=2) and westward (l=3) facing
1545    DO  l = 0, 3
1546       ALLOCATE( surf_def_v(l)%answs( 1:surf_def_v(l)%ns, nbins_aerosol ) )
1547       surf_def_v(l)%answs = 0.0_wp
1548       ALLOCATE( surf_def_v(l)%amsws( 1:surf_def_v(l)%ns, nbins_aerosol*ncomponents_mass ) )
1549       surf_def_v(l)%amsws = 0.0_wp
1550
1551       ALLOCATE( surf_lsm_v(l)%answs( 1:surf_lsm_v(l)%ns, nbins_aerosol ) )
1552       surf_lsm_v(l)%answs = 0.0_wp
1553       ALLOCATE( surf_lsm_v(l)%amsws( 1:surf_lsm_v(l)%ns, nbins_aerosol*ncomponents_mass ) )
1554       surf_lsm_v(l)%amsws = 0.0_wp
1555
1556       ALLOCATE( surf_usm_v(l)%answs( 1:surf_usm_v(l)%ns, nbins_aerosol ) )
1557       surf_usm_v(l)%answs = 0.0_wp
1558       ALLOCATE( surf_usm_v(l)%amsws( 1:surf_usm_v(l)%ns, nbins_aerosol*ncomponents_mass ) )
1559       surf_usm_v(l)%amsws = 0.0_wp
1560
1561    ENDDO
1562
1563!
1564!-- Concentration of gaseous tracers (1. SO4, 2. HNO3, 3. NH3, 4. OCNV, 5. OCSV)
1565!-- (number concentration (#/m3) )
1566!
1567!-- If chemistry is on, read gas phase concentrations from there. Otherwise,
1568!-- allocate salsa_gas array.
1569
1570    IF ( air_chemistry )  THEN
1571       DO  lsp = 1, nvar
1572          SELECT CASE ( TRIM( chem_species(lsp)%name ) )
1573             CASE ( 'H2SO4', 'h2so4' )
1574                gases_available = gases_available + 1
1575                gas_index_chem(1) = lsp
1576             CASE ( 'HNO3', 'hno3' )
1577                gases_available = gases_available + 1
1578                gas_index_chem(2) = lsp
1579             CASE ( 'NH3', 'nh3' )
1580                gases_available = gases_available + 1
1581                gas_index_chem(3) = lsp
1582             CASE ( 'OCNV', 'ocnv' )
1583                gases_available = gases_available + 1
1584                gas_index_chem(4) = lsp
1585             CASE ( 'OCSV', 'ocsv' )
1586                gases_available = gases_available + 1
1587                gas_index_chem(5) = lsp
1588          END SELECT
1589       ENDDO
1590
1591       IF ( gases_available == ngases_salsa )  THEN
1592          salsa_gases_from_chem = .TRUE.
1593       ELSE
1594          WRITE( message_string, * ) 'SALSA is run together with chemistry but not all gaseous '// &
1595                                     'components are provided by kpp (H2SO4, HNO3, NH3, OCNV, OCSV)'
1596       CALL message( 'check_parameters', 'PA0599', 1, 2, 0, 6, 0 )
1597       ENDIF
1598
1599    ELSE
1600
1601       ALLOCATE( salsa_gas(ngases_salsa) )
1602       ALLOCATE( gconc_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ngases_salsa),                 &
1603                 gconc_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ngases_salsa),                 &
1604                 gconc_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ngases_salsa) )
1605       gconc_1 = 0.0_wp
1606       gconc_2 = 0.0_wp
1607       gconc_3 = 0.0_wp
1608
1609       DO i = 1, ngases_salsa
1610          salsa_gas(i)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    => gconc_1(:,:,:,i)
1611          salsa_gas(i)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => gconc_2(:,:,:,i)
1612          salsa_gas(i)%tconc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => gconc_3(:,:,:,i)
1613          ALLOCATE( salsa_gas(i)%flux_s(nzb+1:nzt,0:threads_per_task-1),       &
1614                    salsa_gas(i)%diss_s(nzb+1:nzt,0:threads_per_task-1),       &
1615                    salsa_gas(i)%flux_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),&
1616                    salsa_gas(i)%diss_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),&
1617                    salsa_gas(i)%init(nzb:nzt+1),                              &
1618                    salsa_gas(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1) )
1619          salsa_gas(i)%init = nclim
1620          IF ( include_emission )  THEN
1621             ALLOCATE( salsa_gas(i)%source(nys:nys,nxl:nxr) )
1622             salsa_gas(i)%source = 0.0_wp
1623          ENDIF
1624       ENDDO
1625!
1626!--    Surface fluxes: gtsws = gaseous tracer flux
1627!
1628!--    Horizontal surfaces: default type
1629       DO  l = 0, 2   ! upward (l=0), downward (l=1) and model top (l=2)
1630          ALLOCATE( surf_def_h(l)%gtsws( 1:surf_def_h(l)%ns, ngases_salsa ) )
1631          surf_def_h(l)%gtsws = 0.0_wp
1632       ENDDO
1633!--    Horizontal surfaces: natural type
1634       ALLOCATE( surf_lsm_h%gtsws( 1:surf_lsm_h%ns, ngases_salsa ) )
1635       surf_lsm_h%gtsws = 0.0_wp
1636!--    Horizontal surfaces: urban type
1637       ALLOCATE( surf_usm_h%gtsws( 1:surf_usm_h%ns, ngases_salsa ) )
1638       surf_usm_h%gtsws = 0.0_wp
1639!
1640!--    Vertical surfaces: northward (l=0), southward (l=1), eastward (l=2) and
1641!--    westward (l=3) facing
1642       DO  l = 0, 3
1643          ALLOCATE( surf_def_v(l)%gtsws( 1:surf_def_v(l)%ns, ngases_salsa ) )
1644          surf_def_v(l)%gtsws = 0.0_wp
1645          ALLOCATE( surf_lsm_v(l)%gtsws( 1:surf_lsm_v(l)%ns, ngases_salsa ) )
1646          surf_lsm_v(l)%gtsws = 0.0_wp
1647          ALLOCATE( surf_usm_v(l)%gtsws( 1:surf_usm_v(l)%ns, ngases_salsa ) )
1648          surf_usm_v(l)%gtsws = 0.0_wp
1649       ENDDO
1650    ENDIF
1651
1652    IF ( ws_scheme_sca )  THEN
1653
1654       IF ( salsa )  THEN
1655          ALLOCATE( sums_salsa_ws_l(nzb:nzt+1,0:threads_per_task-1) )
1656          sums_salsa_ws_l = 0.0_wp
1657       ENDIF
1658
1659    ENDIF
1660!
1661!-- Set control flags for decycling only at lateral boundary cores. Within the inner cores the
1662!-- decycle flag is set to .FALSE.. Even though it does not affect the setting of chemistry boundary
1663!-- conditions, this flag is used to set advection control flags appropriately.
1664    decycle_salsa_lr = MERGE( decycle_salsa_lr, .FALSE., nxl == 0  .OR.  nxr == nx )
1665    decycle_salsa_ns = MERGE( decycle_salsa_ns, .FALSE., nys == 0  .OR.  nyn == ny )
1666!
1667!-- Decycling can be applied separately for aerosol variables, while wind and other scalars may have
1668!-- cyclic or nested boundary conditions. However, large gradients near the boundaries may produce
1669!-- stationary numerical oscillations near the lateral boundaries when a higher-order scheme is
1670!-- applied near these boundaries. To get rid-off this, set-up additional flags that control the
1671!-- order of the scalar advection scheme near the lateral boundaries for passive scalars with
1672!-- decycling.
1673    IF ( scalar_advec == 'ws-scheme' )  THEN
1674       ALLOCATE( salsa_advc_flags_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1675!
1676!--    In case of decycling, set Neuman boundary conditions for wall_flags_total_0 bit 31 instead of
1677!--    cyclic boundary conditions. Bit 31 is used to identify extended degradation zones (please see
1678!--    the following comment). Note, since several also other modules may access this bit but may
1679!--    have other boundary conditions, the original value of wall_flags_total_0 bit 31 must not be
1680!--    modified. Hence, store the boundary conditions directly on salsa_advc_flags_s.
1681!--    salsa_advc_flags_s will be later overwritten in ws_init_flags_scalar and bit 31 won't be used
1682!--    to control the numerical order.
1683!--    Initialize with flag 31 only.
1684       salsa_advc_flags_s = 0
1685       salsa_advc_flags_s = MERGE( IBSET( salsa_advc_flags_s, 31 ), 0, BTEST( wall_flags_total_0, 31 ) )
1686
1687       IF ( decycle_salsa_ns )  THEN
1688          IF ( nys == 0 )  THEN
1689             DO  i = 1, nbgp
1690                salsa_advc_flags_s(:,nys-i,:) = MERGE( IBSET( salsa_advc_flags_s(:,nys,:), 31 ),   &
1691                                                       IBCLR( salsa_advc_flags_s(:,nys,:), 31 ),   &
1692                                                       BTEST( salsa_advc_flags_s(:,nys,:), 31 ) )
1693             ENDDO
1694          ENDIF
1695          IF ( nyn == ny )  THEN
1696             DO  i = 1, nbgp
1697                salsa_advc_flags_s(:,nyn+i,:) = MERGE( IBSET( salsa_advc_flags_s(:,nyn,:), 31 ),   &
1698                                                       IBCLR( salsa_advc_flags_s(:,nyn,:), 31 ),   &
1699                                                       BTEST( salsa_advc_flags_s(:,nyn,:), 31 ) )
1700             ENDDO
1701          ENDIF
1702       ENDIF
1703       IF ( decycle_salsa_lr )  THEN
1704          IF ( nxl == 0 )  THEN
1705             DO  i = 1, nbgp
1706                salsa_advc_flags_s(:,:,nxl-i) = MERGE( IBSET( salsa_advc_flags_s(:,:,nxl), 31 ),   &
1707                                                       IBCLR( salsa_advc_flags_s(:,:,nxl), 31 ),   &
1708                                                       BTEST( salsa_advc_flags_s(:,:,nxl), 31 ) )
1709             ENDDO
1710          ENDIF
1711          IF ( nxr == nx )  THEN
1712             DO  i = 1, nbgp
1713                salsa_advc_flags_s(:,:,nxr+i) = MERGE( IBSET( salsa_advc_flags_s(:,:,nxr), 31 ),   &
1714                                                       IBCLR( salsa_advc_flags_s(:,:,nxr), 31 ),   &
1715                                                       BTEST( salsa_advc_flags_s(:,:,nxr), 31 ) )
1716             ENDDO
1717          ENDIF
1718       ENDIF
1719!
1720!--    To initialise the advection flags appropriately, pass the boundary flags to
1721!--    ws_init_flags_scalar. The last argument in ws_init_flags_scalar indicates that a passive
1722!--    scalar is being treated and the horizontal advection terms are degraded already 2 grid points
1723!--    before the lateral boundary. Also, extended degradation zones are applied, where
1724!--    horizontal advection of scalars is discretised by the first-order scheme at all grid points
1725!--    in the vicinity of buildings (<= 3 grid points). Even though no building is within the
1726!--    numerical stencil, the first-order scheme is used. At fourth and fifth grid points, the order
1727!--    of the horizontal advection scheme is successively upgraded.
1728!--    These degradations of the advection scheme are done to avoid stationary numerical
1729!--    oscillations, which are responsible for high concentration maxima that may appear e.g. under
1730!--    shear-free stable conditions.
1731       CALL ws_init_flags_scalar( bc_dirichlet_l  .OR.  bc_radiation_l  .OR.  decycle_salsa_lr,    &
1732                                  bc_dirichlet_n  .OR.  bc_radiation_n  .OR.  decycle_salsa_ns,    &
1733                                  bc_dirichlet_r  .OR.  bc_radiation_r  .OR.  decycle_salsa_lr,    &
1734                                  bc_dirichlet_s  .OR.  bc_radiation_s  .OR.  decycle_salsa_ns,    &
1735                                  salsa_advc_flags_s, .TRUE. )
1736    ENDIF
1737
1738
1739 END SUBROUTINE salsa_init_arrays
1740
1741!------------------------------------------------------------------------------!
1742! Description:
1743! ------------
1744!> Initialization of SALSA. Based on salsa_initialize in UCLALES-SALSA.
1745!> Subroutines salsa_initialize, SALSAinit and DiagInitAero in UCLALES-SALSA are
1746!> also merged here.
1747!------------------------------------------------------------------------------!
1748 SUBROUTINE salsa_init
1749
1750    IMPLICIT NONE
1751
1752    INTEGER(iwp) :: i   !<
1753    INTEGER(iwp) :: ib  !< loop index for aerosol number bins
1754    INTEGER(iwp) :: ic  !< loop index for aerosol mass bins
1755    INTEGER(iwp) :: ig  !< loop index for gases
1756    INTEGER(iwp) :: j   !<
1757
1758    IF ( debug_output )  CALL debug_message( 'salsa_init', 'start' )
1759
1760    bin_low_limits = 0.0_wp
1761    k_topo_top     = 0
1762    nsect          = 0.0_wp
1763    massacc        = 1.0_wp
1764!
1765!-- Initialise
1766    IF ( nldepo )  sedim_vd = 0.0_wp
1767
1768    IF ( .NOT. salsa_gases_from_chem )  THEN
1769       IF ( .NOT. read_restart_data_salsa )  THEN
1770          salsa_gas(1)%conc = h2so4_init
1771          salsa_gas(2)%conc = hno3_init
1772          salsa_gas(3)%conc = nh3_init
1773          salsa_gas(4)%conc = ocnv_init
1774          salsa_gas(5)%conc = ocsv_init
1775       ENDIF
1776       DO  ig = 1, ngases_salsa
1777          salsa_gas(ig)%conc_p    = 0.0_wp
1778          salsa_gas(ig)%tconc_m   = 0.0_wp
1779          salsa_gas(ig)%flux_s    = 0.0_wp
1780          salsa_gas(ig)%diss_s    = 0.0_wp
1781          salsa_gas(ig)%flux_l    = 0.0_wp
1782          salsa_gas(ig)%diss_l    = 0.0_wp
1783          salsa_gas(ig)%sums_ws_l = 0.0_wp
1784          salsa_gas(ig)%conc_p    = salsa_gas(ig)%conc
1785       ENDDO
1786!
1787!--    Set initial value for gas compound tracer
1788       salsa_gas(1)%init = h2so4_init
1789       salsa_gas(2)%init = hno3_init
1790       salsa_gas(3)%init = nh3_init
1791       salsa_gas(4)%init = ocnv_init
1792       salsa_gas(5)%init = ocsv_init
1793    ENDIF
1794!
1795!-- Aerosol radius in each bin: dry and wet (m)
1796    ra_dry = 1.0E-10_wp
1797!
1798!-- Initialise location-dependent aerosol size distributions and chemical compositions:
1799    CALL aerosol_init
1800
1801!-- Initalisation run of SALSA + calculate the vertical top index of the topography
1802    DO  i = nxl, nxr
1803       DO  j = nys, nyn
1804
1805          k_topo_top(j,i) = MAXLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,j,i), 12 ) ), &
1806                                       DIM = 1 ) - 1
1807
1808          CALL salsa_driver( i, j, 1 )
1809          CALL salsa_diagnostics( i, j )
1810       ENDDO
1811    ENDDO
1812
1813    DO  ib = 1, nbins_aerosol
1814       aerosol_number(ib)%conc_p    = aerosol_number(ib)%conc
1815       aerosol_number(ib)%tconc_m   = 0.0_wp
1816       aerosol_number(ib)%flux_s    = 0.0_wp
1817       aerosol_number(ib)%diss_s    = 0.0_wp
1818       aerosol_number(ib)%flux_l    = 0.0_wp
1819       aerosol_number(ib)%diss_l    = 0.0_wp
1820       aerosol_number(ib)%sums_ws_l = 0.0_wp
1821    ENDDO
1822    DO  ic = 1, ncomponents_mass*nbins_aerosol
1823       aerosol_mass(ic)%conc_p    = aerosol_mass(ic)%conc
1824       aerosol_mass(ic)%tconc_m   = 0.0_wp
1825       aerosol_mass(ic)%flux_s    = 0.0_wp
1826       aerosol_mass(ic)%diss_s    = 0.0_wp
1827       aerosol_mass(ic)%flux_l    = 0.0_wp
1828       aerosol_mass(ic)%diss_l    = 0.0_wp
1829       aerosol_mass(ic)%sums_ws_l = 0.0_wp
1830    ENDDO
1831!
1832!
1833!-- Initialise the deposition scheme and surface types
1834    IF ( nldepo )  CALL init_deposition
1835
1836    IF ( include_emission )  THEN
1837!
1838!--    Read in and initialize emissions
1839       CALL salsa_emission_setup( .TRUE. )
1840       IF ( .NOT. salsa_gases_from_chem  .AND.  salsa_emission_mode == 'read_from_file' )  THEN
1841          CALL salsa_gas_emission_setup( .TRUE. )
1842       ENDIF
1843    ENDIF
1844!
1845!-- Partition and dissolutional growth by gaseous HNO3 and NH3
1846    IF ( index_no > 0  .AND.  index_nh > 0  .AND.  index_so4 > 0 )  lspartition = .TRUE.
1847
1848    IF ( debug_output )  CALL debug_message( 'salsa_init', 'end' )
1849
1850 END SUBROUTINE salsa_init
1851
1852!------------------------------------------------------------------------------!
1853! Description:
1854! ------------
1855!> Initializes particle size distribution grid by calculating size bin limits
1856!> and mid-size for *dry* particles in each bin. Called from salsa_initialize
1857!> (only at the beginning of simulation).
1858!> Size distribution described using:
1859!>   1) moving center method (subranges 1 and 2)
1860!>      (Jacobson, Atmos. Env., 31, 131-144, 1997)
1861!>   2) fixed sectional method (subrange 3)
1862!> Size bins in each subrange are spaced logarithmically
1863!> based on given subrange size limits and bin number.
1864!
1865!> Mona changed 06/2017: Use geometric mean diameter to describe the mean
1866!> particle diameter in a size bin, not the arithmeric mean which clearly
1867!> overestimates the total particle volume concentration.
1868!
1869!> Coded by:
1870!> Hannele Korhonen (FMI) 2005
1871!> Harri Kokkola (FMI) 2006
1872!
1873!> Bug fixes for box model + updated for the new aerosol datatype:
1874!> Juha Tonttila (FMI) 2014
1875!------------------------------------------------------------------------------!
1876 SUBROUTINE set_sizebins
1877
1878    IMPLICIT NONE
1879
1880    INTEGER(iwp) ::  cc  !< running index
1881    INTEGER(iwp) ::  dd  !< running index
1882
1883    REAL(wp) ::  ratio_d  !< ratio of the upper and lower diameter of subranges
1884
1885    aero(:)%dwet     = 1.0E-10_wp
1886    aero(:)%veqh2o   = 1.0E-10_wp
1887    aero(:)%numc     = nclim
1888    aero(:)%core     = 1.0E-10_wp
1889    DO  cc = 1, maxspec+1    ! 1:SO4, 2:OC, 3:BC, 4:DU, 5:SS, 6:NO, 7:NH, 8:H2O
1890       aero(:)%volc(cc) = 0.0_wp
1891    ENDDO
1892!
1893!-- vlolim&vhilim: min & max *dry* volumes [fxm]
1894!-- dmid: bin mid *dry* diameter (m)
1895!-- vratiolo&vratiohi: volume ratio between the center and low/high limit
1896!
1897!-- 1) Size subrange 1:
1898    ratio_d = reglim(2) / reglim(1)   ! section spacing (m)
1899    DO  cc = start_subrange_1a, end_subrange_1a
1900       aero(cc)%vlolim = api6 * ( reglim(1) * ratio_d**( REAL( cc-1 ) / nbin(1) ) )**3
1901       aero(cc)%vhilim = api6 * ( reglim(1) * ratio_d**( REAL( cc ) / nbin(1) ) )**3
1902       aero(cc)%dmid = SQRT( ( aero(cc)%vhilim / api6 )**0.33333333_wp *                           &
1903                             ( aero(cc)%vlolim / api6 )**0.33333333_wp )
1904       aero(cc)%vratiohi = aero(cc)%vhilim / ( api6 * aero(cc)%dmid**3 )
1905       aero(cc)%vratiolo = aero(cc)%vlolim / ( api6 * aero(cc)%dmid**3 )
1906    ENDDO
1907!
1908!-- 2) Size subrange 2:
1909!-- 2.1) Sub-subrange 2a: high hygroscopicity
1910    ratio_d = reglim(3) / reglim(2)   ! section spacing
1911    DO  dd = start_subrange_2a, end_subrange_2a
1912       cc = dd - start_subrange_2a
1913       aero(dd)%vlolim = api6 * ( reglim(2) * ratio_d**( REAL( cc ) / nbin(2) ) )**3
1914       aero(dd)%vhilim = api6 * ( reglim(2) * ratio_d**( REAL( cc+1 ) / nbin(2) ) )**3
1915       aero(dd)%dmid = SQRT( ( aero(dd)%vhilim / api6 )**0.33333333_wp *                           &
1916                             ( aero(dd)%vlolim / api6 )**0.33333333_wp )
1917       aero(dd)%vratiohi = aero(dd)%vhilim / ( api6 * aero(dd)%dmid**3 )
1918       aero(dd)%vratiolo = aero(dd)%vlolim / ( api6 * aero(dd)%dmid**3 )
1919    ENDDO
1920!
1921!-- 2.2) Sub-subrange 2b: low hygroscopicity
1922    IF ( .NOT. no_insoluble )  THEN
1923       aero(start_subrange_2b:end_subrange_2b)%vlolim   = aero(start_subrange_2a:end_subrange_2a)%vlolim
1924       aero(start_subrange_2b:end_subrange_2b)%vhilim   = aero(start_subrange_2a:end_subrange_2a)%vhilim
1925       aero(start_subrange_2b:end_subrange_2b)%dmid     = aero(start_subrange_2a:end_subrange_2a)%dmid
1926       aero(start_subrange_2b:end_subrange_2b)%vratiohi = aero(start_subrange_2a:end_subrange_2a)%vratiohi
1927       aero(start_subrange_2b:end_subrange_2b)%vratiolo = aero(start_subrange_2a:end_subrange_2a)%vratiolo
1928    ENDIF
1929!
1930!-- Initialize the wet diameter with the bin dry diameter to avoid numerical problems later
1931    aero(:)%dwet = aero(:)%dmid
1932!
1933!-- Save bin limits (lower diameter) to be delivered to PALM if needed
1934    DO cc = 1, nbins_aerosol
1935       bin_low_limits(cc) = ( aero(cc)%vlolim / api6 )**0.33333333_wp
1936    ENDDO
1937
1938 END SUBROUTINE set_sizebins
1939
1940!------------------------------------------------------------------------------!
1941! Description:
1942! ------------
1943!> Initilize altitude-dependent aerosol size distributions and compositions.
1944!>
1945!> Mona added 06/2017: Correct the number and mass concentrations by normalizing
1946!< by the given total number and mass concentration.
1947!>
1948!> Tomi Raatikainen, FMI, 29.2.2016
1949!------------------------------------------------------------------------------!
1950 SUBROUTINE aerosol_init
1951
1952    USE netcdf_data_input_mod,                                                                     &
1953        ONLY:  check_existence, close_input_file, get_dimension_length,                            &
1954               get_attribute, get_variable,                                                        &
1955               inquire_num_variables, inquire_variable_names,                                      &
1956               open_read_file
1957
1958    IMPLICIT NONE
1959
1960    CHARACTER(LEN=25),  DIMENSION(:), ALLOCATABLE ::  cc_name    !< chemical component name
1961    CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< variable names
1962
1963    INTEGER(iwp) ::  ee        !< index: end
1964    INTEGER(iwp) ::  i         !< loop index: x-direction
1965    INTEGER(iwp) ::  ib        !< loop index: size bins
1966    INTEGER(iwp) ::  ic        !< loop index: chemical components
1967    INTEGER(iwp) ::  id_dyn    !< NetCDF id of PIDS_DYNAMIC_SALSA
1968    INTEGER(iwp) ::  ig        !< loop index: gases
1969    INTEGER(iwp) ::  j         !< loop index: y-direction
1970    INTEGER(iwp) ::  k         !< loop index: z-direction
1971    INTEGER(iwp) ::  lod_aero  !< level of detail of inital aerosol concentrations
1972    INTEGER(iwp) ::  num_vars  !< number of variables
1973    INTEGER(iwp) ::  pr_nbins  !< number of aerosol size bins in file
1974    INTEGER(iwp) ::  pr_ncc    !< number of aerosol chemical components in file
1975    INTEGER(iwp) ::  pr_nz     !< number of vertical grid-points in file
1976    INTEGER(iwp) ::  prunmode  !< running mode of SALSA
1977    INTEGER(iwp) ::  ss        !< index: start
1978
1979    INTEGER(iwp), DIMENSION(maxspec) ::  cc_in2mod
1980
1981    LOGICAL  ::  netcdf_extend = .FALSE. !< Flag: netcdf file exists
1982
1983    REAL(wp) ::  flag  !< flag to mask topography grid points
1984
1985    REAL(wp), DIMENSION(nbins_aerosol) ::  core   !< size of the bin mid aerosol particle
1986
1987    REAL(wp), DIMENSION(0:nz+1) ::  pnf2a   !< number fraction in 2a
1988    REAL(wp), DIMENSION(0:nz+1) ::  pmfoc1a !< mass fraction of OC in 1a
1989
1990    REAL(wp), DIMENSION(0:nz+1,nbins_aerosol)   ::  pndist  !< vertical profile of size dist. (#/m3)
1991    REAL(wp), DIMENSION(0:nz+1,maxspec)         ::  pmf2a   !< mass distributions in subrange 2a
1992    REAL(wp), DIMENSION(0:nz+1,maxspec)         ::  pmf2b   !< mass distributions in subrange 2b
1993
1994    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pr_dmid  !< vertical profile of aerosol bin diameters
1995    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pr_z     !< z levels of profiles
1996
1997    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pr_mass_fracs_a  !< mass fraction: a
1998    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pr_mass_fracs_b  !< and b
1999
2000    cc_in2mod = 0
2001    prunmode = 1
2002!
2003!-- Bin mean aerosol particle volume (m3)
2004    core(1:nbins_aerosol) = api6 * aero(1:nbins_aerosol)%dmid**3
2005!
2006!-- Set concentrations to zero
2007    pndist(:,:)  = 0.0_wp
2008    pnf2a(:)     = nf2a
2009    pmf2a(:,:)   = 0.0_wp
2010    pmf2b(:,:)   = 0.0_wp
2011    pmfoc1a(:)   = 0.0_wp
2012
2013    IF ( init_aerosol_type == 1 )  THEN
2014!
2015!--    Read input profiles from PIDS_DYNAMIC_SALSA
2016#if defined( __netcdf )
2017!
2018!--    Location-dependent size distributions and compositions.
2019       INQUIRE( FILE = TRIM( input_file_dynamic ) //  TRIM( coupling_char ), EXIST = netcdf_extend )
2020       IF ( netcdf_extend )  THEN
2021!
2022!--       Open file in read-only mode
2023          CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), id_dyn )
2024!
2025!--       At first, inquire all variable names
2026          CALL inquire_num_variables( id_dyn, num_vars )
2027!
2028!--       Allocate memory to store variable names
2029          ALLOCATE( var_names(1:num_vars) )
2030          CALL inquire_variable_names( id_dyn, var_names )
2031!
2032!--       Inquire vertical dimension and number of aerosol chemical components
2033          CALL get_dimension_length( id_dyn, pr_nz, 'z' )
2034          IF ( pr_nz /= nz )  THEN
2035             WRITE( message_string, * ) 'Number of inifor horizontal grid points does not match '//&
2036                                        'the number of numeric grid points.'
2037             CALL message( 'aerosol_init', 'PA0601', 1, 2, 0, 6, 0 )
2038          ENDIF
2039          CALL get_dimension_length( id_dyn, pr_ncc, 'composition_index' )
2040!
2041!--       Allocate memory
2042          ALLOCATE( pr_z(1:pr_nz), pr_mass_fracs_a(nzb:nzt+1,pr_ncc),                              &
2043                    pr_mass_fracs_b(nzb:nzt+1,pr_ncc) )
2044          pr_mass_fracs_a = 0.0_wp
2045          pr_mass_fracs_b = 0.0_wp
2046!
2047!--       Read vertical levels
2048          CALL get_variable( id_dyn, 'z', pr_z )
2049!
2050!--       Read the names of chemical components
2051          IF ( check_existence( var_names, 'composition_name' ) )  THEN
2052             CALL get_variable( id_dyn, 'composition_name', cc_name, pr_ncc )
2053          ELSE
2054             WRITE( message_string, * ) 'Missing composition_name in ' // TRIM( input_file_dynamic )
2055             CALL message( 'aerosol_init', 'PA0655', 1, 2, 0, 6, 0 )
2056          ENDIF
2057!
2058!--       Define the index of each chemical component in the model
2059          DO  ic = 1, pr_ncc
2060             SELECT CASE ( TRIM( cc_name(ic) ) )
2061                CASE ( 'H2SO4', 'SO4', 'h2so4', 'so4' )
2062                   cc_in2mod(1) = ic
2063                CASE ( 'OC', 'oc' )
2064                   cc_in2mod(2) = ic
2065                CASE ( 'BC', 'bc' )
2066                   cc_in2mod(3) = ic
2067                CASE ( 'DU', 'du' )
2068                   cc_in2mod(4) = ic
2069                CASE ( 'SS', 'ss' )
2070                   cc_in2mod(5) = ic
2071                CASE ( 'HNO3', 'hno3', 'NO3', 'no3', 'NO', 'no' )
2072                   cc_in2mod(6) = ic
2073                CASE ( 'NH3', 'nh3', 'NH4', 'nh4', 'NH', 'nh' )
2074                   cc_in2mod(7) = ic
2075             END SELECT
2076          ENDDO
2077
2078          IF ( SUM( cc_in2mod ) == 0 )  THEN
2079             message_string = 'None of the aerosol chemical components in ' // TRIM(               &
2080                              input_file_dynamic ) // ' correspond to ones applied in SALSA.'
2081             CALL message( 'salsa_mod: aerosol_init', 'PA0602', 2, 2, 0, 6, 0 )
2082          ENDIF
2083!
2084!--       Vertical profiles of mass fractions of different chemical components:
2085          IF ( check_existence( var_names, 'init_atmosphere_mass_fracs_a' ) )  THEN
2086             CALL get_variable( id_dyn, 'init_atmosphere_mass_fracs_a', pr_mass_fracs_a,           &
2087                                0, pr_ncc-1, 0, pr_nz-1 )
2088          ELSE
2089             WRITE( message_string, * ) 'Missing init_atmosphere_mass_fracs_a in ' //              &
2090                                        TRIM( input_file_dynamic )
2091             CALL message( 'aerosol_init', 'PA0656', 1, 2, 0, 6, 0 )
2092          ENDIF
2093          CALL get_variable( id_dyn, 'init_atmosphere_mass_fracs_b', pr_mass_fracs_b,              &
2094                             0, pr_ncc-1, 0, pr_nz-1  )
2095!
2096!--       Match the input data with the chemical composition applied in the model
2097          DO  ic = 1, maxspec
2098             ss = cc_in2mod(ic)
2099             IF ( ss == 0 )  CYCLE
2100             pmf2a(nzb+1:nzt+1,ic) = pr_mass_fracs_a(nzb:nzt,ss)
2101             pmf2b(nzb+1:nzt+1,ic) = pr_mass_fracs_b(nzb:nzt,ss)
2102          ENDDO
2103!
2104!--       Aerosol concentrations: lod=1 (vertical profile of sectional number size distribution)
2105          CALL get_attribute( id_dyn, 'lod', lod_aero, .FALSE., 'init_atmosphere_aerosol' )
2106          IF ( lod_aero /= 1 )  THEN
2107             message_string = 'Currently only lod=1 accepted for init_atmosphere_aerosol'
2108             CALL message( 'salsa_mod: aerosol_init', 'PA0603', 2, 2, 0, 6, 0 )
2109          ELSE
2110!
2111!--          Bin mean diameters in the input file
2112             CALL get_dimension_length( id_dyn, pr_nbins, 'Dmid')
2113             IF ( pr_nbins /= nbins_aerosol )  THEN
2114                message_string = 'Number of size bins in init_atmosphere_aerosol does not match '  &
2115                                 // 'with that applied in the model'
2116                CALL message( 'salsa_mod: aerosol_init', 'PA0604', 2, 2, 0, 6, 0 )
2117             ENDIF
2118
2119             ALLOCATE( pr_dmid(pr_nbins) )
2120             pr_dmid    = 0.0_wp
2121
2122             CALL get_variable( id_dyn, 'Dmid', pr_dmid )
2123!
2124!--          Check whether the sectional representation conform to the one
2125!--          applied in the model
2126             IF ( ANY( ABS( ( aero(1:nbins_aerosol)%dmid - pr_dmid ) /                             &
2127                              aero(1:nbins_aerosol)%dmid )  > 0.1_wp )  ) THEN
2128                message_string = 'Mean diameters of the aerosol size bins in ' // TRIM(            &
2129                                 input_file_dynamic ) // ' do not match with the sectional '//     &
2130                                 'representation of the model.'
2131                CALL message( 'salsa_mod: aerosol_init', 'PA0605', 2, 2, 0, 6, 0 )
2132             ENDIF
2133!
2134!--          Inital aerosol concentrations
2135             CALL get_variable( id_dyn, 'init_atmosphere_aerosol', pndist(nzb+1:nzt,:),            &
2136                                0, pr_nbins-1, 0, pr_nz-1 )
2137          ENDIF
2138!
2139!--       Set bottom and top boundary condition (Neumann)
2140          pmf2a(nzb,:)    = pmf2a(nzb+1,:)
2141          pmf2a(nzt+1,:)  = pmf2a(nzt,:)
2142          pmf2b(nzb,:)    = pmf2b(nzb+1,:)
2143          pmf2b(nzt+1,:)  = pmf2b(nzt,:)
2144          pndist(nzb,:)   = pndist(nzb+1,:)
2145          pndist(nzt+1,:) = pndist(nzt,:)
2146
2147          IF ( index_so4 < 0 )  THEN
2148             pmf2a(:,1) = 0.0_wp
2149             pmf2b(:,1) = 0.0_wp
2150          ENDIF
2151          IF ( index_oc < 0 )  THEN
2152             pmf2a(:,2) = 0.0_wp
2153             pmf2b(:,2) = 0.0_wp
2154          ENDIF
2155          IF ( index_bc < 0 )  THEN
2156             pmf2a(:,3) = 0.0_wp
2157             pmf2b(:,3) = 0.0_wp
2158          ENDIF
2159          IF ( index_du < 0 )  THEN
2160             pmf2a(:,4) = 0.0_wp
2161             pmf2b(:,4) = 0.0_wp
2162          ENDIF
2163          IF ( index_ss < 0 )  THEN
2164             pmf2a(:,5) = 0.0_wp
2165             pmf2b(:,5) = 0.0_wp
2166          ENDIF
2167          IF ( index_no < 0 )  THEN
2168             pmf2a(:,6) = 0.0_wp
2169             pmf2b(:,6) = 0.0_wp
2170          ENDIF
2171          IF ( index_nh < 0 )  THEN
2172             pmf2a(:,7) = 0.0_wp
2173             pmf2b(:,7) = 0.0_wp
2174          ENDIF
2175
2176          IF ( SUM( pmf2a ) < 0.00001_wp  .AND.  SUM( pmf2b ) < 0.00001_wp )  THEN
2177             message_string = 'Error in initialising mass fractions of chemical components. ' //   &
2178                              'Check that all chemical components are included in parameter file!'
2179             CALL message( 'salsa_mod: aerosol_init', 'PA0606', 2, 2, 0, 6, 0 ) 
2180          ENDIF
2181!
2182!--       Then normalise the mass fraction so that SUM = 1
2183          DO  k = nzb, nzt+1
2184             pmf2a(k,:) = pmf2a(k,:) / SUM( pmf2a(k,:) )
2185             IF ( SUM( pmf2b(k,:) ) > 0.0_wp )  pmf2b(k,:) = pmf2b(k,:) / SUM( pmf2b(k,:) )
2186          ENDDO
2187
2188          DEALLOCATE( pr_z, pr_mass_fracs_a, pr_mass_fracs_b )
2189!
2190!--       Close input file
2191          CALL close_input_file( id_dyn )
2192
2193       ELSE
2194          message_string = 'Input file '// TRIM( input_file_dynamic ) // TRIM( coupling_char ) //  &
2195                           ' for SALSA missing!'
2196          CALL message( 'salsa_mod: aerosol_init', 'PA0607', 1, 2, 0, 6, 0 )
2197
2198       ENDIF   ! netcdf_extend
2199
2200#else
2201       message_string = 'init_aerosol_type = 1 but preprocessor directive __netcdf is not used '// &
2202                        'in compiling!'
2203       CALL message( 'salsa_mod: aerosol_init', 'PA0608', 1, 2, 0, 6, 0 )
2204
2205#endif
2206
2207    ELSEIF ( init_aerosol_type == 0 )  THEN
2208!
2209!--    Mass fractions for species in a and b-bins
2210       IF ( index_so4 > 0 )  THEN
2211          pmf2a(:,1) = mass_fracs_a(index_so4)
2212          pmf2b(:,1) = mass_fracs_b(index_so4)
2213       ENDIF
2214       IF ( index_oc > 0 )  THEN
2215          pmf2a(:,2) = mass_fracs_a(index_oc)
2216          pmf2b(:,2) = mass_fracs_b(index_oc)
2217       ENDIF
2218       IF ( index_bc > 0 )  THEN
2219          pmf2a(:,3) = mass_fracs_a(index_bc)
2220          pmf2b(:,3) = mass_fracs_b(index_bc)
2221       ENDIF
2222       IF ( index_du > 0 )  THEN
2223          pmf2a(:,4) = mass_fracs_a(index_du)
2224          pmf2b(:,4) = mass_fracs_b(index_du)
2225       ENDIF
2226       IF ( index_ss > 0 )  THEN
2227          pmf2a(:,5) = mass_fracs_a(index_ss)
2228          pmf2b(:,5) = mass_fracs_b(index_ss)
2229       ENDIF
2230       IF ( index_no > 0 )  THEN
2231          pmf2a(:,6) = mass_fracs_a(index_no)
2232          pmf2b(:,6) = mass_fracs_b(index_no)
2233       ENDIF
2234       IF ( index_nh > 0 )  THEN
2235          pmf2a(:,7) = mass_fracs_a(index_nh)
2236          pmf2b(:,7) = mass_fracs_b(index_nh)
2237       ENDIF
2238       DO  k = nzb, nzt+1
2239          pmf2a(k,:) = pmf2a(k,:) / SUM( pmf2a(k,:) )
2240          IF ( SUM( pmf2b(k,:) ) > 0.0_wp ) pmf2b(k,:) = pmf2b(k,:) / SUM( pmf2b(k,:) )
2241       ENDDO
2242
2243       CALL size_distribution( n_lognorm, dpg, sigmag, nsect )
2244!
2245!--    Normalize by the given total number concentration
2246       nsect = nsect * SUM( n_lognorm ) / SUM( nsect )
2247       DO  ib = start_subrange_1a, end_subrange_2b
2248          pndist(:,ib) = nsect(ib)
2249       ENDDO
2250    ENDIF
2251
2252    IF ( init_gases_type == 1 )  THEN
2253!
2254!--    Read input profiles from PIDS_CHEM
2255#if defined( __netcdf )
2256!
2257!--    Location-dependent size distributions and compositions.
2258       INQUIRE( FILE = TRIM( input_file_dynamic ) //  TRIM( coupling_char ), EXIST = netcdf_extend )
2259       IF ( netcdf_extend  .AND.  .NOT. salsa_gases_from_chem )  THEN
2260!
2261!--       Open file in read-only mode
2262          CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), id_dyn )
2263!
2264!--       Inquire dimensions:
2265          CALL get_dimension_length( id_dyn, pr_nz, 'z' )
2266          IF ( pr_nz /= nz )  THEN
2267             WRITE( message_string, * ) 'Number of inifor horizontal grid points does not match '//&
2268                                        'the number of numeric grid points.'
2269             CALL message( 'aerosol_init', 'PA0609', 1, 2, 0, 6, 0 )
2270          ENDIF
2271!
2272!--       Read vertical profiles of gases:
2273          CALL get_variable( id_dyn, 'init_atmosphere_H2SO4', salsa_gas(1)%init(nzb+1:nzt) )
2274          CALL get_variable( id_dyn, 'init_atmosphere_HNO3',  salsa_gas(2)%init(nzb+1:nzt) )
2275          CALL get_variable( id_dyn, 'init_atmosphere_NH3',   salsa_gas(3)%init(nzb+1:nzt) )
2276          CALL get_variable( id_dyn, 'init_atmosphere_OCNV',  salsa_gas(4)%init(nzb+1:nzt) )
2277          CALL get_variable( id_dyn, 'init_atmosphere_OCSV',  salsa_gas(5)%init(nzb+1:nzt) )
2278!
2279!--       Set Neumann top and surface boundary condition for initial + initialise concentrations
2280          DO  ig = 1, ngases_salsa
2281             salsa_gas(ig)%init(nzb)   =  salsa_gas(ig)%init(nzb+1)
2282             salsa_gas(ig)%init(nzt+1) =  salsa_gas(ig)%init(nzt)
2283             IF ( .NOT. read_restart_data_salsa )  THEN
2284                DO  k = nzb, nzt+1
2285                   salsa_gas(ig)%conc(k,:,:) = salsa_gas(ig)%init(k)
2286                ENDDO
2287             ENDIF
2288          ENDDO
2289!
2290!--       Close input file
2291          CALL close_input_file( id_dyn )
2292
2293       ELSEIF ( .NOT. netcdf_extend  .AND.  .NOT.  salsa_gases_from_chem )  THEN
2294          message_string = 'Input file '// TRIM( input_file_dynamic ) // TRIM( coupling_char ) //  &
2295                           ' for SALSA missing!'
2296          CALL message( 'salsa_mod: aerosol_init', 'PA0610', 1, 2, 0, 6, 0 )
2297
2298       ENDIF   ! netcdf_extend
2299#else
2300       message_string = 'init_gases_type = 1 but preprocessor directive __netcdf is not used in '//&
2301                        'compiling!'
2302       CALL message( 'salsa_mod: aerosol_init', 'PA0611', 1, 2, 0, 6, 0 )
2303
2304#endif
2305
2306    ENDIF
2307!
2308!-- Both SO4 and OC are included, so use the given mass fractions
2309    IF ( index_oc > 0  .AND.  index_so4 > 0 )  THEN
2310       pmfoc1a(:) = pmf2a(:,2) / ( pmf2a(:,2) + pmf2a(:,1) )  ! Normalize
2311!
2312!-- Pure organic carbon
2313    ELSEIF ( index_oc > 0 )  THEN
2314       pmfoc1a(:) = 1.0_wp
2315!
2316!-- Pure SO4
2317    ELSEIF ( index_so4 > 0 )  THEN
2318       pmfoc1a(:) = 0.0_wp
2319
2320    ELSE
2321       message_string = 'Either OC or SO4 must be active for aerosol region 1a!'
2322       CALL message( 'salsa_mod: aerosol_init', 'PA0612', 1, 2, 0, 6, 0 )
2323    ENDIF
2324
2325!
2326!-- Initialize concentrations
2327    DO  i = nxlg, nxrg
2328       DO  j = nysg, nyng
2329          DO  k = nzb, nzt+1
2330!
2331!--          Predetermine flag to mask topography
2332             flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
2333!
2334!--          a) Number concentrations
2335!--          Region 1:
2336             DO  ib = start_subrange_1a, end_subrange_1a
2337                IF ( .NOT. read_restart_data_salsa )  THEN
2338                   aerosol_number(ib)%conc(k,j,i) = pndist(k,ib) * flag
2339                ENDIF
2340                IF ( prunmode == 1 )  THEN
2341                   aerosol_number(ib)%init = pndist(:,ib)
2342                ENDIF
2343             ENDDO
2344!
2345!--          Region 2:
2346             IF ( nreg > 1 )  THEN
2347                DO  ib = start_subrange_2a, end_subrange_2a
2348                   IF ( .NOT. read_restart_data_salsa )  THEN
2349                      aerosol_number(ib)%conc(k,j,i) = MAX( 0.0_wp, pnf2a(k) ) * pndist(k,ib) * flag
2350                   ENDIF
2351                   IF ( prunmode == 1 )  THEN
2352                      aerosol_number(ib)%init = MAX( 0.0_wp, nf2a ) * pndist(:,ib)
2353                   ENDIF
2354                ENDDO
2355                IF ( .NOT. no_insoluble )  THEN
2356                   DO  ib = start_subrange_2b, end_subrange_2b
2357                      IF ( pnf2a(k) < 1.0_wp )  THEN
2358                         IF ( .NOT. read_restart_data_salsa )  THEN
2359                            aerosol_number(ib)%conc(k,j,i) = MAX( 0.0_wp, 1.0_wp - pnf2a(k) ) *    &
2360                                                             pndist(k,ib) * flag
2361                         ENDIF
2362                         IF ( prunmode == 1 )  THEN
2363                            aerosol_number(ib)%init = MAX( 0.0_wp, 1.0_wp - nf2a ) * pndist(:,ib)
2364                         ENDIF
2365                      ENDIF
2366                   ENDDO
2367                ENDIF
2368             ENDIF
2369!
2370!--          b) Aerosol mass concentrations
2371!--             bin subrange 1: done here separately due to the SO4/OC convention
2372!
2373!--          SO4:
2374             IF ( index_so4 > 0 )  THEN
2375                ss = ( index_so4 - 1 ) * nbins_aerosol + start_subrange_1a !< start
2376                ee = ( index_so4 - 1 ) * nbins_aerosol + end_subrange_1a !< end
2377                ib = start_subrange_1a
2378                DO  ic = ss, ee
2379                   IF ( .NOT. read_restart_data_salsa )  THEN
2380                      aerosol_mass(ic)%conc(k,j,i) = MAX( 0.0_wp, 1.0_wp - pmfoc1a(k) ) *          &
2381                                                     pndist(k,ib) * core(ib) * arhoh2so4 * flag
2382                   ENDIF
2383                   IF ( prunmode == 1 )  THEN
2384                      aerosol_mass(ic)%init(k) = MAX( 0.0_wp, 1.0_wp - pmfoc1a(k) ) * pndist(k,ib) &
2385                                                 * core(ib) * arhoh2so4
2386                   ENDIF
2387                   ib = ib+1
2388                ENDDO
2389             ENDIF
2390!
2391!--          OC:
2392             IF ( index_oc > 0 ) THEN
2393                ss = ( index_oc - 1 ) * nbins_aerosol + start_subrange_1a !< start
2394                ee = ( index_oc - 1 ) * nbins_aerosol + end_subrange_1a !< end
2395                ib = start_subrange_1a
2396                DO  ic = ss, ee
2397                   IF ( .NOT. read_restart_data_salsa )  THEN
2398                      aerosol_mass(ic)%conc(k,j,i) = MAX( 0.0_wp, pmfoc1a(k) ) * pndist(k,ib) *    &
2399                                                     core(ib) * arhooc * flag
2400                   ENDIF
2401                   IF ( prunmode == 1 )  THEN
2402                      aerosol_mass(ic)%init(k) = MAX( 0.0_wp, pmfoc1a(k) ) * pndist(k,ib) *        &
2403                                                 core(ib) * arhooc
2404                   ENDIF
2405                   ib = ib+1
2406                ENDDO 
2407             ENDIF
2408          ENDDO !< k
2409
2410          prunmode = 3  ! Init only once
2411
2412       ENDDO !< j
2413    ENDDO !< i
2414
2415!
2416!-- c) Aerosol mass concentrations
2417!--    bin subrange 2:
2418    IF ( nreg > 1 ) THEN
2419
2420       IF ( index_so4 > 0 ) THEN
2421          CALL set_aero_mass( index_so4, pmf2a(:,1), pmf2b(:,1), pnf2a, pndist, core, arhoh2so4 )
2422       ENDIF
2423       IF ( index_oc > 0 ) THEN
2424          CALL set_aero_mass( index_oc, pmf2a(:,2), pmf2b(:,2), pnf2a, pndist, core, arhooc )
2425       ENDIF
2426       IF ( index_bc > 0 ) THEN
2427          CALL set_aero_mass( index_bc, pmf2a(:,3), pmf2b(:,3), pnf2a, pndist, core, arhobc )
2428       ENDIF
2429       IF ( index_du > 0 ) THEN
2430          CALL set_aero_mass( index_du, pmf2a(:,4), pmf2b(:,4), pnf2a, pndist, core, arhodu )
2431       ENDIF
2432       IF ( index_ss > 0 ) THEN
2433          CALL set_aero_mass( index_ss, pmf2a(:,5), pmf2b(:,5), pnf2a, pndist, core, arhoss )
2434       ENDIF
2435       IF ( index_no > 0 ) THEN
2436          CALL set_aero_mass( index_no, pmf2a(:,6), pmf2b(:,6), pnf2a, pndist, core, arhohno3 )
2437       ENDIF
2438       IF ( index_nh > 0 ) THEN
2439          CALL set_aero_mass( index_nh, pmf2a(:,7), pmf2b(:,7), pnf2a, pndist, core, arhonh3 )
2440       ENDIF
2441
2442    ENDIF
2443
2444 END SUBROUTINE aerosol_init
2445
2446!------------------------------------------------------------------------------!
2447! Description:
2448! ------------
2449!> Create a lognormal size distribution and discretise to a sectional
2450!> representation.
2451!------------------------------------------------------------------------------!
2452 SUBROUTINE size_distribution( in_ntot, in_dpg, in_sigma, psd_sect )
2453
2454    IMPLICIT NONE
2455
2456    INTEGER(iwp) ::  ib         !< running index: bin
2457    INTEGER(iwp) ::  iteration  !< running index: iteration
2458
2459    REAL(wp) ::  d1         !< particle diameter (m, dummy)
2460    REAL(wp) ::  d2         !< particle diameter (m, dummy)
2461    REAL(wp) ::  delta_d    !< (d2-d1)/10
2462    REAL(wp) ::  deltadp    !< bin width
2463    REAL(wp) ::  dmidi      !< ( d1 + d2 ) / 2
2464
2465    REAL(wp), DIMENSION(:), INTENT(in) ::  in_dpg    !< geometric mean diameter (m)
2466    REAL(wp), DIMENSION(:), INTENT(in) ::  in_ntot   !< number conc. (#/m3)
2467    REAL(wp), DIMENSION(:), INTENT(in) ::  in_sigma  !< standard deviation
2468
2469    REAL(wp), DIMENSION(:), INTENT(inout) ::  psd_sect  !< sectional size distribution
2470
2471    DO  ib = start_subrange_1a, end_subrange_2b
2472       psd_sect(ib) = 0.0_wp
2473!
2474!--    Particle diameter at the low limit (largest in the bin) (m)
2475       d1 = ( aero(ib)%vlolim / api6 )**0.33333333_wp
2476!
2477!--    Particle diameter at the high limit (smallest in the bin) (m)
2478       d2 = ( aero(ib)%vhilim / api6 )**0.33333333_wp
2479!
2480!--    Span of particle diameter in a bin (m)
2481       delta_d = 0.1_wp * ( d2 - d1 )
2482!
2483!--    Iterate:
2484       DO  iteration = 1, 10
2485          d1 = ( aero(ib)%vlolim / api6 )**0.33333333_wp + ( ib - 1) * delta_d
2486          d2 = d1 + delta_d
2487          dmidi = 0.5_wp * ( d1 + d2 )
2488          deltadp = LOG10( d2 / d1 )
2489!
2490!--       Size distribution
2491!--       in_ntot = total number, total area, or total volume concentration
2492!--       in_dpg = geometric-mean number, area, or volume diameter
2493!--       n(k) = number, area, or volume concentration in a bin
2494          psd_sect(ib) = psd_sect(ib) + SUM( in_ntot * deltadp / ( SQRT( 2.0_wp * pi ) *           &
2495                        LOG10( in_sigma ) ) * EXP( -LOG10( dmidi / in_dpg )**2.0_wp /              &
2496                        ( 2.0_wp * LOG10( in_sigma ) ** 2.0_wp ) ) )
2497
2498       ENDDO
2499    ENDDO
2500
2501 END SUBROUTINE size_distribution
2502
2503!------------------------------------------------------------------------------!
2504! Description:
2505! ------------
2506!> Sets the mass concentrations to aerosol arrays in 2a and 2b.
2507!>
2508!> Tomi Raatikainen, FMI, 29.2.2016
2509!------------------------------------------------------------------------------!
2510 SUBROUTINE set_aero_mass( ispec, pmf2a, pmf2b, pnf2a, pndist, pcore, prho )
2511
2512    IMPLICIT NONE
2513
2514    INTEGER(iwp) ::  ee        !< index: end
2515    INTEGER(iwp) ::  i         !< loop index
2516    INTEGER(iwp) ::  ib        !< loop index
2517    INTEGER(iwp) ::  ic        !< loop index
2518    INTEGER(iwp) ::  j         !< loop index
2519    INTEGER(iwp) ::  k         !< loop index
2520    INTEGER(iwp) ::  prunmode  !< 1 = initialise
2521    INTEGER(iwp) ::  ss        !< index: start
2522
2523    INTEGER(iwp), INTENT(in) :: ispec  !< Aerosol species index
2524
2525    REAL(wp) ::  flag   !< flag to mask topography grid points
2526
2527    REAL(wp), INTENT(in) ::  prho !< Aerosol density
2528
2529    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pcore !< Aerosol bin mid core volume
2530    REAL(wp), DIMENSION(0:nz+1), INTENT(in)        ::  pnf2a !< Number fraction for 2a
2531    REAL(wp), DIMENSION(0:nz+1), INTENT(in)        ::  pmf2a !< Mass distributions for a
2532    REAL(wp), DIMENSION(0:nz+1), INTENT(in)        ::  pmf2b !< and b bins
2533
2534    REAL(wp), DIMENSION(0:nz+1,nbins_aerosol), INTENT(in) ::  pndist !< Aerosol size distribution
2535
2536    prunmode = 1
2537
2538    DO i = nxlg, nxrg
2539       DO j = nysg, nyng
2540          DO k = nzb, nzt+1
2541!
2542!--          Predetermine flag to mask topography
2543             flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
2544!
2545!--          Regime 2a:
2546             ss = ( ispec - 1 ) * nbins_aerosol + start_subrange_2a
2547             ee = ( ispec - 1 ) * nbins_aerosol + end_subrange_2a
2548             ib = start_subrange_2a
2549             DO ic = ss, ee
2550                IF ( .NOT. read_restart_data_salsa )  THEN
2551                   aerosol_mass(ic)%conc(k,j,i) = MAX( 0.0_wp, pmf2a(k) ) * pnf2a(k) * pndist(k,ib)&
2552                                                  * pcore(ib) * prho * flag
2553                ENDIF
2554                IF ( prunmode == 1 )  THEN
2555                   aerosol_mass(ic)%init(k) = MAX( 0.0_wp, pmf2a(k) ) * pnf2a(k) * pndist(k,ib) *  &
2556                                              pcore(ib) * prho
2557                ENDIF
2558                ib = ib + 1
2559             ENDDO
2560!
2561!--          Regime 2b:
2562             IF ( .NOT. no_insoluble )  THEN
2563                ss = ( ispec - 1 ) * nbins_aerosol + start_subrange_2b
2564                ee = ( ispec - 1 ) * nbins_aerosol + end_subrange_2b
2565                ib = start_subrange_2a
2566                DO ic = ss, ee
2567                   IF ( .NOT. read_restart_data_salsa )  THEN
2568                      aerosol_mass(ic)%conc(k,j,i) = MAX( 0.0_wp, pmf2b(k) ) * ( 1.0_wp - pnf2a(k))&
2569                                                     * pndist(k,ib) * pcore(ib) * prho * flag
2570                   ENDIF
2571                   IF ( prunmode == 1 )  THEN
2572                      aerosol_mass(ic)%init(k) = MAX( 0.0_wp, pmf2b(k) ) * ( 1.0_wp - pnf2a(k) ) * &
2573                                                 pndist(k,ib) * pcore(ib) * prho 
2574                   ENDIF
2575                   ib = ib + 1
2576                ENDDO  ! c
2577
2578             ENDIF
2579          ENDDO   ! k
2580
2581          prunmode = 3  ! Init only once
2582
2583       ENDDO   ! j
2584    ENDDO   ! i
2585
2586 END SUBROUTINE set_aero_mass
2587
2588!------------------------------------------------------------------------------!
2589! Description:
2590! ------------
2591!> Initialise the matching between surface types in LSM and deposition models.
2592!> Do the matching based on Zhang et al. (2001). Atmos. Environ. 35, 549-560
2593!> (here referred as Z01).
2594!------------------------------------------------------------------------------!
2595 SUBROUTINE init_deposition
2596
2597    USE surface_mod,                                                                               &
2598        ONLY:  surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
2599
2600    IMPLICIT NONE
2601
2602    INTEGER(iwp) ::  l  !< loop index for vertical surfaces
2603
2604    LOGICAL :: match_lsm  !< flag to initilise LSM surfaces (if false, initialise USM surfaces)
2605
2606    IF ( depo_pcm_par == 'zhang2001' )  THEN
2607       depo_pcm_par_num = 1
2608    ELSEIF ( depo_pcm_par == 'petroff2010' )  THEN
2609       depo_pcm_par_num = 2
2610    ENDIF
2611
2612    IF ( depo_surf_par == 'zhang2001' )  THEN
2613       depo_surf_par_num = 1
2614    ELSEIF ( depo_surf_par == 'petroff2010' )  THEN
2615       depo_surf_par_num = 2
2616    ENDIF
2617!
2618!-- LSM: Pavement, vegetation and water
2619    IF ( nldepo_surf  .AND.  land_surface )  THEN
2620       match_lsm = .TRUE.
2621       ALLOCATE( lsm_to_depo_h%match_lupg(1:surf_lsm_h%ns),                                         &
2622                 lsm_to_depo_h%match_luvw(1:surf_lsm_h%ns),                                         &
2623                 lsm_to_depo_h%match_luww(1:surf_lsm_h%ns) )
2624       lsm_to_depo_h%match_lupg = 0
2625       lsm_to_depo_h%match_luvw = 0
2626       lsm_to_depo_h%match_luww = 0
2627       CALL match_sm_zhang( surf_lsm_h, lsm_to_depo_h%match_lupg, lsm_to_depo_h%match_luvw,        &
2628                            lsm_to_depo_h%match_luww, match_lsm )
2629       DO  l = 0, 3
2630          ALLOCATE( lsm_to_depo_v(l)%match_lupg(1:surf_lsm_v(l)%ns),                               &
2631                    lsm_to_depo_v(l)%match_luvw(1:surf_lsm_v(l)%ns),                               &
2632                    lsm_to_depo_v(l)%match_luww(1:surf_lsm_v(l)%ns) )
2633          lsm_to_depo_v(l)%match_lupg = 0
2634          lsm_to_depo_v(l)%match_luvw = 0
2635          lsm_to_depo_v(l)%match_luww = 0
2636          CALL match_sm_zhang( surf_lsm_v(l), lsm_to_depo_v(l)%match_lupg,                         &
2637                               lsm_to_depo_v(l)%match_luvw, lsm_to_depo_v(l)%match_luww, match_lsm )
2638       ENDDO
2639    ENDIF
2640!
2641!-- USM: Green roofs/walls, wall surfaces and windows
2642    IF ( nldepo_surf  .AND.  urban_surface )  THEN
2643       match_lsm = .FALSE.
2644       ALLOCATE( usm_to_depo_h%match_lupg(1:surf_usm_h%ns),                                        &
2645                 usm_to_depo_h%match_luvw(1:surf_usm_h%ns),                                        &
2646                 usm_to_depo_h%match_luww(1:surf_usm_h%ns) )
2647       usm_to_depo_h%match_lupg = 0
2648       usm_to_depo_h%match_luvw = 0
2649       usm_to_depo_h%match_luww = 0
2650       CALL match_sm_zhang( surf_usm_h, usm_to_depo_h%match_lupg, usm_to_depo_h%match_luvw,        &
2651                            usm_to_depo_h%match_luww, match_lsm )
2652       DO  l = 0, 3
2653          ALLOCATE( usm_to_depo_v(l)%match_lupg(1:surf_usm_v(l)%ns),                               &
2654                    usm_to_depo_v(l)%match_luvw(1:surf_usm_v(l)%ns),                               &
2655                    usm_to_depo_v(l)%match_luww(1:surf_usm_v(l)%ns) )
2656          usm_to_depo_v(l)%match_lupg = 0
2657          usm_to_depo_v(l)%match_luvw = 0
2658          usm_to_depo_v(l)%match_luww = 0
2659          CALL match_sm_zhang( surf_usm_v(l), usm_to_depo_v(l)%match_lupg,                         &
2660                               usm_to_depo_v(l)%match_luvw, usm_to_depo_v(l)%match_luww, match_lsm )
2661       ENDDO
2662    ENDIF
2663
2664    IF ( nldepo_pcm )  THEN
2665       SELECT CASE ( depo_pcm_type )
2666          CASE ( 'evergreen_needleleaf' )
2667             depo_pcm_type_num = 1
2668          CASE ( 'evergreen_broadleaf' )
2669             depo_pcm_type_num = 2
2670          CASE ( 'deciduous_needleleaf' )
2671             depo_pcm_type_num = 3
2672          CASE ( 'deciduous_broadleaf' )
2673             depo_pcm_type_num = 4
2674          CASE DEFAULT
2675             message_string = 'depo_pcm_type not set correctly.'
2676             CALL message( 'salsa_mod: init_deposition', 'PA0613', 1, 2, 0, 6, 0 )
2677       END SELECT
2678    ENDIF
2679
2680 END SUBROUTINE init_deposition
2681
2682!------------------------------------------------------------------------------!
2683! Description:
2684! ------------
2685!> Match the surface types in PALM and Zhang et al. 2001 deposition module
2686!------------------------------------------------------------------------------!
2687 SUBROUTINE match_sm_zhang( surf, match_pav_green, match_veg_wall, match_wat_win, match_lsm )
2688
2689    USE surface_mod,                                                           &
2690        ONLY:  ind_pav_green, ind_veg_wall, ind_wat_win, surf_type
2691
2692    IMPLICIT NONE
2693
2694    INTEGER(iwp) ::  m              !< index for surface elements
2695    INTEGER(iwp) ::  pav_type_palm  !< pavement / green wall type in PALM
2696    INTEGER(iwp) ::  veg_type_palm  !< vegetation / wall type in PALM
2697    INTEGER(iwp) ::  wat_type_palm  !< water / window type in PALM
2698
2699    INTEGER(iwp), DIMENSION(:), INTENT(inout) ::  match_pav_green  !<  matching pavement/green walls
2700    INTEGER(iwp), DIMENSION(:), INTENT(inout) ::  match_veg_wall   !<  matching vegetation/walls
2701    INTEGER(iwp), DIMENSION(:), INTENT(inout) ::  match_wat_win    !<  matching water/windows
2702
2703    LOGICAL, INTENT(in) :: match_lsm  !< flag to initilise LSM surfaces (if false, initialise USM)
2704
2705    TYPE(surf_type), INTENT(in) :: surf  !< respective surface type
2706
2707    DO  m = 1, surf%ns
2708       IF ( match_lsm )  THEN
2709!
2710!--       Vegetation (LSM):
2711          IF ( surf%frac(ind_veg_wall,m) > 0 )  THEN
2712             veg_type_palm = surf%vegetation_type(m)
2713             SELECT CASE ( veg_type_palm )
2714                CASE ( 0 )
2715                   message_string = 'No vegetation type defined.'
2716                   CALL message( 'salsa_mod: init_depo_surfaces', 'PA0614', 1, 2, 0, 6, 0 )
2717                CASE ( 1 )  ! bare soil
2718                   match_veg_wall(m) = 6  ! grass in Z01
2719                CASE ( 2 )  ! crops, mixed farming
2720                   match_veg_wall(m) = 7  !  crops, mixed farming Z01
2721                CASE ( 3 )  ! short grass
2722                   match_veg_wall(m) = 6  ! grass in Z01
2723                CASE ( 4 )  ! evergreen needleleaf trees
2724                    match_veg_wall(m) = 1  ! evergreen needleleaf trees in Z01
2725                CASE ( 5 )  ! deciduous needleleaf trees
2726                   match_veg_wall(m) = 3  ! deciduous needleleaf trees in Z01
2727                CASE ( 6 )  ! evergreen broadleaf trees
2728                   match_veg_wall(m) = 2  ! evergreen broadleaf trees in Z01
2729                CASE ( 7 )  ! deciduous broadleaf trees
2730                   match_veg_wall(m) = 4  ! deciduous broadleaf trees in Z01
2731                CASE ( 8 )  ! tall grass
2732                   match_veg_wall(m) = 6  ! grass in Z01
2733                CASE ( 9 )  ! desert
2734                   match_veg_wall(m) = 8  ! desert in Z01
2735                CASE ( 10 )  ! tundra
2736                   match_veg_wall(m) = 9  ! tundra in Z01
2737                CASE ( 11 )  ! irrigated crops
2738                   match_veg_wall(m) = 7  !  crops, mixed farming Z01
2739                CASE ( 12 )  ! semidesert
2740                   match_veg_wall(m) = 8  ! desert in Z01
2741                CASE ( 13 )  ! ice caps and glaciers
2742                   match_veg_wall(m) = 12  ! ice cap and glacier in Z01
2743                CASE ( 14 )  ! bogs and marshes
2744                   match_veg_wall(m) = 11  ! wetland with plants in Z01
2745                CASE ( 15 )  ! evergreen shrubs
2746                   match_veg_wall(m) = 10  ! shrubs and interrupted woodlands in Z01
2747                CASE ( 16 )  ! deciduous shrubs
2748                   match_veg_wall(m) = 10  ! shrubs and interrupted woodlands in Z01
2749                CASE ( 17 )  ! mixed forest/woodland
2750                   match_veg_wall(m) = 5  ! mixed broadleaf and needleleaf trees in Z01
2751                CASE ( 18 )  ! interrupted forest
2752                   match_veg_wall(m) = 10  ! shrubs and interrupted woodlands in Z01
2753             END SELECT
2754          ENDIF
2755!
2756!--       Pavement (LSM):
2757          IF ( surf%frac(ind_pav_green,m) > 0 )  THEN
2758             pav_type_palm = surf%pavement_type(m)
2759             IF ( pav_type_palm == 0 )  THEN  ! error
2760                message_string = 'No pavement type defined.'
2761                CALL message( 'salsa_mod: match_sm_zhang', 'PA0615', 1, 2, 0, 6, 0 )
2762             ELSE
2763                match_pav_green(m) = 15  ! urban in Z01
2764             ENDIF
2765          ENDIF
2766!
2767!--       Water (LSM):
2768          IF ( surf%frac(ind_wat_win,m) > 0 )  THEN
2769             wat_type_palm = surf%water_type(m)
2770             IF ( wat_type_palm == 0 )  THEN  ! error
2771                message_string = 'No water type defined.'
2772                CALL message( 'salsa_mod: match_sm_zhang', 'PA0616', 1, 2, 0, 6, 0 )
2773             ELSEIF ( wat_type_palm == 3 )  THEN
2774                match_wat_win(m) = 14  ! ocean in Z01
2775             ELSEIF ( wat_type_palm == 1  .OR.  wat_type_palm == 2 .OR.  wat_type_palm == 4        &
2776                      .OR.  wat_type_palm == 5  )  THEN
2777                match_wat_win(m) = 13  ! inland water in Z01
2778             ENDIF
2779          ENDIF
2780       ELSE
2781!
2782!--       Wall surfaces (USM):
2783          IF ( surf%frac(ind_veg_wall,m) > 0 )  THEN
2784             match_veg_wall(m) = 15  ! urban in Z01
2785          ENDIF
2786!
2787!--       Green walls and roofs (USM):
2788          IF ( surf%frac(ind_pav_green,m) > 0 )  THEN
2789             match_pav_green(m) =  6 ! (short) grass in Z01
2790          ENDIF
2791!
2792!--       Windows (USM):
2793          IF ( surf%frac(ind_wat_win,m) > 0 )  THEN
2794             match_wat_win(m) = 15  ! urban in Z01
2795          ENDIF
2796       ENDIF
2797
2798    ENDDO
2799
2800 END SUBROUTINE match_sm_zhang
2801
2802!------------------------------------------------------------------------------!
2803! Description:
2804! ------------
2805!> Swapping of timelevels
2806!------------------------------------------------------------------------------!
2807 SUBROUTINE salsa_swap_timelevel( mod_count )
2808
2809    IMPLICIT NONE
2810
2811    INTEGER(iwp) ::  ib   !<
2812    INTEGER(iwp) ::  ic   !<
2813    INTEGER(iwp) ::  icc  !<
2814    INTEGER(iwp) ::  ig   !<
2815
2816    INTEGER(iwp), INTENT(IN) ::  mod_count  !<
2817
2818    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
2819
2820       SELECT CASE ( mod_count )
2821
2822          CASE ( 0 )
2823
2824             DO  ib = 1, nbins_aerosol
2825                aerosol_number(ib)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => nconc_1(:,:,:,ib)
2826                aerosol_number(ib)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => nconc_2(:,:,:,ib)
2827
2828                DO  ic = 1, ncomponents_mass
2829                   icc = ( ic-1 ) * nbins_aerosol + ib
2830                   aerosol_mass(icc)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => mconc_1(:,:,:,icc)
2831                   aerosol_mass(icc)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => mconc_2(:,:,:,icc)
2832                ENDDO
2833             ENDDO
2834
2835             IF ( .NOT. salsa_gases_from_chem )  THEN
2836                DO  ig = 1, ngases_salsa
2837                   salsa_gas(ig)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => gconc_1(:,:,:,ig)
2838                   salsa_gas(ig)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => gconc_2(:,:,:,ig)
2839                ENDDO
2840             ENDIF
2841
2842          CASE ( 1 )
2843
2844             DO  ib = 1, nbins_aerosol
2845                aerosol_number(ib)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => nconc_2(:,:,:,ib)
2846                aerosol_number(ib)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => nconc_1(:,:,:,ib)
2847                DO  ic = 1, ncomponents_mass
2848                   icc = ( ic-1 ) * nbins_aerosol + ib
2849                   aerosol_mass(icc)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => mconc_2(:,:,:,icc)
2850                   aerosol_mass(icc)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => mconc_1(:,:,:,icc)
2851                ENDDO
2852             ENDDO
2853
2854             IF ( .NOT. salsa_gases_from_chem )  THEN
2855                DO  ig = 1, ngases_salsa
2856                   salsa_gas(ig)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)   => gconc_2(:,:,:,ig)
2857                   salsa_gas(ig)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => gconc_1(:,:,:,ig)
2858                ENDDO
2859             ENDIF
2860
2861       END SELECT
2862
2863    ENDIF
2864
2865 END SUBROUTINE salsa_swap_timelevel
2866
2867
2868!------------------------------------------------------------------------------!
2869! Description:
2870! ------------
2871!> This routine reads the respective restart data.
2872!------------------------------------------------------------------------------!
2873 SUBROUTINE salsa_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,      &
2874                             nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
2875
2876    USE control_parameters,                                                                        &
2877        ONLY:  length, restart_string
2878
2879    IMPLICIT NONE
2880
2881    INTEGER(iwp) ::  ib              !<
2882    INTEGER(iwp) ::  ic              !<
2883    INTEGER(iwp) ::  ig              !<
2884    INTEGER(iwp) ::  k               !<
2885    INTEGER(iwp) ::  nxlc            !<
2886    INTEGER(iwp) ::  nxlf            !<
2887    INTEGER(iwp) ::  nxl_on_file     !<
2888    INTEGER(iwp) ::  nxrc            !<
2889    INTEGER(iwp) ::  nxrf            !<
2890    INTEGER(iwp) ::  nxr_on_file     !<
2891    INTEGER(iwp) ::  nync            !<
2892    INTEGER(iwp) ::  nynf            !<
2893    INTEGER(iwp) ::  nyn_on_file     !<
2894    INTEGER(iwp) ::  nysc            !<
2895    INTEGER(iwp) ::  nysf            !<
2896    INTEGER(iwp) ::  nys_on_file     !<
2897
2898    LOGICAL, INTENT(OUT)  ::  found  !<
2899
2900    REAL(wp), &
2901       DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
2902
2903    found = .FALSE.
2904
2905    IF ( read_restart_data_salsa )  THEN
2906
2907       SELECT CASE ( restart_string(1:length) )
2908
2909          CASE ( 'aerosol_mass' )
2910             DO  ic = 1, ncomponents_mass * nbins_aerosol
2911                IF ( k == 1 )  READ ( 13 ) tmp_3d
2912                aerosol_mass(ic)%conc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                 &
2913                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2914             ENDDO
2915             found = .TRUE.
2916
2917          CASE ( 'aerosol_number' )
2918             DO  ib = 1, nbins_aerosol
2919                IF ( k == 1 )  READ ( 13 ) tmp_3d
2920                aerosol_number(ib)%conc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =               &
2921                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2922             ENDDO
2923             found = .TRUE.
2924
2925          CASE( 'salsa_gases_av' )
2926             IF ( .NOT. ALLOCATED( salsa_gases_av ) )  THEN
2927                ALLOCATE( salsa_gases_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ngases_salsa) )
2928             ENDIF
2929             DO  ig = 1, ngases_salsa
2930                IF ( k == 1 )  READ ( 13 ) tmp_3d
2931                salsa_gases_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp,ig) =                     &
2932                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2933             ENDDO
2934             found = .TRUE.
2935
2936          CASE ( 'ldsa_av' )
2937             IF ( .NOT. ALLOCATED( ldsa_av ) )  ALLOCATE( ldsa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2938             IF ( k == 1 )  READ ( 13 ) tmp_3d
2939             ldsa_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2940                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2941             found = .TRUE.
2942
2943          CASE ( 'mbins_av' )
2944             IF ( .NOT. ALLOCATED( mbins_av ) )  THEN
2945                ALLOCATE( mbins_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
2946             ENDIF
2947             DO  ib = 1, nbins_aerosol
2948                IF ( k == 1 )  READ ( 13 ) tmp_3d
2949                mbins_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp,ib) =                           &
2950                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2951                found = .TRUE.
2952             ENDDO
2953
2954          CASE ( 'nbins_av' )
2955             IF ( .NOT. ALLOCATED( nbins_av ) )  THEN
2956                ALLOCATE( nbins_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
2957             ENDIF
2958             DO  ib = 1, nbins_aerosol
2959                IF ( k == 1 )  READ ( 13 ) tmp_3d
2960                nbins_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp,ib) =                           &
2961                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2962                found = .TRUE.
2963             ENDDO
2964
2965          CASE ( 'ntot_av' )
2966             IF ( .NOT. ALLOCATED( ntot_av ) )  ALLOCATE( ntot_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2967             IF ( k == 1 )  READ ( 13 ) tmp_3d
2968             ntot_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2969                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2970             found = .TRUE.
2971
2972          CASE ( 'nufp_av' )
2973             IF ( .NOT. ALLOCATED( nufp_av ) )  ALLOCATE( nufp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2974             IF ( k == 1 )  READ ( 13 ) tmp_3d
2975             nufp_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2976                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2977             found = .TRUE.
2978
2979          CASE ( 'pm01_av' )
2980             IF ( .NOT. ALLOCATED( pm01_av ) )  ALLOCATE( pm01_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2981             IF ( k == 1 )  READ ( 13 ) tmp_3d
2982             pm01_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2983                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2984             found = .TRUE.
2985
2986          CASE ( 'pm25_av' )
2987             IF ( .NOT. ALLOCATED( pm25_av ) )  ALLOCATE( pm25_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2988             IF ( k == 1 )  READ ( 13 ) tmp_3d
2989             pm25_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2990                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2991             found = .TRUE.
2992
2993          CASE ( 'pm10_av' )
2994             IF ( .NOT. ALLOCATED( pm10_av ) )  ALLOCATE( pm10_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2995             IF ( k == 1 )  READ ( 13 ) tmp_3d
2996             pm10_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2997                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2998             found = .TRUE.
2999
3000          CASE ( 's_mass_av' )
3001             IF ( .NOT. ALLOCATED( s_mass_av ) )  THEN
3002                ALLOCATE( s_mass_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg,ncomponents_mass) )
3003             ENDIF
3004             DO  ic = 1, ncomponents_mass
3005                IF ( k == 1 )  READ ( 13 ) tmp_3d
3006                s_mass_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp,ic) =                          &
3007                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3008             ENDDO
3009             found = .TRUE.
3010
3011          CASE ( 's_h2o_av' )
3012             IF ( .NOT. ALLOCATED( s_h2o_av ) )  ALLOCATE( s_h2o_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
3013             IF ( k == 1 )  READ ( 13 ) tmp_3d
3014             s_h2o_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
3015                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3016             found = .TRUE.
3017
3018          CASE ( 'salsa_gas' )
3019             IF ( .NOT. salsa_gases_from_chem )  THEN
3020                DO  ig = 1, ngases_salsa
3021                   IF ( k == 1 )  READ ( 13 ) tmp_3d
3022                   salsa_gas(ig)%conc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                 &
3023                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3024                ENDDO
3025                found = .TRUE.
3026             ENDIF
3027
3028          CASE DEFAULT
3029             found = .FALSE.
3030
3031       END SELECT
3032    ENDIF
3033
3034 END SUBROUTINE salsa_rrd_local
3035
3036!------------------------------------------------------------------------------!
3037! Description:
3038! ------------
3039!> This routine writes the respective restart data.
3040!> Note that the following input variables in PARIN have to be equal between
3041!> restart runs:
3042!>    listspec, nbin, nbin2, nf2a, ncc, mass_fracs_a, mass_fracs_b
3043!------------------------------------------------------------------------------!
3044 SUBROUTINE salsa_wrd_local
3045
3046    USE control_parameters,                                                                        &
3047        ONLY:  write_binary
3048
3049    IMPLICIT NONE
3050
3051    INTEGER(iwp) ::  ib   !<
3052    INTEGER(iwp) ::  ic   !<
3053    INTEGER(iwp) ::  ig  !<
3054
3055    IF ( write_binary  .AND.  write_binary_salsa )  THEN
3056
3057       CALL wrd_write_string( 'aerosol_mass' )
3058       DO  ic = 1, nbins_aerosol * ncomponents_mass
3059          WRITE ( 14 )  aerosol_mass(ic)%conc
3060       ENDDO
3061
3062       CALL wrd_write_string( 'aerosol_number' )
3063       DO  ib = 1, nbins_aerosol
3064          WRITE ( 14 )  aerosol_number(ib)%conc
3065       ENDDO
3066
3067       IF (  .NOT. salsa_gases_from_chem )  THEN
3068
3069          IF ( ALLOCATED( salsa_gases_av ) )  THEN
3070             CALL wrd_write_string( 'salsa_gases_av' )
3071             DO  ig = 1, ngases_salsa
3072                WRITE ( 14 )  salsa_gases_av(:,:,:,ig)
3073             ENDDO
3074          ENDIF
3075       ENDIF
3076
3077       IF ( ALLOCATED( ldsa_av ) )  THEN
3078       CALL wrd_write_string( 'ldsa_av' )
3079       WRITE ( 14 )  ldsa_av
3080       ENDIF
3081
3082       IF ( ALLOCATED( mbins_av ) )  THEN
3083          CALL wrd_write_string( 'mbins_av' )
3084          DO  ib = 1, nbins_aerosol
3085             WRITE ( 14 )  mbins_av(:,:,:,ib)
3086          ENDDO
3087       ENDIF
3088
3089       IF ( ALLOCATED( nbins_av ) )  THEN
3090          CALL wrd_write_string( 'nbins_av' )
3091          DO  ib = 1, nbins_aerosol
3092             WRITE ( 14 )  nbins_av(:,:,:,ib)
3093          ENDDO
3094       ENDIF
3095
3096       IF ( ALLOCATED( ldsa_av ) )  THEN
3097          CALL wrd_write_string( 'ntot_av' )
3098          WRITE ( 14 )  ntot_av
3099       ENDIF
3100
3101       IF ( ALLOCATED( nufp_av ) )  THEN
3102          CALL wrd_write_string( 'nufp_av' )
3103          WRITE ( 14 )  nufp_av
3104       ENDIF
3105
3106       IF ( ALLOCATED( pm01_av ) )  THEN
3107          CALL wrd_write_string( 'pm01_av' )
3108          WRITE ( 14 )  pm01_av
3109       ENDIF
3110
3111       IF ( ALLOCATED( pm25_av ) )  THEN
3112          CALL wrd_write_string( 'pm25_av' )
3113          WRITE ( 14 )  pm25_av
3114       ENDIF
3115
3116       IF ( ALLOCATED( pm10_av ) )  THEN
3117          CALL wrd_write_string( 'pm10_av' )
3118          WRITE ( 14 )  pm10_av
3119       ENDIF
3120
3121       IF ( ALLOCATED( s_mass_av ) )  THEN
3122          CALL wrd_write_string( 's_mass_av' )
3123          DO  ic = 1, ncomponents_mass
3124             WRITE ( 14 )  s_mass_av(:,:,:,ic)
3125          ENDDO
3126       ENDIF
3127
3128       IF ( ALLOCATED( s_h2o_av ) )  THEN
3129          CALL wrd_write_string( 's_h2o_av' )
3130          WRITE ( 14 )  s_h2o_av
3131       ENDIF
3132
3133       IF ( .NOT. salsa_gases_from_chem )  THEN
3134          CALL wrd_write_string( 'salsa_gas' )
3135          DO  ig = 1, ngases_salsa
3136             WRITE ( 14 )  salsa_gas(ig)%conc
3137          ENDDO
3138       ENDIF
3139
3140    ENDIF
3141
3142 END SUBROUTINE salsa_wrd_local
3143
3144!------------------------------------------------------------------------------!
3145! Description:
3146! ------------
3147!> Performs necessary unit and dimension conversion between the host model and
3148!> SALSA module, and calls the main SALSA routine.
3149!> Partially adobted form the original SALSA boxmodel version.
3150!> Now takes masses in as kg/kg from LES!! Converted to m3/m3 for SALSA
3151!> 05/2016 Juha: This routine is still pretty much in its original shape.
3152!>               It's dumb as a mule and twice as ugly, so implementation of
3153!>               an improved solution is necessary sooner or later.
3154!> Juha Tonttila, FMI, 2014
3155!> Jaakko Ahola, FMI, 2016
3156!> Only aerosol processes included, Mona Kurppa, UHel, 2017
3157!------------------------------------------------------------------------------!
3158 SUBROUTINE salsa_driver( i, j, prunmode )
3159
3160    USE arrays_3d,                                                                                 &
3161        ONLY: pt_p, q_p, u, v, w
3162
3163    USE plant_canopy_model_mod,                                                                    &
3164        ONLY: lad_s
3165
3166    USE surface_mod,                                                                               &
3167        ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
3168
3169    IMPLICIT NONE
3170
3171    INTEGER(iwp) ::  endi    !< end index
3172    INTEGER(iwp) ::  ib      !< loop index
3173    INTEGER(iwp) ::  ic      !< loop index
3174    INTEGER(iwp) ::  ig      !< loop index
3175    INTEGER(iwp) ::  k_wall  !< vertical index of topography top
3176    INTEGER(iwp) ::  k       !< loop index
3177    INTEGER(iwp) ::  l       !< loop index
3178    INTEGER(iwp) ::  nc_h2o  !< index of H2O in the prtcl index table
3179    INTEGER(iwp) ::  ss      !< loop index
3180    INTEGER(iwp) ::  str     !< start index
3181    INTEGER(iwp) ::  vc      !< default index in prtcl
3182
3183    INTEGER(iwp), INTENT(in) ::  i         !< loop index
3184    INTEGER(iwp), INTENT(in) ::  j         !< loop index
3185    INTEGER(iwp), INTENT(in) ::  prunmode  !< 1: Initialization, 2: Spinup, 3: Regular runtime
3186
3187    REAL(wp) ::  cw_old  !< previous H2O mixing ratio
3188    REAL(wp) ::  flag    !< flag to mask topography grid points
3189    REAL(wp) ::  in_lad  !< leaf area density (m2/m3)
3190    REAL(wp) ::  in_rh   !< relative humidity
3191    REAL(wp) ::  zgso4   !< SO4
3192    REAL(wp) ::  zghno3  !< HNO3
3193    REAL(wp) ::  zgnh3   !< NH3
3194    REAL(wp) ::  zgocnv  !< non-volatile OC
3195    REAL(wp) ::  zgocsv  !< semi-volatile OC
3196
3197    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_adn  !< air density (kg/m3)
3198    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_cs   !< H2O sat. vapour conc.
3199    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_cw   !< H2O vapour concentration
3200    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_p    !< pressure (Pa)
3201    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_t    !< temperature (K)
3202    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_u    !< wind magnitude (m/s)
3203    REAL(wp), DIMENSION(nzb:nzt+1) ::  kvis    !< kinematic viscosity of air(m2/s)
3204    REAL(wp), DIMENSION(nzb:nzt+1) ::  ppm_to_nconc  !< Conversion factor from ppm to #/m3
3205
3206    REAL(wp), DIMENSION(nzb:nzt+1,nbins_aerosol) ::  schmidt_num  !< particle Schmidt number
3207    REAL(wp), DIMENSION(nzb:nzt+1,nbins_aerosol) ::  vd           !< particle fall seed (m/s)
3208
3209    TYPE(t_section), DIMENSION(nbins_aerosol) ::  lo_aero   !< additional variable for OpenMP
3210    TYPE(t_section), DIMENSION(nbins_aerosol) ::  aero_old  !< helper array
3211
3212    aero_old(:)%numc = 0.0_wp
3213    in_lad           = 0.0_wp
3214    in_u             = 0.0_wp
3215    kvis             = 0.0_wp
3216    lo_aero          = aero
3217    schmidt_num      = 0.0_wp
3218    vd               = 0.0_wp
3219    zgso4            = nclim
3220    zghno3           = nclim
3221    zgnh3            = nclim
3222    zgocnv           = nclim
3223    zgocsv           = nclim
3224!
3225!-- Aerosol number is always set, but mass can be uninitialized
3226    DO ib = 1, nbins_aerosol
3227       lo_aero(ib)%volc(:)  = 0.0_wp
3228       aero_old(ib)%volc(:) = 0.0_wp
3229    ENDDO
3230!
3231!-- Set the salsa runtime config (How to make this more efficient?)
3232    CALL set_salsa_runtime( prunmode )
3233!
3234!-- Calculate thermodynamic quantities needed in SALSA
3235    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 )
3236!
3237!-- Magnitude of wind: needed for deposition
3238    IF ( lsdepo )  THEN
3239       in_u(nzb+1:nzt) = SQRT( ( 0.5_wp * ( u(nzb+1:nzt,j,i) + u(nzb+1:nzt,j,i+1) ) )**2 +         &
3240                               ( 0.5_wp * ( v(nzb+1:nzt,j,i) + v(nzb+1:nzt,j+1,i) ) )**2 +         &
3241                               ( 0.5_wp * ( w(nzb:nzt-1,j,i) + w(nzb+1:nzt,j,  i) ) )**2 )
3242    ENDIF
3243!
3244!-- Calculate conversion factors for gas concentrations
3245    ppm_to_nconc(:) = for_ppm_to_nconc * in_p(:) / in_t(:)
3246!
3247!-- Determine topography-top index on scalar grid
3248    k_wall = k_topo_top(j,i)
3249
3250    DO k = nzb+1, nzt
3251!
3252!--    Predetermine flag to mask topography
3253       flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
3254!
3255!--    Wind velocity for dry depositon on vegetation
3256       IF ( lsdepo_pcm  .AND.  plant_canopy )  THEN
3257          in_lad = lad_s( MAX( k-k_wall,0 ),j,i)
3258       ENDIF
3259!
3260!--    For initialization and spinup, limit the RH with the parameter rhlim
3261       IF ( prunmode < 3 ) THEN
3262          in_cw(k) = MIN( in_cw(k), in_cs(k) * rhlim )
3263       ELSE
3264          in_cw(k) = in_cw(k)
3265       ENDIF
3266       cw_old = in_cw(k) !* in_adn(k)
3267!
3268!--    Set volume concentrations:
3269!--    Sulphate (SO4) or sulphuric acid H2SO4
3270       IF ( index_so4 > 0 )  THEN
3271          vc = 1
3272          str = ( index_so4-1 ) * nbins_aerosol + 1    ! start index
3273          endi = index_so4 * nbins_aerosol             ! end index
3274          ic = 1
3275          DO ss = str, endi
3276             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoh2so4
3277             ic = ic+1
3278          ENDDO
3279          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3280       ENDIF
3281!
3282!--    Organic carbon (OC) compounds
3283       IF ( index_oc > 0 )  THEN
3284          vc = 2
3285          str = ( index_oc-1 ) * nbins_aerosol + 1
3286          endi = index_oc * nbins_aerosol
3287          ic = 1
3288          DO ss = str, endi
3289             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhooc
3290             ic = ic+1
3291          ENDDO
3292          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3293       ENDIF
3294!
3295!--    Black carbon (BC)
3296       IF ( index_bc > 0 )  THEN
3297          vc = 3
3298          str = ( index_bc-1 ) * nbins_aerosol + 1 + end_subrange_1a
3299          endi = index_bc * nbins_aerosol
3300          ic = 1 + end_subrange_1a
3301          DO ss = str, endi
3302             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhobc
3303             ic = ic+1
3304          ENDDO
3305          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3306       ENDIF
3307!
3308!--    Dust (DU)
3309       IF ( index_du > 0 )  THEN
3310          vc = 4
3311          str = ( index_du-1 ) * nbins_aerosol + 1 + end_subrange_1a
3312          endi = index_du * nbins_aerosol
3313          ic = 1 + end_subrange_1a
3314          DO ss = str, endi
3315             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhodu
3316             ic = ic+1
3317          ENDDO
3318          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3319       ENDIF
3320!
3321!--    Sea salt (SS)
3322       IF ( index_ss > 0 )  THEN
3323          vc = 5
3324          str = ( index_ss-1 ) * nbins_aerosol + 1 + end_subrange_1a
3325          endi = index_ss * nbins_aerosol
3326          ic = 1 + end_subrange_1a
3327          DO ss = str, endi
3328             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoss
3329             ic = ic+1
3330          ENDDO
3331          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3332       ENDIF
3333!
3334!--    Nitrate (NO(3-)) or nitric acid HNO3
3335       IF ( index_no > 0 )  THEN
3336          vc = 6
3337          str = ( index_no-1 ) * nbins_aerosol + 1 
3338          endi = index_no * nbins_aerosol
3339          ic = 1
3340          DO ss = str, endi
3341             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhohno3
3342             ic = ic+1
3343          ENDDO
3344          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3345       ENDIF
3346!
3347!--    Ammonium (NH(4+)) or ammonia NH3
3348       IF ( index_nh > 0 )  THEN
3349          vc = 7
3350          str = ( index_nh-1 ) * nbins_aerosol + 1
3351          endi = index_nh * nbins_aerosol
3352          ic = 1
3353          DO ss = str, endi
3354             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhonh3
3355             ic = ic+1
3356          ENDDO
3357          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3358       ENDIF
3359!
3360!--    Water (always used)
3361       nc_h2o = get_index( prtcl,'H2O' )
3362       vc = 8
3363       str = ( nc_h2o-1 ) * nbins_aerosol + 1
3364       endi = nc_h2o * nbins_aerosol
3365       ic = 1
3366       IF ( advect_particle_water )  THEN
3367          DO ss = str, endi
3368             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoh2o
3369             ic = ic+1
3370          ENDDO
3371       ELSE
3372         lo_aero(1:nbins_aerosol)%volc(vc) = mclim
3373       ENDIF
3374       aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
3375!
3376!--    Number concentrations (numc) and particle sizes
3377!--    (dwet = wet diameter, core = dry volume)
3378       DO  ib = 1, nbins_aerosol
3379          lo_aero(ib)%numc = aerosol_number(ib)%conc(k,j,i)
3380          aero_old(ib)%numc = lo_aero(ib)%numc
3381          IF ( lo_aero(ib)%numc > nclim )  THEN
3382             lo_aero(ib)%dwet = ( SUM( lo_aero(ib)%volc(:) ) / lo_aero(ib)%numc / api6 )**0.33333333_wp
3383             lo_aero(ib)%core = SUM( lo_aero(ib)%volc(1:7) ) / lo_aero(ib)%numc
3384          ELSE
3385             lo_aero(ib)%dwet = lo_aero(ib)%dmid
3386             lo_aero(ib)%core = api6 * ( lo_aero(ib)%dwet )**3
3387          ENDIF
3388       ENDDO
3389!
3390!--    Calculate the ambient sizes of particles by equilibrating soluble fraction of particles with
3391!--    water using the ZSR method.
3392       in_rh = in_cw(k) / in_cs(k)
3393       IF ( prunmode==1  .OR.  .NOT. advect_particle_water )  THEN
3394          CALL equilibration( in_rh, in_t(k), lo_aero, .TRUE. )
3395       ENDIF
3396!
3397!--    Gaseous tracer concentrations in #/m3
3398       IF ( salsa_gases_from_chem )  THEN
3399!
3400!--       Convert concentrations in ppm to #/m3
3401          zgso4  = chem_species(gas_index_chem(1))%conc(k,j,i) * ppm_to_nconc(k)
3402          zghno3 = chem_species(gas_index_chem(2))%conc(k,j,i) * ppm_to_nconc(k)
3403          zgnh3  = chem_species(gas_index_chem(3))%conc(k,j,i) * ppm_to_nconc(k)
3404          zgocnv = chem_species(gas_index_chem(4))%conc(k,j,i) * ppm_to_nconc(k)
3405          zgocsv = chem_species(gas_index_chem(5))%conc(k,j,i) * ppm_to_nconc(k)
3406       ELSE
3407          zgso4  = salsa_gas(1)%conc(k,j,i)
3408          zghno3 = salsa_gas(2)%conc(k,j,i)
3409          zgnh3  = salsa_gas(3)%conc(k,j,i)
3410          zgocnv = salsa_gas(4)%conc(k,j,i)
3411          zgocsv = salsa_gas(5)%conc(k,j,i)
3412       ENDIF
3413!
3414!--    Calculate aerosol processes:
3415!--    *********************************************************************************************
3416!
3417!--    Coagulation
3418       IF ( lscoag )   THEN
3419          CALL coagulation( lo_aero, dt_salsa, in_t(k), in_p(k) )
3420       ENDIF
3421!
3422!--    Condensation
3423       IF ( lscnd )   THEN
3424          CALL condensation( lo_aero, zgso4, zgocnv, zgocsv,  zghno3, zgnh3, in_cw(k), in_cs(k),   &
3425                             in_t(k), in_p(k), dt_salsa, prtcl )
3426       ENDIF
3427!
3428!--    Deposition
3429       IF ( lsdepo )  THEN
3430          CALL deposition( lo_aero, in_t(k), in_adn(k), in_u(k), in_lad, kvis(k), schmidt_num(k,:),&
3431                           vd(k,:) )
3432       ENDIF
3433!
3434!--    Size distribution bin update
3435       IF ( lsdistupdate )   THEN
3436          CALL distr_update( lo_aero )
3437       ENDIF
3438!--    *********************************************************************************************
3439
3440       IF ( lsdepo ) sedim_vd(k,j,i,:) = vd(k,:)
3441!
3442!--    Calculate changes in concentrations
3443       DO ib = 1, nbins_aerosol
3444          aerosol_number(ib)%conc(k,j,i) = aerosol_number(ib)%conc(k,j,i) + ( lo_aero(ib)%numc -   &
3445                                           aero_old(ib)%numc ) * flag
3446       ENDDO
3447
3448       IF ( index_so4 > 0 )  THEN
3449          vc = 1
3450          str = ( index_so4-1 ) * nbins_aerosol + 1
3451          endi = index_so4 * nbins_aerosol
3452          ic = 1
3453          DO ss = str, endi
3454             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3455                                            aero_old(ic)%volc(vc) ) * arhoh2so4 * flag
3456             ic = ic+1
3457          ENDDO
3458       ENDIF
3459
3460       IF ( index_oc > 0 )  THEN
3461          vc = 2
3462          str = ( index_oc-1 ) * nbins_aerosol + 1
3463          endi = index_oc * nbins_aerosol
3464          ic = 1
3465          DO ss = str, endi
3466             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3467                                            aero_old(ic)%volc(vc) ) * arhooc * flag
3468             ic = ic+1
3469          ENDDO
3470       ENDIF
3471
3472       IF ( index_bc > 0 )  THEN
3473          vc = 3
3474          str = ( index_bc-1 ) * nbins_aerosol + 1 + end_subrange_1a
3475          endi = index_bc * nbins_aerosol
3476          ic = 1 + end_subrange_1a
3477          DO ss = str, endi
3478             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3479                                            aero_old(ic)%volc(vc) ) * arhobc * flag
3480             ic = ic+1
3481          ENDDO
3482       ENDIF
3483
3484       IF ( index_du > 0 )  THEN
3485          vc = 4
3486          str = ( index_du-1 ) * nbins_aerosol + 1 + end_subrange_1a
3487          endi = index_du * nbins_aerosol
3488          ic = 1 + end_subrange_1a
3489          DO ss = str, endi
3490             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3491                                            aero_old(ic)%volc(vc) ) * arhodu * flag
3492             ic = ic+1
3493          ENDDO
3494       ENDIF
3495
3496       IF ( index_ss > 0 )  THEN
3497          vc = 5
3498          str = ( index_ss-1 ) * nbins_aerosol + 1 + end_subrange_1a
3499          endi = index_ss * nbins_aerosol
3500          ic = 1 + end_subrange_1a
3501          DO ss = str, endi
3502             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3503                                            aero_old(ic)%volc(vc) ) * arhoss * flag
3504             ic = ic+1
3505          ENDDO
3506       ENDIF
3507
3508       IF ( index_no > 0 )  THEN
3509          vc = 6
3510          str = ( index_no-1 ) * nbins_aerosol + 1
3511          endi = index_no * nbins_aerosol
3512          ic = 1
3513          DO ss = str, endi
3514             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3515                                            aero_old(ic)%volc(vc) ) * arhohno3 * flag
3516             ic = ic+1
3517          ENDDO
3518       ENDIF
3519
3520       IF ( index_nh > 0 )  THEN
3521          vc = 7
3522          str = ( index_nh-1 ) * nbins_aerosol + 1
3523          endi = index_nh * nbins_aerosol
3524          ic = 1
3525          DO ss = str, endi
3526             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3527                                            aero_old(ic)%volc(vc) ) * arhonh3 * flag
3528             ic = ic+1
3529          ENDDO
3530       ENDIF
3531
3532       IF ( advect_particle_water )  THEN
3533          nc_h2o = get_index( prtcl,'H2O' )
3534          vc = 8
3535          str = ( nc_h2o-1 ) * nbins_aerosol + 1
3536          endi = nc_h2o * nbins_aerosol
3537          ic = 1
3538          DO ss = str, endi
3539             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -&
3540                                            aero_old(ic)%volc(vc) ) * arhoh2o * flag
3541             ic = ic+1
3542          ENDDO
3543          IF ( prunmode == 1 )  THEN
3544             nc_h2o = get_index( prtcl,'H2O' )
3545             vc = 8
3546             str = ( nc_h2o-1 ) * nbins_aerosol + 1
3547             endi = nc_h2o * nbins_aerosol
3548             ic = 1
3549             DO ss = str, endi
3550                aerosol_mass(ss)%init(k) = MAX( aerosol_mass(ss)%init(k), ( lo_aero(ic)%volc(vc) - &
3551                                                aero_old(ic)%volc(vc) ) * arhoh2o )
3552                IF ( k == nzb+1 )  THEN
3553                   aerosol_mass(ss)%init(k-1) = aerosol_mass(ss)%init(k)
3554                ELSEIF ( k == nzt  )  THEN
3555                   aerosol_mass(ss)%init(k+1) = aerosol_mass(ss)%init(k)
3556                   aerosol_mass(ss)%conc(k+1,j,i) = aerosol_mass(ss)%init(k)
3557                ENDIF
3558                ic = ic+1
3559             ENDDO
3560          ENDIF
3561       ENDIF
3562!
3563!--    Condensation of precursor gases
3564       IF ( lscndgas )  THEN
3565          IF ( salsa_gases_from_chem )  THEN
3566!
3567!--          SO4 (or H2SO4)
3568             ig = gas_index_chem(1)
3569             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zgso4 /               &
3570                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3571!
3572!--          HNO3
3573             ig = gas_index_chem(2)
3574             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zghno3 /              &
3575                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3576!
3577!--          NH3
3578             ig = gas_index_chem(3)
3579             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zgnh3 /               &
3580                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3581!
3582!--          non-volatile OC
3583             ig = gas_index_chem(4)
3584             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zgocnv /              &
3585                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3586!
3587!--          semi-volatile OC
3588             ig = gas_index_chem(5)
3589             chem_species(ig)%conc(k,j,i) = chem_species(ig)%conc(k,j,i) + ( zgocsv /              &
3590                                            ppm_to_nconc(k) - chem_species(ig)%conc(k,j,i) ) * flag
3591
3592          ELSE
3593!
3594!--          SO4 (or H2SO4)
3595             salsa_gas(1)%conc(k,j,i) = salsa_gas(1)%conc(k,j,i) + ( zgso4 -                       &
3596                                        salsa_gas(1)%conc(k,j,i) ) * flag
3597!
3598!--          HNO3
3599             salsa_gas(2)%conc(k,j,i) = salsa_gas(2)%conc(k,j,i) + ( zghno3 -                      &
3600                                        salsa_gas(2)%conc(k,j,i) ) * flag
3601!
3602!--          NH3
3603             salsa_gas(3)%conc(k,j,i) = salsa_gas(3)%conc(k,j,i) + ( zgnh3 -                       &
3604                                        salsa_gas(3)%conc(k,j,i) ) * flag
3605!
3606!--          non-volatile OC
3607             salsa_gas(4)%conc(k,j,i) = salsa_gas(4)%conc(k,j,i) + ( zgocnv -                      &
3608                                        salsa_gas(4)%conc(k,j,i) ) * flag
3609!
3610!--          semi-volatile OC
3611             salsa_gas(5)%conc(k,j,i) = salsa_gas(5)%conc(k,j,i) + ( zgocsv -                      &
3612                                        salsa_gas(5)%conc(k,j,i) ) * flag
3613          ENDIF
3614       ENDIF
3615!
3616!--    Tendency of water vapour mixing ratio is obtained from the change in RH during SALSA run.
3617!--    This releases heat and changes pt. Assumes no temperature change during SALSA run.
3618!--    q = r / (1+r), Euler method for integration
3619!
3620       IF ( feedback_to_palm )  THEN
3621          q_p(k,j,i) = q_p(k,j,i) + 1.0_wp / ( in_cw(k) * in_adn(k) + 1.0_wp )**2 *                &
3622                       ( in_cw(k) - cw_old ) * in_adn(k) * flag
3623          pt_p(k,j,i) = pt_p(k,j,i) + alv / c_p * ( in_cw(k) - cw_old ) * in_adn(k) / ( in_cw(k) / &
3624                        in_adn(k) + 1.0_wp )**2 * pt_p(k,j,i) / in_t(k) * flag
3625       ENDIF
3626
3627    ENDDO   ! k
3628
3629!
3630!-- Set surfaces and wall fluxes due to deposition
3631    IF ( lsdepo  .AND.  lsdepo_surf  .AND.  prunmode == 3 )  THEN
3632       IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
3633          CALL depo_surf( i, j, surf_def_h(0), vd, schmidt_num, kvis, in_u, .TRUE. )
3634          DO  l = 0, 3
3635             CALL depo_surf( i, j, surf_def_v(l), vd, schmidt_num, kvis, in_u, .FALSE. )
3636          ENDDO
3637       ELSE
3638          CALL depo_surf( i, j, surf_usm_h, vd, schmidt_num, kvis, in_u, .TRUE., usm_to_depo_h )
3639          DO  l = 0, 3
3640             CALL depo_surf( i, j, surf_usm_v(l), vd, schmidt_num, kvis, in_u, .FALSE.,            &
3641                             usm_to_depo_v(l) )
3642          ENDDO
3643          CALL depo_surf( i, j, surf_lsm_h, vd, schmidt_num, kvis, in_u, .TRUE., lsm_to_depo_h )
3644          DO  l = 0, 3
3645             CALL depo_surf( i, j, surf_lsm_v(l), vd, schmidt_num, kvis, in_u, .FALSE.,            &
3646                             lsm_to_depo_v(l) )
3647          ENDDO
3648       ENDIF
3649    ENDIF
3650
3651    IF ( prunmode < 3 )  THEN
3652       !$OMP MASTER
3653       aero = lo_aero
3654       !$OMP END MASTER
3655    END IF
3656
3657 END SUBROUTINE salsa_driver
3658
3659!------------------------------------------------------------------------------!
3660! Description:
3661! ------------
3662!> Set logical switches according to the salsa_parameters options.
3663!> Juha Tonttila, FMI, 2014
3664!> Only aerosol processes included, Mona Kurppa, UHel, 2017
3665!------------------------------------------------------------------------------!
3666 SUBROUTINE set_salsa_runtime( prunmode )
3667
3668    IMPLICIT NONE
3669
3670    INTEGER(iwp), INTENT(in) ::  prunmode
3671
3672    SELECT CASE(prunmode)
3673
3674       CASE(1) !< Initialization
3675          lscoag       = .FALSE.
3676          lscnd        = .FALSE.
3677          lscndgas     = .FALSE.
3678          lscndh2oae   = .FALSE.
3679          lsdepo       = .FALSE.
3680          lsdepo_pcm   = .FALSE.
3681          lsdepo_surf  = .FALSE.
3682          lsdistupdate = .TRUE.
3683          lspartition  = .FALSE.
3684
3685       CASE(2)  !< Spinup period
3686          lscoag      = ( .FALSE. .AND. nlcoag   )
3687          lscnd       = ( .TRUE.  .AND. nlcnd    )
3688          lscndgas    = ( .TRUE.  .AND. nlcndgas )
3689          lscndh2oae  = ( .TRUE.  .AND. nlcndh2oae )
3690
3691       CASE(3)  !< Run
3692          lscoag       = nlcoag
3693          lscnd        = nlcnd
3694          lscndgas     = nlcndgas
3695          lscndh2oae   = nlcndh2oae
3696          lsdepo       = nldepo
3697          lsdepo_pcm   = nldepo_pcm
3698          lsdepo_surf  = nldepo_surf
3699          lsdistupdate = nldistupdate
3700    END SELECT
3701
3702
3703 END SUBROUTINE set_salsa_runtime
3704 
3705!------------------------------------------------------------------------------!
3706! Description:
3707! ------------
3708!> Calculates the absolute temperature (using hydrostatic pressure), saturation
3709!> vapour pressure and mixing ratio over water, relative humidity and air
3710!> density needed in the SALSA model.
3711!> NOTE, no saturation adjustment takes place -> the resulting water vapour
3712!> mixing ratio can be supersaturated, allowing the microphysical calculations
3713!> in SALSA.
3714!
3715!> Juha Tonttila, FMI, 2014 (original SALSAthrm)
3716!> Mona Kurppa, UHel, 2017 (adjustment for PALM and only aerosol processes)
3717!------------------------------------------------------------------------------!
3718 SUBROUTINE salsa_thrm_ij( i, j, p_ij, temp_ij, cw_ij, cs_ij, adn_ij )
3719
3720    USE arrays_3d,                                                                                 &
3721        ONLY: pt, q, zu
3722
3723    USE basic_constants_and_equations_mod,                                                         &
3724        ONLY:  barometric_formula, exner_function, ideal_gas_law_rho, magnus
3725
3726    IMPLICIT NONE
3727
3728    INTEGER(iwp), INTENT(in) ::  i  !<
3729    INTEGER(iwp), INTENT(in) ::  j  !<
3730
3731    REAL(wp) ::  t_surface  !< absolute surface temperature (K)
3732
3733    REAL(wp), DIMENSION(nzb:nzt+1) ::  e_s  !< saturation vapour pressure over water (Pa)
3734
3735    REAL(wp), DIMENSION(:), INTENT(inout) ::  adn_ij   !< air density (kg/m3)
3736    REAL(wp), DIMENSION(:), INTENT(inout) ::  p_ij     !< air pressure (Pa)
3737    REAL(wp), DIMENSION(:), INTENT(inout) ::  temp_ij  !< air temperature (K)
3738
3739    REAL(wp), DIMENSION(:), INTENT(inout), OPTIONAL ::  cw_ij  !< water vapour concentration (kg/m3)
3740    REAL(wp), DIMENSION(:), INTENT(inout), OPTIONAL ::  cs_ij  !< saturation water vap. conc.(kg/m3)
3741!
3742!-- Pressure p_ijk (Pa) = hydrostatic pressure
3743    t_surface = pt_surface * exner_function( surface_pressure * 100.0_wp )
3744    p_ij(:) = barometric_formula( zu, t_surface, surface_pressure * 100.0_wp )
3745!
3746!-- Absolute ambient temperature (K)
3747    temp_ij(:) = pt(:,j,i) * exner_function( p_ij(:) )
3748!
3749!-- Air density
3750    adn_ij(:) = ideal_gas_law_rho( p_ij(:), temp_ij(:) )
3751!
3752!-- Water vapour concentration r_v (kg/m3)
3753    IF ( PRESENT( cw_ij ) )  THEN
3754       cw_ij(:) = ( q(:,j,i) / ( 1.0_wp - q(:,j,i) ) ) * adn_ij(:)
3755    ENDIF
3756!
3757!-- Saturation mixing ratio r_s (kg/kg) from vapour pressure at temp (Pa)
3758    IF ( PRESENT( cs_ij ) )  THEN
3759       e_s(:) = 611.0_wp * EXP( alv_d_rv * ( 3.6609E-3_wp - 1.0_wp /           &
3760                temp_ij(:) ) )! magnus( temp_ij(:) )
3761       cs_ij(:) = ( 0.622_wp * e_s / ( p_ij(:) - e_s(:) ) ) * adn_ij(:)
3762    ENDIF
3763
3764 END SUBROUTINE salsa_thrm_ij
3765
3766!------------------------------------------------------------------------------!
3767! Description:
3768! ------------
3769!> Calculates ambient sizes of particles by equilibrating soluble fraction of
3770!> particles with water using the ZSR method (Stokes and Robinson, 1966).
3771!> Method:
3772!> Following chemical components are assumed water-soluble
3773!> - (ammonium) sulphate (100%)
3774!> - sea salt (100 %)
3775!> - organic carbon (epsoc * 100%)
3776!> Exact thermodynamic considerations neglected.
3777!> - If particles contain no sea salt, calculation according to sulphate
3778!>   properties
3779!> - If contain sea salt but no sulphate, calculation according to sea salt
3780!>   properties
3781!> - If contain both sulphate and sea salt -> the molar fraction of these
3782!>   compounds determines which one of them is used as the basis of calculation.
3783!> If sulphate and sea salt coexist in a particle, it is assumed that the Cl is
3784!> replaced by sulphate; thus only either sulphate + organics or sea salt +
3785!> organics is included in the calculation of soluble fraction.
3786!> Molality parameterizations taken from Table 1 of Tang: Thermodynamic and
3787!> optical properties of mixed-salt aerosols of atmospheric importance,
3788!> J. Geophys. Res., 102 (D2), 1883-1893 (1997)
3789!
3790!> Coded by:
3791!> Hannele Korhonen (FMI) 2005
3792!> Harri Kokkola (FMI) 2006
3793!> Matti Niskanen(FMI) 2012
3794!> Anton Laakso  (FMI) 2013
3795!> Modified for the new aerosol datatype, Juha Tonttila (FMI) 2014
3796!
3797!> fxm: should sea salt form a solid particle when prh is very low (even though
3798!> it could be mixed with e.g. sulphate)?
3799!> fxm: crashes if no sulphate or sea salt
3800!> fxm: do we really need to consider Kelvin effect for subrange 2
3801!------------------------------------------------------------------------------!
3802 SUBROUTINE equilibration( prh, ptemp, paero, init )
3803
3804    IMPLICIT NONE
3805
3806    INTEGER(iwp) :: ib      !< loop index
3807    INTEGER(iwp) :: counti  !< loop index
3808
3809    LOGICAL, INTENT(in) ::  init   !< TRUE: Initialization, FALSE: Normal runtime: update water
3810                                   !< content only for 1a
3811
3812    REAL(wp) ::  zaw      !< water activity [0-1]
3813    REAL(wp) ::  zcore    !< Volume of dry particle
3814    REAL(wp) ::  zdold    !< Old diameter
3815    REAL(wp) ::  zdwet    !< Wet diameter or mean droplet diameter
3816    REAL(wp) ::  zke      !< Kelvin term in the Köhler equation
3817    REAL(wp) ::  zlwc     !< liquid water content [kg/m3-air]
3818    REAL(wp) ::  zrh      !< Relative humidity
3819
3820    REAL(wp), DIMENSION(maxspec) ::  zbinmol  !< binary molality of each components (mol/kg)
3821    REAL(wp), DIMENSION(maxspec) ::  zvpart   !< volume of chem. compounds in one particle
3822
3823    REAL(wp), INTENT(in) ::  prh    !< relative humidity [0-1]
3824    REAL(wp), INTENT(in) ::  ptemp  !< temperature (K)
3825
3826    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< aerosol properties
3827
3828    zaw       = 0.0_wp
3829    zlwc      = 0.0_wp
3830!
3831!-- Relative humidity:
3832    zrh = prh
3833    zrh = MAX( zrh, 0.05_wp )
3834    zrh = MIN( zrh, 0.98_wp)
3835!
3836!-- 1) Regime 1: sulphate and partly water-soluble OC. Done for every CALL
3837    DO  ib = start_subrange_1a, end_subrange_1a   ! size bin
3838
3839       zbinmol = 0.0_wp
3840       zdold   = 1.0_wp
3841       zke     = 1.02_wp
3842
3843       IF ( paero(ib)%numc > nclim )  THEN
3844!
3845!--       Volume in one particle
3846          zvpart = 0.0_wp
3847          zvpart(1:2) = paero(ib)%volc(1:2) / paero(ib)%numc
3848          zvpart(6:7) = paero(ib)%volc(6:7) / paero(ib)%numc
3849!
3850!--       Total volume and wet diameter of one dry particle
3851          zcore = SUM( zvpart(1:2) )
3852          zdwet = paero(ib)%dwet
3853
3854          counti = 0
3855          DO  WHILE ( ABS( zdwet / zdold - 1.0_wp ) > 1.0E-2_wp )
3856
3857             zdold = MAX( zdwet, 1.0E-20_wp )
3858             zaw = MAX( 1.0E-3_wp, zrh / zke ) ! To avoid underflow
3859!
3860!--          Binary molalities (mol/kg):
3861!--          Sulphate
3862             zbinmol(1) = 1.1065495E+2_wp - 3.6759197E+2_wp * zaw + 5.0462934E+2_wp * zaw**2 -     &
3863                          3.1543839E+2_wp * zaw**3 + 6.770824E+1_wp  * zaw**4
3864!--          Organic carbon
3865             zbinmol(2) = 1.0_wp / ( zaw * amh2o ) - 1.0_wp / amh2o
3866!--          Nitric acid
3867             zbinmol(6) = 2.306844303E+1_wp - 3.563608869E+1_wp * zaw - 6.210577919E+1_wp * zaw**2 &
3868                          + 5.510176187E+2_wp * zaw**3 - 1.460055286E+3_wp * zaw**4                &
3869                          + 1.894467542E+3_wp * zaw**5 - 1.220611402E+3_wp * zaw**6                &
3870                          + 3.098597737E+2_wp * zaw**7
3871!
3872!--          Calculate the liquid water content (kg/m3-air) using ZSR (see e.g. Eq. 10.98 in
3873!--          Seinfeld and Pandis (2006))
3874             zlwc = ( paero(ib)%volc(1) * ( arhoh2so4 / amh2so4 ) ) / zbinmol(1) +                 &
3875                    epsoc * paero(ib)%volc(2) * ( arhooc / amoc ) / zbinmol(2) +                   &
3876                    ( paero(ib)%volc(6) * ( arhohno3/amhno3 ) ) / zbinmol(6)
3877!
3878!--          Particle wet diameter (m)
3879             zdwet = ( zlwc / paero(ib)%numc / arhoh2o / api6 + ( SUM( zvpart(6:7) ) / api6 ) +    &
3880                       zcore / api6 )**0.33333333_wp
3881!
3882!--          Kelvin effect (Eq. 10.85 in in Seinfeld and Pandis (2006)). Avoid
3883!--          overflow.
3884             zke = EXP( MIN( 50.0_wp, 4.0_wp * surfw0 * amvh2so4 / ( abo * ptemp *  zdwet ) ) )
3885
3886             counti = counti + 1
3887             IF ( counti > 1000 )  THEN
3888                message_string = 'Subrange 1: no convergence!'
3889                CALL message( 'salsa_mod: equilibration', 'PA0617', 1, 2, 0, 6, 0 )
3890             ENDIF
3891          ENDDO
3892!
3893!--       Instead of lwc, use the volume concentration of water from now on
3894!--       (easy to convert...)
3895          paero(ib)%volc(8) = zlwc / arhoh2o
3896!
3897!--       If this is initialization, update the core and wet diameter
3898          IF ( init )  THEN
3899             paero(ib)%dwet = zdwet
3900             paero(ib)%core = zcore
3901          ENDIF
3902
3903       ELSE
3904!--       If initialization
3905!--       1.2) empty bins given bin average values
3906          IF ( init )  THEN
3907             paero(ib)%dwet = paero(ib)%dmid
3908             paero(ib)%core = api6 * paero(ib)%dmid**3
3909          ENDIF
3910
3911       ENDIF
3912
3913    ENDDO  ! ib
3914!
3915!-- 2) Regime 2a: sulphate, OC, BC and sea salt
3916!--    This is done only for initialization call, otherwise the water contents
3917!--    are computed via condensation
3918    IF ( init )  THEN
3919       DO  ib = start_subrange_2a, end_subrange_2b
3920!
3921!--       Initialize
3922          zke     = 1.02_wp
3923          zbinmol = 0.0_wp
3924          zdold   = 1.0_wp
3925!
3926!--       1) Particle properties calculated for non-empty bins
3927          IF ( paero(ib)%numc > nclim )  THEN
3928!
3929!--          Volume in one particle [fxm]
3930             zvpart = 0.0_wp
3931             zvpart(1:7) = paero(ib)%volc(1:7) / paero(ib)%numc
3932!
3933!--          Total volume and wet diameter of one dry particle [fxm]
3934             zcore = SUM( zvpart(1:5) )
3935             zdwet = paero(ib)%dwet
3936
3937             counti = 0
3938             DO  WHILE ( ABS( zdwet / zdold - 1.0_wp ) > 1.0E-12_wp )
3939
3940                zdold = MAX( zdwet, 1.0E-20_wp )
3941                zaw = zrh / zke
3942!
3943!--             Binary molalities (mol/kg):
3944!--             Sulphate
3945                zbinmol(1) = 1.1065495E+2_wp - 3.6759197E+2_wp * zaw + 5.0462934E+2_wp * zaw**2 -  &
3946                             3.1543839E+2_wp * zaw**3 + 6.770824E+1_wp  * zaw**4
3947!--             Organic carbon
3948                zbinmol(2) = 1.0_wp / ( zaw * amh2o ) - 1.0_wp / amh2o
3949!--             Nitric acid
3950                zbinmol(6) = 2.306844303E+1_wp          - 3.563608869E+1_wp * zaw -                &
3951                             6.210577919E+1_wp * zaw**2 + 5.510176187E+2_wp * zaw**3 -             &
3952                             1.460055286E+3_wp * zaw**4 + 1.894467542E+3_wp * zaw**5 -             &
3953                             1.220611402E+3_wp * zaw**6 + 3.098597737E+2_wp * zaw**7 
3954!--             Sea salt (natrium chloride)
3955                zbinmol(5) = 5.875248E+1_wp - 1.8781997E+2_wp * zaw + 2.7211377E+2_wp * zaw**2 -   &
3956                             1.8458287E+2_wp * zaw**3 + 4.153689E+1_wp  * zaw**4
3957!
3958!--             Calculate the liquid water content (kg/m3-air)
3959                zlwc = ( paero(ib)%volc(1) * ( arhoh2so4 / amh2so4 ) ) / zbinmol(1) +              &
3960                       epsoc * ( paero(ib)%volc(2) * ( arhooc / amoc ) ) / zbinmol(2) +            &
3961                       ( paero(ib)%volc(6) * ( arhohno3 / amhno3 ) ) / zbinmol(6) +                &
3962                       ( paero(ib)%volc(5) * ( arhoss / amss ) ) / zbinmol(5)
3963
3964!--             Particle wet radius (m)
3965                zdwet = ( zlwc / paero(ib)%numc / arhoh2o / api6 + ( SUM( zvpart(6:7) ) / api6 )  + &
3966                           zcore / api6 )**0.33333333_wp
3967!
3968!--             Kelvin effect (Eq. 10.85 in Seinfeld and Pandis (2006))
3969                zke = EXP( MIN( 50.0_wp, 4.0_wp * surfw0 * amvh2so4 / ( abo * zdwet * ptemp ) ) )
3970
3971                counti = counti + 1
3972                IF ( counti > 1000 )  THEN
3973                   message_string = 'Subrange 2: no convergence!'
3974                CALL message( 'salsa_mod: equilibration', 'PA0618', 1, 2, 0, 6, 0 )
3975                ENDIF
3976             ENDDO
3977!
3978!--          Liquid water content; instead of LWC use the volume concentration
3979             paero(ib)%volc(8) = zlwc / arhoh2o
3980             paero(ib)%dwet    = zdwet
3981             paero(ib)%core    = zcore
3982
3983          ELSE
3984!--          2.2) empty bins given bin average values
3985             paero(ib)%dwet = paero(ib)%dmid
3986             paero(ib)%core = api6 * paero(ib)%dmid**3
3987          ENDIF
3988
3989       ENDDO   ! ib
3990    ENDIF
3991
3992 END SUBROUTINE equilibration
3993
3994!------------------------------------------------------------------------------!
3995!> Description:
3996!> ------------
3997!> Calculation of the settling velocity vc (m/s) per aerosol size bin and
3998!> deposition on plant canopy (lsdepo_pcm).
3999!