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

Last change on this file since 3872 was 3872, checked in by knoop, 4 years ago

Including last commit, salsa dependency for advec_ws removed

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