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

Last change on this file since 3871 was 3871, checked in by knoop, 6 years ago

Moving prognostic equations of bcm into bulk_cloud_model_mod

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