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

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

corrected the OpenMP implementation for salsa and some minor bugs in salsa_mod

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