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

Last change on this file since 3872 was 3872, checked in by knoop, 6 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)
3932    REAL(wp), INTENT(in) ::  mass1  !< mass of colliding particle 1 (kg)
3933    REAL(wp), INTENT(in) ::  mass2  !< mass of colliding particle 2 (kg)
3934    REAL(wp), INTENT(in) ::  pres   !< ambient pressure (Pa?) [fxm]
3935    REAL(wp), INTENT(in) ::  temp   !< ambient temperature (K)
3936
3937    REAL(wp), DIMENSION (2) ::  beta    !< Cunningham correction factor
3938    REAL(wp), DIMENSION (2) ::  dfpart  !< particle diffusion coefficient (m2/s)
3939    REAL(wp), DIMENSION (2) ::  diam    !< diameters of particles (m)
3940    REAL(wp), DIMENSION (2) ::  flux    !< flux in continuum and free molec. regime (m/s)
3941    REAL(wp), DIMENSION (2) ::  knud    !< particle Knudsen number
3942    REAL(wp), DIMENSION (2) ::  mpart   !< masses of particles (kg)
3943    REAL(wp), DIMENSION (2) ::  mtvel   !< particle mean thermal velocity (m/s)
3944    REAL(wp), DIMENSION (2) ::  omega   !< particle mean free path
3945    REAL(wp), DIMENSION (2) ::  tva     !< temporary variable (m)
3946!
3947!-- Initialisation
3948    coagc   = 0.0_wp
3949!
3950!-- 1) Initializing particle and ambient air variables
3951    diam  = (/ diam1, diam2 /) !< particle diameters (m)
3952    mpart = (/ mass1, mass2 /) !< particle masses (kg)
3953!
3954!-- Viscosity of air (kg/(m s))
3955    visc = ( 7.44523E-3_wp * temp ** 1.5_wp ) / ( 5093.0_wp * ( temp + 110.4_wp ) )
3956!
3957!-- Mean free path of air (m)
3958    mfp = ( 1.656E-10_wp * temp + 1.828E-8_wp ) * ( p_0 + 1325.0_wp ) / pres
3959!
3960!-- 2) Slip correction factor for small particles
3961    knud = 2.0_wp * EXP( LOG(mfp) - LOG(diam) )! Knudsen number for air (15.23)
3962!
3963!-- Cunningham correction factor (Allen and Raabe, Aerosol Sci. Tech. 4, 269)
3964    beta = 1.0_wp + knud * ( 1.142_wp + 0.558_wp * EXP( -0.999_wp / knud ) )
3965!
3966!-- 3) Particle properties
3967!-- Diffusion coefficient (m2/s) (Jacobson (2005) eq. 15.29)
3968    dfpart = beta * abo * temp / ( 3.0_wp * pi * visc * diam )
3969!
3970!-- Mean thermal velocity (m/s) (Jacobson (2005) eq. 15.32)
3971    mtvel = SQRT( ( 8.0_wp * abo * temp ) / ( pi * mpart ) )
3972!
3973!-- Particle mean free path (m) (Jacobson (2005) eq. 15.34 )
3974    omega = 8.0_wp * dfpart / ( pi * mtvel )
3975!
3976!-- Mean diameter (m)
3977    mdiam = 0.5_wp * ( diam(1) + diam(2) )
3978!
3979!-- 4) Calculation of fluxes (Brownian collision kernels) and flux matching
3980!-- following Jacobson (2005):
3981!
3982!-- Flux in continuum regime (m3/s) (eq. 15.28)
3983    flux(1) = 4.0_wp * pi * mdiam * ( dfpart(1) + dfpart(2) )
3984!
3985!-- Flux in free molec. regime (m3/s) (eq. 15.31)
3986    flux(2) = pi * SQRT( ( mtvel(1)**2 ) + ( mtvel(2)**2 ) ) * ( mdiam**2 )
3987!
3988!-- temporary variables (m) to calculate flux matching distance (m)
3989    tva(1) = ( ( mdiam + omega(1) )**3 - ( mdiam**2 + omega(1)**2 ) * SQRT( ( mdiam**2 +           &
3990               omega(1)**2 ) ) ) / ( 3.0_wp * mdiam * omega(1) ) - mdiam
3991    tva(2) = ( ( mdiam + omega(2) )**3 - ( mdiam**2 + omega(2)**2 ) * SQRT( ( mdiam**2 +           &
3992               omega(2)**2 ) ) ) / ( 3.0_wp * mdiam * omega(2) ) - mdiam
3993!
3994!-- Flux matching distance (m): the mean distance from the centre of a sphere reached by particles
3995!-- that leave sphere's surface and travel a distance of particle mean free path (eq. 15.34)
3996    fmdist = SQRT( tva(1)**2 + tva(2)**2 )
3997!
3998!-- 5) Coagulation coefficient = coalescence efficiency * collision kernel (m3/s) (eq. 15.33).
3999!--    Here assumed coalescence efficiency 1!!
4000    coagc = flux(1) / ( mdiam / ( mdiam + fmdist) + flux(1) / flux(2) )
4001!
4002!-- Corrected collision kernel (Karl et al., 2016 (ACP)): Include van der Waals and viscous forces
4003    IF ( van_der_waals_coagc )  THEN
4004       knud_p = SQRT( omega(1)**2 + omega(2)**2 ) / mdiam
4005       IF ( knud_p >= 0.1_wp  .AND.  knud_p <= 10.0_wp )  THEN
4006          coagc = coagc * ( 2.0_wp + 0.4_wp * LOG( knud_p ) )
4007       ELSE
4008          coagc = coagc * 3.0_wp
4009       ENDIF
4010    ENDIF
4011
4012 END FUNCTION coagc
4013
4014!------------------------------------------------------------------------------!
4015! Description:
4016! ------------
4017!> Calculates the change in particle volume and gas phase
4018!> concentrations due to nucleation, condensation and dissolutional growth.
4019!
4020!> Sulphuric acid and organic vapour: only condensation and no evaporation.
4021!
4022!> New gas and aerosol phase concentrations calculated according to Jacobson
4023!> (1997): Numerical techniques to solve condensational and dissolutional growth
4024!> equations when growth is coupled to reversible reactions, Aerosol Sci. Tech.,
4025!> 27, pp 491-498.
4026!
4027!> Following parameterization has been used:
4028!> Molecular diffusion coefficient of condensing vapour (m2/s)
4029!> (Reid et al. (1987): Properties of gases and liquids, McGraw-Hill, New York.)
4030!> D = {1.d-7*sqrt(1/M_air + 1/M_gas)*T^1.75} / &
4031!      {p_atm/p_stand * (d_air^(1/3) + d_gas^(1/3))^2 }
4032!> M_air = 28.965 : molar mass of air (g/mol)
4033!> d_air = 19.70  : diffusion volume of air
4034!> M_h2so4 = 98.08 : molar mass of h2so4 (g/mol)
4035!> d_h2so4 = 51.96  : diffusion volume of h2so4
4036!
4037!> Called from main aerosol model
4038!> For equations, see Jacobson, Fundamentals of Atmospheric Modeling, 2nd Edition (2005)
4039!
4040!> Coded by:
4041!> Hannele Korhonen (FMI) 2005
4042!> Harri Kokkola (FMI) 2006
4043!> Juha Tonttila (FMI) 2014
4044!> Rewritten to PALM by Mona Kurppa (UHel) 2017
4045!------------------------------------------------------------------------------!
4046 SUBROUTINE condensation( paero, pc_sa, pc_ocnv, pcocsv, pchno3, pc_nh3, pcw, pcs, ptemp, ppres,   &
4047                          ptstep, prtcl )
4048
4049    IMPLICIT NONE
4050
4051    INTEGER(iwp) ::  ss      !< start index
4052    INTEGER(iwp) ::  ee      !< end index
4053
4054    REAL(wp) ::  zcs_ocnv    !< condensation sink of nonvolatile organics (1/s)
4055    REAL(wp) ::  zcs_ocsv    !< condensation sink of semivolatile organics (1/s)
4056    REAL(wp) ::  zcs_su      !< condensation sink of sulfate (1/s)
4057    REAL(wp) ::  zcs_tot     !< total condensation sink (1/s) (gases)
4058    REAL(wp) ::  zcvap_new1  !< vapour concentration after time step (#/m3): sulphuric acid
4059    REAL(wp) ::  zcvap_new2  !< nonvolatile organics
4060    REAL(wp) ::  zcvap_new3  !< semivolatile organics
4061    REAL(wp) ::  zdfvap      !< air diffusion coefficient (m2/s)
4062    REAL(wp) ::  zdvap1      !< change in vapour concentration (#/m3): sulphuric acid
4063    REAL(wp) ::  zdvap2      !< nonvolatile organics
4064    REAL(wp) ::  zdvap3      !< semivolatile organics
4065    REAL(wp) ::  zmfp        !< mean free path of condensing vapour (m)
4066    REAL(wp) ::  zrh         !< Relative humidity [0-1]
4067    REAL(wp) ::  zvisc       !< viscosity of air (kg/(m s))
4068    REAL(wp) ::  zn_vs_c     !< ratio of nucleation of all mass transfer in the smallest bin
4069    REAL(wp) ::  zxocnv      !< ratio of organic vapour in 3nm particles
4070    REAL(wp) ::  zxsa        !< Ratio in 3nm particles: sulphuric acid
4071
4072    REAL(wp), INTENT(in) ::  ppres   !< ambient pressure (Pa)
4073    REAL(wp), INTENT(in) ::  pcs     !< Water vapour saturation concentration (kg/m3)
4074    REAL(wp), INTENT(in) ::  ptemp   !< ambient temperature (K)
4075    REAL(wp), INTENT(in) ::  ptstep  !< timestep (s)
4076
4077    REAL(wp), INTENT(inout) ::  pchno3   !< Gas concentrations (#/m3): nitric acid HNO3
4078    REAL(wp), INTENT(inout) ::  pc_nh3   !< ammonia NH3
4079    REAL(wp), INTENT(inout) ::  pc_ocnv  !< non-volatile organics
4080    REAL(wp), INTENT(inout) ::  pcocsv   !< semi-volatile organics
4081    REAL(wp), INTENT(inout) ::  pc_sa    !< sulphuric acid H2SO4
4082    REAL(wp), INTENT(inout) ::  pcw      !< Water vapor concentration (kg/m3)
4083
4084    REAL(wp), DIMENSION(nbins_aerosol)               ::  zbeta          !< transitional correction factor
4085    REAL(wp), DIMENSION(nbins_aerosol)               ::  zcolrate       !< collision rate (1/s)
4086    REAL(wp), DIMENSION(nbins_aerosol)               ::  zcolrate_ocnv  !< collision rate of non-vol. OC (1/s)
4087    REAL(wp), DIMENSION(start_subrange_1a+1) ::  zdfpart        !< particle diffusion coefficient (m2/s)
4088    REAL(wp), DIMENSION(nbins_aerosol)               ::  zdvoloc        !< change of organics volume
4089    REAL(wp), DIMENSION(nbins_aerosol)               ::  zdvolsa        !< change of sulphate volume
4090    REAL(wp), DIMENSION(2)                   ::  zj3n3          !< Formation massrate of molecules
4091                                                                !< in nucleation, (molec/m3s),
4092                                                                !< 1: H2SO4 and 2: organic vapor
4093    REAL(wp), DIMENSION(nbins_aerosol)   ::  zknud          !< particle Knudsen number
4094
4095    TYPE(component_index), INTENT(in) :: prtcl  !< Keeps track which substances are used
4096
4097    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< Aerosol properties
4098
4099    zj3n3  = 0.0_wp
4100    zrh    = pcw / pcs
4101    zxocnv = 0.0_wp
4102    zxsa   = 0.0_wp
4103!
4104!-- Nucleation
4105    IF ( nsnucl > 0 )  THEN
4106       CALL nucleation( paero, ptemp, zrh, ppres, pc_sa, pc_ocnv, pc_nh3, ptstep, zj3n3, zxsa,     &
4107                        zxocnv )
4108    ENDIF
4109!
4110!-- Condensation on pre-existing particles
4111    IF ( lscndgas )  THEN
4112!
4113!--    Initialise:
4114       zdvolsa = 0.0_wp
4115       zdvoloc = 0.0_wp
4116       zcolrate = 0.0_wp
4117!
4118!--    1) Properties of air and condensing gases:
4119!--    Viscosity of air (kg/(m s)) (Eq. 4.54 in Jabonson (2005))
4120       zvisc = ( 7.44523E-3_wp * ptemp ** 1.5_wp ) / ( 5093.0_wp * ( ptemp + 110.4_wp ) )
4121!
4122!--    Diffusion coefficient of air (m2/s)
4123       zdfvap = 5.1111E-10_wp * ptemp ** 1.75_wp * ( p_0 + 1325.0_wp ) / ppres
4124!
4125!--    Mean free path (m): same for H2SO4 and organic compounds
4126       zmfp = 3.0_wp * zdfvap * SQRT( pi * amh2so4 / ( 8.0_wp * argas * ptemp ) )
4127!
4128!--    2) Transition regime correction factor zbeta for particles (Fuchs and Sutugin (1971)):
4129!--       Size of condensing molecule considered only for nucleation mode (3 - 20 nm).
4130!
4131!--    Particle Knudsen number: condensation of gases on aerosols
4132       ss = start_subrange_1a
4133       ee = start_subrange_1a+1
4134       zknud(ss:ee) = 2.0_wp * zmfp / ( paero(ss:ee)%dwet + d_sa )
4135       ss = start_subrange_1a+2
4136       ee = end_subrange_2b
4137       zknud(ss:ee) = 2.0_wp * zmfp / paero(ss:ee)%dwet
4138!
4139!--    Transitional correction factor: aerosol + gas (the semi-empirical Fuchs- Sutugin
4140!--    interpolation function (Fuchs and Sutugin, 1971))
4141       zbeta = ( zknud + 1.0_wp ) / ( 0.377_wp * zknud + 1.0_wp + 4.0_wp / ( 3.0_wp * massacc ) *  &
4142               ( zknud + zknud ** 2 ) )
4143!
4144!--    3) Collision rate of molecules to particles
4145!--       Particle diffusion coefficient considered only for nucleation mode (3 - 20 nm)
4146!
4147!--    Particle diffusion coefficient (m2/s) (e.g. Eq. 15.29 in Jacobson (2005))
4148       zdfpart = abo * ptemp * zbeta(start_subrange_1a:start_subrange_1a+1) / ( 3.0_wp * pi * zvisc&
4149                 * paero(start_subrange_1a:start_subrange_1a+1)%dwet)
4150!
4151!--    Collision rate (mass-transfer coefficient): gases on aerosols (1/s) (Eq. 16.64 in
4152!--    Jacobson (2005))
4153       ss = start_subrange_1a
4154       ee = start_subrange_1a+1
4155       zcolrate(ss:ee) = MERGE( 2.0_wp * pi * ( paero(ss:ee)%dwet + d_sa ) * ( zdfvap + zdfpart ) *&
4156                               zbeta(ss:ee) * paero(ss:ee)%numc, 0.0_wp, paero(ss:ee)%numc > nclim )
4157       ss = start_subrange_1a+2
4158       ee = end_subrange_2b
4159       zcolrate(ss:ee) = MERGE( 2.0_wp * pi * paero(ss:ee)%dwet * zdfvap * zbeta(ss:ee) *          &
4160                                paero(ss:ee)%numc, 0.0_wp, paero(ss:ee)%numc > nclim )
4161!
4162!-- 4) Condensation sink (1/s)
4163       zcs_tot = SUM( zcolrate )   ! total sink
4164!
4165!--    5) Changes in gas-phase concentrations and particle volume
4166!
4167!--    5.1) Organic vapours
4168!
4169!--    5.1.1) Non-volatile organic compound: condenses onto all bins
4170       IF ( pc_ocnv > 1.0E+10_wp  .AND.  zcs_tot > 1.0E-30_wp  .AND. index_oc > 0 )  &
4171       THEN
4172!--       Ratio of nucleation vs. condensation rates in the smallest bin
4173          zn_vs_c = 0.0_wp
4174          IF ( zj3n3(2) > 1.0_wp )  THEN
4175             zn_vs_c = ( zj3n3(2) ) / ( zj3n3(2) + pc_ocnv * zcolrate(start_subrange_1a) )
4176          ENDIF
4177!
4178!--       Collision rate in the smallest bin, including nucleation and condensation (see
4179!--       Jacobson (2005), eq. (16.73) )
4180          zcolrate_ocnv = zcolrate
4181          zcolrate_ocnv(start_subrange_1a) = zcolrate_ocnv(start_subrange_1a) + zj3n3(2) / pc_ocnv
4182!
4183!--       Total sink for organic vapor
4184          zcs_ocnv = zcs_tot + zj3n3(2) / pc_ocnv
4185!
4186!--       New gas phase concentration (#/m3)
4187          zcvap_new2 = pc_ocnv / ( 1.0_wp + ptstep * zcs_ocnv )
4188!
4189!--       Change in gas concentration (#/m3)
4190          zdvap2 = pc_ocnv - zcvap_new2
4191!
4192!--       Updated vapour concentration (#/m3)
4193          pc_ocnv = zcvap_new2
4194!
4195!--       Volume change of particles (m3(OC)/m3(air))
4196          zdvoloc = zcolrate_ocnv(start_subrange_1a:end_subrange_2b) / zcs_ocnv * amvoc * zdvap2
4197!
4198!--       Change of volume due to condensation in 1a-2b
4199          paero(start_subrange_1a:end_subrange_2b)%volc(2) =                                       &
4200                                          paero(start_subrange_1a:end_subrange_2b)%volc(2) + zdvoloc
4201!
4202!--       Change of number concentration in the smallest bin caused by nucleation (Jacobson (2005),
4203!--       eq. (16.75)). If zxocnv = 0, then the chosen nucleation mechanism doesn't take into
4204!--       account the non-volatile organic vapors and thus the paero doesn't have to be updated.
4205          IF ( zxocnv > 0.0_wp )  THEN
4206             paero(start_subrange_1a)%numc = paero(start_subrange_1a)%numc + zn_vs_c *             &
4207                                             zdvoloc(start_subrange_1a) / amvoc / ( n3 * zxocnv )
4208          ENDIF
4209       ENDIF
4210!
4211!--    5.1.2) Semivolatile organic compound: all bins except subrange 1
4212       zcs_ocsv = SUM( zcolrate(start_subrange_2a:end_subrange_2b) ) !< sink for semi-volatile organics
4213       IF ( pcocsv > 1.0E+10_wp  .AND.  zcs_ocsv > 1.0E-30  .AND. is_used( prtcl,'OC') )  THEN
4214!
4215!--       New gas phase concentration (#/m3)
4216          zcvap_new3 = pcocsv / ( 1.0_wp + ptstep * zcs_ocsv )
4217!
4218!--       Change in gas concentration (#/m3)
4219          zdvap3 = pcocsv - zcvap_new3 
4220!
4221!--       Updated gas concentration (#/m3)
4222          pcocsv = zcvap_new3
4223!
4224!--       Volume change of particles (m3(OC)/m3(air))
4225          ss = start_subrange_2a
4226          ee = end_subrange_2b
4227          zdvoloc(ss:ee) = zdvoloc(ss:ee) + zcolrate(ss:ee) / zcs_ocsv * amvoc * zdvap3
4228!
4229!--       Change of volume due to condensation in 1a-2b
4230          paero(start_subrange_1a:end_subrange_2b)%volc(2) =                                       &
4231                                          paero(start_subrange_1a:end_subrange_2b)%volc(2) + zdvoloc
4232       ENDIF
4233!
4234!--    5.2) Sulphate: condensed on all bins
4235       IF ( pc_sa > 1.0E+10_wp  .AND.  zcs_tot > 1.0E-30_wp  .AND.  index_so4 > 0 )  THEN
4236!
4237!--    Ratio of mass transfer between nucleation and condensation
4238          zn_vs_c = 0.0_wp
4239          IF ( zj3n3(1) > 1.0_wp )  THEN
4240             zn_vs_c = ( zj3n3(1) ) / ( zj3n3(1) + pc_sa * zcolrate(start_subrange_1a) )
4241          ENDIF
4242!
4243!--       Collision rate in the smallest bin, including nucleation and condensation (see
4244!--       Jacobson (2005), eq. (16.73))
4245          zcolrate(start_subrange_1a) = zcolrate(start_subrange_1a) + zj3n3(1) / pc_sa
4246!
4247!--       Total sink for sulfate (1/s)
4248          zcs_su = zcs_tot + zj3n3(1) / pc_sa
4249!
4250!--       Sulphuric acid:
4251!--       New gas phase concentration (#/m3)
4252          zcvap_new1 = pc_sa / ( 1.0_wp + ptstep * zcs_su )
4253!
4254!--       Change in gas concentration (#/m3)
4255          zdvap1 = pc_sa - zcvap_new1
4256!
4257!--       Updating vapour concentration (#/m3)
4258          pc_sa = zcvap_new1
4259!
4260!--       Volume change of particles (m3(SO4)/m3(air)) by condensation
4261          zdvolsa = zcolrate(start_subrange_1a:end_subrange_2b) / zcs_su * amvh2so4 * zdvap1
4262!
4263!--       Change of volume concentration of sulphate in aerosol [fxm]
4264          paero(start_subrange_1a:end_subrange_2b)%volc(1) =                                       &
4265                                          paero(start_subrange_1a:end_subrange_2b)%volc(1) + zdvolsa
4266!
4267!--       Change of number concentration in the smallest bin caused by nucleation
4268!--       (Jacobson (2005), equation (16.75))
4269          IF ( zxsa > 0.0_wp )  THEN
4270             paero(start_subrange_1a)%numc = paero(start_subrange_1a)%numc + zn_vs_c *             &
4271                                             zdvolsa(start_subrange_1a) / amvh2so4 / ( n3 * zxsa)
4272          ENDIF
4273       ENDIF
4274!
4275!--    Partitioning of H2O, HNO3, and NH3: Dissolutional growth
4276       IF ( lspartition  .AND.  ( pchno3 > 1.0E+10_wp  .OR.  pc_nh3 > 1.0E+10_wp ) )  THEN
4277          CALL gpparthno3( ppres, ptemp, paero, pchno3, pc_nh3, pcw, pcs, zbeta, ptstep )
4278       ENDIF
4279    ENDIF
4280!
4281!-- Condensation of water vapour
4282    IF ( lscndh2oae )  THEN
4283       CALL gpparth2o( paero, ptemp, ppres, pcs, pcw, ptstep )
4284    ENDIF
4285
4286 END SUBROUTINE condensation
4287
4288!------------------------------------------------------------------------------!
4289! Description:
4290! ------------
4291!> Calculates the particle number and volume increase, and gas-phase
4292!> concentration decrease due to nucleation subsequent growth to detectable size
4293!> of 3 nm.
4294!
4295!> Method:
4296!> When the formed clusters grow by condensation (possibly also by self-
4297!> coagulation), their number is reduced due to scavenging to pre-existing
4298!> particles. Thus, the apparent nucleation rate at 3 nm is significantly lower
4299!> than the real nucleation rate (at ~1 nm).
4300!
4301!> Calculation of the formation rate of detectable particles at 3 nm (i.e. J3):
4302!> nj3 = 1: Kerminen, V.-M. and Kulmala, M. (2002), J. Aerosol Sci.,33, 609-622.
4303!> nj3 = 2: Lehtinen et al. (2007), J. Aerosol Sci., 38(9), 988-994.
4304!> nj3 = 3: Anttila et al. (2010), J. Aerosol Sci., 41(7), 621-636.
4305!
4306!> c = aerosol of critical radius (1 nm)
4307!> x = aerosol with radius 3 nm
4308!> 2 = wet or mean droplet
4309!
4310!> Called from subroutine condensation (in module salsa_dynamics_mod.f90)
4311!
4312!> Calls one of the following subroutines:
4313!>  - binnucl
4314!>  - ternucl
4315!>  - kinnucl
4316!>  - actnucl
4317!
4318!> fxm: currently only sulphuric acid grows particles from 1 to 3 nm
4319!>  (if asked from Markku, this is terribly wrong!!!)
4320!
4321!> Coded by:
4322!> Hannele Korhonen (FMI) 2005
4323!> Harri Kokkola (FMI) 2006
4324!> Matti Niskanen(FMI) 2012
4325!> Anton Laakso  (FMI) 2013
4326!------------------------------------------------------------------------------!
4327
4328 SUBROUTINE nucleation( paero, ptemp, prh, ppres, pc_sa, pc_ocnv, pc_nh3, ptstep, pj3n3, pxsa,     &
4329                        pxocnv )
4330
4331    IMPLICIT NONE
4332
4333    INTEGER(iwp) ::  iteration
4334
4335    REAL(wp) ::  zc_h2so4     !< H2SO4 conc. (#/cm3) !UNITS!
4336    REAL(wp) ::  zc_org       !< organic vapour conc. (#/cm3)
4337    REAL(wp) ::  zcc_c        !< Cunningham correct factor for c = critical (1nm)
4338    REAL(wp) ::  zcc_x        !< Cunningham correct factor for x = 3nm
4339    REAL(wp) ::  zcoags_c     !< coagulation sink (1/s) for c = critical (1nm)
4340    REAL(wp) ::  zcoags_x     !< coagulation sink (1/s) for x = 3nm
4341    REAL(wp) ::  zcoagstot    !< total particle losses due to coagulation, including condensation
4342                              !< and self-coagulation
4343    REAL(wp) ::  zcocnv_local !< organic vapour conc. (#/m3)
4344    REAL(wp) ::  zcsink       !< condensational sink (#/m2)
4345    REAL(wp) ::  zcsa_local   !< H2SO4 conc. (#/m3)
4346    REAL(wp) ::  zcv_c        !< mean relative thermal velocity (m/s) for c = critical (1nm)
4347    REAL(wp) ::  zcv_x        !< mean relative thermal velocity (m/s) for x = 3nm
4348    REAL(wp) ::  zdcrit       !< diameter of critical cluster (m)
4349    REAL(wp) ::  zdelta_vap   !< change of H2SO4 and organic vapour concentration (#/m3)
4350    REAL(wp) ::  zdfvap       !< air diffusion coefficient (m2/s)
4351    REAL(wp) ::  zdmean       !< mean diameter of existing particles (m)
4352    REAL(wp) ::  zeta         !< constant: proportional to ratio of CS/GR (m)
4353                              !< (condensation sink / growth rate)
4354    REAL(wp) ::  zgamma       !< proportionality factor ((nm2*m2)/h)
4355    REAL(wp) ::  z_gr_clust   !< growth rate of formed clusters (nm/h)
4356    REAL(wp) ::  z_gr_tot     !< total growth rate
4357    REAL(wp) ::  zj3          !< number conc. of formed 3nm particles (#/m3)
4358    REAL(wp) ::  zjnuc        !< nucleation rate at ~1nm (#/m3s)
4359    REAL(wp) ::  z_k_eff      !< effective cogulation coefficient for freshly nucleated particles
4360    REAL(wp) ::  zknud_c      !< Knudsen number for c = critical (1nm)
4361    REAL(wp) ::  zknud_x      !< Knudsen number for x = 3nm
4362    REAL(wp) ::  zkocnv       !< lever: zkocnv=1 --> organic compounds involved in nucleation
4363    REAL(wp) ::  zksa         !< lever: zksa=1 --> H2SO4 involved in nucleation
4364    REAL(wp) ::  zlambda      !< parameter for adjusting the growth rate due to self-coagulation
4365    REAL(wp) ::  zm_c         !< particle mass (kg) for c = critical (1nm)
4366    REAL(wp) ::  zm_para      !< Parameter m for calculating the coagulation sink (Eq. 5&6 in
4367                              !< Lehtinen et al. 2007)
4368    REAL(wp) ::  zm_x         !< particle mass (kg) for x = 3nm
4369    REAL(wp) ::  zmfp         !< mean free path of condesing vapour(m)
4370    REAL(wp) ::  zmixnh3      !< ammonia mixing ratio (ppt)
4371    REAL(wp) ::  zmyy         !< gas dynamic viscosity (N*s/m2)
4372    REAL(wp) ::  z_n_nuc      !< number of clusters/particles at the size range d1-dx (#/m3)
4373    REAL(wp) ::  znoc         !< number of organic molecules in critical cluster
4374    REAL(wp) ::  znsa         !< number of H2SO4 molecules in critical cluster
4375
4376    REAL(wp), INTENT(in) ::  pc_nh3   !< ammonia concentration (#/m3)
4377    REAL(wp), INTENT(in) ::  pc_ocnv  !< conc. of non-volatile OC (#/m3)
4378    REAL(wp), INTENT(in) ::  pc_sa    !< sulphuric acid conc. (#/m3)
4379    REAL(wp), INTENT(in) ::  ppres    !< ambient air pressure (Pa)
4380    REAL(wp), INTENT(in) ::  prh      !< ambient rel. humidity [0-1]
4381    REAL(wp), INTENT(in) ::  ptemp    !< ambient temperature (K)
4382    REAL(wp), INTENT(in) ::  ptstep   !< time step (s) of SALSA
4383
4384    REAL(wp), INTENT(inout) ::  pj3n3(2) !< formation mass rate of molecules (molec/m3s) for
4385                                         !< 1: H2SO4 and 2: organic vapour
4386
4387    REAL(wp), INTENT(out) ::  pxocnv  !< ratio of non-volatile organic vapours in 3 nm particles
4388    REAL(wp), INTENT(out) ::  pxsa    !< ratio of H2SO4 in 3 nm aerosol particles
4389
4390    REAL(wp), DIMENSION(nbins_aerosol) ::  zbeta       !< transitional correction factor
4391    REAL(wp), DIMENSION(nbins_aerosol) ::  zcc_2       !< Cunningham correct factor:2
4392    REAL(wp), DIMENSION(nbins_aerosol) ::  zcv_2       !< mean relative thermal velocity (m/s): 2
4393    REAL(wp), DIMENSION(nbins_aerosol) ::  zcv_c2      !< average velocity after coagulation: c & 2
4394    REAL(wp), DIMENSION(nbins_aerosol) ::  zcv_x2      !< average velocity after coagulation: x & 2
4395    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_2       !< particle diffusion coefficient (m2/s): 2
4396    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_c       !< particle diffusion coefficient (m2/s): c
4397    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_c2      !< sum of diffusion coef. for c and 2
4398    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_x       !< particle diffusion coefficient (m2/s): x
4399    REAL(wp), DIMENSION(nbins_aerosol) ::  zdc_x2      !< sum of diffusion coef. for: x & 2
4400    REAL(wp), DIMENSION(nbins_aerosol) ::  zgamma_f_2  !< zgamma_f for calculating zomega
4401    REAL(wp), DIMENSION(nbins_aerosol) ::  zgamma_f_c  !< zgamma_f for calculating zomega
4402    REAL(wp), DIMENSION(nbins_aerosol) ::  zgamma_f_x  !< zgamma_f for calculating zomega
4403    REAL(wp), DIMENSION(nbins_aerosol) ::  z_k_c2      !< coagulation coef. in the continuum
4404                                                       !< regime: c & 2
4405    REAL(wp), DIMENSION(nbins_aerosol) ::  z_k_x2      !< coagulation coef. in the continuum
4406                                                       !< regime: x & 2
4407    REAL(wp), DIMENSION(nbins_aerosol) ::  zknud       !< particle Knudsen number
4408    REAL(wp), DIMENSION(nbins_aerosol) ::  zknud_2     !< particle Knudsen number: 2
4409    REAL(wp), DIMENSION(nbins_aerosol) ::  zm_2        !< particle mass (kg): 2
4410    REAL(wp), DIMENSION(nbins_aerosol) ::  zomega_2c   !< zomega (m) for calculating zsigma: c & 2
4411    REAL(wp), DIMENSION(nbins_aerosol) ::  zomega_2x   !< zomega (m) for calculating zsigma: x & 2
4412    REAL(wp), DIMENSION(nbins_aerosol) ::  zomega_c    !< zomega (m) for calculating zsigma: c
4413    REAL(wp), DIMENSION(nbins_aerosol) ::  zomega_x    !< zomega (m) for calculating zsigma: x
4414    REAL(wp), DIMENSION(nbins_aerosol) ::  z_r_c2      !< sum of the radii: c & 2
4415    REAL(wp), DIMENSION(nbins_aerosol) ::  z_r_x2      !< sum of the radii: x & 2
4416    REAL(wp), DIMENSION(nbins_aerosol) ::  zsigma_c2   !<
4417    REAL(wp), DIMENSION(nbins_aerosol) ::  zsigma_x2   !<
4418
4419    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< aerosol properties
4420!
4421!-- 1) Nucleation rate (zjnuc) and diameter of critical cluster (zdcrit)
4422    zjnuc  = 0.0_wp
4423    znsa   = 0.0_wp
4424    znoc   = 0.0_wp
4425    zdcrit = 0.0_wp
4426    zksa   = 0.0_wp
4427    zkocnv = 0.0_wp
4428
4429    SELECT CASE ( nsnucl )
4430!
4431!--    Binary H2SO4-H2O nucleation
4432       CASE(1)
4433
4434          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4435          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa, znoc, zdcrit,  zksa, zkocnv )
4436!
4437!--    Activation type nucleation
4438       CASE(2)
4439
4440          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4441          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa,  znoc, zdcrit, zksa, zkocnv )
4442          CALL actnucl( pc_sa, zjnuc, zdcrit, znsa, znoc, zksa, zkocnv, act_coeff )
4443!
4444!--    Kinetically limited nucleation of (NH4)HSO4 clusters
4445       CASE(3)
4446
4447          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4448          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa, znoc, zdcrit, zksa, zkocnv )
4449          CALL kinnucl( zc_h2so4, zjnuc, zdcrit, znsa, znoc, zksa, zkocnv )
4450!
4451!--    Ternary H2SO4-H2O-NH3 nucleation
4452       CASE(4)
4453
4454          zmixnh3 = pc_nh3 * ptemp * argas / ( ppres * avo )
4455          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4456          CALL ternucl( zc_h2so4, zmixnh3, ptemp, prh, zjnuc, znsa, znoc, zdcrit, zksa, zkocnv )
4457!
4458!--    Organic nucleation, J~[ORG] or J~[ORG]**2
4459       CASE(5)
4460
4461          zc_org = pc_ocnv * 1.0E-6_wp   ! conc. of non-volatile OC to #/cm3
4462          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4463          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa, znoc, zdcrit, zksa, zkocnv )
4464          CALL orgnucl( pc_ocnv, zjnuc, zdcrit, znsa, znoc, zksa, zkocnv )
4465!
4466!--    Sum of H2SO4 and organic activation type nucleation, J~[H2SO4]+[ORG]
4467       CASE(6)
4468
4469          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4470          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa, znoc, zdcrit, zksa, zkocnv )
4471          CALL sumnucl( pc_sa, pc_ocnv, zjnuc, zdcrit, znsa, znoc, zksa, zkocnv )
4472!
4473!--    Heteromolecular nucleation, J~[H2SO4]*[ORG]
4474       CASE(7)
4475
4476          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4477          zc_org = pc_ocnv * 1.0E-6_wp   ! conc. of non-volatile OC to #/cm3
4478          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa, znoc, zdcrit, zksa, zkocnv )
4479          CALL hetnucl( zc_h2so4, zc_org, zjnuc, zdcrit, znsa, znoc, zksa, zkocnv )
4480!
4481!--    Homomolecular nucleation of H2SO4 and heteromolecular nucleation of H2SO4 and organic vapour,
4482!--    J~[H2SO4]**2 + [H2SO4]*[ORG] (EUCAARI project)
4483       CASE(8)
4484          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4485          zc_org = pc_ocnv * 1.0E-6_wp   ! conc. of non-volatile OC to #/cm3
4486          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa, znoc, zdcrit, zksa, zkocnv )
4487          CALL SAnucl( zc_h2so4, zc_org, zjnuc, zdcrit, znsa, znoc, zksa, zkocnv )
4488!
4489!--    Homomolecular nucleation of H2SO4 and organic vapour and heteromolecular nucleation of H2SO4
4490!--    and organic vapour, J~[H2SO4]**2 + [H2SO4]*[ORG]+[ORG]**2 (EUCAARI project)
4491       CASE(9)
4492
4493          zc_h2so4 = pc_sa * 1.0E-6_wp   ! sulphuric acid conc. to #/cm3
4494          zc_org = pc_ocnv * 1.0E-6_wp   ! conc. of non-volatile OC to #/cm3
4495          CALL binnucl( zc_h2so4, ptemp, prh, zjnuc, znsa, znoc, zdcrit, zksa, zkocnv )
4496          CALL SAORGnucl( zc_h2so4, zc_org, zjnuc, zdcrit, znsa, znoc, zksa, zkocnv )
4497
4498    END SELECT
4499
4500    zcsa_local = pc_sa
4501    zcocnv_local = pc_ocnv
4502!
4503!-- 2) Change of particle and gas concentrations due to nucleation
4504!
4505!-- 2.1) Check that there is enough H2SO4 and organic vapour to produce the nucleation
4506    IF ( nsnucl <= 4 )  THEN 
4507!
4508!--    If the chosen nucleation scheme is 1-4, nucleation occurs only due to H2SO4. All of the total
4509!--    vapour concentration that is taking part to the nucleation is there for sulphuric acid
4510!--    (sa = H2SO4) and non-volatile organic vapour is zero.
4511       pxsa   = 1.0_wp   ! ratio of sulphuric acid in 3nm particles
4512       pxocnv = 0.0_wp   ! ratio of non-volatile origanic vapour
4513                                ! in 3nm particles
4514    ELSEIF ( nsnucl > 4 )  THEN
4515!
4516!--    If the chosen nucleation scheme is 5-9, nucleation occurs due to organic vapour or the
4517!--    combination of organic vapour and H2SO4. The number of needed molecules depends on the chosen
4518!--    nucleation type and it has an effect also on the minimum ratio of the molecules present.
4519       IF ( pc_sa * znsa + pc_ocnv * znoc < 1.E-14_wp )  THEN
4520          pxsa   = 0.0_wp
4521          pxocnv = 0.0_wp
4522       ELSE
4523          pxsa   = pc_sa * znsa / ( pc_sa * znsa + pc_ocnv * znoc ) 
4524          pxocnv = pc_ocnv * znoc / ( pc_sa * znsa + pc_ocnv * znoc )
4525       ENDIF
4526    ENDIF
4527!
4528!-- The change in total vapour concentration is the sum of the concentrations of the vapours taking
4529!-- part to the nucleation (depends on the chosen nucleation scheme)
4530    zdelta_vap = MIN( zjnuc * ( znoc + znsa ), ( pc_ocnv * zkocnv + pc_sa * zksa ) / ptstep )
4531!
4532!-- Nucleation rate J at ~1nm (#/m3s)
4533    zjnuc = zdelta_vap / ( znoc + znsa )
4534!
4535!-- H2SO4 concentration after nucleation (#/m3)
4536    zcsa_local = MAX( 1.0_wp, pc_sa - zdelta_vap * pxsa )
4537!
4538!-- Non-volative organic vapour concentration after nucleation (#/m3)
4539    zcocnv_local = MAX( 1.0_wp, pc_ocnv - zdelta_vap * pxocnv )
4540!
4541!-- 2.2) Formation rate of 3 nm particles (Kerminen & Kulmala, 2002)
4542!
4543!-- Growth rate by H2SO4 and organic vapour (nm/h, Eq. 21)
4544    z_gr_clust = 2.3623E-15_wp * SQRT( ptemp ) * ( zcsa_local + zcocnv_local )
4545!
4546!-- 2.2.2) Condensational sink of pre-existing particle population
4547!
4548!-- Diffusion coefficient (m2/s)
4549    zdfvap = 5.1111E-10_wp * ptemp**1.75_wp * ( p_0 + 1325.0_wp ) / ppres
4550!
4551!-- Mean free path of condensing vapour (m) (Jacobson (2005), Eq. 15.25 and 16.29)
4552    zmfp = 3.0_wp * zdfvap * SQRT( pi * amh2so4 / ( 8.0_wp * argas * ptemp ) )
4553!
4554!-- Knudsen number
4555    zknud = 2.0_wp * zmfp / ( paero(:)%dwet + d_sa )
4556!
4557!-- Transitional regime correction factor (zbeta) according to Fuchs and Sutugin (1971) (Eq. 4 in
4558!-- Kerminen and Kulmala, 2002)
4559    zbeta = ( zknud + 1.0_wp) / ( 0.377_wp * zknud + 1.0_wp + 4.0_wp / ( 3.0_wp * massacc ) *      &
4560            ( zknud + zknud**2 ) )
4561!
4562!-- Condensational sink (#/m2, Eq. 3)
4563    zcsink = SUM( paero(:)%dwet * zbeta * paero(:)%numc )
4564!
4565!-- 2.2.3) Parameterised formation rate of detectable 3 nm particles (i.e. J3)
4566    IF ( nj3 == 1 )  THEN   ! Kerminen and Kulmala (2002)
4567!
4568!--    Constants needed for the parameterisation: dapp = 3 nm and dens_nuc = 1830 kg/m3
4569       IF ( zcsink < 1.0E-30_wp )  THEN
4570          zeta = 0._dp
4571       ELSE
4572!
4573!--       Mean diameter of backgroud population (nm)
4574          zdmean = 1.0_wp / SUM( paero(:)%numc ) * SUM( paero(:)%numc * paero(:)%dwet ) * 1.0E+9_wp
4575!
4576!--       Proportionality factor (nm2*m2/h) (Eq. 22)
4577          zgamma = 0.23_wp * ( zdcrit * 1.0E+9_wp )**0.2_wp * ( zdmean / 150.0_wp )**0.048_wp *    &
4578                   ( ptemp / 293.0_wp )**( -0.75_wp ) * ( arhoh2so4 / 1000.0_wp )**( -0.33_wp )
4579!
4580!--       Factor eta (nm, Eq. 11)
4581          zeta = MIN( zgamma * zcsink / z_gr_clust, zdcrit * 1.0E11_wp )
4582       ENDIF
4583!
4584!--    Number conc. of clusters surviving to 3 nm in a time step (#/m3, Eq.14)
4585       zj3 = zjnuc * EXP( MIN( 0.0_wp, zeta / 3.0_wp - zeta / ( zdcrit * 1.0E9_wp ) ) )
4586
4587    ELSEIF ( nj3 > 1 )  THEN   ! Lehtinen et al. (2007) or Anttila et al. (2010)
4588!
4589!--    Defining the parameter m (zm_para) for calculating the coagulation sink onto background
4590!--    particles (Eq. 5&6 in Lehtinen et al. 2007). The growth is investigated between
4591!--    [d1,reglim(1)] = [zdcrit,3nm] and m = LOG( CoagS_dx / CoagX_zdcrit ) / LOG( reglim / zdcrit )
4592!--    (Lehtinen et al. 2007, Eq. 6).
4593!--    The steps for the coagulation sink for reglim = 3nm and zdcrit ~= 1nm are explained in
4594!--    Kulmala et al. (2001). The particles of diameter zdcrit ~1.14 nm  and reglim = 3nm are both
4595!--    in turn the "number 1" variables (Kulmala et al. 2001).
4596!--    c = critical (1nm), x = 3nm, 2 = wet or mean droplet
4597!
4598!--    Sum of the radii, R12 = R1 + R2 (m) of two particles 1 and 2
4599       z_r_c2 = zdcrit / 2.0_wp + paero(:)%dwet / 2.0_wp
4600       z_r_x2 = reglim(1) / 2.0_wp + paero(:)%dwet / 2.0_wp
4601!
4602!--    Particle mass (kg) (comes only from H2SO4)
4603       zm_c = 4.0_wp / 3.0_wp * pi * ( zdcrit / 2.0_wp )**3 * arhoh2so4
4604       zm_x = 4.0_wp / 3.0_wp * pi * ( reglim(1) / 2.0_wp )**3 * arhoh2so4
4605       zm_2 = 4.0_wp / 3.0_wp * pi * ( 0.5_wp * paero(:)%dwet )**3 * arhoh2so4
4606!
4607!--    Mean relative thermal velocity between the particles (m/s)
4608       zcv_c = SQRT( 8.0_wp * abo * ptemp / ( pi * zm_c ) )
4609       zcv_x = SQRT( 8.0_wp * abo * ptemp / ( pi * zm_x ) )
4610       zcv_2 = SQRT( 8.0_wp * abo * ptemp / ( pi * zm_2 ) )
4611!
4612!--    Average velocity after coagulation
4613       zcv_c2(:) = SQRT( zcv_c**2 + zcv_2**2 )
4614       zcv_x2(:) = SQRT( zcv_x**2 + zcv_2**2 )
4615!
4616!--    Knudsen number (zmfp = mean free path of condensing vapour)
4617       zknud_c = 2.0_wp * zmfp / zdcrit
4618       zknud_x = 2.0_wp * zmfp / reglim(1)
4619       zknud_2(:) = MAX( 0.0_wp, 2.0_wp * zmfp / paero(:)%dwet )
4620!
4621!--    Cunningham correction factors (Allen and Raabe, 1985)
4622       zcc_c    = 1.0_wp + zknud_c    * ( 1.142_wp + 0.558_wp * EXP( -0.999_wp / zknud_c ) )
4623       zcc_x    = 1.0_wp + zknud_x    * ( 1.142_wp + 0.558_wp * EXP( -0.999_wp / zknud_x ) )
4624       zcc_2(:) = 1.0_wp + zknud_2(:) * ( 1.142_wp + 0.558_wp * EXP( -0.999_wp / zknud_2(:) ) )
4625!
4626!--    Gas dynamic viscosity (N*s/m2). Here, viscocity(air @20C) = 1.81e-5_dp N/m2 *s (Hinds, p. 25)
4627       zmyy = 1.81E-5_wp * ( ptemp / 293.0_wp )**0.74_wp
4628!
4629!--    Particle diffusion coefficient (m2/s) (continuum regime)
4630       zdc_c(:) = abo * ptemp * zcc_c    / ( 3.0_wp * pi * zmyy * zdcrit )
4631       zdc_x(:) = abo * ptemp * zcc_x    / ( 3.0_wp * pi * zmyy * reglim(1) )
4632       zdc_2(:) = abo * ptemp * zcc_2(:) / ( 3.0_wp * pi * zmyy * paero(:)%dwet )
4633!
4634!--    D12 = D1+D2 (Seinfield and Pandis, 2nd ed. Eq. 13.38)
4635       zdc_c2 = zdc_c + zdc_2
4636       zdc_x2 = zdc_x + zdc_2
4637!
4638!--    zgamma_f = 8*D/pi/zcv (m) for calculating zomega (Fuchs, 1964)
4639       zgamma_f_c = 8.0_wp * zdc_c / pi / zcv_c
4640       zgamma_f_x = 8.0_wp * zdc_x / pi / zcv_x
4641       zgamma_f_2 = 8.0_wp * zdc_2 / pi / zcv_2
4642!
4643!--    zomega (m) for calculating zsigma
4644       zomega_c = ( ( z_r_c2 + zgamma_f_c )**3 - ( z_r_c2 ** 2 + zgamma_f_c )**1.5_wp ) /          &
4645                  ( 3.0_wp * z_r_c2 * zgamma_f_c ) - z_r_c2
4646       zomega_x = ( ( z_r_x2 + zgamma_f_x )**3 - ( z_r_x2**2 + zgamma_f_x )** 1.5_wp ) /           &
4647                  ( 3.0_wp * z_r_x2 * zgamma_f_x ) - z_r_x2
4648       zomega_2c = ( ( z_r_c2 + zgamma_f_2 )**3 - ( z_r_c2**2 + zgamma_f_2 )**1.5_wp ) /           &
4649                   ( 3.0_wp * z_r_c2 * zgamma_f_2 ) - z_r_c2
4650       zomega_2x = ( ( z_r_x2 + zgamma_f_2 )**3 - ( z_r_x2**2 + zgamma_f_2 )**1.5_wp ) /           &
4651                   ( 3.0_wp * z_r_x2 * zgamma_f_2 ) - z_r_x2 
4652!
4653!--    The distance (m) at which the two fluxes are matched (condensation and coagulation sinks)
4654       zsigma_c2 = SQRT( zomega_c**2 + zomega_2c**2 )
4655       zsigma_x2 = SQRT( zomega_x**2 + zomega_2x**2 )
4656!
4657!--    Coagulation coefficient in the continuum regime (m*m2/s, Eq. 17 in Kulmala et al., 2001)
4658       z_k_c2 = 4.0_wp * pi * z_r_c2 * zdc_c2 / ( z_r_c2 / ( z_r_c2 + zsigma_c2 ) +                &
4659               4.0_wp * zdc_c2 / ( zcv_c2 * z_r_c2 ) )
4660       z_k_x2 = 4.0_wp * pi * z_r_x2 * zdc_x2 / ( z_r_x2 / ( z_r_x2 + zsigma_x2 ) +                &
4661               4.0_wp * zdc_x2 / ( zcv_x2 * z_r_x2 ) )
4662!
4663!--    Coagulation sink (1/s, Eq. 16 in Kulmala et al., 2001)
4664       zcoags_c = MAX( 1.0E-20_wp, SUM( z_k_c2 * paero(:)%numc ) )
4665       zcoags_x = MAX( 1.0E-20_wp, SUM( z_k_x2 * paero(:)%numc ) )
4666!
4667!--    Parameter m for calculating the coagulation sink onto background particles (Eq. 5&6 in
4668!--    Lehtinen et al. 2007)
4669       zm_para = LOG( zcoags_x / zcoags_c ) / LOG( reglim(1) / zdcrit )
4670!
4671!--    Parameter gamma for calculating the formation rate J of particles having
4672!--    a diameter zdcrit < d < reglim(1) (Anttila et al. 2010, eq. 5 or Lehtinen et al.,2007, eq. 7)
4673       zgamma = ( ( ( reglim(1) / zdcrit )**( zm_para + 1.0_wp ) ) - 1.0_wp ) / ( zm_para + 1.0_wp )
4674
4675       IF ( nj3 == 2 )  THEN   ! Lehtinen et al. (2007): coagulation sink
4676!
4677!--       Formation rate J before iteration (#/m3s)
4678          zj3 = zjnuc * EXP( MIN( 0.0_wp, -zgamma * zdcrit * zcoags_c / ( z_gr_clust * 1.0E-9_wp / &
4679                60.0_wp**2 ) ) )
4680
4681       ELSEIF ( nj3 == 3 )  THEN  ! Anttila et al. (2010): coagulation sink and self-coag.
4682!
4683!--       If air is polluted, the self-coagulation becomes important. Self-coagulation of small
4684!--       particles < 3 nm.
4685!
4686!--       "Effective" coagulation coefficient between freshly-nucleated particles:
4687          z_k_eff = 5.0E-16_wp   ! m3/s
4688!
4689!--       zlambda parameter for "adjusting" the growth rate due to the self-coagulation
4690          zlambda = 6.0_wp
4691
4692          IF ( reglim(1) >= 10.0E-9_wp )  THEN   ! for particles >10 nm:
4693             z_k_eff   = 5.0E-17_wp
4694             zlambda = 3.0_wp
4695          ENDIF
4696!
4697!--       Initial values for coagulation sink and growth rate  (m/s)
4698          zcoagstot = zcoags_c
4699          z_gr_tot = z_gr_clust * 1.0E-9_wp / 60.0_wp**2
4700!
4701!--       Number of clusters/particles at the size range [d1,dx] (#/m3):
4702          z_n_nuc = zjnuc / zcoagstot !< Initial guess
4703!
4704!--       Coagulation sink and growth rate due to self-coagulation:
4705          DO  iteration = 1, 5
4706             zcoagstot = zcoags_c + z_k_eff * z_n_nuc * 1.0E-6_wp   ! (1/s, Anttila et al., eq. 1)
4707             z_gr_tot = z_gr_clust * 2.77777777E-7_wp +  1.5708E-6_wp * zlambda * zdcrit**3 *      &
4708                      ( z_n_nuc * 1.0E-6_wp ) * zcv_c * avo * 2.77777777E-7_wp ! (Eq. 3)
4709             zeta = - zcoagstot / ( ( zm_para + 1.0_wp ) * z_gr_tot * ( zdcrit**zm_para ) ) ! (Eq. 7b)
4710!
4711!--          Calculate Eq. 7a (Taylor series for the number of particles between [d1,dx])
4712             z_n_nuc =  z_n_nuc_tayl( zdcrit, reglim(1), zm_para, zjnuc, zeta, z_gr_tot )
4713          ENDDO
4714!
4715!--       Calculate the final values with new z_n_nuc:
4716          zcoagstot = zcoags_c + z_k_eff * z_n_nuc * 1.0E-6_wp   ! (1/s)
4717          z_gr_tot = z_gr_clust * 1.0E-9_wp / 3600.0_wp + 1.5708E-6_wp *  zlambda * zdcrit**3 *    &
4718                   ( z_n_nuc * 1.0E-6_wp ) * zcv_c * avo * 1.0E-9_wp / 3600.0_wp !< (m/s)
4719          zj3 = zjnuc * EXP( MIN( 0.0_wp, -zgamma * zdcrit * zcoagstot / z_gr_tot ) ) ! (#/m3s, Eq. 5a)
4720
4721       ENDIF
4722    ENDIF
4723!
4724!-- If J3 very small (< 1 #/cm3), neglect particle formation. In real atmosphere this would mean
4725!-- that clusters form but coagulate to pre-existing particles who gain sulphate. Since
4726!-- CoagS ~ CS (4piD*CS'), we do *not* update H2SO4 concentration here but let condensation take
4727!-- care of it. Formation mass rate of molecules (molec/m3s) for 1: H2SO4 and 2: organic vapour
4728    pj3n3(1) = zj3 * n3 * pxsa
4729    pj3n3(2) = zj3 * n3 * pxocnv
4730
4731 END SUBROUTINE nucleation
4732
4733!------------------------------------------------------------------------------!
4734! Description:
4735! ------------
4736!> Calculate the nucleation rate and the size of critical clusters assuming
4737!> binary nucleation.
4738!> Parametrisation according to Vehkamaki et al. (2002), J. Geophys. Res.,
4739!> 107(D22), 4622. Called from subroutine nucleation.
4740!------------------------------------------------------------------------------!
4741 SUBROUTINE binnucl( pc_sa, ptemp, prh, pnuc_rate, pn_crit_sa, pn_crit_ocnv, pd_crit, pk_sa,       &
4742                     pk_ocnv )
4743
4744    IMPLICIT NONE
4745
4746    REAL(wp) ::  za      !<
4747    REAL(wp) ::  zb      !<
4748    REAL(wp) ::  zc      !<
4749    REAL(wp) ::  zcoll   !<
4750    REAL(wp) ::  zlogsa  !<  LOG( zpcsa )
4751    REAL(wp) ::  zlogrh  !<  LOG( zrh )
4752    REAL(wp) ::  zm1     !<
4753    REAL(wp) ::  zm2     !<
4754    REAL(wp) ::  zma     !<
4755    REAL(wp) ::  zmw     !<
4756    REAL(wp) ::  zntot   !< number of molecules in critical cluster
4757    REAL(wp) ::  zpcsa   !< sulfuric acid concentration
4758    REAL(wp) ::  zrh     !< relative humidity
4759    REAL(wp) ::  zroo    !<
4760    REAL(wp) ::  zt      !< temperature
4761    REAL(wp) ::  zv1     !<
4762    REAL(wp) ::  zv2     !<
4763    REAL(wp) ::  zx      !< mole fraction of sulphate in critical cluster
4764    REAL(wp) ::  zxmass  !<
4765
4766    REAL(wp), INTENT(in) ::   pc_sa   !< H2SO4 conc. (#/cm3)
4767    REAL(wp), INTENT(in) ::   prh     !< relative humidity [0-1
4768    REAL(wp), INTENT(in) ::   ptemp   !< ambient temperature (K)
4769
4770    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucleation rate (#/(m3 s))
4771    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
4772    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
4773    REAL(wp), INTENT(out) ::  pd_crit       !< diameter of critical cluster (m)
4774    REAL(wp), INTENT(out) ::  pk_sa         !< Lever: if pk_sa = 1, H2SO4 is involved in nucleation.
4775    REAL(wp), INTENT(out) ::  pk_ocnv       !< Lever: if pk_ocnv = 1, organic compounds are involved
4776
4777    pnuc_rate = 0.0_wp
4778    pd_crit   = 1.0E-9_wp
4779!
4780!-- 1) Checking that we are in the validity range of the parameterization
4781    zpcsa  = MAX( pc_sa, 1.0E4_wp  )
4782    zpcsa  = MIN( zpcsa, 1.0E11_wp )
4783    zrh    = MAX( prh,   0.0001_wp )
4784    zrh    = MIN( zrh,   1.0_wp    )
4785    zt     = MAX( ptemp, 190.15_wp )
4786    zt     = MIN( zt,    300.15_wp )
4787
4788    zlogsa = LOG( zpcsa )
4789    zlogrh   = LOG( prh )
4790!
4791!-- 2) Mole fraction of sulphate in a critical cluster (Eq. 11)
4792    zx = 0.7409967177282139_wp                  - 0.002663785665140117_wp * zt +                   &
4793         0.002010478847383187_wp * zlogrh       - 0.0001832894131464668_wp* zt * zlogrh +          &
4794         0.001574072538464286_wp * zlogrh**2    - 0.00001790589121766952_wp * zt * zlogrh**2 +     &
4795         0.0001844027436573778_wp * zlogrh**3   - 1.503452308794887E-6_wp * zt * zlogrh**3 -       &
4796         0.003499978417957668_wp * zlogsa     + 0.0000504021689382576_wp * zt * zlogsa
4797!
4798!-- 3) Nucleation rate (Eq. 12)
4799    pnuc_rate = 0.1430901615568665_wp + 2.219563673425199_wp * zt -                                &
4800                0.02739106114964264_wp * zt**2 + 0.00007228107239317088_wp * zt**3 +               &
4801                5.91822263375044_wp / zx + 0.1174886643003278_wp * zlogrh +                        &
4802                0.4625315047693772_wp * zt * zlogrh - 0.01180591129059253_wp * zt**2 * zlogrh +    &
4803                0.0000404196487152575_wp * zt**3 * zlogrh +                                        &
4804                ( 15.79628615047088_wp * zlogrh ) / zx - 0.215553951893509_wp * zlogrh**2 -        &
4805                0.0810269192332194_wp * zt * zlogrh**2 +                                           &
4806                0.001435808434184642_wp * zt**2 * zlogrh**2 -                                      &
4807                4.775796947178588E-6_wp * zt**3 * zlogrh**2 -                                      &
4808                ( 2.912974063702185_wp * zlogrh**2 ) / zx - 3.588557942822751_wp * zlogrh**3 +     &
4809                0.04950795302831703_wp * zt * zlogrh**3 -                                          &
4810                0.0002138195118737068_wp * zt**2 * zlogrh**3 +                                     &
4811                3.108005107949533E-7_wp * zt**3 * zlogrh**3 -                                      &
4812                ( 0.02933332747098296_wp * zlogrh**3 ) / zx + 1.145983818561277_wp * zlogsa -      &
4813                0.6007956227856778_wp * zt * zlogsa + 0.00864244733283759_wp * zt**2 * zlogsa -    &
4814                0.00002289467254710888_wp * zt**3 * zlogsa -                                       &
4815                ( 8.44984513869014_wp * zlogsa ) / zx + 2.158548369286559_wp * zlogrh * zlogsa +   &
4816                0.0808121412840917_wp * zt * zlogrh * zlogsa -                                     &
4817                0.0004073815255395214_wp * zt**2 * zlogrh * zlogsa -                               &
4818                4.019572560156515E-7_wp * zt**3 * zlogrh * zlogsa +                                &
4819                ( 0.7213255852557236_wp * zlogrh * zlogsa ) / zx +                                 &
4820                1.62409850488771_wp * zlogrh**2 * zlogsa -                                         &
4821                0.01601062035325362_wp * zt * zlogrh**2 * zlogsa +                                 &
4822                0.00003771238979714162_wp*zt**2* zlogrh**2 * zlogsa +                              &
4823                3.217942606371182E-8_wp * zt**3 * zlogrh**2 * zlogsa -                             &
4824                ( 0.01132550810022116_wp * zlogrh**2 * zlogsa ) / zx +                             &
4825                9.71681713056504_wp * zlogsa**2 - 0.1150478558347306_wp * zt * zlogsa**2 +         &
4826                0.0001570982486038294_wp * zt**2 * zlogsa**2 +                                     &
4827                4.009144680125015E-7_wp * zt**3 * zlogsa**2 +                                      &
4828                ( 0.7118597859976135_wp * zlogsa**2 ) / zx -                                       &
4829                1.056105824379897_wp * zlogrh * zlogsa**2 +                                        &
4830                0.00903377584628419_wp * zt * zlogrh * zlogsa**2 -                                 &
4831                0.00001984167387090606_wp * zt**2 * zlogrh * zlogsa**2 +                           &
4832                2.460478196482179E-8_wp * zt**3 * zlogrh * zlogsa**2 -                             &
4833                ( 0.05790872906645181_wp * zlogrh * zlogsa**2 ) / zx -                             &
4834                0.1487119673397459_wp * zlogsa**3 + 0.002835082097822667_wp * zt * zlogsa**3 -     &
4835                9.24618825471694E-6_wp * zt**2 * zlogsa**3 +                                       &
4836                5.004267665960894E-9_wp * zt**3 * zlogsa**3 -                                      &
4837                ( 0.01270805101481648_wp * zlogsa**3 ) / zx
4838!
4839!-- Nucleation rate in #/(cm3 s)
4840    pnuc_rate = EXP( pnuc_rate ) 
4841!
4842!-- Check the validity of parameterization
4843    IF ( pnuc_rate < 1.0E-7_wp )  THEN
4844       pnuc_rate = 0.0_wp
4845       pd_crit   = 1.0E-9_wp
4846    ENDIF
4847!
4848!-- 4) Total number of molecules in the critical cluster (Eq. 13)
4849    zntot = - 0.002954125078716302_wp - 0.0976834264241286_wp * zt +                               &
4850              0.001024847927067835_wp * zt**2 - 2.186459697726116E-6_wp * zt**3 -                  &
4851              0.1017165718716887_wp / zx - 0.002050640345231486_wp * zlogrh -                      &
4852              0.007585041382707174_wp * zt * zlogrh + 0.0001926539658089536_wp * zt**2 * zlogrh -  &
4853              6.70429719683894E-7_wp * zt**3 * zlogrh - ( 0.2557744774673163_wp * zlogrh ) / zx +  &
4854              0.003223076552477191_wp * zlogrh**2 + 0.000852636632240633_wp * zt * zlogrh**2 -     &
4855              0.00001547571354871789_wp * zt**2 * zlogrh**2 +                                      &
4856              5.666608424980593E-8_wp * zt**3 * zlogrh**2 +                                        &
4857              ( 0.03384437400744206_wp * zlogrh**2 ) / zx +                                        &
4858              0.04743226764572505_wp * zlogrh**3 - 0.0006251042204583412_wp * zt * zlogrh**3 +     &
4859              2.650663328519478E-6_wp * zt**2 * zlogrh**3 -                                        &
4860              3.674710848763778E-9_wp * zt**3 * zlogrh**3 -                                        &
4861              ( 0.0002672510825259393_wp * zlogrh**3 ) / zx - 0.01252108546759328_wp * zlogsa +    &
4862              0.005806550506277202_wp * zt * zlogsa - 0.0001016735312443444_wp * zt**2 * zlogsa +  &
4863              2.881946187214505E-7_wp * zt**3 * zlogsa + ( 0.0942243379396279_wp * zlogsa ) / zx - &
4864              0.0385459592773097_wp * zlogrh * zlogsa -                                            &
4865              0.0006723156277391984_wp * zt * zlogrh * zlogsa  +                                   &
4866              2.602884877659698E-6_wp * zt**2 * zlogrh * zlogsa +                                  &
4867              1.194163699688297E-8_wp * zt**3 * zlogrh * zlogsa -                                  &
4868              ( 0.00851515345806281_wp * zlogrh * zlogsa ) / zx -                                  &
4869              0.01837488495738111_wp * zlogrh**2 * zlogsa +                                        &
4870              0.0001720723574407498_wp * zt * zlogrh**2 * zlogsa -                                 &
4871              3.717657974086814E-7_wp * zt**2 * zlogrh**2 * zlogsa -                               &
4872              5.148746022615196E-10_wp * zt**3 * zlogrh**2 * zlogsa +                              &
4873              ( 0.0002686602132926594_wp * zlogrh**2 * zlogsa ) / zx -                             &
4874              0.06199739728812199_wp * zlogsa**2 + 0.000906958053583576_wp * zt * zlogsa**2 -      &
4875              9.11727926129757E-7_wp * zt**2 * zlogsa**2 -                                         &
4876              5.367963396508457E-9_wp * zt**3 * zlogsa**2 -                                        &
4877              ( 0.007742343393937707_wp * zlogsa**2 ) / zx +                                       &
4878              0.0121827103101659_wp * zlogrh * zlogsa**2 -                                         &
4879              0.0001066499571188091_wp * zt * zlogrh * zlogsa**2 +                                 &
4880              2.534598655067518E-7_wp * zt**2 * zlogrh * zlogsa**2 -                               &
4881              3.635186504599571E-10_wp * zt**3 * zlogrh * zlogsa**2 +                              &
4882              ( 0.0006100650851863252_wp * zlogrh * zlogsa **2 ) / zx +                            &
4883              0.0003201836700403512_wp * zlogsa**3 - 0.0000174761713262546_wp * zt * zlogsa**3 +   &
4884              6.065037668052182E-8_wp * zt**2 * zlogsa**3 -                                        &
4885              1.421771723004557E-11_wp * zt**3 * zlogsa**3 +                                       &
4886              ( 0.0001357509859501723_wp * zlogsa**3 ) / zx
4887    zntot = EXP( zntot )  ! in #
4888!
4889!-- 5) Size of the critical cluster pd_crit (m) (diameter) (Eq. 14)
4890    pn_crit_sa = zx * zntot
4891    pd_crit = 2.0E-9_wp * EXP( -1.6524245_wp + 0.42316402_wp * zx + 0.33466487_wp * LOG( zntot ) )
4892!
4893!-- 6) Organic compounds not involved when binary nucleation is assumed
4894    pn_crit_ocnv = 0.0_wp   ! number of organic molecules
4895    pk_sa        = 1.0_wp   ! if = 1, H2SO4 involved in nucleation
4896    pk_ocnv      = 0.0_wp   ! if = 1, organic compounds involved
4897!
4898!-- Set nucleation rate to collision rate
4899    IF ( pn_crit_sa < 4.0_wp ) THEN
4900!
4901!--    Volumes of the colliding objects
4902       zma    = 96.0_wp   ! molar mass of SO4 in g/mol
4903       zmw    = 18.0_wp   ! molar mass of water in g/mol
4904       zxmass = 1.0_wp    ! mass fraction of H2SO4
4905       za = 0.7681724_wp + zxmass * ( 2.1847140_wp + zxmass *                                      &
4906                                      ( 7.1630022_wp + zxmass *                                    &
4907                                        ( -44.31447_wp + zxmass *                                  &
4908                                          ( 88.75606 + zxmass *                                    &
4909                                            ( -75.73729_wp + zxmass * 23.43228_wp ) ) ) ) )
4910       zb = 1.808225E-3_wp + zxmass * ( -9.294656E-3_wp + zxmass *                                 &
4911                                        ( -0.03742148_wp + zxmass *                                &
4912                                          ( 0.2565321_wp + zxmass *                                &
4913                                            ( -0.5362872_wp + zxmass *                             &
4914                                              ( 0.4857736 - zxmass * 0.1629592_wp ) ) ) ) )
4915       zc = - 3.478524E-6_wp + zxmass * ( 1.335867E-5_wp + zxmass *                                &
4916                                          ( 5.195706E-5_wp + zxmass *                              &
4917                                            ( -3.717636E-4_wp + zxmass *                           &
4918                                              ( 7.990811E-4_wp + zxmass *                          &
4919                                                ( -7.458060E-4_wp + zxmass * 2.58139E-4_wp ) ) ) ) )
4920!
4921!--    Density for the sulphuric acid solution (Eq. 10 in Vehkamaki)
4922       zroo = ( za + zt * ( zb + zc * zt ) ) * 1.0E+3_wp   ! (kg/m^3
4923       zm1  = 0.098_wp   ! molar mass of H2SO4 in kg/mol
4924       zm2  = zm1
4925       zv1  = zm1 / avo / zroo   ! volume
4926       zv2  = zv1
4927!
4928!--    Collision rate
4929       zcoll =  zpcsa * zpcsa * ( 3.0_wp * pi / 4.0_wp )**0.16666666_wp *                          &
4930                SQRT( 6.0_wp * argas * zt / zm1 + 6.0_wp * argas * zt / zm2 ) *                    &
4931                ( zv1**0.33333333_wp + zv2**0.33333333_wp )**2 * 1.0E+6_wp    ! m3 -> cm3
4932       zcoll = MIN( zcoll, 1.0E+10_wp )
4933       pnuc_rate  = zcoll   ! (#/(cm3 s))
4934
4935    ELSE
4936       pnuc_rate  = MIN( pnuc_rate, 1.0E+10_wp )
4937    ENDIF
4938    pnuc_rate = pnuc_rate * 1.0E+6_wp   ! (#/(m3 s))
4939
4940 END SUBROUTINE binnucl
4941 
4942!------------------------------------------------------------------------------!
4943! Description:
4944! ------------
4945!> Calculate the nucleation rate and the size of critical clusters assuming
4946!> ternary nucleation. Parametrisation according to:
4947!> Napari et al. (2002), J. Chem. Phys., 116, 4221-4227 and
4948!> Napari et al. (2002), J. Geophys. Res., 107(D19), AAC 6-1-ACC 6-6.
4949!------------------------------------------------------------------------------!
4950 SUBROUTINE ternucl( pc_sa, pc_nh3, ptemp, prh, pnuc_rate, pn_crit_sa, pn_crit_ocnv, pd_crit,      &
4951                     pk_sa, pk_ocnv )
4952
4953    IMPLICIT NONE
4954
4955    REAL(wp) ::  zlnj     !< logarithm of nucleation rate
4956    REAL(wp) ::  zlognh3  !< LOG( pc_nh3 )
4957    REAL(wp) ::  zlogrh   !< LOG( prh )
4958    REAL(wp) ::  zlogsa   !< LOG( pc_sa )
4959
4960    REAL(wp), INTENT(in) ::   pc_nh3  !< ammonia mixing ratio (ppt)
4961    REAL(wp), INTENT(in) ::   pc_sa   !< H2SO4 conc. (#/cm3)
4962    REAL(wp), INTENT(in) ::   prh     !< relative humidity [0-1]
4963    REAL(wp), INTENT(in) ::   ptemp   !< ambient temperature (K)
4964
4965    REAL(wp), INTENT(out) ::  pd_crit  !< diameter of critical cluster (m)
4966    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate in nucleation
4967    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 participate in nucleation
4968    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
4969    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
4970    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucleation rate (#/(m3 s))
4971!
4972!-- 1) Checking that we are in the validity range of the parameterization.
4973!--    Validity of parameterization : DO NOT REMOVE!
4974    IF ( ptemp < 240.0_wp  .OR.  ptemp > 300.0_wp )  THEN
4975       message_string = 'Invalid input value: ptemp'
4976       CALL message( 'salsa_mod: ternucl', 'PA0619', 1, 2, 0, 6, 0 )
4977    ENDIF
4978    IF ( prh < 0.05_wp  .OR.  prh > 0.95_wp )  THEN
4979       message_string = 'Invalid input value: prh'
4980       CALL message( 'salsa_mod: ternucl', 'PA0620', 1, 2, 0, 6, 0 )
4981    ENDIF
4982    IF ( pc_sa < 1.0E+4_wp  .OR.  pc_sa > 1.0E+9_wp )  THEN
4983       message_string = 'Invalid input value: pc_sa'
4984       CALL message( 'salsa_mod: ternucl', 'PA0621', 1, 2, 0, 6, 0 )
4985    ENDIF
4986    IF ( pc_nh3 < 0.1_wp  .OR.  pc_nh3 > 100.0_wp )  THEN
4987       message_string = 'Invalid input value: pc_nh3'
4988       CALL message( 'salsa_mod: ternucl', 'PA0622', 1, 2, 0, 6, 0 )
4989    ENDIF
4990
4991    zlognh3 = LOG( pc_nh3 )
4992    zlogrh  = LOG( prh )
4993    zlogsa  = LOG( pc_sa )
4994!
4995!-- 2) Nucleation rate (Eq. 7 in Napari et al., 2002: Parameterization of
4996!--    ternary nucleation of sulfuric acid - ammonia - water.
4997    zlnj = - 84.7551114741543_wp + 0.3117595133628944_wp * prh +                                   &
4998           1.640089605712946_wp * prh * ptemp - 0.003438516933381083_wp * prh * ptemp**2 -         &
4999           0.00001097530402419113_wp * prh * ptemp**3 - 0.3552967070274677_wp / zlogsa -           &
5000           ( 0.06651397829765026_wp * prh ) / zlogsa - ( 33.84493989762471_wp * ptemp ) / zlogsa - &
5001           ( 7.823815852128623_wp * prh * ptemp ) / zlogsa +                                       &
5002           ( 0.3453602302090915_wp * ptemp**2 ) / zlogsa +                                         &
5003           ( 0.01229375748100015_wp * prh * ptemp**2 ) / zlogsa -                                  &
5004           ( 0.000824007160514956_wp *ptemp**3 ) / zlogsa +                                        &
5005           ( 0.00006185539100670249_wp * prh * ptemp**3 ) / zlogsa +                               &
5006           3.137345238574998_wp * zlogsa + 3.680240980277051_wp * prh * zlogsa -                   &
5007           0.7728606202085936_wp * ptemp * zlogsa - 0.204098217156962_wp * prh * ptemp * zlogsa +  &
5008           0.005612037586790018_wp * ptemp**2 * zlogsa +                                           &
5009           0.001062588391907444_wp * prh * ptemp**2 * zlogsa -                                     &
5010           9.74575691760229E-6_wp * ptemp**3 * zlogsa -                                            &
5011           1.265595265137352E-6_wp * prh * ptemp**3 * zlogsa + 19.03593713032114_wp * zlogsa**2 -  &
5012           0.1709570721236754_wp * ptemp * zlogsa**2 +                                             &
5013           0.000479808018162089_wp * ptemp**2 * zlogsa**2 -                                        &
5014           4.146989369117246E-7_wp * ptemp**3 * zlogsa**2 + 1.076046750412183_wp * zlognh3 +       &
5015           0.6587399318567337_wp * prh * zlognh3 + 1.48932164750748_wp * ptemp * zlognh3 +         &
5016           0.1905424394695381_wp * prh * ptemp * zlognh3 -                                         &
5017           0.007960522921316015_wp * ptemp**2 * zlognh3 -                                          &
5018           0.001657184248661241_wp * prh * ptemp**2 * zlognh3 +                                    &
5019           7.612287245047392E-6_wp * ptemp**3 * zlognh3 +                                          &
5020           3.417436525881869E-6_wp * prh * ptemp**3 * zlognh3 +                                    &
5021           ( 0.1655358260404061_wp * zlognh3 ) / zlogsa +                                          &
5022           ( 0.05301667612522116_wp * prh * zlognh3 ) / zlogsa +                                   &
5023           ( 3.26622914116752_wp * ptemp * zlognh3 ) / zlogsa -                                    &
5024           ( 1.988145079742164_wp * prh * ptemp * zlognh3 ) / zlogsa -                             &
5025           ( 0.04897027401984064_wp * ptemp**2 * zlognh3 ) / zlogsa +                              &
5026           ( 0.01578269253599732_wp * prh * ptemp**2 * zlognh3 ) / zlogsa +                        &
5027           ( 0.0001469672236351303_wp * ptemp**3 * zlognh3 ) / zlogsa -                            &
5028           ( 0.00002935642836387197_wp * prh * ptemp**3 *zlognh3 ) / zlogsa +                      &
5029           6.526451177887659_wp * zlogsa * zlognh3 -                                               &
5030           0.2580021816722099_wp * ptemp * zlogsa * zlognh3 +                                      &
5031           0.001434563104474292_wp * ptemp**2 * zlogsa * zlognh3 -                                 &
5032           2.020361939304473E-6_wp * ptemp**3 * zlogsa * zlognh3 -                                 &
5033           0.160335824596627_wp * zlogsa**2 * zlognh3 +                                            &
5034           0.00889880721460806_wp * ptemp * zlogsa**2 * zlognh3 -                                  &
5035           0.00005395139051155007_wp * ptemp**2 * zlogsa**2 * zlognh3 +                            &
5036           8.39521718689596E-8_wp * ptemp**3 * zlogsa**2 * zlognh3 +                               &
5037           6.091597586754857_wp * zlognh3**2 + 8.5786763679309_wp * prh * zlognh3**2 -             &
5038           1.253783854872055_wp * ptemp * zlognh3**2 -                                             &
5039           0.1123577232346848_wp * prh * ptemp * zlognh3**2 +                                      &
5040           0.00939835595219825_wp * ptemp**2 * zlognh3**2 +                                        &
5041           0.0004726256283031513_wp * prh * ptemp**2 * zlognh3**2 -                                &
5042           0.00001749269360523252_wp * ptemp**3 * zlognh3**2 -                                     &
5043           6.483647863710339E-7_wp * prh * ptemp**3 * zlognh3**2 +                                 &
5044           ( 0.7284285726576598_wp * zlognh3**2 ) / zlogsa +                                       &
5045           ( 3.647355600846383_wp * ptemp * zlognh3**2 ) / zlogsa -                                &
5046           ( 0.02742195276078021_wp * ptemp**2 * zlognh3**2 ) / zlogsa +                           &
5047           ( 0.00004934777934047135_wp * ptemp**3 * zlognh3**2 ) / zlogsa +                        &
5048           41.30162491567873_wp * zlogsa * zlognh3**2 -                                            &
5049           0.357520416800604_wp * ptemp * zlogsa * zlognh3**2 +                                    &
5050           0.000904383005178356_wp * ptemp**2 * zlogsa * zlognh3**2 -                              &
5051           5.737876676408978E-7_wp * ptemp**3 * zlogsa * zlognh3**2 -                              &
5052           2.327363918851818_wp * zlogsa**2 * zlognh3**2 +                                         &
5053           0.02346464261919324_wp * ptemp * zlogsa**2 * zlognh3**2 -                               &
5054           0.000076518969516405_wp * ptemp**2 * zlogsa**2 * zlognh3**2 +                           &
5055           8.04589834836395E-8_wp * ptemp**3 * zlogsa**2 * zlognh3**2 -                            &
5056           0.02007379204248076_wp * zlogrh - 0.7521152446208771_wp * ptemp * zlogrh +              &
5057           0.005258130151226247_wp * ptemp**2 * zlogrh -                                           &
5058           8.98037634284419E-6_wp * ptemp**3 * zlogrh +                                            &
5059           ( 0.05993213079516759_wp * zlogrh ) / zlogsa +                                          &
5060           ( 5.964746463184173_wp * ptemp * zlogrh ) / zlogsa -                                    &
5061           ( 0.03624322255690942_wp * ptemp**2 * zlogrh ) / zlogsa +                               &
5062           ( 0.00004933369382462509_wp * ptemp**3 * zlogrh ) / zlogsa -                            &
5063           0.7327310805365114_wp * zlognh3 * zlogrh -                                              &
5064           0.01841792282958795_wp * ptemp * zlognh3 * zlogrh +                                     &
5065           0.0001471855981005184_wp * ptemp**2 * zlognh3 * zlogrh -                                &
5066           2.377113195631848E-7_wp * ptemp**3 * zlognh3 * zlogrh
5067    pnuc_rate = EXP( zlnj )   ! (#/(cm3 s))
5068!
5069!-- Check validity of parametrization
5070    IF ( pnuc_rate < 1.0E-5_wp )  THEN
5071       pnuc_rate = 0.0_wp
5072       pd_crit   = 1.0E-9_wp
5073    ELSEIF ( pnuc_rate > 1.0E6_wp )  THEN
5074       message_string = 'Invalid output value: nucleation rate > 10^6 1/cm3s'
5075       CALL message( 'salsa_mod: ternucl', 'PA0623', 1, 2, 0, 6, 0 )
5076    ENDIF
5077    pnuc_rate = pnuc_rate * 1.0E6_wp   ! (#/(m3 s))
5078!
5079!-- 3) Number of H2SO4 molecules in a critical cluster (Eq. 9)
5080    pn_crit_sa = 38.16448247950508_wp + 0.7741058259731187_wp * zlnj +                             &
5081                 0.002988789927230632_wp * zlnj**2 - 0.3576046920535017_wp * ptemp -               &
5082                 0.003663583011953248_wp * zlnj * ptemp + 0.000855300153372776_wp * ptemp**2
5083!
5084!-- Kinetic limit: at least 2 H2SO4 molecules in a cluster
5085    pn_crit_sa = MAX( pn_crit_sa, 2.0E0_wp )
5086!
5087!-- 4) Size of the critical cluster in nm (Eq. 12)
5088    pd_crit = 0.1410271086638381_wp - 0.001226253898894878_wp * zlnj -                             &
5089              7.822111731550752E-6_wp * zlnj**2 - 0.001567273351921166_wp * ptemp -                &
5090              0.00003075996088273962_wp * zlnj * ptemp + 0.00001083754117202233_wp * ptemp**2
5091    pd_crit = pd_crit * 2.0E-9_wp   ! Diameter in m
5092!
5093!-- 5) Organic compounds not involved when ternary nucleation assumed
5094    pn_crit_ocnv = 0.0_wp
5095    pk_sa   = 1.0_wp
5096    pk_ocnv = 0.0_wp
5097
5098 END SUBROUTINE ternucl
5099
5100!------------------------------------------------------------------------------!
5101! Description:
5102! ------------
5103!> Calculate the nucleation rate and the size of critical clusters assuming
5104!> kinetic nucleation. Each sulphuric acid molecule forms an (NH4)HSO4 molecule
5105!> in the atmosphere and two colliding (NH4)HSO4 molecules form a stable
5106!> cluster. See Sihto et al. (2006), Atmos. Chem. Phys., 6(12), 4079-4091.
5107!>
5108!> Below the following assumption have been made:
5109!>  nucrate = coagcoeff*zpcsa**2
5110!>  coagcoeff = 8*sqrt(3*boltz*ptemp*r_abs/dens_abs)
5111!>  r_abs = 0.315d-9 radius of bisulphate molecule [m]
5112!>  dens_abs = 1465  density of - " - [kg/m3]
5113!------------------------------------------------------------------------------!
5114 SUBROUTINE kinnucl( pc_sa, pnuc_rate, pd_crit, pn_crit_sa, pn_crit_ocnv, pk_sa, pk_ocnv )
5115
5116    IMPLICIT NONE
5117
5118    REAL(wp), INTENT(in) ::  pc_sa  !< H2SO4 conc. (#/m3)
5119
5120    REAL(wp), INTENT(out) ::  pd_crit  !< critical diameter of clusters (m)
5121    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate in nucleation
5122    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 is participate in nucleation
5123    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5124    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5125    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucl. rate (#/(m3 s))
5126!
5127!-- Nucleation rate (#/(m3 s))
5128    pnuc_rate = 5.0E-13_wp * pc_sa**2.0_wp * 1.0E+6_wp
5129!
5130!-- Organic compounds not involved when kinetic nucleation is assumed.
5131    pn_crit_sa   = 2.0_wp
5132    pn_crit_ocnv = 0.0_wp
5133    pk_sa        = 1.0_wp
5134    pk_ocnv      = 0.0_wp
5135    pd_crit      = 7.9375E-10_wp   ! (m)
5136
5137 END SUBROUTINE kinnucl
5138
5139!------------------------------------------------------------------------------!
5140! Description:
5141! ------------
5142!> Calculate the nucleation rate and the size of critical clusters assuming
5143!> activation type nucleation.
5144!> See Riipinen et al. (2007), Atmos. Chem. Phys., 7(8), 1899-1914.
5145!------------------------------------------------------------------------------!
5146 SUBROUTINE actnucl( psa_conc, pnuc_rate, pd_crit, pn_crit_sa, pn_crit_ocnv, pk_sa, pk_ocnv, activ )
5147
5148    IMPLICIT NONE
5149
5150    REAL(wp), INTENT(in) ::  activ     !< activation coefficient (1e-7 by default)
5151    REAL(wp), INTENT(in) ::  psa_conc  !< H2SO4 conc. (#/m3)
5152
5153    REAL(wp), INTENT(out) ::  pd_crit  !< critical diameter of clusters (m)
5154    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate in nucleation
5155    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 participate in nucleation
5156    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5157    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5158    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucl. rate (#/(m3 s))
5159!
5160!-- Nucleation rate (#/(m3 s))
5161    pnuc_rate = activ * psa_conc   ! (#/(m3 s))
5162!
5163!-- Organic compounds not involved when kinetic nucleation is assumed.
5164    pn_crit_sa   = 2.0_wp
5165    pn_crit_ocnv = 0.0_wp
5166    pk_sa        = 1.0_wp
5167    pk_ocnv      = 0.0_wp
5168    pd_crit      = 7.9375E-10_wp   ! (m)
5169
5170 END SUBROUTINE actnucl
5171
5172!------------------------------------------------------------------------------!
5173! Description:
5174! ------------
5175!> Conciders only the organic matter in nucleation. Paasonen et al. (2010)
5176!> determined particle formation rates for 2 nm particles, J2, from different
5177!> kind of combinations of sulphuric acid and organic matter concentration.
5178!> See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.
5179!------------------------------------------------------------------------------!
5180 SUBROUTINE orgnucl( pc_org, pnuc_rate, pd_crit, pn_crit_sa, pn_crit_ocnv,     &
5181                     pk_sa, pk_ocnv )
5182
5183    IMPLICIT NONE
5184
5185    REAL(wp) ::  a_org = 1.3E-7_wp  !< (1/s) (Paasonen et al. Table 4: median)
5186
5187    REAL(wp), INTENT(in) ::  pc_org   !< organic vapour concentration (#/m3)
5188
5189    REAL(wp), INTENT(out) ::  pd_crit  !< critical diameter of clusters (m)
5190    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate in nucleation
5191    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 participate in nucleation
5192    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5193    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5194    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucl. rate (#/(m3 s))
5195!
5196!-- Homomolecular nuleation rate
5197    pnuc_rate = a_org * pc_org
5198!
5199!-- H2SO4 not involved when pure organic nucleation is assumed.
5200    pn_crit_sa   = 0.0_wp
5201    pn_crit_ocnv = 1.0_wp
5202    pk_sa        = 0.0_wp
5203    pk_ocnv      = 1.0_wp
5204    pd_crit      = 1.5E-9_wp   ! (m)
5205
5206 END SUBROUTINE orgnucl
5207
5208!------------------------------------------------------------------------------!
5209! Description:
5210! ------------
5211!> Conciders both the organic vapor and H2SO4 in nucleation - activation type
5212!> of nucleation.
5213!> See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.
5214!------------------------------------------------------------------------------!
5215 SUBROUTINE sumnucl( pc_sa, pc_org, pnuc_rate, pd_crit, pn_crit_sa, pn_crit_ocnv, pk_sa, pk_ocnv )
5216
5217    IMPLICIT NONE
5218
5219    REAL(wp) ::  a_s1 = 6.1E-7_wp   !< (1/s)
5220    REAL(wp) ::  a_s2 = 0.39E-7_wp  !< (1/s) (Paasonen et al. Table 3.)
5221
5222    REAL(wp), INTENT(in) ::  pc_org   !< organic vapour concentration (#/m3)
5223    REAL(wp), INTENT(in) ::  pc_sa    !< H2SO4 conc. (#/m3)
5224
5225    REAL(wp), INTENT(out) ::  pd_crit  !< critical diameter of clusters (m)
5226    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate in nucleation
5227    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 participate in nucleation
5228    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5229    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5230    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucl. rate (#/(m3 s))
5231!
5232!-- Nucleation rate  (#/m3/s)
5233    pnuc_rate = a_s1 * pc_sa + a_s2 * pc_org
5234!
5235!-- Both organic compounds and H2SO4 are involved when sumnucleation is assumed.
5236    pn_crit_sa   = 1.0_wp
5237    pn_crit_ocnv = 1.0_wp
5238    pk_sa        = 1.0_wp
5239    pk_ocnv      = 1.0_wp
5240    pd_crit      = 1.5E-9_wp   ! (m)
5241
5242 END SUBROUTINE sumnucl
5243
5244!------------------------------------------------------------------------------!
5245! Description:
5246! ------------
5247!> Conciders both the organic vapor and H2SO4 in nucleation - heteromolecular
5248!> nucleation.
5249!> See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.
5250!------------------------------------------------------------------------------!
5251 SUBROUTINE hetnucl( pc_sa, pc_org, pnuc_rate, pd_crit, pn_crit_sa, pn_crit_ocnv, pk_sa, pk_ocnv )
5252
5253    IMPLICIT NONE
5254
5255    REAL(wp) ::  z_k_het = 4.1E-14_wp  !< (cm3/s) (Paasonen et al. Table 4: median)
5256
5257    REAL(wp), INTENT(in) ::  pc_org   !< organic vapour concentration (#/m3)
5258    REAL(wp), INTENT(in) ::  pc_sa    !< H2SO4 conc. (#/m3)
5259
5260    REAL(wp), INTENT(out) ::  pd_crit  !< critical diameter of clusters (m)
5261    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate in nucleation
5262    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 participate in nucleation
5263    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5264    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5265    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucl. rate (#/(m3 s))
5266!
5267!-- Nucleation rate (#/m3/s)
5268    pnuc_rate = z_k_het * pc_sa * pc_org * 1.0E6_wp
5269!
5270!-- Both organic compounds and H2SO4 are involved when heteromolecular
5271!-- nucleation is assumed.
5272    pn_crit_sa   = 1.0_wp
5273    pn_crit_ocnv = 1.0_wp
5274    pk_sa        = 1.0_wp
5275    pk_ocnv      = 1.0_wp
5276    pd_crit      = 1.5E-9_wp   ! (m)
5277
5278 END SUBROUTINE hetnucl
5279
5280!------------------------------------------------------------------------------!
5281! Description:
5282! ------------
5283!> Takes into account the homomolecular nucleation of sulphuric acid H2SO4 with
5284!> both of the available vapours.
5285!> See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.
5286!------------------------------------------------------------------------------!
5287 SUBROUTINE SAnucl( pc_sa, pc_org, pnuc_rate, pd_crit, pn_crit_sa, pn_crit_ocnv, pk_sa, pk_ocnv )
5288
5289    IMPLICIT NONE
5290
5291    REAL(wp) ::  z_k_sa1 = 1.1E-14_wp  !< (cm3/s)
5292    REAL(wp) ::  z_k_sa2 = 3.2E-14_wp  !< (cm3/s) (Paasonen et al. Table 3.)
5293
5294    REAL(wp), INTENT(in) ::  pc_org   !< organic vapour concentration (#/m3)
5295    REAL(wp), INTENT(in) ::  pc_sa    !< H2SO4 conc. (#/m3)
5296
5297    REAL(wp), INTENT(out) ::  pd_crit  !< critical diameter of clusters (m)
5298    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate nucleation
5299    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 participate in nucleation
5300    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5301    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5302    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucleation rate (#/(m3 s))
5303!
5304!-- Nucleation rate (#/m3/s)
5305    pnuc_rate = ( z_k_sa1 * pc_sa**2 + z_k_sa2 * pc_sa * pc_org ) * 1.0E+6_wp
5306!
5307!-- Both organic compounds and H2SO4 are involved when SAnucleation is assumed.
5308    pn_crit_sa   = 3.0_wp
5309    pn_crit_ocnv = 1.0_wp 
5310    pk_sa        = 1.0_wp
5311    pk_ocnv      = 1.0_wp
5312    pd_crit      = 1.5E-9_wp   ! (m)
5313
5314 END SUBROUTINE SAnucl
5315
5316!------------------------------------------------------------------------------!
5317! Description:
5318! ------------
5319!> Takes into account the homomolecular nucleation of both sulphuric acid and
5320!> Lorganic with heteromolecular nucleation.
5321!> See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.
5322!------------------------------------------------------------------------------!
5323 SUBROUTINE SAORGnucl( pc_sa, pc_org, pnuc_rate, pd_crit, pn_crit_sa, pn_crit_ocnv, pk_sa, pk_ocnv )
5324
5325    IMPLICIT NONE
5326
5327    REAL(wp) ::  z_k_s1 = 1.4E-14_wp    !< (cm3/s])
5328    REAL(wp) ::  z_k_s2 = 2.6E-14_wp    !< (cm3/s])
5329    REAL(wp) ::  z_k_s3 = 0.037E-14_wp  !< (cm3/s]) (Paasonen et al. Table 3.)
5330
5331    REAL(wp), INTENT(in) ::  pc_org   !< organic vapour concentration (#/m3)
5332    REAL(wp), INTENT(in) ::  pc_sa    !< H2SO4 conc. (#/m3)
5333
5334    REAL(wp), INTENT(out) ::  pd_crit  !< critical diameter of clusters (m)
5335    REAL(wp), INTENT(out) ::  pk_ocnv  !< if pk_ocnv = 1, organic compounds participate in nucleation
5336    REAL(wp), INTENT(out) ::  pk_sa    !< if pk_sa = 1, H2SO4 participate in nucleation
5337    REAL(wp), INTENT(out) ::  pn_crit_ocnv  !< number of organic molecules in cluster (#)
5338    REAL(wp), INTENT(out) ::  pn_crit_sa    !< number of H2SO4 molecules in cluster (#)
5339    REAL(wp), INTENT(out) ::  pnuc_rate     !< nucl. rate (#/(m3 s))
5340!
5341!-- Nucleation rate (#/m3/s)
5342    pnuc_rate = ( z_k_s1 * pc_sa**2 + z_k_s2 * pc_sa * pc_org + z_k_s3 * pc_org**2 ) * 1.0E+6_wp
5343!
5344!-- Organic compounds not involved when kinetic nucleation is assumed.
5345    pn_crit_sa   = 3.0_wp
5346    pn_crit_ocnv = 3.0_wp
5347    pk_sa        = 1.0_wp
5348    pk_ocnv      = 1.0_wp
5349    pd_crit      = 1.5E-9_wp   ! (m)
5350
5351 END SUBROUTINE SAORGnucl
5352
5353!------------------------------------------------------------------------------!
5354! Description:
5355! ------------
5356!> Function z_n_nuc_tayl is connected to the calculation of self-coagualtion of
5357!> small particles. It calculates number of the particles in the size range
5358!> [zdcrit,dx] using Taylor-expansion (please note that the expansion is not
5359!> valid for certain rational numbers, e.g. -4/3 and -3/2)
5360!------------------------------------------------------------------------------!
5361 FUNCTION z_n_nuc_tayl( d1, dx, zm_para, zjnuc_t, zeta, z_gr_tot )
5362
5363    IMPLICIT NONE
5364
5365    INTEGER(iwp) ::  i !< running index
5366
5367    REAL(wp) ::  d1            !< lower diameter limit
5368    REAL(wp) ::  dx            !< upper diameter limit
5369    REAL(wp) ::  zjnuc_t       !< initial nucleation rate (1/s)
5370    REAL(wp) ::  zeta          !< ratio of CS/GR (m) (condensation sink / growth rate)
5371    REAL(wp) ::  term1         !<
5372    REAL(wp) ::  term2         !<
5373    REAL(wp) ::  term3         !<
5374    REAL(wp) ::  term4         !<
5375    REAL(wp) ::  term5         !<
5376    REAL(wp) ::  z_n_nuc_tayl  !< final nucleation rate (1/s)
5377    REAL(wp) ::  z_gr_tot      !< total growth rate (nm/h)
5378    REAL(wp) ::  zm_para       !< m parameter in Lehtinen et al. (2007), Eq. 6
5379
5380    z_n_nuc_tayl = 0.0_wp
5381
5382    DO  i = 0, 29
5383       IF ( i == 0  .OR.  i == 1 )  THEN
5384          term1 = 1.0_wp
5385       ELSE
5386          term1 = term1 * REAL( i, SELECTED_REAL_KIND(12,307) )
5387       END IF
5388       term2 = ( REAL( i, SELECTED_REAL_KIND(12,307) ) * ( zm_para + 1.0_wp ) + 1.0_wp ) * term1
5389       term3 = zeta**i
5390       term4 = term3 / term2
5391       term5 = REAL( i, SELECTED_REAL_KIND(12,307) ) * ( zm_para + 1.0_wp ) + 1.0_wp
5392       z_n_nuc_tayl = z_n_nuc_tayl + term4 * ( dx**term5 - d1**term5 )
5393    ENDDO
5394    z_n_nuc_tayl = z_n_nuc_tayl * zjnuc_t * EXP( -zeta * ( d1**( zm_para + 1 ) ) ) / z_gr_tot
5395
5396 END FUNCTION z_n_nuc_tayl
5397
5398!------------------------------------------------------------------------------!
5399! Description:
5400! ------------
5401!> Calculates the condensation of water vapour on aerosol particles. Follows the
5402!> analytical predictor method by Jacobson (2005).
5403!> For equations, see Jacobson (2005), Fundamentals of atmospheric modelling
5404!> (2nd edition).
5405!------------------------------------------------------------------------------!
5406 SUBROUTINE gpparth2o( paero, ptemp, ppres, pcs, pcw, ptstep )
5407
5408    IMPLICIT NONE
5409
5410    INTEGER(iwp) ::  ib   !< loop index
5411    INTEGER(iwp) ::  nstr !<
5412
5413    REAL(wp) ::  adt        !< internal timestep in this subroutine
5414    REAL(wp) ::  rhoair     !< air density (kg/m3)
5415    REAL(wp) ::  ttot       !< total time (s)
5416    REAL(wp) ::  zact       !< Water activity
5417    REAL(wp) ::  zaelwc1    !< Current aerosol water content (kg/m3)
5418    REAL(wp) ::  zaelwc2    !< New aerosol water content after equilibrium calculation (kg/m3)
5419    REAL(wp) ::  zbeta      !< Transitional correction factor
5420    REAL(wp) ::  zcwc       !< Current water vapour mole concentration in aerosols (mol/m3)
5421    REAL(wp) ::  zcwint     !< Current and new water vapour mole concentrations (mol/m3)
5422    REAL(wp) ::  zcwn       !< New water vapour mole concentration (mol/m3)
5423    REAL(wp) ::  zcwtot     !< Total water mole concentration (mol/m3)
5424    REAL(wp) ::  zdfh2o     !< molecular diffusion coefficient (cm2/s) for water
5425    REAL(wp) ::  zhlp1      !< intermediate variable to calculate the mass transfer coefficient
5426    REAL(wp) ::  zhlp2      !< intermediate variable to calculate the mass transfer coefficient
5427    REAL(wp) ::  zhlp3      !< intermediate variable to calculate the mass transfer coefficient
5428    REAL(wp) ::  zknud      !< Knudsen number
5429    REAL(wp) ::  zmfph2o    !< mean free path of H2O gas molecule
5430    REAL(wp) ::  zrh        !< relative humidity [0-1]
5431    REAL(wp) ::  zthcond    !< thermal conductivity of air (W/m/K)
5432
5433    REAL(wp), DIMENSION(nbins_aerosol) ::  zcwcae     !< Current water mole concentrations
5434    REAL(wp), DIMENSION(nbins_aerosol) ::  zcwintae   !< Current and new aerosol water mole concentration
5435    REAL(wp), DIMENSION(nbins_aerosol) ::  zcwnae     !< New water mole concentration in aerosols
5436    REAL(wp), DIMENSION(nbins_aerosol) ::  zcwsurfae  !< Surface mole concentration
5437    REAL(wp), DIMENSION(nbins_aerosol) ::  zkelvin    !< Kelvin effect
5438    REAL(wp), DIMENSION(nbins_aerosol) ::  zmtae      !< Mass transfer coefficients
5439    REAL(wp), DIMENSION(nbins_aerosol) ::  zwsatae    !< Water saturation ratio above aerosols
5440
5441    REAL(wp), INTENT(in) ::  ppres   !< Air pressure (Pa)
5442    REAL(wp), INTENT(in) ::  pcs     !< Water vapour saturation concentration (kg/m3)
5443    REAL(wp), INTENT(in) ::  ptemp   !< Ambient temperature (K)
5444    REAL(wp), INTENT(in) ::  ptstep  !< timestep (s)
5445
5446    REAL(wp), INTENT(inout) ::  pcw  !< Water vapour concentration (kg/m3)
5447
5448    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero  !< Aerosol properties
5449!
5450!-- Relative humidity [0-1]
5451    zrh = pcw / pcs
5452!
5453!-- Calculate the condensation only for 2a/2b aerosol bins
5454    nstr = start_subrange_2a
5455!
5456!-- Save the current aerosol water content, 8 in paero is H2O
5457    zaelwc1 = SUM( paero(start_subrange_1a:end_subrange_2b)%volc(8) ) * arhoh2o
5458!
5459!-- Equilibration:
5460    IF ( advect_particle_water )  THEN
5461       IF ( zrh < 0.98_wp  .OR.  .NOT. lscndh2oae )  THEN
5462          CALL equilibration( zrh, ptemp, paero, .TRUE. )
5463       ELSE
5464          CALL equilibration( zrh, ptemp, paero, .FALSE. )
5465       ENDIF
5466    ENDIF
5467!
5468!-- The new aerosol water content after equilibrium calculation
5469    zaelwc2 = SUM( paero(start_subrange_1a:end_subrange_2b)%volc(8) ) * arhoh2o
5470!
5471!-- New water vapour mixing ratio (kg/m3)
5472    pcw = pcw - ( zaelwc2 - zaelwc1 ) * ppres * amdair / ( argas * ptemp )
5473!
5474!-- Initialise variables
5475    zcwsurfae(:) = 0.0_wp
5476    zhlp1        = 0.0_wp
5477    zhlp2        = 0.0_wp
5478    zhlp3        = 0.0_wp
5479    zmtae(:)     = 0.0_wp
5480    zwsatae(:)   = 0.0_wp
5481!
5482!-- Air:
5483!-- Density (kg/m3)
5484    rhoair = amdair * ppres / ( argas * ptemp )
5485!
5486!-- Thermal conductivity of air
5487    zthcond = 0.023807_wp + 7.1128E-5_wp * ( ptemp - 273.16_wp )
5488!
5489!-- Water vapour:
5490!-- Molecular diffusion coefficient (cm2/s) (eq.16.17)
5491    zdfh2o = ( 5.0_wp / ( 16.0_wp * avo * rhoair * 1.0E-3_wp * 3.11E-8_wp**2 ) ) * SQRT( argas *   &
5492               1.0E+7_wp * ptemp * amdair * 1.0E+3_wp * ( amh2o + amdair ) * 1.0E+3_wp /           &
5493               ( pi * amh2o * 2.0E+3_wp ) )
5494    zdfh2o = zdfh2o * 1.0E-4   ! Unit change to m^2/s
5495!
5496!-- Mean free path (eq. 15.25 & 16.29)
5497    zmfph2o = 3.0_wp * zdfh2o * SQRT( pi * amh2o / ( 8.0_wp * argas * ptemp ) )
5498!
5499!-- Kelvin effect (eq. 16.33)
5500    zkelvin(:) = EXP( 4.0_wp * surfw0 * amh2o / ( argas * ptemp * arhoh2o * paero(:)%dwet) )
5501
5502    DO  ib = 1, nbins_aerosol
5503       IF ( paero(ib)%numc > nclim  .AND.  zrh > 0.98_wp )  THEN
5504!
5505!--       Water activity
5506          zact = acth2o( paero(ib) )
5507!
5508!--       Saturation mole concentration over flat surface. Limit the super-
5509!--       saturation to max 1.01 for the mass transfer. Experimental!
5510          zcwsurfae(ib) = MAX( pcs, pcw / 1.01_wp ) * rhoair / amh2o
5511!
5512!--       Equilibrium saturation ratio
5513          zwsatae(ib) = zact * zkelvin(ib)
5514!
5515!--       Knudsen number (eq. 16.20)
5516          zknud = 2.0_wp * zmfph2o / paero(ib)%dwet
5517!
5518!--       Transitional correction factor (Fuks & Sutugin, 1971)
5519          zbeta = ( zknud + 1.0_wp ) / ( 0.377_wp * zknud + 1.0_wp + 4.0_wp /                      &
5520                  ( 3.0_wp * massacc(ib) ) * ( zknud + zknud**2 ) )
5521!
5522!--       Mass transfer of H2O: Eq. 16.64 but here D^eff =  zdfh2o * zbeta
5523          zhlp1 = paero(ib)%numc * 2.0_wp * pi * paero(ib)%dwet * zdfh2o * zbeta
5524!
5525!--       1st term on the left side of the denominator in eq. 16.55
5526          zhlp2 = amh2o * zdfh2o * alv * zwsatae(ib) * zcwsurfae(ib) / ( zthcond * ptemp )
5527!
5528!--       2nd term on the left side of the denominator in eq. 16.55
5529          zhlp3 = ( ( alv * amh2o ) / ( argas * ptemp ) ) - 1.0_wp
5530!
5531!--       Full eq. 16.64: Mass transfer coefficient (1/s)
5532          zmtae(ib) = zhlp1 / ( zhlp2 * zhlp3 + 1.0_wp )
5533       ENDIF
5534    ENDDO
5535!
5536!-- Current mole concentrations of water
5537    zcwc        = pcw * rhoair / amh2o   ! as vapour
5538    zcwcae(:)   = paero(:)%volc(8) * arhoh2o / amh2o   ! in aerosols
5539    zcwtot      = zcwc + SUM( zcwcae )   ! total water concentration
5540    zcwnae(:)   = 0.0_wp
5541    zcwintae(:) = zcwcae(:)
5542!
5543!-- Substepping loop
5544    zcwint = 0.0_wp
5545    ttot   = 0.0_wp
5546    DO  WHILE ( ttot < ptstep )
5547       adt = 2.0E-2_wp   ! internal timestep
5548!
5549!--    New vapour concentration: (eq. 16.71)
5550       zhlp1 = zcwc + adt * ( SUM( zmtae(nstr:nbins_aerosol) * zwsatae(nstr:nbins_aerosol) *       &
5551                                   zcwsurfae(nstr:nbins_aerosol) ) )   ! numerator
5552       zhlp2 = 1.0_wp + adt * ( SUM( zmtae(nstr:nbins_aerosol) ) )   ! denomin.
5553       zcwint = zhlp1 / zhlp2   ! new vapour concentration
5554       zcwint = MIN( zcwint, zcwtot )
5555       IF ( ANY( paero(:)%numc > nclim )  .AND. zrh > 0.98_wp )  THEN
5556          DO  ib = nstr, nbins_aerosol
5557             zcwintae(ib) = zcwcae(ib) + MIN( MAX( adt * zmtae(ib) * ( zcwint - zwsatae(ib) *      &
5558                                                   zcwsurfae(ib) ), -0.02_wp * zcwcae(ib) ),       &
5559                                            0.05_wp * zcwcae(ib) )
5560             zwsatae(ib) = acth2o( paero(ib), zcwintae(ib) ) * zkelvin(ib)
5561          ENDDO
5562       ENDIF
5563       zcwintae(nstr:nbins_aerosol) = MAX( zcwintae(nstr:nbins_aerosol), 0.0_wp )
5564!
5565!--    Update vapour concentration for consistency
5566       zcwint = zcwtot - SUM( zcwintae(1:nbins_aerosol) )
5567!
5568!--    Update "old" values for next cycle
5569       zcwcae = zcwintae
5570
5571       ttot = ttot + adt
5572
5573    ENDDO   ! ADT
5574
5575    zcwn      = zcwint
5576    zcwnae(:) = zcwintae(:)
5577    pcw       = zcwn * amh2o / rhoair
5578    paero(:)%volc(8) = MAX( 0.0_wp, zcwnae(:) * amh2o / arhoh2o )
5579
5580 END SUBROUTINE gpparth2o
5581
5582!------------------------------------------------------------------------------!
5583! Description:
5584! ------------
5585!> Calculates the activity coefficient of liquid water
5586!------------------------------------------------------------------------------!
5587 REAL(wp) FUNCTION acth2o( ppart, pcw )
5588
5589    IMPLICIT NONE
5590
5591    REAL(wp) ::  zns  !< molar concentration of solutes (mol/m3)
5592    REAL(wp) ::  znw  !< molar concentration of water (mol/m3)
5593
5594    REAL(wp), INTENT(in), OPTIONAL ::  pcw !< molar concentration of water (mol/m3)
5595
5596    TYPE(t_section), INTENT(in) ::  ppart !< Aerosol properties of a bin
5597
5598    zns = ( 3.0_wp * ( ppart%volc(1) * arhoh2so4 / amh2so4 ) + ( ppart%volc(2) * arhooc / amoc ) + &
5599            2.0_wp * ( ppart%volc(5) * arhoss / amss ) + ( ppart%volc(6) * arhohno3 / amhno3 ) +   &
5600            ( ppart%volc(7) * arhonh3 / amnh3 ) )
5601
5602    IF ( PRESENT(pcw) ) THEN
5603       znw = pcw
5604    ELSE
5605       znw = ppart%volc(8) * arhoh2o / amh2o
5606    ENDIF
5607!
5608!-- Activity = partial pressure of water vapour / sat. vapour pressure of water over a liquid surface
5609!--          = molality * activity coefficient (Jacobson, 2005: eq. 17.20-21)
5610!-- Assume activity coefficient of 1 for water
5611    acth2o = MAX( 0.1_wp, znw / MAX( EPSILON( 1.0_wp ),( znw + zns ) ) )
5612
5613 END FUNCTION acth2o
5614
5615!------------------------------------------------------------------------------!
5616! Description:
5617! ------------
5618!> Calculates the dissolutional growth of particles (i.e. gas transfers to a
5619!> particle surface and dissolves in liquid water on the surface). Treated here
5620!> as a non-equilibrium (time-dependent) process. Gases: HNO3 and NH3
5621!> (Chapter 17.14 in Jacobson, 2005).
5622!
5623!> Called from subroutine condensation.
5624!> Coded by:
5625!> Harri Kokkola (FMI)
5626!------------------------------------------------------------------------------!
5627 SUBROUTINE gpparthno3( ppres, ptemp, paero, pghno3, pgnh3, pcw, pcs, pbeta, ptstep )
5628
5629    IMPLICIT NONE
5630
5631    INTEGER(iwp) ::  ib  !< loop index
5632
5633    REAL(wp) ::  adt          !< timestep
5634    REAL(wp) ::  zc_nh3_c     !< Current NH3 gas concentration
5635    REAL(wp) ::  zc_nh3_int   !< Intermediate NH3 gas concentration
5636    REAL(wp) ::  zc_nh3_n     !< New NH3 gas concentration
5637    REAL(wp) ::  zc_nh3_tot   !< Total NH3 concentration
5638    REAL(wp) ::  zc_hno3_c    !< Current HNO3 gas concentration
5639    REAL(wp) ::  zc_hno3_int  !< Intermediate HNO3 gas concentration
5640    REAL(wp) ::  zc_hno3_n    !< New HNO3 gas concentration
5641    REAL(wp) ::  zc_hno3_tot  !< Total HNO3 concentration
5642    REAL(wp) ::  zdfvap       !< Diffusion coefficient for vapors
5643    REAL(wp) ::  zhlp1        !< intermediate variable
5644    REAL(wp) ::  zhlp2        !< intermediate variable
5645    REAL(wp) ::  zrh          !< relative humidity
5646
5647    REAL(wp), INTENT(in) ::  ppres      !< ambient pressure (Pa)
5648    REAL(wp), INTENT(in) ::  pcs        !< water vapour saturation
5649                                        !< concentration (kg/m3)
5650    REAL(wp), INTENT(in) ::  ptemp      !< ambient temperature (K)
5651    REAL(wp), INTENT(in) ::  ptstep     !< time step (s)
5652
5653    REAL(wp), INTENT(inout) ::  pghno3  !< nitric acid concentration (#/m3)
5654    REAL(wp), INTENT(inout) ::  pgnh3   !< ammonia conc. (#/m3)
5655    REAL(wp), INTENT(inout) ::  pcw     !< water vapour concentration (kg/m3)
5656
5657    REAL(wp), DIMENSION(nbins_aerosol) ::  zac_hno3_ae     !< Activity coefficients for HNO3
5658    REAL(wp), DIMENSION(nbins_aerosol) ::  zac_hhso4_ae    !< Activity coefficients for HHSO4
5659    REAL(wp), DIMENSION(nbins_aerosol) ::  zac_nh3_ae      !< Activity coefficients for NH3
5660    REAL(wp), DIMENSION(nbins_aerosol) ::  zac_nh4hso2_ae  !< Activity coefficients for NH4HSO2
5661    REAL(wp), DIMENSION(nbins_aerosol) ::  zcg_hno3_eq_ae  !< Equilibrium gas concentration: HNO3
5662    REAL(wp), DIMENSION(nbins_aerosol) ::  zcg_nh3_eq_ae   !< Equilibrium gas concentration: NH3
5663    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_hno3_int_ae  !< Intermediate HNO3 aerosol concentration
5664    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_hno3_c_ae    !< Current HNO3 in aerosols
5665    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_hno3_n_ae    !< New HNO3 in aerosols
5666    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_nh3_int_ae   !< Intermediate NH3 aerosol concentration
5667    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_nh3_c_ae     !< Current NH3 in aerosols
5668    REAL(wp), DIMENSION(nbins_aerosol) ::  zc_nh3_n_ae     !< New NH3 in aerosols
5669    REAL(wp), DIMENSION(nbins_aerosol) ::  zkel_hno3_ae    !< Kelvin effect for HNO3
5670    REAL(wp), DIMENSION(nbins_aerosol) ::  zkel_nh3_ae     !< Kelvin effects for NH3
5671    REAL(wp), DIMENSION(nbins_aerosol) ::  zmt_hno3_ae     !< Mass transfer coefficients for HNO3
5672    REAL(wp), DIMENSION(nbins_aerosol) ::  zmt_nh3_ae      !< Mass transfer coefficients for NH3
5673    REAL(wp), DIMENSION(nbins_aerosol) ::  zsat_hno3_ae    !< HNO3 saturation ratio over a surface
5674    REAL(wp), DIMENSION(nbins_aerosol) ::  zsat_nh3_ae     !< NH3 saturation ratio over a surface
5675
5676    REAL(wp), DIMENSION(nbins_aerosol,maxspec) ::  zion_mols   !< Ion molalities from pdfite aerosols
5677
5678    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pbeta !< transitional correction factor for
5679
5680    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero !< Aerosol properties
5681!
5682!-- Initialise:
5683    adt            = ptstep
5684    zac_hhso4_ae   = 0.0_wp
5685    zac_nh3_ae     = 0.0_wp
5686    zac_nh4hso2_ae = 0.0_wp
5687    zac_hno3_ae    = 0.0_wp
5688    zcg_nh3_eq_ae  = 0.0_wp
5689    zcg_hno3_eq_ae = 0.0_wp
5690    zion_mols      = 0.0_wp
5691    zsat_nh3_ae    = 1.0_wp
5692    zsat_hno3_ae   = 1.0_wp
5693!
5694!-- Diffusion coefficient (m2/s)
5695    zdfvap = 5.1111E-10_wp * ptemp**1.75_wp * ( p_0 + 1325.0_wp ) / ppres
5696!
5697!-- Kelvin effects (Jacobson (2005), eq. 16.33)
5698    zkel_hno3_ae(1:nbins_aerosol) = EXP( 4.0_wp * surfw0 * amvhno3 /                               &
5699                                    ( abo * ptemp * paero(1:nbins_aerosol)%dwet ) )
5700    zkel_nh3_ae(1:nbins_aerosol) = EXP( 4.0_wp * surfw0 * amvnh3 /                                 &
5701                                   ( abo * ptemp * paero(1:nbins_aerosol)%dwet ) )
5702!
5703!-- Current vapour mole concentrations (mol/m3)
5704    zc_hno3_c = pghno3 / avo  ! HNO3
5705    zc_nh3_c = pgnh3 / avo   ! NH3
5706!
5707!-- Current particle mole concentrations (mol/m3)
5708    zc_hno3_c_ae(1:nbins_aerosol) = paero(1:nbins_aerosol)%volc(6) * arhohno3 / amhno3
5709    zc_nh3_c_ae(1:nbins_aerosol) = paero(1:nbins_aerosol)%volc(7) * arhonh3 / amnh3
5710!
5711!-- Total mole concentrations: gas and particle phase
5712    zc_hno3_tot = zc_hno3_c + SUM( zc_hno3_c_ae(1:nbins_aerosol) )
5713    zc_nh3_tot = zc_nh3_c + SUM( zc_nh3_c_ae(1:nbins_aerosol) )
5714!
5715!-- Relative humidity [0-1]
5716    zrh = pcw / pcs
5717!
5718!-- Mass transfer coefficients (Jacobson, Eq. 16.64)
5719    zmt_hno3_ae(:) = 2.0_wp * pi * paero(:)%dwet * zdfvap * paero(:)%numc * pbeta(:)
5720    zmt_nh3_ae(:)  = 2.0_wp * pi * paero(:)%dwet * zdfvap * paero(:)%numc * pbeta(:)
5721
5722!
5723!-- Get the equilibrium concentrations above aerosols
5724    CALL nitrate_ammonium_equilibrium( zrh, ptemp, paero, zcg_hno3_eq_ae, zcg_nh3_eq_ae,           &
5725                                       zac_hno3_ae, zac_nh3_ae, zac_nh4hso2_ae, zac_hhso4_ae,      &
5726                                       zion_mols )
5727!
5728!-- Calculate NH3 and HNO3 saturation ratios for aerosols
5729    CALL nitrate_ammonium_saturation( ptemp, paero, zac_hno3_ae, zac_nh4hso2_ae, zac_hhso4_ae,     &
5730                                      zcg_hno3_eq_ae, zc_hno3_c_ae, zc_nh3_c_ae, zkel_hno3_ae,     &
5731                                      zkel_nh3_ae, zsat_hno3_ae, zsat_nh3_ae )
5732!
5733!-- Intermediate gas concentrations of HNO3 and NH3
5734    zhlp1 = SUM( zc_hno3_c_ae(:) / ( 1.0_wp + adt * zmt_hno3_ae(:) * zsat_hno3_ae(:) ) )
5735    zhlp2 = SUM( zmt_hno3_ae(:) / ( 1.0_wp + adt * zmt_hno3_ae(:) * zsat_hno3_ae(:) ) )
5736    zc_hno3_int = ( zc_hno3_tot - zhlp1 ) / ( 1.0_wp + adt * zhlp2 )
5737
5738    zhlp1 = SUM( zc_nh3_c_ae(:) / ( 1.0_wp + adt * zmt_nh3_ae(:) * zsat_nh3_ae(:) ) )
5739    zhlp2 = SUM( zmt_nh3_ae(:) / ( 1.0_wp + adt * zmt_nh3_ae(:) * zsat_nh3_ae(:) ) )
5740    zc_nh3_int = ( zc_nh3_tot - zhlp1 )/( 1.0_wp + adt * zhlp2 )
5741
5742    zc_hno3_int = MIN( zc_hno3_int, zc_hno3_tot )
5743    zc_nh3_int = MIN( zc_nh3_int, zc_nh3_tot )
5744!
5745!-- Calculate the new concentration on aerosol particles
5746    zc_hno3_int_ae = zc_hno3_c_ae
5747    zc_nh3_int_ae = zc_nh3_c_ae
5748    DO  ib = 1, nbins_aerosol
5749       zc_hno3_int_ae(ib) = ( zc_hno3_c_ae(ib) + adt * zmt_hno3_ae(ib) * zc_hno3_int ) /           &
5750                            ( 1.0_wp + adt * zmt_hno3_ae(ib) * zsat_hno3_ae(ib) )
5751       zc_nh3_int_ae(ib) = ( zc_nh3_c_ae(ib) + adt * zmt_nh3_ae(ib) * zc_nh3_int ) /               &
5752                           ( 1.0_wp + adt * zmt_nh3_ae(ib) * zsat_nh3_ae(ib) )
5753    ENDDO
5754
5755    zc_hno3_int_ae(:) = MAX( zc_hno3_int_ae(:), 0.0_wp )
5756    zc_nh3_int_ae(:) = MAX( zc_nh3_int_ae(:), 0.0_wp )
5757!
5758!-- Final molar gas concentration and molar particle concentration of HNO3
5759    zc_hno3_n   = zc_hno3_int
5760    zc_hno3_n_ae = zc_hno3_int_ae
5761!
5762!-- Final molar gas concentration and molar particle concentration of NH3
5763    zc_nh3_n   = zc_nh3_int
5764    zc_nh3_n_ae = zc_nh3_int_ae
5765!
5766!-- Model timestep reached - update the gas concentrations
5767    pghno3 = zc_hno3_n * avo
5768    pgnh3  = zc_nh3_n * avo
5769!
5770!-- Update the particle concentrations
5771    DO  ib = start_subrange_1a, end_subrange_2b
5772       paero(ib)%volc(6) = zc_hno3_n_ae(ib) * amhno3 / arhohno3
5773       paero(ib)%volc(7) = zc_nh3_n_ae(ib) * amnh3 / arhonh3
5774    ENDDO
5775
5776 END SUBROUTINE gpparthno3
5777!------------------------------------------------------------------------------!
5778! Description:
5779! ------------
5780!> Calculate the equilibrium concentrations above aerosols (reference?)
5781!------------------------------------------------------------------------------!
5782 SUBROUTINE nitrate_ammonium_equilibrium( prh, ptemp, ppart, pcg_hno3_eq, pcg_nh3_eq, pgamma_hno3, &
5783                                          pgamma_nh4, pgamma_nh4hso2, pgamma_hhso4, pmols )
5784
5785    IMPLICIT NONE
5786
5787    INTEGER(iwp) ::  ib  !< loop index: aerosol bins
5788
5789    REAL(wp) ::  zhlp         !< intermediate variable
5790    REAL(wp) ::  zp_hcl       !< Equilibrium vapor pressures (Pa) of HCl
5791    REAL(wp) ::  zp_hno3      !< Equilibrium vapor pressures (Pa) of HNO3
5792    REAL(wp) ::  zp_nh3       !< Equilibrium vapor pressures (Pa) of NH3
5793    REAL(wp) ::  zwatertotal  !< Total water in particles (mol/m3)
5794
5795    REAL(wp), INTENT(in) ::  prh    !< relative humidity
5796    REAL(wp), INTENT(in) ::  ptemp  !< ambient temperature (K)
5797
5798    REAL(wp), DIMENSION(maxspec) ::  zgammas  !< Activity coefficients
5799    REAL(wp), DIMENSION(maxspec) ::  zions    !< molar concentration of ion (mol/m3)
5800
5801    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pcg_nh3_eq      !< equilibrium molar
5802                                                                          !< concentration: of NH3
5803    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pcg_hno3_eq     !< of HNO3
5804    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pgamma_hhso4    !< activity coeff. of HHSO4
5805    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pgamma_nh4      !< activity coeff. of NH3
5806    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pgamma_nh4hso2  !< activity coeff. of NH4HSO2
5807    REAL(wp), DIMENSION(nbins_aerosol), INTENT(inout) ::  pgamma_hno3     !< activity coeff. of HNO3
5808
5809    REAL(wp), DIMENSION(nbins_aerosol,maxspec), INTENT(inout) ::  pmols  !< Ion molalities
5810
5811    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  ppart  !< Aerosol properties
5812
5813    zgammas     = 0.0_wp
5814    zhlp        = 0.0_wp
5815    zions       = 0.0_wp
5816    zp_hcl      = 0.0_wp
5817    zp_hno3     = 0.0_wp
5818    zp_nh3      = 0.0_wp
5819    zwatertotal = 0.0_wp
5820
5821    DO  ib = 1, nbins_aerosol
5822
5823       IF ( ppart(ib)%numc < nclim )  CYCLE
5824!
5825!--    Ion molar concentrations: 2*H2SO4 + CL + NO3 - Na - NH4
5826       zhlp = 2.0_wp * ppart(ib)%volc(1) * arhoh2so4 / amh2so4 + ppart(ib)%volc(5) * arhoss / amss &
5827              + ppart(ib)%volc(6) * arhohno3 / amhno3 - ppart(ib)%volc(5) * arhoss / amss -        &
5828              ppart(ib)%volc(7) * arhonh3 / amnh3
5829
5830       zions(1) = zhlp                                   ! H+
5831       zions(2) = ppart(ib)%volc(7) * arhonh3 / amnh3     ! NH4+
5832       zions(3) = ppart(ib)%volc(5) * arhoss / amss       ! Na+
5833       zions(4) = ppart(ib)%volc(1) * arhoh2so4 / amh2so4 ! SO4(2-)
5834       zions(5) = 0.0_wp                                 ! HSO4-
5835       zions(6) = ppart(ib)%volc(6) * arhohno3 / amhno3   ! NO3-
5836       zions(7) = ppart(ib)%volc(5) * arhoss / amss       ! Cl-
5837
5838       zwatertotal = ppart(ib)%volc(8) * arhoh2o / amh2o
5839       IF ( zwatertotal > 1.0E-30_wp )  THEN
5840          CALL inorganic_pdfite( prh, ptemp, zions, zwatertotal, zp_hno3, zp_hcl, zp_nh3, zgammas, &
5841                                 pmols(ib,:) )
5842       ENDIF
5843!
5844!--    Activity coefficients
5845       pgamma_hno3(ib)    = zgammas(1)  ! HNO3
5846       pgamma_nh4(ib)     = zgammas(3)  ! NH3
5847       pgamma_nh4hso2(ib) = zgammas(6)  ! NH4HSO2
5848       pgamma_hhso4(ib)   = zgammas(7)  ! HHSO4
5849!
5850!--    Equilibrium molar concentrations (mol/m3) from equlibrium pressures (Pa)
5851       pcg_hno3_eq(ib) = zp_hno3 / ( argas * ptemp )
5852       pcg_nh3_eq(ib) = zp_nh3 / ( argas * ptemp )
5853
5854    ENDDO
5855
5856  END SUBROUTINE nitrate_ammonium_equilibrium
5857
5858!------------------------------------------------------------------------------!
5859! Description:
5860! ------------
5861!> Calculate saturation ratios of NH4 and HNO3 for aerosols
5862!------------------------------------------------------------------------------!
5863 SUBROUTINE nitrate_ammonium_saturation( ptemp, ppart, pachno3, pacnh4hso2, pachhso4, pchno3eq,    &
5864                                         pchno3, pc_nh3, pkelhno3, pkelnh3, psathno3, psatnh3 )
5865
5866    IMPLICIT NONE
5867
5868    INTEGER(iwp) :: ib   !< running index for aerosol bins
5869
5870    REAL(wp) ::  k_ll_h2o   !< equilibrium constants of equilibrium reactions:
5871                            !< H2O(aq) <--> H+ + OH- (mol/kg)
5872    REAL(wp) ::  k_ll_nh3   !< NH3(aq) + H2O(aq) <--> NH4+ + OH- (mol/kg)
5873    REAL(wp) ::  k_gl_nh3   !< NH3(g) <--> NH3(aq) (mol/kg/atm)
5874    REAL(wp) ::  k_gl_hno3  !< HNO3(g) <--> H+ + NO3- (mol2/kg2/atm)
5875    REAL(wp) ::  zmol_no3   !< molality of NO3- (mol/kg)
5876    REAL(wp) ::  zmol_h     !< molality of H+ (mol/kg)
5877    REAL(wp) ::  zmol_so4   !< molality of SO4(2-) (mol/kg)
5878    REAL(wp) ::  zmol_cl    !< molality of Cl- (mol/kg)
5879    REAL(wp) ::  zmol_nh4   !< molality of NH4+ (mol/kg)
5880    REAL(wp) ::  zmol_na    !< molality of Na+ (mol/kg)
5881    REAL(wp) ::  zhlp1      !< intermediate variable
5882    REAL(wp) ::  zhlp2      !< intermediate variable
5883    REAL(wp) ::  zhlp3      !< intermediate variable
5884    REAL(wp) ::  zxi        !< particle mole concentration ratio: (NH3+SS)/H2SO4
5885    REAL(wp) ::  zt0        !< reference temp
5886
5887    REAL(wp), PARAMETER ::  a1 = -22.52_wp     !<
5888    REAL(wp), PARAMETER ::  a2 = -1.50_wp      !<
5889    REAL(wp), PARAMETER ::  a3 = 13.79_wp      !<
5890    REAL(wp), PARAMETER ::  a4 = 29.17_wp      !<
5891    REAL(wp), PARAMETER ::  b1 = 26.92_wp      !<
5892    REAL(wp), PARAMETER ::  b2 = 26.92_wp      !<
5893    REAL(wp), PARAMETER ::  b3 = -5.39_wp      !<
5894    REAL(wp), PARAMETER ::  b4 = 16.84_wp      !<
5895    REAL(wp), PARAMETER ::  K01 = 1.01E-14_wp  !<
5896    REAL(wp), PARAMETER ::  K02 = 1.81E-5_wp   !<
5897    REAL(wp), PARAMETER ::  K03 = 57.64_wp     !<
5898    REAL(wp), PARAMETER ::  K04 = 2.51E+6_wp   !<
5899
5900    REAL(wp), INTENT(in) ::  ptemp  !< ambient temperature (K)
5901
5902    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pachhso4    !< activity coeff. of HHSO4
5903    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pacnh4hso2  !< activity coeff. of NH4HSO2
5904    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pachno3     !< activity coeff. of HNO3
5905    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pchno3eq    !< eq. surface concentration: HNO3
5906    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pchno3      !< current particle mole
5907                                                                   !< concentration of HNO3 (mol/m3)
5908    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pc_nh3      !< of NH3 (mol/m3)
5909    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pkelhno3    !< Kelvin effect for HNO3
5910    REAL(wp), DIMENSION(nbins_aerosol), INTENT(in) ::  pkelnh3     !< Kelvin effect for NH3
5911
5912    REAL(wp), DIMENSION(nbins_aerosol), INTENT(out) ::  psathno3 !< saturation ratio of HNO3
5913    REAL(wp), DIMENSION(nbins_aerosol), INTENT(out) ::  psatnh3  !< saturation ratio of NH3
5914
5915    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  ppart  !< Aerosol properties
5916
5917    zmol_cl  = 0.0_wp
5918    zmol_h   = 0.0_wp
5919    zmol_na  = 0.0_wp
5920    zmol_nh4 = 0.0_wp
5921    zmol_no3 = 0.0_wp
5922    zmol_so4 = 0.0_wp
5923    zt0      = 298.15_wp
5924    zxi      = 0.0_wp
5925!
5926!-- Calculates equlibrium rate constants based on Table B.7 in Jacobson (2005):
5927!-- K^ll_H20, K^ll_NH3, K^gl_NH3, K^gl_HNO3
5928    zhlp1 = zt0 / ptemp
5929    zhlp2 = zhlp1 - 1.0_wp
5930    zhlp3 = 1.0_wp + LOG( zhlp1 ) - zhlp1
5931
5932    k_ll_h2o  = K01 * EXP( a1 * zhlp2 + b1 * zhlp3 )
5933    k_ll_nh3  = K02 * EXP( a2 * zhlp2 + b2 * zhlp3 )
5934    k_gl_nh3  = K03 * EXP( a3 * zhlp2 + b3 * zhlp3 )
5935    k_gl_hno3 = K04 * EXP( a4 * zhlp2 + b4 * zhlp3 )
5936
5937    DO  ib = 1, nbins_aerosol
5938
5939       IF ( ppart(ib)%numc > nclim  .AND.  ppart(ib)%volc(8) > 1.0E-30_wp  )  THEN
5940!
5941!--       Molality of H+ and NO3-
5942          zhlp1 = pc_nh3(ib) * amnh3 + ppart(ib)%volc(1) * arhoh2so4 + ppart(ib)%volc(2) * arhooc  &
5943                  + ppart(ib)%volc(5) * arhoss + ppart(ib)%volc(8) * arhoh2o
5944          zmol_no3 = pchno3(ib) / zhlp1  !< mol/kg
5945!
5946!--       Particle mole concentration ratio: (NH3+SS)/H2SO4
5947          zxi = ( pc_nh3(ib) + ppart(ib)%volc(5) * arhoss / amss ) / ( ppart(ib)%volc(1) *         &
5948                  arhoh2so4 / amh2so4 )
5949
5950          IF ( zxi <= 2.0_wp )  THEN
5951!
5952!--          Molality of SO4(2-)
5953             zhlp1 = pc_nh3(ib) * amnh3 + pchno3(ib) * amhno3 + ppart(ib)%volc(2) * arhooc +       &
5954                     ppart(ib)%volc(5) * arhoss + ppart(ib)%volc(8) * arhoh2o
5955             zmol_so4 = ( ppart(ib)%volc(1) * arhoh2so4 / amh2so4 ) / zhlp1
5956!
5957!--          Molality of Cl-
5958             zhlp1 = pc_nh3(ib) * amnh3 + pchno3(ib) * amhno3 + ppart(ib)%volc(2) * arhooc +       &
5959                     ppart(ib)%volc(1) * arhoh2so4 + ppart(ib)%volc(8) * arhoh2o
5960             zmol_cl = ( ppart(ib)%volc(5) * arhoss / amss ) / zhlp1
5961!
5962!--          Molality of NH4+
5963             zhlp1 =  pchno3(ib) * amhno3 + ppart(ib)%volc(1) * arhoh2so4 + ppart(ib)%volc(2) *    &
5964                      arhooc + ppart(ib)%volc(5) * arhoss + ppart(ib)%volc(8) * arhoh2o
5965             zmol_nh4 = pc_nh3(ib) / zhlp1
5966!
5967!--          Molality of Na+
5968             zmol_na = zmol_cl
5969!
5970!--          Molality of H+
5971             zmol_h = 2.0_wp * zmol_so4 + zmol_no3 + zmol_cl - ( zmol_nh4 + zmol_na )
5972
5973          ELSE
5974
5975             zhlp2 = pkelhno3(ib) * zmol_no3 * pachno3(ib)**2
5976
5977             IF ( zhlp2 > 1.0E-30_wp )  THEN
5978                zmol_h = k_gl_hno3 * pchno3eq(ib) / zhlp2 ! Eq. 17.38
5979             ELSE
5980                zmol_h = 0.0_wp
5981             ENDIF
5982
5983          ENDIF
5984
5985          zhlp1 = ppart(ib)%volc(8) * arhoh2o * argas * ptemp * k_gl_hno3
5986!
5987!--       Saturation ratio for NH3 and for HNO3
5988          IF ( zmol_h > 0.0_wp )  THEN
5989             zhlp2 = pkelnh3(ib) / ( zhlp1 * zmol_h )
5990             zhlp3 = k_ll_h2o / ( k_ll_nh3 + k_gl_nh3 )
5991             psatnh3(ib) = zhlp2 * ( ( pacnh4hso2(ib) / pachhso4(ib) )**2 ) * zhlp3
5992             psathno3(ib) = ( pkelhno3(ib) * zmol_h * pachno3(ib)**2 ) / zhlp1
5993          ELSE
5994             psatnh3(ib) = 1.0_wp
5995             psathno3(ib) = 1.0_wp
5996          ENDIF
5997       ELSE
5998          psatnh3(ib) = 1.0_wp
5999          psathno3(ib) = 1.0_wp
6000       ENDIF
6001
6002    ENDDO
6003
6004  END SUBROUTINE nitrate_ammonium_saturation
6005
6006!------------------------------------------------------------------------------!
6007! Description:
6008! ------------
6009!> Prototype module for calculating the water content of a mixed inorganic/
6010!> organic particle + equilibrium water vapour pressure above the solution
6011!> (HNO3, HCL, NH3 and representative organic compounds. Efficient calculation
6012!> of the partitioning of species between gas and aerosol. Based in a chamber
6013!> study.
6014!
6015!> Written by Dave Topping. Pure organic component properties predicted by Mark
6016!> Barley based on VOCs predicted in MCM simulations performed by Mike Jenkin.
6017!> Delivered by Gordon McFiggans as Deliverable D22 from WP1.4 in the EU FP6
6018!> EUCAARI Integrated Project.
6019!
6020!> REFERENCES
6021!> Clegg et al. (1998) A Thermodynamic Model of the System H+-NH4+-Na+-SO42- -NO3--Cl--H2O at
6022!>    298.15 K, J. Phys. Chem., 102A, 2155-2171.
6023!> Clegg et al. (2001) Thermodynamic modelling of aqueous aerosols containing electrolytes and
6024!>    dissolved organic compounds. Journal of Aerosol Science 2001;32(6):713-738.
6025!> Topping et al. (2005a) A curved multi-component aerosol hygroscopicity model framework: Part 1 -
6026!>    Inorganic compounds. Atmospheric Chemistry and Physics 2005;5:1205-1222.
6027!> Topping et al. (2005b) A curved multi-component aerosol hygroscopicity model framework: Part 2 -
6028!>    Including organic compounds. Atmospheric Chemistry and Physics 2005;5:1223-1242.
6029!> Wagman et al. (1982). The NBS tables of chemical thermodynamic properties: selected values for
6030!>    inorganic and C₁ and C₂ organic substances in SI units (book)
6031!> Zaveri et al. (2005). A new method for multicomponent activity coefficients of electrolytes in
6032!>    aqueous atmospheric aerosols, JGR, 110, D02201, 2005.
6033!
6034!> Queries concerning the use of this code through Gordon McFiggans,
6035!> g.mcfiggans@manchester.ac.uk,
6036!> Ownership: D. Topping, Centre for Atmospheric Sciences, University of
6037!> Manchester, 2007
6038!
6039!> Rewritten to PALM by Mona Kurppa, UHel, 2017
6040!------------------------------------------------------------------------------!
6041 SUBROUTINE inorganic_pdfite( rh, temp, ions, water_total, press_hno3, press_hcl, press_nh3,       &
6042                              gamma_out, mols_out )
6043
6044    IMPLICIT NONE
6045
6046    INTEGER(iwp) ::  binary_case
6047    INTEGER(iwp) ::  full_complexity
6048
6049    REAL(wp) ::  a                         !< auxiliary variable
6050    REAL(wp) ::  act_product               !< ionic activity coef. product:
6051                                           !< = (gamma_h2so4**3d0) / gamma_hhso4**2d0)
6052    REAL(wp) ::  ammonium_chloride         !<
6053    REAL(wp) ::  ammonium_chloride_eq_frac !<
6054    REAL(wp) ::  ammonium_nitrate          !<
6055    REAL(wp) ::  ammonium_nitrate_eq_frac  !<
6056    REAL(wp) ::  ammonium_sulphate         !<
6057    REAL(wp) ::  ammonium_sulphate_eq_frac !<
6058    REAL(wp) ::  b                         !< auxiliary variable
6059    REAL(wp) ::  binary_h2so4              !< binary H2SO4 activity coeff.
6060    REAL(wp) ::  binary_hcl                !< binary HCL activity coeff.
6061    REAL(wp) ::  binary_hhso4              !< binary HHSO4 activity coeff.
6062    REAL(wp) ::  binary_hno3               !< binary HNO3 activity coeff.
6063    REAL(wp) ::  binary_nh4hso4            !< binary NH4HSO4 activity coeff.
6064    REAL(wp) ::  c                         !< auxiliary variable
6065    REAL(wp) ::  charge_sum                !< sum of ionic charges
6066    REAL(wp) ::  gamma_h2so4               !< activity coefficient
6067    REAL(wp) ::  gamma_hcl                 !< activity coefficient
6068    REAL(wp) ::  gamma_hhso4               !< activity coeffient
6069    REAL(wp) ::  gamma_hno3                !< activity coefficient
6070    REAL(wp) ::  gamma_nh3                 !< activity coefficient
6071    REAL(wp) ::  gamma_nh4hso4             !< activity coefficient
6072    REAL(wp) ::  h_out                     !<
6073    REAL(wp) ::  h_real                    !< new hydrogen ion conc.
6074    REAL(wp) ::  h2so4_hcl                 !< contribution of H2SO4
6075    REAL(wp) ::  h2so4_hno3                !< contribution of H2SO4
6076    REAL(wp) ::  h2so4_nh3                 !< contribution of H2SO4
6077    REAL(wp) ::  h2so4_nh4hso4             !< contribution of H2SO4
6078    REAL(wp) ::  hcl_h2so4                 !< contribution of HCL
6079    REAL(wp) ::  hcl_hhso4                 !< contribution of HCL
6080    REAL(wp) ::  hcl_hno3                  !< contribution of HCL
6081    REAL(wp) ::  hcl_nh4hso4               !< contribution of HCL
6082    REAL(wp) ::  henrys_temp_dep           !< temperature dependence of Henry's Law
6083    REAL(wp) ::  hno3_h2so4                !< contribution of HNO3
6084    REAL(wp) ::  hno3_hcl                  !< contribution of HNO3
6085    REAL(wp) ::  hno3_hhso4                !< contribution of HNO3
6086    REAL(wp) ::  hno3_nh3                  !< contribution of HNO3
6087    REAL(wp) ::  hno3_nh4hso4              !< contribution of HNO3
6088    REAL(wp) ::  hso4_out                  !<
6089    REAL(wp) ::  hso4_real                 !< new bisulphate ion conc.
6090    REAL(wp) ::  hydrochloric_acid         !<
6091    REAL(wp) ::  hydrochloric_acid_eq_frac !<
6092    REAL(wp) ::  k_h                       !< equilibrium constant for H+
6093    REAL(wp) ::  k_hcl                     !< equilibrium constant of HCL
6094    REAL(wp) ::  k_hno3                    !< equilibrium constant of HNO3
6095    REAL(wp) ::  k_nh4                     !< equilibrium constant for NH4+
6096    REAL(wp) ::  k_h2o                     !< equil. const. for water_surface
6097    REAL(wp) ::  ln_h2so4_act              !< gamma_h2so4 = EXP(ln_h2so4_act)
6098    REAL(wp) ::  ln_HCL_act                !< gamma_hcl = EXP( ln_HCL_act )
6099    REAL(wp) ::  ln_hhso4_act              !< gamma_hhso4 = EXP(ln_hhso4_act)
6100    REAL(wp) ::  ln_hno3_act               !< gamma_hno3 = EXP( ln_hno3_act )
6101    REAL(wp) ::  ln_nh4hso4_act            !< gamma_nh4hso4 = EXP( ln_nh4hso4_act )
6102    REAL(wp) ::  molality_ratio_nh3        !< molality ratio of NH3 (NH4+ and H+)
6103    REAL(wp) ::  na2so4_h2so4              !< contribution of Na2SO4
6104    REAL(wp) ::  na2so4_hcl                !< contribution of Na2SO4
6105    REAL(wp) ::  na2so4_hhso4              !< contribution of Na2SO4
6106    REAL(wp) ::  na2so4_hno3               !< contribution of Na2SO4
6107    REAL(wp) ::  na2so4_nh3                !< contribution of Na2SO4
6108    REAL(wp) ::  na2so4_nh4hso4            !< contribution of Na2SO4
6109    REAL(wp) ::  nacl_h2so4                !< contribution of NaCl
6110    REAL(wp) ::  nacl_hcl                  !< contribution of NaCl
6111    REAL(wp) ::  nacl_hhso4                !< contribution of NaCl
6112    REAL(wp) ::  nacl_hno3                 !< contribution of NaCl
6113    REAL(wp) ::  nacl_nh3                  !< contribution of NaCl
6114    REAL(wp) ::  nacl_nh4hso4              !< contribution of NaCl
6115    REAL(wp) ::  nano3_h2so4               !< contribution of NaNO3
6116    REAL(wp) ::  nano3_hcl                 !< contribution of NaNO3
6117    REAL(wp) ::  nano3_hhso4               !< contribution of NaNO3
6118    REAL(wp) ::  nano3_hno3                !< contribution of NaNO3
6119    REAL(wp) ::  nano3_nh3                 !< contribution of NaNO3
6120    REAL(wp) ::  nano3_nh4hso4             !< contribution of NaNO3
6121    REAL(wp) ::  nh42so4_h2so4             !< contribution of NH42SO4
6122    REAL(wp) ::  nh42so4_hcl               !< contribution of NH42SO4
6123    REAL(wp) ::  nh42so4_hhso4             !< contribution of NH42SO4
6124    REAL(wp) ::  nh42so4_hno3              !< contribution of NH42SO4
6125    REAL(wp) ::  nh42so4_nh3               !< contribution of NH42SO4
6126    REAL(wp) ::  nh42so4_nh4hso4           !< contribution of NH42SO4
6127    REAL(wp) ::  nh4cl_h2so4               !< contribution of NH4Cl
6128    REAL(wp) ::  nh4cl_hcl                 !< contribution of NH4Cl
6129    REAL(wp) ::  nh4cl_hhso4               !< contribution of NH4Cl
6130    REAL(wp) ::  nh4cl_hno3                !< contribution of NH4Cl
6131    REAL(wp) ::  nh4cl_nh3                 !< contribution of NH4Cl
6132    REAL(wp) ::  nh4cl_nh4hso4             !< contribution of NH4Cl
6133    REAL(wp) ::  nh4no3_h2so4              !< contribution of NH4NO3
6134    REAL(wp) ::  nh4no3_hcl                !< contribution of NH4NO3
6135    REAL(wp) ::  nh4no3_hhso4              !< contribution of NH4NO3
6136    REAL(wp) ::  nh4no3_hno3               !< contribution of NH4NO3
6137    REAL(wp) ::  nh4no3_nh3                !< contribution of NH4NO3
6138    REAL(wp) ::  nh4no3_nh4hso4            !< contribution of NH4NO3
6139    REAL(wp) ::  nitric_acid               !<
6140    REAL(wp) ::  nitric_acid_eq_frac       !< Equivalent fractions
6141    REAL(wp) ::  press_hcl                 !< partial pressure of HCL
6142    REAL(wp) ::  press_hno3                !< partial pressure of HNO3
6143    REAL(wp) ::  press_nh3                 !< partial pressure of NH3
6144    REAL(wp) ::  rh                        !< relative humidity [0-1]
6145    REAL(wp) ::  root1                     !< auxiliary variable
6146    REAL(wp) ::  root2                     !< auxiliary variable
6147    REAL(wp) ::  so4_out                   !<
6148    REAL(wp) ::  so4_real                  !< new sulpate ion concentration
6149    REAL(wp) ::  sodium_chloride           !<
6150    REAL(wp) ::  sodium_chloride_eq_frac   !<
6151    REAL(wp) ::  sodium_nitrate            !<
6152    REAL(wp) ::  sodium_nitrate_eq_frac    !<
6153    REAL(wp) ::  sodium_sulphate           !<
6154    REAL(wp) ::  sodium_sulphate_eq_frac   !<
6155    REAL(wp) ::  solutes                   !<
6156    REAL(wp) ::  sulphuric_acid            !<
6157    REAL(wp) ::  sulphuric_acid_eq_frac    !<
6158    REAL(wp) ::  temp                      !< temperature
6159    REAL(wp) ::  water_total               !<
6160
6161    REAL(wp), DIMENSION(:) ::  gamma_out !< Activity coefficient for calculating the non-ideal
6162                                         !< dissociation constants
6163                                         !< 1: HNO3, 2: HCL, 3: NH4+/H+ (NH3), 4: HHSO4**2/H2SO4,
6164                                         !< 5: H2SO4**3/HHSO4**2, 6: NH4HSO2, 7: HHSO4
6165    REAL(wp), DIMENSION(:) ::  ions      !< ion molarities (mol/m3): 1: H+, 2: NH4+, 3: Na+,
6166                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
6167    REAL(wp), DIMENSION(7) ::  ions_mol  !< ion molalities (mol/kg): 1: H+, 2: NH4+, 3: Na+,
6168                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
6169    REAL(wp), DIMENSION(:) ::  mols_out  !< ion molality output (mol/kg): 1: H+, 2: NH4+, 3: Na+,
6170                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
6171!
6172!-- Value initialisation
6173    binary_h2so4    = 0.0_wp
6174    binary_hcl      = 0.0_wp
6175    binary_hhso4    = 0.0_wp
6176    binary_hno3     = 0.0_wp
6177    binary_nh4hso4  = 0.0_wp
6178    henrys_temp_dep = ( 1.0_wp / temp - 0.0033557_wp ) ! 1/T - 1/298 K
6179    hcl_hno3        = 1.0_wp
6180    h2so4_hno3      = 1.0_wp
6181    nh42so4_hno3    = 1.0_wp
6182    nh4no3_hno3     = 1.0_wp
6183    nh4cl_hno3      = 1.0_wp
6184    na2so4_hno3     = 1.0_wp
6185    nano3_hno3      = 1.0_wp
6186    nacl_hno3       = 1.0_wp
6187    hno3_hcl        = 1.0_wp
6188    h2so4_hcl       = 1.0_wp
6189    nh42so4_hcl     = 1.0_wp
6190    nh4no3_hcl      = 1.0_wp
6191    nh4cl_hcl       = 1.0_wp
6192    na2so4_hcl      = 1.0_wp
6193    nano3_hcl       = 1.0_wp
6194    nacl_hcl        = 1.0_wp
6195    hno3_nh3        = 1.0_wp
6196    h2so4_nh3       = 1.0_wp
6197    nh42so4_nh3     = 1.0_wp
6198    nh4no3_nh3      = 1.0_wp
6199    nh4cl_nh3       = 1.0_wp
6200    na2so4_nh3      = 1.0_wp
6201    nano3_nh3       = 1.0_wp
6202    nacl_nh3        = 1.0_wp
6203    hno3_hhso4      = 1.0_wp
6204    hcl_hhso4       = 1.0_wp
6205    nh42so4_hhso4   = 1.0_wp
6206    nh4no3_hhso4    = 1.0_wp
6207    nh4cl_hhso4     = 1.0_wp
6208    na2so4_hhso4    = 1.0_wp
6209    nano3_hhso4     = 1.0_wp
6210    nacl_hhso4      = 1.0_wp
6211    hno3_h2so4      = 1.0_wp
6212    hcl_h2so4       = 1.0_wp
6213    nh42so4_h2so4   = 1.0_wp
6214    nh4no3_h2so4    = 1.0_wp
6215    nh4cl_h2so4     = 1.0_wp
6216    na2so4_h2so4    = 1.0_wp
6217    nano3_h2so4     = 1.0_wp
6218    nacl_h2so4      = 1.0_wp
6219!
6220!-- New NH3 variables
6221    hno3_nh4hso4    = 1.0_wp
6222    hcl_nh4hso4     = 1.0_wp
6223    h2so4_nh4hso4   = 1.0_wp
6224    nh42so4_nh4hso4 = 1.0_wp
6225    nh4no3_nh4hso4  = 1.0_wp
6226    nh4cl_nh4hso4   = 1.0_wp
6227    na2so4_nh4hso4  = 1.0_wp
6228    nano3_nh4hso4   = 1.0_wp
6229    nacl_nh4hso4    = 1.0_wp
6230!
6231!-- Juha Tonttila added
6232    mols_out   = 0.0_wp
6233    press_hno3 = 0.0_wp  !< Initialising vapour pressures over the
6234    press_hcl  = 0.0_wp  !< multicomponent particle
6235    press_nh3  = 0.0_wp
6236    gamma_out  = 1.0_wp  !< i.e. don't alter the ideal mixing ratios if there's nothing there.
6237!
6238!-- 1) - COMPOSITION DEFINITIONS
6239!
6240!-- a) Inorganic ion pairing:
6241!-- In order to calculate the water content, which is also used in calculating vapour pressures, one
6242!-- needs to pair the anions and cations for use in the ZSR mixing rule. The equation provided by
6243!-- Clegg et al. (2001) is used for ion pairing. The solutes chosen comprise of 9 inorganic salts
6244!-- and acids which provide a pairing between each anion and cation: (NH4)2SO4, NH4NO3, NH4Cl,
6245!-- Na2SO4, NaNO3, NaCl, H2SO4, HNO3, HCL. The organic compound is treated as a seperate solute.
6246!-- Ions: 1: H+, 2: NH4+, 3: Na+, 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
6247!
6248    charge_sum = ions(1) + ions(2) + ions(3) + 2.0_wp * ions(4) + ions(5) + ions(6) + ions(7)
6249    nitric_acid       = ( 2.0_wp * ions(1) * ions(6) ) / charge_sum
6250    hydrochloric_acid = ( 2.0_wp * ions(1) * ions(7) ) / charge_sum
6251    sulphuric_acid    = ( 2.0_wp * ions(1) * ions(4) ) / charge_sum
6252    ammonium_sulphate = ( 2.0_wp * ions(2) * ions(4) ) / charge_sum
6253    ammonium_nitrate  = ( 2.0_wp * ions(2) * ions(6) ) / charge_sum
6254    ammonium_chloride = ( 2.0_wp * ions(2) * ions(7) ) / charge_sum
6255    sodium_sulphate   = ( 2.0_wp * ions(3) * ions(4) ) / charge_sum
6256    sodium_nitrate    = ( 2.0_wp * ions(3) * ions(6) ) / charge_sum
6257    sodium_chloride   = ( 2.0_wp * ions(3) * ions(7) ) / charge_sum
6258    solutes = 0.0_wp
6259    solutes = 3.0_wp * sulphuric_acid    + 2.0_wp * hydrochloric_acid + 2.0_wp * nitric_acid +     &
6260              3.0_wp * ammonium_sulphate + 2.0_wp * ammonium_nitrate + 2.0_wp * ammonium_chloride +&
6261              3.0_wp * sodium_sulphate   + 2.0_wp * sodium_nitrate   + 2.0_wp * sodium_chloride
6262!
6263!-- b) Inorganic equivalent fractions:
6264!-- These values are calculated so that activity coefficients can be expressed by a linear additive
6265!-- rule, thus allowing more efficient calculations and future expansion (see more detailed
6266!-- description below)
6267    nitric_acid_eq_frac       = 2.0_wp * nitric_acid / solutes
6268    hydrochloric_acid_eq_frac = 2.0_wp * hydrochloric_acid / solutes
6269    sulphuric_acid_eq_frac    = 3.0_wp * sulphuric_acid / solutes
6270    ammonium_sulphate_eq_frac = 3.0_wp * ammonium_sulphate / solutes
6271    ammonium_nitrate_eq_frac  = 2.0_wp * ammonium_nitrate / solutes
6272    ammonium_chloride_eq_frac = 2.0_wp * ammonium_chloride / solutes
6273    sodium_sulphate_eq_frac   = 3.0_wp * sodium_sulphate / solutes
6274    sodium_nitrate_eq_frac    = 2.0_wp * sodium_nitrate / solutes
6275    sodium_chloride_eq_frac   = 2.0_wp * sodium_chloride / solutes
6276!
6277!-- Inorganic ion molalities
6278    ions_mol(1) = ions(1) / ( water_total * 18.01528E-3_wp )   ! H+
6279    ions_mol(2) = ions(2) / ( water_total * 18.01528E-3_wp )   ! NH4+
6280    ions_mol(3) = ions(3) / ( water_total * 18.01528E-3_wp )   ! Na+
6281    ions_mol(4) = ions(4) / ( water_total * 18.01528E-3_wp )   ! SO4(2-)
6282    ions_mol(5) = ions(5) / ( water_total * 18.01528E-3_wp )   ! HSO4(2-)
6283    ions_mol(6) = ions(6) / ( water_total * 18.01528E-3_wp )   !  NO3-
6284    ions_mol(7) = ions(7) / ( water_total * 18.01528E-3_wp )   ! Cl-
6285
6286!-- ***
6287!-- At this point we may need to introduce a method for prescribing H+ when there is no 'real' value
6288!-- for H+..i.e. in the sulphate poor domain. This will give a value for solve quadratic proposed by
6289!-- Zaveri et al. 2005
6290!
6291!-- 2) - WATER CALCULATION
6292!
6293!-- a) The water content is calculated using the ZSR rule with solute concentrations calculated
6294!-- using 1a above. Whilst the usual approximation of ZSR relies on binary data consisting of 5th or
6295!-- higher order polynomials, in this code 4 different RH regimes are used, each housing cubic
6296!-- equations for the water associated with each solute listed above. Binary water contents for
6297!-- inorganic components were calculated using AIM online (Clegg et al 1998). The water associated
6298!-- with the organic compound is calculated assuming ideality and that aw = RH.
6299!
6300!-- b) Molality of each inorganic ion and organic solute (initial input) is calculated for use in
6301!-- vapour pressure calculation.
6302!
6303!-- 3) - BISULPHATE ION DISSOCIATION CALCULATION
6304!
6305!-- The dissociation of the bisulphate ion is calculated explicitly. A solution to the equilibrium
6306!-- equation between the bisulphate ion, hydrogen ion and sulphate ion is found using tabulated
6307!-- equilibrium constants (referenced). It is necessary to calculate the activity coefficients of
6308!-- HHSO4 and H2SO4 in a non-iterative manner. These are calculated using the same format as
6309!-- described in 4) below, where both activity coefficients were fit to the output from ADDEM
6310!-- (Topping et al 2005a,b) covering an extensive composition space, providing the activity
6311!-- coefficients and bisulphate ion dissociation as a function of equivalent mole fractions and
6312!-- relative humidity.
6313!
6314!-- NOTE: the flags "binary_case" and "full_complexity" are not used in this prototype. They are
6315!-- used for simplification of the fit expressions when using limited composition regions. This
6316!-- section of code calculates the bisulphate ion concentration.
6317!
6318    IF ( ions(1) > 0.0_wp .AND. ions(4) > 0.0_wp ) THEN
6319!
6320!--    HHSO4:
6321       binary_case = 1
6322       IF ( rh > 0.1_wp  .AND.  rh < 0.9_wp )  THEN
6323          binary_hhso4 = -4.9521_wp * rh**3 + 9.2881_wp * rh**2 - 10.777_wp * rh + 6.0534_wp
6324       ELSEIF ( rh >= 0.9_wp  .AND.  rh < 0.955_wp )  THEN
6325          binary_hhso4 = -6.3777_wp * rh + 5.962_wp
6326       ELSEIF ( rh >= 0.955_wp  .AND.  rh < 0.99_wp )  THEN
6327          binary_hhso4 = 2367.2_wp * rh**3 - 6849.7_wp * rh**2 + 6600.9_wp * rh - 2118.7_wp
6328       ELSEIF ( rh >= 0.99_wp  .AND.  rh < 0.9999_wp )  THEN
6329          binary_hhso4 = 3E-7_wp * rh**5 - 2E-5_wp * rh**4 + 0.0004_wp * rh**3 - 0.0035_wp * rh**2 &
6330                         + 0.0123_wp * rh - 0.3025_wp
6331       ENDIF
6332
6333       IF ( nitric_acid > 0.0_wp )  THEN
6334          hno3_hhso4 = -4.2204_wp * rh**4 + 12.193_wp * rh**3 - 12.481_wp * rh**2 + 6.459_wp * rh  &
6335                       - 1.9004_wp
6336       ENDIF
6337
6338       IF ( hydrochloric_acid > 0.0_wp )  THEN
6339          hcl_hhso4 = -54.845_wp * rh**7 + 209.54_wp * rh**6 - 336.59_wp * rh**5 + 294.21_wp *     &
6340                      rh**4 - 150.07_wp * rh**3 + 43.767_wp * rh**2 - 6.5495_wp * rh + 0.60048_wp
6341       ENDIF
6342
6343       IF ( ammonium_sulphate > 0.0_wp )  THEN
6344          nh42so4_hhso4 = 16.768_wp * rh**3 - 28.75_wp * rh**2 + 20.011_wp * rh - 8.3206_wp
6345       ENDIF
6346
6347       IF ( ammonium_nitrate > 0.0_wp )  THEN
6348          nh4no3_hhso4 = -17.184_wp * rh**4 + 56.834_wp * rh**3 - 65.765_wp * rh**2 +              &
6349                         35.321_wp * rh - 9.252_wp
6350       ENDIF
6351
6352       IF (ammonium_chloride > 0.0_wp )  THEN
6353          IF ( rh < 0.2_wp .AND. rh >= 0.1_wp )  THEN
6354             nh4cl_hhso4 = 3.2809_wp * rh - 2.0637_wp
6355          ELSEIF ( rh >= 0.2_wp .AND. rh < 0.99_wp )  THEN
6356             nh4cl_hhso4 = -1.2981_wp * rh**3 + 4.7461_wp * rh**2 - 2.3269_wp * rh - 1.1259_wp
6357          ENDIF
6358       ENDIF
6359
6360       IF ( sodium_sulphate > 0.0_wp )  THEN
6361          na2so4_hhso4 = 118.87_wp * rh**6 - 358.63_wp * rh**5 + 435.85_wp * rh**4 - 272.88_wp *   &
6362                         rh**3 + 94.411_wp * rh**2 - 18.21_wp * rh + 0.45935_wp
6363       ENDIF
6364
6365       IF ( sodium_nitrate > 0.0_wp )  THEN
6366          IF ( rh < 0.2_wp  .AND.  rh >= 0.1_wp )  THEN
6367             nano3_hhso4 = 4.8456_wp * rh - 2.5773_wp
6368          ELSEIF ( rh >= 0.2_wp  .AND.  rh < 0.99_wp )  THEN
6369             nano3_hhso4 = 0.5964_wp * rh**3 - 0.38967_wp * rh**2 + 1.7918_wp * rh - 1.9691_wp
6370          ENDIF
6371       ENDIF
6372
6373       IF ( sodium_chloride > 0.0_wp )  THEN
6374          IF ( rh < 0.2_wp )  THEN
6375             nacl_hhso4 = 0.51995_wp * rh - 1.3981_wp
6376          ELSEIF ( rh >= 0.2_wp  .AND.  rh < 0.99_wp )  THEN
6377             nacl_hhso4 = 1.6539_wp * rh - 1.6101_wp
6378          ENDIF
6379       ENDIF
6380
6381       ln_hhso4_act = binary_hhso4 + nitric_acid_eq_frac * hno3_hhso4 +                            &
6382                      hydrochloric_acid_eq_frac * hcl_hhso4 +                                      &
6383                      ammonium_sulphate_eq_frac * nh42so4_hhso4 +                                  &
6384                      ammonium_nitrate_eq_frac  * nh4no3_hhso4 +                                   &
6385                      ammonium_chloride_eq_frac * nh4cl_hhso4 +                                    &
6386                      sodium_sulphate_eq_frac   * na2so4_hhso4 +                                   &
6387                      sodium_nitrate_eq_frac * nano3_hhso4 + sodium_chloride_eq_frac   * nacl_hhso4
6388
6389       gamma_hhso4 = EXP( ln_hhso4_act )   ! molal activity coefficient of HHSO4
6390
6391!--    H2SO4 (sulphuric acid):
6392       IF ( rh >= 0.1_wp  .AND.  rh < 0.9_wp )  THEN
6393          binary_h2so4 = 2.4493_wp * rh**2 - 6.2326_wp * rh + 2.1763_wp
6394       ELSEIF ( rh >= 0.9_wp  .AND.  rh < 0.98 )  THEN
6395          binary_h2so4 = 914.68_wp * rh**3 - 2502.3_wp * rh**2 + 2281.9_wp * rh - 695.11_wp
6396       ELSEIF ( rh >= 0.98  .AND.  rh < 0.9999 )  THEN
6397          binary_h2so4 = 3.0E-8_wp * rh**4 - 5E-6_wp * rh**3 + 0.0003_wp * rh**2 - 0.0022_wp *     &
6398                         rh - 1.1305_wp
6399       ENDIF
6400
6401       IF ( nitric_acid > 0.0_wp )  THEN
6402          hno3_h2so4 = - 16.382_wp * rh**5 + 46.677_wp * rh**4 - 54.149_wp * rh**3 + 34.36_wp *    &
6403                         rh**2 - 12.54_wp * rh + 2.1368_wp
6404       ENDIF
6405
6406       IF ( hydrochloric_acid > 0.0_wp )  THEN
6407          hcl_h2so4 = - 14.409_wp * rh**5 + 42.804_wp * rh**4 - 47.24_wp * rh**3 + 24.668_wp *     &
6408                        rh**2 - 5.8015_wp * rh + 0.084627_wp
6409       ENDIF
6410
6411       IF ( ammonium_sulphate > 0.0_wp )  THEN
6412          nh42so4_h2so4 = 66.71_wp * rh**5 - 187.5_wp * rh**4 + 210.57_wp * rh**3 - 121.04_wp *    &
6413                          rh**2 + 39.182_wp * rh - 8.0606_wp
6414       ENDIF
6415
6416       IF ( ammonium_nitrate > 0.0_wp )  THEN
6417          nh4no3_h2so4 = - 22.532_wp * rh**4 + 66.615_wp * rh**3 - 74.647_wp * rh**2 + 37.638_wp * &
6418                         rh - 6.9711_wp
6419       ENDIF
6420
6421       IF ( ammonium_chloride > 0.0_wp )  THEN
6422          IF ( rh >= 0.1_wp  .AND.  rh < 0.2_wp )  THEN
6423             nh4cl_h2so4 = - 0.32089_wp * rh + 0.57738_wp
6424          ELSEIF ( rh >= 0.2_wp  .AND.  rh < 0.9_wp )  THEN
6425             nh4cl_h2so4 = 18.089_wp * rh**5 - 51.083_wp * rh**4 + 50.32_wp * rh**3 - 17.012_wp *  &
6426                           rh**2 - 0.93435_wp * rh + 1.0548_wp
6427          ELSEIF ( rh >= 0.9_wp  .AND.  rh < 0.99_wp )  THEN
6428             nh4cl_h2so4 = - 1.5749_wp * rh + 1.7002_wp
6429          ENDIF
6430       ENDIF
6431
6432       IF ( sodium_sulphate > 0.0_wp )  THEN
6433          na2so4_h2so4 = 29.843_wp * rh**4 - 69.417_wp * rh**3 + 61.507_wp * rh**2 - 29.874_wp *   &
6434                         rh + 7.7556_wp
6435       ENDIF
6436
6437       IF ( sodium_nitrate > 0.0_wp )  THEN
6438          nano3_h2so4 = - 122.37_wp * rh**6 + 427.43_wp * rh**5 - 604.68_wp * rh**4 + 443.08_wp *  &
6439                        rh**3 - 178.61_wp * rh**2 + 37.242_wp * rh - 1.9564_wp
6440       ENDIF
6441
6442       IF ( sodium_chloride > 0.0_wp )  THEN
6443          nacl_h2so4 = - 40.288_wp * rh**5 + 115.61_wp * rh**4 - 129.99_wp * rh**3 + 72.652_wp *   &
6444                       rh**2 - 22.124_wp * rh + 4.2676_wp
6445       ENDIF
6446
6447       ln_h2so4_act = binary_h2so4 + nitric_acid_eq_frac * hno3_h2so4 +                            &
6448                      hydrochloric_acid_eq_frac * hcl_h2so4 +                                      &
6449                      ammonium_sulphate_eq_frac * nh42so4_h2so4 +                                  &
6450                      ammonium_nitrate_eq_frac  * nh4no3_h2so4 +                                   &
6451                      ammonium_chloride_eq_frac * nh4cl_h2so4 +                                    &
6452                      sodium_sulphate_eq_frac * na2so4_h2so4 +                                     &
6453                      sodium_nitrate_eq_frac * nano3_h2so4 + sodium_chloride_eq_frac * nacl_h2so4
6454
6455       gamma_h2so4 = EXP( ln_h2so4_act )    ! molal activity coefficient
6456!
6457!--    Export activity coefficients
6458       IF ( gamma_h2so4 > 1.0E-10_wp )  THEN
6459          gamma_out(4) = gamma_hhso4**2 / gamma_h2so4
6460       ENDIF
6461       IF ( gamma_hhso4 > 1.0E-10_wp )  THEN
6462          gamma_out(5) = gamma_h2so4**3 / gamma_hhso4**2
6463       ENDIF
6464!
6465!--    Ionic activity coefficient product
6466       act_product = gamma_h2so4**3 / gamma_hhso4**2
6467!
6468!--    Solve the quadratic equation (i.e. x in ax**2 + bx + c = 0)
6469       a = 1.0_wp
6470       b = -1.0_wp * ( ions(4) + ions(1) + ( ( water_total * 18.0E-3_wp ) /                        &
6471           ( 99.0_wp * act_product ) ) )
6472       c = ions(4) * ions(1)
6473       root1 = ( ( -1.0_wp * b ) + ( ( ( b**2 ) - 4.0_wp * a * c )**0.5_wp ) ) / ( 2.0_wp * a )
6474       root2 = ( ( -1.0_wp * b ) - ( ( ( b**2 ) - 4.0_wp * a * c) **0.5_wp ) ) / ( 2.0_wp * a )
6475
6476       IF ( root1 > ions(1)  .OR.  root1 < 0.0_wp )  THEN
6477          root1 = 0.0_wp
6478       ENDIF
6479
6480       IF ( root2 > ions(1)  .OR.  root2 < 0.0_wp )  THEN
6481          root2 = 0.0_wp
6482       ENDIF
6483!
6484!--    Calculate the new hydrogen ion, bisulphate ion and sulphate ion
6485!--    concentration
6486       h_real    = ions(1)
6487       so4_real  = ions(4)
6488       hso4_real = MAX( root1, root2 )
6489       h_real   = ions(1) - hso4_real
6490       so4_real = ions(4) - hso4_real
6491!
6492!--    Recalculate ion molalities
6493       ions_mol(1) = h_real    / ( water_total * 18.01528E-3_wp )   ! H+
6494       ions_mol(4) = so4_real  / ( water_total * 18.01528E-3_wp )   ! SO4(2-)
6495       ions_mol(5) = hso4_real / ( water_total * 18.01528E-3_wp )   ! HSO4(2-)
6496
6497       h_out    = h_real
6498       hso4_out = hso4_real
6499       so4_out  = so4_real
6500
6501    ELSE
6502       h_out    = ions(1)
6503       hso4_out = 0.0_wp
6504       so4_out  = ions(4)
6505    ENDIF
6506
6507!
6508!-- 4) ACTIVITY COEFFICIENTS -for vapour pressures of HNO3,HCL and NH3
6509!
6510!-- This section evaluates activity coefficients and vapour pressures using the water content
6511!-- calculated above) for each inorganic condensing species: a - HNO3, b - NH3, c - HCL.
6512!-- The following procedure is used: Zaveri et al (2005) found that one could express the variation
6513!-- of activity coefficients linearly in log-space if equivalent mole fractions were used.
6514!-- So, by a taylor series expansion LOG( activity coefficient ) =
6515!--    LOG( binary activity coefficient at a given RH ) +
6516!--    (equivalent mole fraction compound A) *
6517!--    ('interaction' parameter between A and condensing species) +
6518!--    equivalent mole fraction compound B) *
6519!--    ('interaction' parameter between B and condensing species).
6520!-- Here, the interaction parameters have been fit to ADDEM by searching the whole compositon space
6521!-- and fit usign the Levenberg-Marquardt non-linear least squares algorithm.
6522!
6523!-- They are given as a function of RH and vary with complexity ranging from linear to 5th order
6524!-- polynomial expressions, the binary activity coefficients were calculated using AIM online.
6525!-- NOTE: for NH3, no binary activity coefficient was used and the data were fit to the ratio of the
6526!-- activity coefficients for the ammonium and hydrogen ions. Once the activity coefficients are
6527!-- obtained the vapour pressure can be easily calculated using tabulated equilibrium constants
6528!-- (referenced). This procedure differs from that of Zaveri et al (2005) in that it is not assumed
6529!-- one can carry behaviour from binary mixtures in multicomponent systems. To this end we have fit
6530!-- the 'interaction' parameters explicitly to a general inorganic equilibrium model
6531!-- (ADDEM - Topping et al. 2005a,b). Such parameters take into account bisulphate ion dissociation
6532!-- and water content. This also allows us to consider one regime for all composition space, rather
6533!-- than defining sulphate rich and sulphate poor regimes.
6534!-- NOTE: The flags "binary_case" and "full_complexity" are not used in this prototype. They are
6535!-- used for simplification of the fit expressions when using limited composition regions.
6536!
6537!-- a) - ACTIVITY COEFF/VAPOUR PRESSURE - HNO3
6538    IF ( ions(1) > 0.0_wp  .AND.  ions(6) > 0.0_wp )  THEN
6539       binary_case = 1
6540       IF ( rh > 0.1_wp  .AND.  rh < 0.98_wp )  THEN
6541          IF ( binary_case == 1 )  THEN
6542             binary_hno3 = 1.8514_wp * rh**3 - 4.6991_wp * rh**2 + 1.5514_wp * rh + 0.90236_wp
6543          ELSEIF ( binary_case == 2 )  THEN
6544             binary_hno3 = - 1.1751_wp * ( rh**2 ) - 0.53794_wp * rh + 1.2808_wp
6545          ENDIF
6546       ELSEIF ( rh >= 0.98_wp  .AND.  rh < 0.9999_wp )  THEN
6547          binary_hno3 = 1244.69635941351_wp * rh**3 - 2613.93941099991_wp * rh**2 +                &
6548                        1525.0684974546_wp * rh -155.946764059316_wp
6549       ENDIF
6550!
6551!--    Contributions from other solutes
6552       full_complexity = 1
6553       IF ( hydrochloric_acid > 0.0_wp )  THEN   ! HCL
6554          IF ( full_complexity == 1  .OR.  rh < 0.4_wp )  THEN
6555             hcl_hno3 = 16.051_wp * rh**4 - 44.357_wp * rh**3 + 45.141_wp * rh**2 - 21.638_wp *    &
6556                        rh + 4.8182_wp
6557          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6558             hcl_hno3 = - 1.5833_wp * rh + 1.5569_wp
6559          ENDIF
6560       ENDIF
6561
6562       IF ( sulphuric_acid > 0.0_wp )  THEN   ! H2SO4
6563          IF ( full_complexity == 1  .OR.  rh < 0.4_wp )  THEN
6564             h2so4_hno3 = - 3.0849_wp * rh**3 + 5.9609_wp * rh**2 - 4.468_wp * rh + 1.5658_wp
6565          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6566             h2so4_hno3 = - 0.93473_wp * rh + 0.9363_wp
6567          ENDIF
6568       ENDIF
6569
6570       IF ( ammonium_sulphate > 0.0_wp )  THEN   ! NH42SO4
6571          nh42so4_hno3 = 16.821_wp * rh**3 - 28.391_wp * rh**2 + 18.133_wp * rh - 6.7356_wp
6572       ENDIF
6573
6574       IF ( ammonium_nitrate > 0.0_wp )  THEN   ! NH4NO3
6575          nh4no3_hno3 = 11.01_wp * rh**3 - 21.578_wp * rh**2 + 14.808_wp * rh - 4.2593_wp
6576       ENDIF
6577
6578       IF ( ammonium_chloride > 0.0_wp )  THEN   ! NH4Cl
6579          IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
6580             nh4cl_hno3 = - 1.176_wp * rh**3 + 5.0828_wp * rh**2 - 3.8792_wp * rh - 0.05518_wp
6581          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6582             nh4cl_hno3 = 2.6219_wp * rh**2 - 2.2609_wp * rh - 0.38436_wp
6583          ENDIF
6584       ENDIF
6585
6586       IF ( sodium_sulphate > 0.0_wp )  THEN   ! Na2SO4
6587          na2so4_hno3 = 35.504_wp * rh**4 - 80.101_wp * rh**3 + 67.326_wp * rh**2 - 28.461_wp *    &
6588                        rh + 5.6016_wp
6589       ENDIF
6590
6591       IF ( sodium_nitrate > 0.0_wp )  THEN   ! NaNO3
6592          IF ( full_complexity == 1 .OR. rh <= 0.4_wp ) THEN
6593             nano3_hno3 = 23.659_wp * rh**5 - 66.917_wp * rh**4 + 74.686_wp * rh**3 - 40.795_wp *  &
6594                          rh**2 + 10.831_wp * rh - 1.4701_wp
6595          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6596             nano3_hno3 = 14.749_wp * rh**4 - 35.237_wp * rh**3 + 31.196_wp * rh**2 - 12.076_wp *  &
6597                          rh + 1.3605_wp
6598          ENDIF
6599       ENDIF
6600
6601       IF ( sodium_chloride > 0.0_wp )  THEN   ! NaCl
6602          IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
6603             nacl_hno3 = 13.682_wp * rh**4 - 35.122_wp * rh**3 + 33.397_wp * rh**2 - 14.586_wp *   &
6604                         rh + 2.6276_wp
6605          ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6606             nacl_hno3 = 1.1882_wp * rh**3 - 1.1037_wp * rh**2 - 0.7642_wp * rh + 0.6671_wp
6607          ENDIF
6608       ENDIF
6609
6610       ln_hno3_act = binary_hno3 + hydrochloric_acid_eq_frac * hcl_hno3 +                          &
6611                     sulphuric_acid_eq_frac    * h2so4_hno3 +                                      &
6612                     ammonium_sulphate_eq_frac * nh42so4_hno3 +                                    &
6613                     ammonium_nitrate_eq_frac  * nh4no3_hno3 +                                     &
6614                     ammonium_chloride_eq_frac * nh4cl_hno3 +                                      &
6615                     sodium_sulphate_eq_frac * na2so4_hno3 +                                       &
6616                     sodium_nitrate_eq_frac * nano3_hno3 + sodium_chloride_eq_frac   * nacl_hno3
6617
6618       gamma_hno3   = EXP( ln_hno3_act )   ! Molal activity coefficient of HNO3
6619       gamma_out(1) = gamma_hno3
6620!
6621!--    Partial pressure calculation
6622!--    k_hno3 = 2.51 * ( 10**6 )
6623!--    k_hno3 = 2.628145923d6 !< calculated by AIM online (Clegg et al 1998) after Chameides (1984)
6624       k_hno3     = 2.6E6_wp * EXP( 8700.0_wp * henrys_temp_dep )
6625       press_hno3 = ( ions_mol(1) * ions_mol(6) * ( gamma_hno3**2 ) ) / k_hno3
6626    ENDIF
6627!
6628!-- b) - ACTIVITY COEFF/VAPOUR PRESSURE - NH3
6629!-- Follow the two solute approach of Zaveri et al. (2005)
6630    IF ( ions(2) > 0.0_wp  .AND.  ions_mol(1) > 0.0_wp )  THEN
6631!
6632!--    NH4HSO4:
6633       binary_nh4hso4 = 56.907_wp * rh**6 - 155.32_wp * rh**5 + 142.94_wp * rh**4 - 32.298_wp *    &
6634                        rh**3 - 27.936_wp * rh**2 + 19.502_wp * rh - 4.2618_wp
6635       IF ( nitric_acid > 0.0_wp)  THEN   ! HNO3
6636          hno3_nh4hso4 = 104.8369_wp * rh**8 - 288.8923_wp * rh**7 + 129.3445_wp * rh**6 +         &
6637                         373.0471_wp * rh**5 - 571.0385_wp * rh**4 + 326.3528_wp * rh**3 -         &
6638                         74.169_wp * rh**2 - 2.4999_wp * rh + 3.17_wp
6639       ENDIF
6640
6641       IF ( hydrochloric_acid > 0.0_wp)  THEN   ! HCL
6642          hcl_nh4hso4 = - 7.9133_wp * rh**8 + 126.6648_wp * rh**7 - 460.7425_wp * rh**6 +          &
6643                         731.606_wp * rh**5 - 582.7467_wp * rh**4 + 216.7197_wp * rh**3 -          &
6644                         11.3934_wp * rh**2 - 17.7728_wp  * rh + 5.75_wp
6645       ENDIF
6646
6647       IF ( sulphuric_acid > 0.0_wp)  THEN   ! H2SO4
6648          h2so4_nh4hso4 = 195.981_wp * rh**8 - 779.2067_wp * rh**7 + 1226.3647_wp * rh**6 -        &
6649                         964.0261_wp * rh**5 + 391.7911_wp * rh**4 - 84.1409_wp  * rh**3 +         &
6650                          20.0602_wp * rh**2 - 10.2663_wp  * rh + 3.5817_wp
6651       ENDIF
6652
6653       IF ( ammonium_sulphate > 0.0_wp)  THEN   ! NH42SO4
6654          nh42so4_nh4hso4 = 617.777_wp * rh**8 -  2547.427_wp * rh**7 + 4361.6009_wp * rh**6 -     &
6655                           4003.162_wp * rh**5 + 2117.8281_wp * rh**4 - 640.0678_wp * rh**3 +      &
6656                            98.0902_wp * rh**2 -    2.2615_wp * rh - 2.3811_wp
6657       ENDIF
6658
6659       IF ( ammonium_nitrate > 0.0_wp)  THEN   ! NH4NO3
6660          nh4no3_nh4hso4 = - 104.4504_wp * rh**8 + 539.5921_wp * rh**7 - 1157.0498_wp * rh**6 +    &
6661                            1322.4507_wp * rh**5 - 852.2475_wp * rh**4 + 298.3734_wp * rh**3 -     &
6662                              47.0309_wp * rh**2 +    1.297_wp * rh - 0.8029_wp
6663       ENDIF
6664
6665       IF ( ammonium_chloride > 0.0_wp)  THEN   ! NH4Cl
6666          nh4cl_nh4hso4 = 258.1792_wp * rh**8 - 1019.3777_wp * rh**7 + 1592.8918_wp * rh**6 -      &
6667                         1221.0726_wp * rh**5 +  442.2548_wp * rh**4 -   43.6278_wp * rh**3 -      &
6668                            7.5282_wp * rh**2 -    3.8459_wp * rh + 2.2728_wp
6669       ENDIF
6670
6671       IF ( sodium_sulphate > 0.0_wp)  THEN   ! Na2SO4
6672          na2so4_nh4hso4 = 225.4238_wp * rh**8 - 732.4113_wp * rh**7 + 843.7291_wp * rh**6 -       &
6673                           322.7328_wp * rh**5 -  88.6252_wp * rh**4 +  72.4434_wp * rh**3 +       &
6674                            22.9252_wp * rh**2 -  25.3954_wp * rh + 4.6971_wp
6675       ENDIF
6676
6677       IF ( sodium_nitrate > 0.0_wp)  THEN   ! NaNO3
6678          nano3_nh4hso4 = 96.1348_wp * rh**8 - 341.6738_wp * rh**7 + 406.5314_wp * rh**6 -         &
6679                          98.5777_wp * rh**5 - 172.8286_wp * rh**4 + 149.3151_wp * rh**3 -         &
6680                          38.9998_wp * rh**2 -   0.2251_wp * rh + 0.4953_wp
6681       ENDIF
6682
6683       IF ( sodium_chloride > 0.0_wp)  THEN   ! NaCl
6684          nacl_nh4hso4 = 91.7856_wp * rh**8 - 316.6773_wp * rh**7 + 358.2703_wp * rh**6 -          &
6685                         68.9142_wp * rh**5 - 156.5031_wp * rh**4 + 116.9592_wp * rh**3 -          &
6686                         22.5271_wp * rh**2 - 3.7716_wp * rh + 1.56_wp
6687       ENDIF
6688
6689       ln_nh4hso4_act = binary_nh4hso4 + nitric_acid_eq_frac * hno3_nh4hso4 +                      &
6690                        hydrochloric_acid_eq_frac * hcl_nh4hso4 +                                  &
6691                        sulphuric_acid_eq_frac * h2so4_nh4hso4 +                                   &
6692                        ammonium_sulphate_eq_frac * nh42so4_nh4hso4 +                              &
6693                        ammonium_nitrate_eq_frac * nh4no3_nh4hso4 +                                &
6694                        ammonium_chloride_eq_frac * nh4cl_nh4hso4 +                                &
6695                        sodium_sulphate_eq_frac * na2so4_nh4hso4 +                                 &
6696                        sodium_nitrate_eq_frac * nano3_nh4hso4 +                                   &
6697                        sodium_chloride_eq_frac * nacl_nh4hso4
6698
6699       gamma_nh4hso4 = EXP( ln_nh4hso4_act ) ! molal act. coefficient of NH4HSO4
6700!
6701!--    Molal activity coefficient of NO3-
6702       gamma_out(6)  = gamma_nh4hso4
6703!
6704!--    Molal activity coefficient of NH4+
6705       gamma_nh3     = gamma_nh4hso4**2 / gamma_hhso4**2
6706       gamma_out(3)  = gamma_nh3
6707!
6708!--    This actually represents the ratio of the ammonium to hydrogen ion activity coefficients
6709!--    (see Zaveri paper) - multiply this by the ratio of the ammonium to hydrogen ion molality and
6710!--    the ratio of appropriate equilibrium constants
6711!
6712!--    Equilibrium constants
6713!--    k_h = 57.64d0    ! Zaveri et al. (2005)
6714       k_h = 5.8E1_wp * EXP( 4085.0_wp * henrys_temp_dep )   ! after Chameides (1984)
6715!--    k_nh4 = 1.81E-5_wp    ! Zaveri et al. (2005)
6716       k_nh4 = 1.7E-5_wp * EXP( -4325.0_wp * henrys_temp_dep )   ! Chameides (1984)
6717!--    k_h2o = 1.01E-14_wp    ! Zaveri et al (2005)
6718       k_h2o = 1.E-14_wp * EXP( -6716.0_wp * henrys_temp_dep )   ! Chameides (1984)
6719!
6720       molality_ratio_nh3 = ions_mol(2) / ions_mol(1)
6721!
6722!--    Partial pressure calculation
6723       press_nh3 = molality_ratio_nh3 * gamma_nh3 * ( k_h2o / ( k_h * k_nh4 ) )
6724
6725    ENDIF
6726!
6727!-- c) - ACTIVITY COEFF/VAPOUR PRESSURE - HCL
6728    IF ( ions(1) > 0.0_wp  .AND.  ions(7) > 0.0_wp )  THEN
6729       binary_case = 1
6730       IF ( rh > 0.1_wp  .AND.  rh < 0.98 )  THEN
6731          IF ( binary_case == 1 )  THEN
6732             binary_hcl = - 5.0179_wp * rh**3 + 9.8816_wp * rh**2 - 10.789_wp * rh + 5.4737_wp
6733          ELSEIF ( binary_case == 2 )  THEN
6734             binary_hcl = - 4.6221_wp * rh + 4.2633_wp
6735          ENDIF
6736       ELSEIF ( rh >= 0.98_wp  .AND.  rh < 0.9999_wp )  THEN
6737          binary_hcl = 775.6111008626_wp * rh**3 - 2146.01320888771_wp * rh**2 +                   &
6738                       1969.01979670259_wp *  rh - 598.878230033926_wp
6739       ENDIF
6740    ENDIF
6741
6742    IF ( nitric_acid > 0.0_wp )  THEN   ! HNO3
6743       IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
6744          hno3_hcl = 9.6256_wp * rh**4 - 26.507_wp * rh**3 + 27.622_wp * rh**2 - 12.958_wp * rh +  &
6745                     2.2193_wp
6746       ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6747          hno3_hcl = 1.3242_wp * rh**2 - 1.8827_wp * rh + 0.55706_wp
6748       ENDIF
6749    ENDIF
6750
6751    IF ( sulphuric_acid > 0.0_wp )  THEN   ! H2SO4
6752       IF ( full_complexity == 1  .OR.  rh <= 0.4 )  THEN
6753          h2so4_hcl = 1.4406_wp * rh**3 - 2.7132_wp * rh**2 + 1.014_wp * rh + 0.25226_wp
6754       ELSEIF ( full_complexity == 0 .AND. rh > 0.4_wp ) THEN
6755          h2so4_hcl = 0.30993_wp * rh**2 - 0.99171_wp * rh + 0.66913_wp
6756       ENDIF
6757    ENDIF
6758
6759    IF ( ammonium_sulphate > 0.0_wp )  THEN   ! NH42SO4
6760       nh42so4_hcl = 22.071_wp * rh**3 - 40.678_wp * rh**2 + 27.893_wp * rh - 9.4338_wp
6761    ENDIF
6762
6763    IF ( ammonium_nitrate > 0.0_wp )  THEN   ! NH4NO3
6764       nh4no3_hcl = 19.935_wp * rh**3 - 42.335_wp * rh**2 + 31.275_wp * rh - 8.8675_wp
6765    ENDIF
6766
6767    IF ( ammonium_chloride > 0.0_wp )  THEN   ! NH4Cl
6768       IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
6769          nh4cl_hcl = 2.8048_wp * rh**3 - 4.3182_wp * rh**2 + 3.1971_wp * rh - 1.6824_wp
6770       ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6771          nh4cl_hcl = 1.2304_wp * rh**2 - 0.18262_wp * rh - 1.0643_wp
6772       ENDIF
6773    ENDIF
6774
6775    IF ( sodium_sulphate > 0.0_wp )  THEN   ! Na2SO4
6776       na2so4_hcl = 36.104_wp * rh**4 - 78.658_wp * rh**3 + 63.441_wp * rh**2 - 26.727_wp * rh +   &
6777                    5.7007_wp
6778    ENDIF
6779
6780    IF ( sodium_nitrate > 0.0_wp )  THEN   ! NaNO3
6781       IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
6782          nano3_hcl = 54.471_wp * rh**5 - 159.42_wp * rh**4 + 180.25_wp * rh**3 - 98.176_wp * rh**2&
6783                      + 25.309_wp * rh - 2.4275_wp
6784       ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6785          nano3_hcl = 21.632_wp * rh**4 - 53.088_wp * rh**3 + 47.285_wp * rh**2 - 18.519_wp * rh   &
6786                      + 2.6846_wp
6787       ENDIF
6788    ENDIF
6789
6790    IF ( sodium_chloride > 0.0_wp )  THEN   ! NaCl
6791       IF ( full_complexity == 1  .OR.  rh <= 0.4_wp )  THEN
6792          nacl_hcl = 5.4138_wp * rh**4 - 12.079_wp * rh**3 + 9.627_wp * rh**2 - 3.3164_wp * rh +   &
6793                     0.35224_wp
6794       ELSEIF ( full_complexity == 0  .AND.  rh > 0.4_wp )  THEN
6795          nacl_hcl = 2.432_wp * rh**3 - 4.3453_wp * rh**2 + 2.3834_wp * rh - 0.4762_wp
6796       ENDIF
6797    ENDIF
6798
6799    ln_HCL_act = binary_hcl + nitric_acid_eq_frac * hno3_hcl + sulphuric_acid_eq_frac * h2so4_hcl +&
6800                 ammonium_sulphate_eq_frac * nh42so4_hcl + ammonium_nitrate_eq_frac * nh4no3_hcl + &
6801                 ammonium_chloride_eq_frac * nh4cl_hcl + sodium_sulphate_eq_frac * na2so4_hcl +    &
6802                 sodium_nitrate_eq_frac    * nano3_hcl + sodium_chloride_eq_frac   * nacl_hcl
6803
6804     gamma_hcl    = EXP( ln_HCL_act )   ! Molal activity coefficient
6805     gamma_out(2) = gamma_hcl
6806!
6807!--  Equilibrium constant after Wagman et al. (1982) (and NIST database)
6808     k_hcl = 2E6_wp * EXP( 9000.0_wp * henrys_temp_dep )
6809
6810     press_hcl = ( ions_mol(1) * ions_mol(7) * gamma_hcl**2 ) / k_hcl
6811!
6812!-- 5) Ion molility output
6813    mols_out = ions_mol
6814
6815 END SUBROUTINE inorganic_pdfite
6816
6817!------------------------------------------------------------------------------!
6818! Description:
6819! ------------
6820!> Update the particle size distribution. Put particles into corrects bins.
6821!>
6822!> Moving-centre method assumed, i.e. particles are allowed to grow to their
6823!> exact size as long as they are not crossing the fixed diameter bin limits.
6824!> If the particles in a size bin cross the lower or upper diameter limit, they
6825!> are all moved to the adjacent diameter bin and their volume is averaged with
6826!> the particles in the new bin, which then get a new diameter.
6827!
6828!> Moving-centre method minimises numerical diffusion.
6829!------------------------------------------------------------------------------!
6830 SUBROUTINE distr_update( paero )
6831
6832    IMPLICIT NONE
6833
6834    INTEGER(iwp) ::  ib      !< loop index
6835    INTEGER(iwp) ::  mm      !< loop index
6836    INTEGER(iwp) ::  counti  !< number of while loops
6837
6838    LOGICAL  ::  within_bins !< logical (particle belongs to the bin?)
6839
6840    REAL(wp) ::  znfrac  !< number fraction to be moved to the larger bin
6841    REAL(wp) ::  zvfrac  !< volume fraction to be moved to the larger bin
6842    REAL(wp) ::  zVexc   !< Volume in the grown bin which exceeds the bin upper limit
6843    REAL(wp) ::  zVihi   !< particle volume at the high end of the bin
6844    REAL(wp) ::  zVilo   !< particle volume at the low end of the bin
6845    REAL(wp) ::  zvpart  !< particle volume (m3)
6846    REAL(wp) ::  zVrat   !< volume ratio of a size bin
6847
6848    TYPE(t_section), DIMENSION(nbins_aerosol), INTENT(inout) ::  paero !< aerosol properties
6849
6850    zvpart      = 0.0_wp
6851    zvfrac      = 0.0_wp
6852    within_bins = .FALSE.
6853!
6854!-- Check if the volume of the bin is within bin limits after update
6855    counti = 0
6856    DO  WHILE ( .NOT. within_bins )
6857       within_bins = .TRUE.
6858!
6859!--    Loop from larger to smaller size bins
6860       DO  ib = end_subrange_2b-1, start_subrange_1a, -1
6861          mm = 0
6862          IF ( paero(ib)%numc > nclim )  THEN
6863             zvpart = 0.0_wp
6864             zvfrac = 0.0_wp
6865
6866             IF ( ib == end_subrange_2a )  CYCLE
6867!
6868!--          Dry volume
6869             zvpart = SUM( paero(ib)%volc(1:7) ) / paero(ib)%numc
6870!
6871!--          Smallest bin cannot decrease
6872             IF ( paero(ib)%vlolim > zvpart  .AND.  ib == start_subrange_1a ) CYCLE
6873!
6874!--          Decreasing bins
6875             IF ( paero(ib)%vlolim > zvpart )  THEN
6876                mm = ib - 1
6877                IF ( ib == start_subrange_2b )  mm = end_subrange_1a    ! 2b goes to 1a
6878
6879                paero(mm)%numc = paero(mm)%numc + paero(ib)%numc
6880                paero(ib)%numc = 0.0_wp
6881                paero(mm)%volc(:) = paero(mm)%volc(:) + paero(ib)%volc(:)
6882                paero(ib)%volc(:) = 0.0_wp
6883                CYCLE
6884             ENDIF
6885!
6886!--          If size bin has not grown, cycle.
6887!--          Changed by Mona: compare to the arithmetic mean volume, as done originally. Now
6888!--          particle volume is derived from the geometric mean diameter, not arithmetic (see
6889!--          SUBROUTINE set_sizebins).
6890             IF ( zvpart <= api6 * ( ( aero(ib)%vhilim + aero(ib)%vlolim ) / ( 2.0_wp * api6 ) ) ) &
6891             CYCLE
6892!
6893!--          Avoid precision problems
6894             IF ( ABS( zvpart - api6 * paero(ib)%dmid**3 ) < 1.0E-35_wp )  CYCLE
6895!
6896!--          Volume ratio of the size bin
6897             zVrat = paero(ib)%vhilim / paero(ib)%vlolim
6898!
6899!--          Particle volume at the low end of the bin
6900             zVilo = 2.0_wp * zvpart / ( 1.0_wp + zVrat )
6901!
6902!--          Particle volume at the high end of the bin
6903             zVihi = zVrat * zVilo
6904!
6905!--          Volume in the grown bin which exceeds the bin upper limit
6906             zVexc = 0.5_wp * ( zVihi + paero(ib)%vhilim )
6907!
6908!--          Number fraction to be moved to the larger bin
6909             znfrac = MIN( 1.0_wp, ( zVihi - paero(ib)%vhilim) / ( zVihi - zVilo ) )
6910!
6911!--          Volume fraction to be moved to the larger bin
6912             zvfrac = MIN( 0.99_wp, znfrac * zVexc / zvpart )
6913             IF ( zvfrac < 0.0_wp )  THEN
6914                message_string = 'Error: zvfrac < 0'
6915                CALL message( 'salsa_mod: distr_update', 'PA0624', 1, 2, 0, 6, 0 )
6916             ENDIF
6917!
6918!--          Update bin
6919             mm = ib + 1
6920!
6921!--          Volume (cm3/cm3)
6922             paero(mm)%volc(:) = paero(mm)%volc(:) + znfrac * paero(ib)%numc * zVexc *             &
6923                                 paero(ib)%volc(:) / SUM( paero(ib)%volc(:) )
6924             paero(ib)%volc(:) = paero(ib)%volc(:) - znfrac * paero(ib)%numc * zVexc *             &
6925                                 paero(ib)%volc(:) / SUM( paero(ib)%volc(:) )
6926
6927!--          Number concentration (#/m3)
6928             paero(mm)%numc = paero(mm)%numc + znfrac * paero(ib)%numc
6929             paero(ib)%numc = paero(ib)%numc * ( 1.0_wp - znfrac )
6930
6931          ENDIF     ! nclim
6932
6933          IF ( paero(ib)%numc > nclim )   THEN
6934             zvpart = SUM( paero(ib)%volc(:) ) / paero(ib)%numc
6935             within_bins = ( paero(ib)%vlolim < zvpart  .AND. zvpart < paero(ib)%vhilim )
6936          ENDIF
6937
6938       ENDDO ! - ib
6939
6940       counti = counti + 1
6941       IF ( counti > 100 )  THEN
6942          message_string = 'Error: Aerosol bin update not converged'
6943          CALL message( 'salsa_mod: distr_update', 'PA0625', 1, 2, 0, 6, 0 )
6944       ENDIF
6945
6946    ENDDO ! - within bins
6947
6948 END SUBROUTINE distr_update
6949
6950!------------------------------------------------------------------------------!
6951! Description:
6952! ------------
6953!> salsa_diagnostics: Update properties for the current timestep:
6954!>
6955!> Juha Tonttila, FMI, 2014
6956!> Tomi Raatikainen, FMI, 2016
6957!------------------------------------------------------------------------------!
6958 SUBROUTINE salsa_diagnostics( i, j )
6959
6960    USE cpulog,                                                                &
6961        ONLY:  cpu_log, log_point_s
6962
6963    IMPLICIT NONE
6964
6965    INTEGER(iwp) ::  ib   !<
6966    INTEGER(iwp) ::  ic   !<
6967    INTEGER(iwp) ::  icc  !<
6968    INTEGER(iwp) ::  ig   !<
6969    INTEGER(iwp) ::  k    !<
6970
6971    INTEGER(iwp), INTENT(in) ::  i  !<
6972    INTEGER(iwp), INTENT(in) ::  j  !<
6973
6974    REAL(wp), DIMENSION(nzb:nzt+1) ::  flag          !< flag to mask topography
6975    REAL(wp), DIMENSION(nzb:nzt+1) ::  flag_zddry    !< flag to mask zddry
6976    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_adn        !< air density (kg/m3)
6977    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_p          !< pressure
6978    REAL(wp), DIMENSION(nzb:nzt+1) ::  in_t          !< temperature (K)
6979    REAL(wp), DIMENSION(nzb:nzt+1) ::  mcsum         !< sum of mass concentration
6980    REAL(wp), DIMENSION(nzb:nzt+1) ::  ppm_to_nconc  !< Conversion factor: ppm to #/m3
6981    REAL(wp), DIMENSION(nzb:nzt+1) ::  zddry         !< particle dry diameter
6982    REAL(wp), DIMENSION(nzb:nzt+1) ::  zvol          !< particle volume
6983
6984    flag_zddry   = 0.0_wp
6985    in_adn       = 0.0_wp
6986    in_p         = 0.0_wp
6987    in_t         = 0.0_wp
6988    ppm_to_nconc = 1.0_wp
6989    zddry        = 0.0_wp
6990    zvol         = 0.0_wp
6991
6992    CALL cpu_log( log_point_s(94), 'salsa diagnostics ', 'start' )
6993!
6994!-- Calculate thermodynamic quantities needed in SALSA
6995    CALL salsa_thrm_ij( i, j, p_ij=in_p, temp_ij=in_t, adn_ij=in_adn )
6996!
6997!-- Calculate conversion factors for gas concentrations
6998    ppm_to_nconc = for_ppm_to_nconc * in_p / in_t
6999!
7000!-- Predetermine flag to mask topography
7001    flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(:,j,i), 0 ) )
7002
7003    DO  ib = 1, nbins_aerosol   ! aerosol size bins
7004!
7005!--    Remove negative values
7006       aerosol_number(ib)%conc(:,j,i) = MAX( nclim, aerosol_number(ib)%conc(:,j,i) ) * flag
7007!
7008!--    Calculate total mass concentration per bin
7009       mcsum = 0.0_wp
7010       DO  ic = 1, ncomponents_mass
7011          icc = ( ic - 1 ) * nbins_aerosol + ib
7012          mcsum = mcsum + aerosol_mass(icc)%conc(:,j,i) * flag
7013       ENDDO
7014!
7015!--    Check that number and mass concentration match qualitatively
7016       IF ( ANY ( aerosol_number(ib)%conc(:,j,i) > nclim  .AND. mcsum <= 0.0_wp ) )  THEN
7017          DO  k = nzb+1, nzt
7018             IF ( aerosol_number(ib)%conc(k,j,i) > nclim  .AND. mcsum(k) <= 0.0_wp )  THEN
7019                aerosol_number(ib)%conc(k,j,i) = nclim * flag(k)
7020                DO  ic = 1, ncomponents_mass
7021                   icc = ( ic - 1 ) * nbins_aerosol + ib
7022                   aerosol_mass(icc)%conc(k,j,i) = mclim * flag(k)
7023                ENDDO
7024             ENDIF
7025          ENDDO
7026       ENDIF
7027!
7028!--    Update aerosol particle radius
7029       CALL bin_mixrat( 'dry', ib, i, j, zvol )
7030       zvol = zvol / arhoh2so4    ! Why on sulphate?
7031!
7032!--    Particles smaller then 0.1 nm diameter are set to zero
7033       zddry = ( zvol / MAX( nclim, aerosol_number(ib)%conc(:,j,i) ) / api6 )**0.33333333_wp
7034       flag_zddry = MERGE( 1.0_wp, 0.0_wp, ( zddry < 1.0E-10_wp  .AND.                             &
7035                           aerosol_number(ib)%conc(:,j,i) > nclim ) )
7036!
7037!--    Volatile species to the gas phase
7038       IF ( index_so4 > 0 .AND. lscndgas )  THEN
7039          ic = ( index_so4 - 1 ) * nbins_aerosol + ib
7040          IF ( salsa_gases_from_chem )  THEN
7041             ig = gas_index_chem(1)
7042             chem_species(ig)%conc(:,j,i) = chem_species(ig)%conc(:,j,i) +                         &
7043                                            aerosol_mass(ic)%conc(:,j,i) * avo * flag_zddry /      &
7044                                            ( amh2so4 * ppm_to_nconc ) * flag
7045          ELSE
7046             salsa_gas(1)%conc(:,j,i) = salsa_gas(1)%conc(:,j,i) + aerosol_mass(ic)%conc(:,j,i) /  &
7047                                        amh2so4 * avo * flag_zddry * flag
7048          ENDIF
7049       ENDIF
7050       IF ( index_oc > 0  .AND.  lscndgas )  THEN
7051          ic = ( index_oc - 1 ) * nbins_aerosol + ib
7052          IF ( salsa_gases_from_chem )  THEN
7053             ig = gas_index_chem(5)
7054             chem_species(ig)%conc(:,j,i) = chem_species(ig)%conc(:,j,i) +                         &
7055                                            aerosol_mass(ic)%conc(:,j,i) * avo * flag_zddry /      &
7056                                            ( amoc * ppm_to_nconc ) * flag
7057          ELSE
7058             salsa_gas(5)%conc(:,j,i) = salsa_gas(5)%conc(:,j,i) + aerosol_mass(ic)%conc(:,j,i) /  &
7059                                        amoc * avo * flag_zddry * flag
7060          ENDIF
7061       ENDIF
7062       IF ( index_no > 0  .AND.  lscndgas )  THEN
7063          ic = ( index_no - 1 ) * nbins_aerosol + ib
7064          IF ( salsa_gases_from_chem )  THEN
7065             ig = gas_index_chem(2)
7066             chem_species(ig)%conc(:,j,i) = chem_species(ig)%conc(:,j,i) +                         &
7067                                            aerosol_mass(ic)%conc(:,j,i) * avo * flag_zddry /      &
7068                                            ( amhno3 * ppm_to_nconc ) *flag
7069          ELSE
7070             salsa_gas(2)%conc(:,j,i) = salsa_gas(2)%conc(:,j,i) + aerosol_mass(ic)%conc(:,j,i) /  &
7071                                        amhno3 * avo * flag_zddry * flag
7072          ENDIF
7073       ENDIF
7074       IF ( index_nh > 0  .AND.  lscndgas )  THEN
7075          ic = ( index_nh - 1 ) * nbins_aerosol + ib
7076          IF ( salsa_gases_from_chem )  THEN
7077             ig = gas_index_chem(3)
7078             chem_species(ig)%conc(:,j,i) = chem_species(ig)%conc(:,j,i) +                         &
7079                                            aerosol_mass(ic)%conc(:,j,i) * avo * flag_zddry /      &
7080                                            ( amnh3 * ppm_to_nconc ) *flag
7081          ELSE
7082             salsa_gas(3)%conc(:,j,i) = salsa_gas(3)%conc(:,j,i) + aerosol_mass(ic)%conc(:,j,i) /  &
7083                                        amnh3 * avo * flag_zddry *flag
7084          ENDIF
7085       ENDIF
7086!
7087!--    Mass and number to zero (insoluble species and water are lost)
7088       DO  ic = 1, ncomponents_mass
7089          icc = ( ic - 1 ) * nbins_aerosol + ib
7090          aerosol_mass(icc)%conc(:,j,i) = MERGE( mclim * flag, aerosol_mass(icc)%conc(:,j,i),      &
7091                                                 flag_zddry > 0.0_wp )
7092       ENDDO
7093       aerosol_number(ib)%conc(:,j,i) = MERGE( nclim, aerosol_number(ib)%conc(:,j,i),              &
7094                                               flag_zddry > 0.0_wp )
7095       ra_dry(:,j,i,ib) = MAX( 1.0E-10_wp, 0.5_wp * zddry )
7096
7097    ENDDO
7098    IF ( .NOT. salsa_gases_from_chem )  THEN
7099       DO  ig = 1, ngases_salsa
7100          salsa_gas(ig)%conc(:,j,i) = MAX( nclim, salsa_gas(ig)%conc(:,j,i) ) * flag
7101       ENDDO
7102    ENDIF
7103
7104    CALL cpu_log( log_point_s(94), 'salsa diagnostics ', 'stop' )
7105
7106 END SUBROUTINE salsa_diagnostics
7107
7108
7109!------------------------------------------------------------------------------!
7110! Description:
7111! ------------
7112!> Call for all grid points
7113!------------------------------------------------------------------------------!
7114 SUBROUTINE salsa_actions( location )
7115
7116
7117    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
7118
7119    SELECT CASE ( location )
7120
7121       CASE ( 'before_timestep' )
7122
7123          IF ( ws_scheme_sca )  sums_salsa_ws_l = 0.0_wp
7124
7125       CASE DEFAULT
7126          CONTINUE
7127
7128    END SELECT
7129
7130 END SUBROUTINE salsa_actions
7131
7132
7133!------------------------------------------------------------------------------!
7134! Description:
7135! ------------
7136!> Call for grid points i,j
7137!------------------------------------------------------------------------------!
7138
7139 SUBROUTINE salsa_actions_ij( i, j, location )
7140
7141
7142    INTEGER(iwp),      INTENT(IN) ::  i         !< grid index in x-direction
7143    INTEGER(iwp),      INTENT(IN) ::  j         !< grid index in y-direction
7144    CHARACTER (LEN=*), INTENT(IN) ::  location  !< call location string
7145    INTEGER(iwp)  ::  dummy  !< call location string
7146
7147    IF ( salsa    )   dummy = i + j
7148
7149    SELECT CASE ( location )
7150
7151       CASE ( 'before_timestep' )
7152
7153          IF ( ws_scheme_sca )  sums_salsa_ws_l = 0.0_wp
7154
7155       CASE DEFAULT
7156          CONTINUE
7157
7158    END SELECT
7159
7160
7161 END SUBROUTINE salsa_actions_ij
7162
7163!
7164!------------------------------------------------------------------------------!
7165! Description:
7166! ------------
7167!> Calculate the prognostic equation for aerosol number and mass, and gas
7168!> concentrations. Cache-optimized.
7169!------------------------------------------------------------------------------!
7170 SUBROUTINE salsa_prognostic_equations_ij( i, j, i_omp_start, tn )
7171
7172    USE control_parameters,                                                                        &
7173        ONLY:  time_since_reference_point
7174
7175    IMPLICIT NONE
7176
7177    INTEGER(iwp) ::  i            !<
7178    INTEGER(iwp) ::  i_omp_start  !<
7179    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
7180    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
7181    INTEGER(iwp) ::  icc          !< (c-1)*nbins_aerosol+b
7182    INTEGER(iwp) ::  ig           !< loop index for salsa gases
7183    INTEGER(iwp) ::  j            !<
7184    INTEGER(iwp) ::  tn           !<
7185
7186    LOGICAL ::  sedim  !< calculate sedimentation only for aerosols (number and mass)
7187
7188    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
7189!
7190!--    Aerosol number
7191       DO  ib = 1, nbins_aerosol
7192          sums_salsa_ws_l = aerosol_number(ib)%sums_ws_l
7193          CALL salsa_tendency( 'aerosol_number', aerosol_number(ib)%conc_p, aerosol_number(ib)%conc,&
7194                               aerosol_number(ib)%tconc_m, i, j, i_omp_start, tn, ib, ib,          &
7195                               aerosol_number(ib)%flux_s, aerosol_number(ib)%diss_s,               &
7196                               aerosol_number(ib)%flux_l, aerosol_number(ib)%diss_l,               &
7197                               aerosol_number(ib)%init, sedim )
7198          aerosol_number(ib)%sums_ws_l = sums_salsa_ws_l
7199!
7200!--       Aerosol mass
7201          DO  ic = 1, ncomponents_mass
7202             icc = ( ic - 1 ) * nbins_aerosol + ib
7203             sums_salsa_ws_l = aerosol_mass(icc)%sums_ws_l
7204             CALL salsa_tendency( 'aerosol_mass', aerosol_mass(icc)%conc_p, aerosol_mass(icc)%conc,&
7205                                  aerosol_mass(icc)%tconc_m, i, j, i_omp_start, tn, ib, ic,        &
7206                                  aerosol_mass(icc)%flux_s, aerosol_mass(icc)%diss_s,              &
7207                                  aerosol_mass(icc)%flux_l, aerosol_mass(icc)%diss_l,              &
7208                                  aerosol_mass(icc)%init, sedim )
7209             aerosol_mass(icc)%sums_ws_l = sums_salsa_ws_l
7210
7211          ENDDO  ! ic
7212       ENDDO  ! ib
7213!
7214!--    Gases
7215       IF ( .NOT. salsa_gases_from_chem )  THEN
7216
7217          DO  ig = 1, ngases_salsa
7218             sums_salsa_ws_l = salsa_gas(ig)%sums_ws_l
7219             CALL salsa_tendency( 'salsa_gas', salsa_gas(ig)%conc_p, salsa_gas(ig)%conc,           &
7220                                  salsa_gas(ig)%tconc_m, i, j, i_omp_start, tn, ig, ig,            &
7221                                  salsa_gas(ig)%flux_s, salsa_gas(ig)%diss_s, salsa_gas(ig)%flux_l,&
7222                                  salsa_gas(ig)%diss_l, salsa_gas(ig)%init, sedim )
7223             salsa_gas(ig)%sums_ws_l = sums_salsa_ws_l
7224
7225          ENDDO  ! ig
7226
7227       ENDIF
7228
7229    ENDIF
7230
7231 END SUBROUTINE salsa_prognostic_equations_ij
7232!
7233!------------------------------------------------------------------------------!
7234! Description:
7235! ------------
7236!> Calculate the prognostic equation for aerosol number and mass, and gas
7237!> concentrations. Cache-optimized.
7238!------------------------------------------------------------------------------!
7239 SUBROUTINE salsa_prognostic_equations()
7240
7241    USE control_parameters,                                                                        &
7242        ONLY:  time_since_reference_point
7243
7244    IMPLICIT NONE
7245
7246    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
7247    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
7248    INTEGER(iwp) ::  icc          !< (c-1)*nbins_aerosol+b
7249    INTEGER(iwp) ::  ig           !< loop index for salsa gases
7250
7251    LOGICAL ::  sedim  !< calculate sedimentation only for aerosols (number and mass)
7252
7253    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
7254!
7255!--    Aerosol number
7256       DO  ib = 1, nbins_aerosol
7257          sums_salsa_ws_l = aerosol_number(ib)%sums_ws_l
7258          CALL salsa_tendency( 'aerosol_number', aerosol_number(ib)%conc_p, aerosol_number(ib)%conc,&
7259                               aerosol_number(ib)%tconc_m, ib, ib, aerosol_number(ib)%init, sedim )
7260          aerosol_number(ib)%sums_ws_l = sums_salsa_ws_l
7261!
7262!--       Aerosol mass
7263          DO  ic = 1, ncomponents_mass
7264             icc = ( ic - 1 ) * nbins_aerosol + ib
7265             sums_salsa_ws_l = aerosol_mass(icc)%sums_ws_l
7266             CALL salsa_tendency( 'aerosol_mass', aerosol_mass(icc)%conc_p, aerosol_mass(icc)%conc,&
7267                                  aerosol_mass(icc)%tconc_m, ib, ic, aerosol_mass(icc)%init, sedim )
7268             aerosol_mass(icc)%sums_ws_l = sums_salsa_ws_l
7269
7270          ENDDO  ! ic
7271       ENDDO  ! ib
7272!
7273!--    Gases
7274       IF ( .NOT. salsa_gases_from_chem )  THEN
7275
7276          DO  ig = 1, ngases_salsa
7277             sums_salsa_ws_l = salsa_gas(ig)%sums_ws_l
7278             CALL salsa_tendency( 'salsa_gas', salsa_gas(ig)%conc_p, salsa_gas(ig)%conc,           &
7279                                  salsa_gas(ig)%tconc_m, ig, ig, salsa_gas(ig)%init, sedim )
7280             salsa_gas(ig)%sums_ws_l = sums_salsa_ws_l
7281
7282          ENDDO  ! ig
7283
7284       ENDIF
7285
7286    ENDIF
7287
7288 END SUBROUTINE salsa_prognostic_equations
7289!
7290!------------------------------------------------------------------------------!
7291! Description:
7292! ------------
7293!> Tendencies for aerosol number and mass and gas concentrations.
7294!> Cache-optimized.
7295!------------------------------------------------------------------------------!
7296 SUBROUTINE salsa_tendency_ij( id, rs_p, rs, trs_m, i, j, i_omp_start, tn, ib, ic, flux_s, diss_s, &
7297                               flux_l, diss_l, rs_init, do_sedimentation )
7298
7299    USE advec_ws,                                                                                  &
7300        ONLY:  advec_s_ws
7301
7302    USE advec_s_pw_mod,                                                                            &
7303        ONLY:  advec_s_pw
7304
7305    USE advec_s_up_mod,                                                                            &
7306        ONLY:  advec_s_up
7307
7308    USE arrays_3d,                                                                                 &
7309        ONLY:  ddzu, rdf_sc, tend
7310
7311    USE diffusion_s_mod,                                                                           &
7312        ONLY:  diffusion_s
7313
7314    USE indices,                                                                                   &
7315        ONLY:  wall_flags_0
7316
7317    USE pegrid,                                                                                    &
7318        ONLY:  threads_per_task
7319
7320    USE surface_mod,                                                                               &
7321        ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
7322
7323    IMPLICIT NONE
7324
7325    CHARACTER(LEN = *) ::  id  !<
7326
7327    INTEGER(iwp) ::  i            !<
7328    INTEGER(iwp) ::  i_omp_start  !<
7329    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
7330    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
7331    INTEGER(iwp) ::  icc          !< (c-1)*nbins_aerosol+b
7332    INTEGER(iwp) ::  j            !<
7333    INTEGER(iwp) ::  k            !<
7334    INTEGER(iwp) ::  tn           !<
7335
7336    LOGICAL ::  do_sedimentation  !<
7337
7338    REAL(wp), DIMENSION(nzb:nzt+1) ::  rs_init  !<
7339
7340    REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  diss_s  !<
7341    REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  flux_s  !<
7342
7343    REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  diss_l  !<
7344    REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  flux_l  !<
7345
7346    REAL(wp), DIMENSION(:,:,:), POINTER ::  rs_p    !<
7347    REAL(wp), DIMENSION(:,:,:), POINTER ::  rs      !<
7348    REAL(wp), DIMENSION(:,:,:), POINTER ::  trs_m   !<
7349
7350    icc = ( ic - 1 ) * nbins_aerosol + ib
7351!
7352!-- Tendency-terms for reactive scalar
7353    tend(:,j,i) = 0.0_wp
7354!
7355!-- Advection terms
7356    IF ( timestep_scheme(1:5) == 'runge' )  THEN
7357       IF ( ws_scheme_sca )  THEN
7358          CALL advec_s_ws( i, j, rs, id, flux_s, diss_s, flux_l, diss_l, i_omp_start, tn )
7359       ELSE
7360          CALL advec_s_pw( i, j, rs )
7361       ENDIF
7362    ELSE
7363       CALL advec_s_up( i, j, rs )
7364    ENDIF
7365!
7366!-- Diffusion terms
7367    SELECT CASE ( id )
7368       CASE ( 'aerosol_number' )
7369          CALL diffusion_s( i, j, rs, surf_def_h(0)%answs(:,ib),                                   &
7370                                      surf_def_h(1)%answs(:,ib), surf_def_h(2)%answs(:,ib),        &
7371                                      surf_lsm_h%answs(:,ib),    surf_usm_h%answs(:,ib),           &
7372                                      surf_def_v(0)%answs(:,ib), surf_def_v(1)%answs(:,ib),        &
7373                                      surf_def_v(2)%answs(:,ib), surf_def_v(3)%answs(:,ib),        &
7374                                      surf_lsm_v(0)%answs(:,ib), surf_lsm_v(1)%answs(:,ib),        &
7375                                      surf_lsm_v(2)%answs(:,ib), surf_lsm_v(3)%answs(:,ib),        &
7376                                      surf_usm_v(0)%answs(:,ib), surf_usm_v(1)%answs(:,ib),        &
7377                                      surf_usm_v(2)%answs(:,ib), surf_usm_v(3)%answs(:,ib) )
7378       CASE ( 'aerosol_mass' )
7379          CALL diffusion_s( i, j, rs, surf_def_h(0)%amsws(:,icc),                                  &
7380                                      surf_def_h(1)%amsws(:,icc), surf_def_h(2)%amsws(:,icc),      &
7381                                      surf_lsm_h%amsws(:,icc),    surf_usm_h%amsws(:,icc),         &
7382                                      surf_def_v(0)%amsws(:,icc), surf_def_v(1)%amsws(:,icc),      &
7383                                      surf_def_v(2)%amsws(:,icc), surf_def_v(3)%amsws(:,icc),      &
7384                                      surf_lsm_v(0)%amsws(:,icc), surf_lsm_v(1)%amsws(:,icc),      &
7385                                      surf_lsm_v(2)%amsws(:,icc), surf_lsm_v(3)%amsws(:,icc),      &
7386                                      surf_usm_v(0)%amsws(:,icc), surf_usm_v(1)%amsws(:,icc),      &
7387                                      surf_usm_v(2)%amsws(:,icc), surf_usm_v(3)%amsws(:,icc) )
7388       CASE ( 'salsa_gas' )
7389          CALL diffusion_s( i, j, rs, surf_def_h(0)%gtsws(:,ib),                                   &
7390                                      surf_def_h(1)%gtsws(:,ib), surf_def_h(2)%gtsws(:,ib),        &
7391                                      surf_lsm_h%gtsws(:,ib), surf_usm_h%gtsws(:,ib),              &
7392                                      surf_def_v(0)%gtsws(:,ib), surf_def_v(1)%gtsws(:,ib),        &
7393                                      surf_def_v(2)%gtsws(:,ib), surf_def_v(3)%gtsws(:,ib),        &
7394                                      surf_lsm_v(0)%gtsws(:,ib), surf_lsm_v(1)%gtsws(:,ib),        &
7395                                      surf_lsm_v(2)%gtsws(:,ib), surf_lsm_v(3)%gtsws(:,ib),        &
7396                                      surf_usm_v(0)%gtsws(:,ib), surf_usm_v(1)%gtsws(:,ib),        &
7397                                      surf_usm_v(2)%gtsws(:,ib), surf_usm_v(3)%gtsws(:,ib) )
7398    END SELECT
7399!
7400!-- Sedimentation for aerosol number and mass
7401    IF ( lsdepo  .AND.  do_sedimentation )  THEN
7402       tend(nzb+1:nzt,j,i) = tend(nzb+1:nzt,j,i) - MAX( 0.0_wp,                                    &
7403                             ( rs(nzb+2:nzt+1,j,i) * sedim_vd(nzb+2:nzt+1,j,i,ib) -                &
7404                               rs(nzb+1:nzt,j,i) * sedim_vd(nzb+1:nzt,j,i,ib) ) * ddzu(nzb+1:nzt) )&
7405                             * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(nzb:nzt-1,j,i), 0 ) )
7406    ENDIF
7407!
7408!-- Prognostic equation for a scalar
7409    DO  k = nzb+1, nzt
7410       rs_p(k,j,i) = rs(k,j,i) + ( dt_3d * ( tsc(2) * tend(k,j,i) + tsc(3) * trs_m(k,j,i) )        &
7411                                           - tsc(5) * rdf_sc(k) * ( rs(k,j,i) - rs_init(k) ) )     &
7412                                 * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
7413       IF ( rs_p(k,j,i) < 0.0_wp )  rs_p(k,j,i) = 0.1_wp * rs(k,j,i)
7414    ENDDO
7415!
7416!-- Calculate tendencies for the next Runge-Kutta step
7417    IF ( timestep_scheme(1:5) == 'runge' )  THEN
7418       IF ( intermediate_timestep_count == 1 )  THEN
7419          DO  k = nzb+1, nzt
7420             trs_m(k,j,i) = tend(k,j,i)
7421          ENDDO
7422       ELSEIF ( intermediate_timestep_count < intermediate_timestep_count_max )  THEN
7423          DO  k = nzb+1, nzt
7424             trs_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * trs_m(k,j,i)
7425          ENDDO
7426       ENDIF
7427    ENDIF
7428
7429 END SUBROUTINE salsa_tendency_ij
7430!
7431!------------------------------------------------------------------------------!
7432! Description:
7433! ------------
7434!> Calculate the tendencies for aerosol number and mass concentrations.
7435!> Vector-optimized.
7436!------------------------------------------------------------------------------!
7437 SUBROUTINE salsa_tendency( id, rs_p, rs, trs_m, ib, ic, rs_init, do_sedimentation )
7438
7439    USE advec_ws,                                                                                  &
7440        ONLY:  advec_s_ws
7441    USE advec_s_pw_mod,                                                                            &
7442        ONLY:  advec_s_pw
7443    USE advec_s_up_mod,                                                                            &
7444        ONLY:  advec_s_up
7445    USE arrays_3d,                                                                                 &
7446        ONLY:  ddzu, rdf_sc, tend
7447    USE diffusion_s_mod,                                                                           &
7448        ONLY:  diffusion_s
7449    USE indices,                                                                                   &
7450        ONLY:  wall_flags_0
7451    USE surface_mod,                                                                               &
7452        ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
7453
7454    IMPLICIT NONE
7455
7456    CHARACTER(LEN = *) ::  id
7457
7458    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
7459    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
7460    INTEGER(iwp) ::  icc  !< (c-1)*nbins_aerosol+b
7461    INTEGER(iwp) ::  i    !<
7462    INTEGER(iwp) ::  j    !<
7463    INTEGER(iwp) ::  k    !<
7464
7465    LOGICAL ::  do_sedimentation  !<
7466
7467    REAL(wp), DIMENSION(nzb:nzt+1) ::  rs_init !<
7468
7469    REAL(wp), DIMENSION(:,:,:), POINTER ::  rs_p    !<
7470    REAL(wp), DIMENSION(:,:,:), POINTER ::  rs      !<
7471    REAL(wp), DIMENSION(:,:,:), POINTER ::  trs_m   !<
7472
7473    icc = ( ic - 1 ) * nbins_aerosol + ib
7474!
7475!-- Tendency-terms for reactive scalar
7476    tend = 0.0_wp
7477!
7478!-- Advection terms
7479    IF ( timestep_scheme(1:5) == 'runge' )  THEN
7480       IF ( ws_scheme_sca )  THEN
7481          CALL advec_s_ws( rs, id )
7482       ELSE
7483          CALL advec_s_pw( rs )
7484       ENDIF
7485    ELSE
7486       CALL advec_s_up( rs )
7487    ENDIF
7488!
7489!-- Diffusion terms
7490    SELECT CASE ( id )
7491       CASE ( 'aerosol_number' )
7492          CALL diffusion_s( rs, surf_def_h(0)%answs(:,ib),                                         &
7493                                surf_def_h(1)%answs(:,ib), surf_def_h(2)%answs(:,ib),              &
7494                                surf_lsm_h%answs(:,ib),    surf_usm_h%answs(:,ib),                 &
7495                                surf_def_v(0)%answs(:,ib), surf_def_v(1)%answs(:,ib),              &
7496                                surf_def_v(2)%answs(:,ib), surf_def_v(3)%answs(:,ib),              &
7497                                surf_lsm_v(0)%answs(:,ib), surf_lsm_v(1)%answs(:,ib),              &
7498                                surf_lsm_v(2)%answs(:,ib), surf_lsm_v(3)%answs(:,ib),              &
7499                                surf_usm_v(0)%answs(:,ib), surf_usm_v(1)%answs(:,ib),              &
7500                                surf_usm_v(2)%answs(:,ib), surf_usm_v(3)%answs(:,ib) )
7501       CASE ( 'aerosol_mass' )
7502          CALL diffusion_s( rs, surf_def_h(0)%amsws(:,icc),                                        &
7503                                surf_def_h(1)%amsws(:,icc), surf_def_h(2)%amsws(:,icc),            &
7504                                surf_lsm_h%amsws(:,icc),    surf_usm_h%amsws(:,icc),               &
7505                                surf_def_v(0)%amsws(:,icc), surf_def_v(1)%amsws(:,icc),            &
7506                                surf_def_v(2)%amsws(:,icc), surf_def_v(3)%amsws(:,icc),            &
7507                                surf_lsm_v(0)%amsws(:,icc), surf_lsm_v(1)%amsws(:,icc),            &
7508                                surf_lsm_v(2)%amsws(:,icc), surf_lsm_v(3)%amsws(:,icc),            &
7509                                surf_usm_v(0)%amsws(:,icc), surf_usm_v(1)%amsws(:,icc),            &
7510                                surf_usm_v(2)%amsws(:,icc), surf_usm_v(3)%amsws(:,icc) )
7511       CASE ( 'salsa_gas' )
7512          CALL diffusion_s( rs, surf_def_h(0)%gtsws(:,ib),                                         &
7513                                surf_def_h(1)%gtsws(:,ib), surf_def_h(2)%gtsws(:,ib),              &
7514                                surf_lsm_h%gtsws(:,ib),    surf_usm_h%gtsws(:,ib),                 &
7515                                surf_def_v(0)%gtsws(:,ib), surf_def_v(1)%gtsws(:,ib),              &
7516                                surf_def_v(2)%gtsws(:,ib), surf_def_v(3)%gtsws(:,ib),              &
7517                                surf_lsm_v(0)%gtsws(:,ib), surf_lsm_v(1)%gtsws(:,ib),              &
7518                                surf_lsm_v(2)%gtsws(:,ib), surf_lsm_v(3)%gtsws(:,ib),              &
7519                                surf_usm_v(0)%gtsws(:,ib), surf_usm_v(1)%gtsws(:,ib),              &
7520                                surf_usm_v(2)%gtsws(:,ib), surf_usm_v(3)%gtsws(:,ib) )
7521    END SELECT
7522!
7523!-- Prognostic equation for a scalar
7524    DO  i = nxl, nxr
7525       DO  j = nys, nyn
7526!
7527!--       Sedimentation for aerosol number and mass
7528          IF ( lsdepo  .AND.  do_sedimentation )  THEN
7529             tend(nzb+1:nzt,j,i) = tend(nzb+1:nzt,j,i) - MAX( 0.0_wp, ( rs(nzb+2:nzt+1,j,i) *      &
7530                                   sedim_vd(nzb+2:nzt+1,j,i,ib) - rs(nzb+1:nzt,j,i) *              &
7531                                   sedim_vd(nzb+1:nzt,j,i,ib) ) * ddzu(nzb+1:nzt) ) *              &
7532                                   MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(nzb:nzt-1,j,i), 0 ) )
7533          ENDIF
7534          DO  k = nzb+1, nzt
7535             rs_p(k,j,i) = rs(k,j,i) +  ( dt_3d  * ( tsc(2) * tend(k,j,i) + tsc(3) * trs_m(k,j,i) )&
7536                                                  - tsc(5) * rdf_sc(k) * ( rs(k,j,i) - rs_init(k) )&
7537                                        ) * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
7538             IF ( rs_p(k,j,i) < 0.0_wp )  rs_p(k,j,i) = 0.1_wp * rs(k,j,i)
7539          ENDDO
7540       ENDDO
7541    ENDDO
7542!
7543!-- Calculate tendencies for the next Runge-Kutta step
7544    IF ( timestep_scheme(1:5) == 'runge' )  THEN
7545       IF ( intermediate_timestep_count == 1 )  THEN
7546          DO  i = nxl, nxr
7547             DO  j = nys, nyn
7548                DO  k = nzb+1, nzt
7549                   trs_m(k,j,i) = tend(k,j,i)
7550                ENDDO
7551             ENDDO
7552          ENDDO
7553       ELSEIF ( intermediate_timestep_count < intermediate_timestep_count_max )  THEN
7554          DO  i = nxl, nxr
7555             DO  j = nys, nyn
7556                DO  k = nzb+1, nzt
7557                   trs_m(k,j,i) =  -9.5625_wp * tend(k,j,i) + 5.3125_wp * trs_m(k,j,i)
7558                ENDDO
7559             ENDDO
7560          ENDDO
7561       ENDIF
7562    ENDIF
7563
7564 END SUBROUTINE salsa_tendency
7565
7566!------------------------------------------------------------------------------!
7567! Description:
7568! ------------
7569!> Boundary conditions for prognostic variables in SALSA
7570!------------------------------------------------------------------------------!
7571 SUBROUTINE salsa_boundary_conds
7572
7573    USE arrays_3d,                                                                                 &
7574        ONLY:  dzu
7575
7576    USE surface_mod,                                                                               &
7577        ONLY :  bc_h
7578
7579    IMPLICIT NONE
7580
7581    INTEGER(iwp) ::  i    !< grid index x direction
7582    INTEGER(iwp) ::  ib   !< index for aerosol size bins
7583    INTEGER(iwp) ::  ic   !< index for chemical compounds in aerosols
7584    INTEGER(iwp) ::  icc  !< additional index for chemical compounds in aerosols
7585    INTEGER(iwp) ::  ig   !< idex for gaseous compounds
7586    INTEGER(iwp) ::  j    !< grid index y direction
7587    INTEGER(iwp) ::  k    !< grid index y direction
7588    INTEGER(iwp) ::  kb   !< variable to set respective boundary value, depends on facing.
7589    INTEGER(iwp) ::  l    !< running index boundary type, for up- and downward-facing walls
7590    INTEGER(iwp) ::  m    !< running index surface elements
7591
7592    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
7593
7594!
7595!--    Surface conditions:
7596       IF ( ibc_salsa_b == 0 )  THEN   ! Dirichlet
7597!
7598!--       Run loop over all non-natural and natural walls. Note, in wall-datatype the k coordinate
7599!--       belongs to the atmospheric grid point, therefore, set s_p at k-1
7600          DO  l = 0, 1
7601!
7602!--          Set kb, for upward-facing surfaces value at topography top (k-1) is
7603!--          set, for downward-facing surfaces at topography bottom (k+1)
7604             kb = MERGE ( -1, 1, l == 0 )
7605             !$OMP PARALLEL PRIVATE( ib, ic, icc, ig, i, j, k )
7606             !$OMP DO
7607             DO  m = 1, bc_h(l)%ns
7608
7609                i = bc_h(l)%i(m)
7610                j = bc_h(l)%j(m)
7611                k = bc_h(l)%k(m)
7612
7613                DO  ib = 1, nbins_aerosol
7614                   aerosol_number(ib)%conc_p(k+kb,j,i) = aerosol_number(ib)%conc(k+kb,j,i)
7615                   DO  ic = 1, ncomponents_mass
7616                      icc = ( ic - 1 ) * nbins_aerosol + ib
7617                      aerosol_mass(icc)%conc_p(k+kb,j,i) = aerosol_mass(icc)%conc(k+kb,j,i)
7618                   ENDDO
7619                ENDDO
7620                IF ( .NOT. salsa_gases_from_chem )  THEN
7621                   DO  ig = 1, ngases_salsa
7622                      salsa_gas(ig)%conc_p(k+kb,j,i) = salsa_gas(ig)%conc(k+kb,j,i)
7623                   ENDDO
7624                ENDIF
7625
7626             ENDDO
7627             !$OMP END PARALLEL
7628
7629          ENDDO
7630
7631       ELSE   ! Neumann
7632
7633          DO l = 0, 1
7634!
7635!--          Set kb, for upward-facing surfaces value at topography top (k-1) is
7636!--          set, for downward-facing surfaces at topography bottom (k+1)
7637             kb = MERGE( -1, 1, l == 0 )
7638             !$OMP PARALLEL PRIVATE( ib, ic, icc, ig, i, j, k )
7639             !$OMP DO
7640             DO  m = 1, bc_h(l)%ns
7641
7642                i = bc_h(l)%i(m)
7643                j = bc_h(l)%j(m)
7644                k = bc_h(l)%k(m)
7645
7646                DO  ib = 1, nbins_aerosol
7647                   aerosol_number(ib)%conc_p(k+kb,j,i) = aerosol_number(ib)%conc_p(k,j,i)
7648                   DO  ic = 1, ncomponents_mass
7649                      icc = ( ic - 1 ) * nbins_aerosol + ib
7650                      aerosol_mass(icc)%conc_p(k+kb,j,i) = aerosol_mass(icc)%conc_p(k,j,i)
7651                   ENDDO
7652                ENDDO
7653                IF ( .NOT. salsa_gases_from_chem ) THEN
7654                   DO  ig = 1, ngases_salsa
7655                      salsa_gas(ig)%conc_p(k+kb,j,i) = salsa_gas(ig)%conc_p(k,j,i)
7656                   ENDDO
7657                ENDIF
7658
7659             ENDDO
7660             !$OMP END PARALLEL
7661          ENDDO
7662
7663       ENDIF
7664!
7665!--   Top boundary conditions:
7666       IF ( ibc_salsa_t == 0 )  THEN   ! Dirichlet
7667
7668          DO  ib = 1, nbins_aerosol
7669             aerosol_number(ib)%conc_p(nzt+1,:,:) = aerosol_number(ib)%conc(nzt+1,:,:)
7670             DO  ic = 1, ncomponents_mass
7671                icc = ( ic - 1 ) * nbins_aerosol + ib
7672                aerosol_mass(icc)%conc_p(nzt+1,:,:) = aerosol_mass(icc)%conc(nzt+1,:,:)
7673             ENDDO
7674          ENDDO
7675          IF ( .NOT. salsa_gases_from_chem )  THEN
7676             DO  ig = 1, ngases_salsa
7677                salsa_gas(ig)%conc_p(nzt+1,:,:) = salsa_gas(ig)%conc(nzt+1,:,:)
7678             ENDDO
7679          ENDIF
7680
7681       ELSEIF ( ibc_salsa_t == 1 )  THEN   ! Neumann
7682
7683          DO  ib = 1, nbins_aerosol
7684             aerosol_number(ib)%conc_p(nzt+1,:,:) = aerosol_number(ib)%conc_p(nzt,:,:)
7685             DO  ic = 1, ncomponents_mass
7686                icc = ( ic - 1 ) * nbins_aerosol + ib
7687                aerosol_mass(icc)%conc_p(nzt+1,:,:) = aerosol_mass(icc)%conc_p(nzt,:,:)
7688             ENDDO
7689          ENDDO
7690          IF ( .NOT. salsa_gases_from_chem )  THEN
7691             DO  ig = 1, ngases_salsa
7692                salsa_gas(ig)%conc_p(nzt+1,:,:) = salsa_gas(ig)%conc_p(nzt,:,:)
7693             ENDDO
7694          ENDIF
7695
7696       ELSEIF ( ibc_salsa_t == 2 )  THEN   ! nested
7697
7698          DO  ib = 1, nbins_aerosol
7699             aerosol_number(ib)%conc_p(nzt+1,:,:) = aerosol_number(ib)%conc_p(nzt,:,:) +              &
7700                                                    bc_an_t_val(ib) * dzu(nzt+1)
7701             DO  ic = 1, ncomponents_mass
7702                icc = ( ic - 1 ) * nbins_aerosol + ib
7703                aerosol_mass(icc)%conc_p(nzt+1,:,:) = aerosol_mass(icc)%conc_p(nzt,:,:) +             &
7704                                                      bc_am_t_val(icc) * dzu(nzt+1)
7705             ENDDO
7706          ENDDO
7707          IF ( .NOT. salsa_gases_from_chem )  THEN
7708             DO  ig = 1, ngases_salsa
7709                salsa_gas(ig)%conc_p(nzt+1,:,:) = salsa_gas(ig)%conc_p(nzt,:,:) +                     &
7710                                                  bc_gt_t_val(ig) * dzu(nzt+1)
7711             ENDDO
7712          ENDIF
7713
7714       ENDIF
7715!
7716!--    Lateral boundary conditions at the outflow
7717       IF ( bc_radiation_s )  THEN
7718          DO  ib = 1, nbins_aerosol
7719             aerosol_number(ib)%conc_p(:,nys-1,:) = aerosol_number(ib)%conc_p(:,nys,:)
7720             DO  ic = 1, ncomponents_mass
7721                icc = ( ic - 1 ) * nbins_aerosol + ib
7722                aerosol_mass(icc)%conc_p(:,nys-1,:) = aerosol_mass(icc)%conc_p(:,nys,:)
7723             ENDDO
7724          ENDDO
7725          IF ( .NOT. salsa_gases_from_chem )  THEN
7726             DO  ig = 1, ngases_salsa
7727                salsa_gas(ig)%conc_p(:,nys-1,:) = salsa_gas(ig)%conc_p(:,nys,:)
7728             ENDDO
7729          ENDIF
7730
7731       ELSEIF ( bc_radiation_n )  THEN
7732          DO  ib = 1, nbins_aerosol
7733             aerosol_number(ib)%conc_p(:,nyn+1,:) = aerosol_number(ib)%conc_p(:,nyn,:)
7734             DO  ic = 1, ncomponents_mass
7735                icc = ( ic - 1 ) * nbins_aerosol + ib
7736                aerosol_mass(icc)%conc_p(:,nyn+1,:) = aerosol_mass(icc)%conc_p(:,nyn,:)
7737             ENDDO
7738          ENDDO
7739          IF ( .NOT. salsa_gases_from_chem )  THEN
7740             DO  ig = 1, ngases_salsa
7741                salsa_gas(ig)%conc_p(:,nyn+1,:) = salsa_gas(ig)%conc_p(:,nyn,:)
7742             ENDDO
7743          ENDIF
7744
7745       ELSEIF ( bc_radiation_l )  THEN
7746          DO  ib = 1, nbins_aerosol
7747             aerosol_number(ib)%conc_p(:,:,nxl-1) = aerosol_number(ib)%conc_p(:,:,nxl)
7748             DO  ic = 1, ncomponents_mass
7749                icc = ( ic - 1 ) * nbins_aerosol + ib
7750                aerosol_mass(icc)%conc_p(:,:,nxl-1) = aerosol_mass(icc)%conc_p(:,:,nxl)
7751             ENDDO
7752          ENDDO
7753          IF ( .NOT. salsa_gases_from_chem )  THEN
7754             DO  ig = 1, ngases_salsa
7755                salsa_gas(ig)%conc_p(:,:,nxl-1) = salsa_gas(ig)%conc_p(:,:,nxl)
7756             ENDDO
7757          ENDIF
7758
7759       ELSEIF ( bc_radiation_r )  THEN
7760          DO  ib = 1, nbins_aerosol
7761             aerosol_number(ib)%conc_p(:,:,nxr+1) = aerosol_number(ib)%conc_p(:,:,nxr)
7762             DO  ic = 1, ncomponents_mass
7763                icc = ( ic - 1 ) * nbins_aerosol + ib
7764                aerosol_mass(icc)%conc_p(:,:,nxr+1) = aerosol_mass(icc)%conc_p(:,:,nxr)
7765             ENDDO
7766          ENDDO
7767          IF ( .NOT. salsa_gases_from_chem )  THEN
7768             DO  ig = 1, ngases_salsa
7769                salsa_gas(ig)%conc_p(:,:,nxr+1) = salsa_gas(ig)%conc_p(:,:,nxr)
7770             ENDDO
7771          ENDIF
7772
7773       ENDIF
7774
7775    ENDIF
7776
7777 END SUBROUTINE salsa_boundary_conds
7778
7779!------------------------------------------------------------------------------!
7780! Description:
7781! ------------
7782! Undoing of the previously done cyclic boundary conditions.
7783!------------------------------------------------------------------------------!
7784 SUBROUTINE salsa_boundary_conds_decycle ( sq, sq_init )
7785
7786    IMPLICIT NONE
7787
7788    INTEGER(iwp) ::  boundary  !<
7789    INTEGER(iwp) ::  ee        !<
7790    INTEGER(iwp) ::  copied    !<
7791    INTEGER(iwp) ::  i         !<
7792    INTEGER(iwp) ::  j         !<
7793    INTEGER(iwp) ::  k         !<
7794    INTEGER(iwp) ::  ss        !<
7795
7796    REAL(wp) ::  flag  !< flag to mask topography grid points
7797
7798    REAL(wp), DIMENSION(nzb:nzt+1) ::  sq_init  !< initial concentration profile
7799
7800    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sq  !< concentration array
7801
7802    flag = 0.0_wp
7803!
7804!-- Left and right boundaries
7805    IF ( decycle_lr  .AND.  ( bc_lr_cyc  .OR. bc_lr == 'nested' ) )  THEN
7806
7807       DO  boundary = 1, 2
7808
7809          IF ( decycle_method(boundary) == 'dirichlet' )  THEN
7810!
7811!--          Initial profile is copied to ghost and first three layers
7812             ss = 1
7813             ee = 0
7814             IF ( boundary == 1  .AND.  nxl == 0 )  THEN
7815                ss = nxlg
7816                ee = nxl+2
7817             ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
7818                ss = nxr-2
7819                ee = nxrg
7820             ENDIF
7821
7822             DO  i = ss, ee
7823                DO  j = nysg, nyng
7824                   DO  k = nzb+1, nzt
7825                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
7826                      sq(k,j,i) = sq_init(k) * flag
7827                   ENDDO
7828                ENDDO
7829             ENDDO
7830
7831          ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
7832!
7833!--          The value at the boundary is copied to the ghost layers to simulate an outlet with
7834!--          zero gradient
7835             ss = 1
7836             ee = 0
7837             IF ( boundary == 1  .AND.  nxl == 0 )  THEN
7838                ss = nxlg
7839                ee = nxl-1
7840                copied = nxl
7841             ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
7842                ss = nxr+1
7843                ee = nxrg
7844                copied = nxr
7845             ENDIF
7846
7847              DO  i = ss, ee
7848                DO  j = nysg, nyng
7849                   DO  k = nzb+1, nzt
7850                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
7851                      sq(k,j,i) = sq(k,j,copied) * flag
7852                   ENDDO
7853                ENDDO
7854             ENDDO
7855
7856          ELSE
7857             WRITE(message_string,*) 'unknown decycling method: decycle_method (', boundary,       &
7858                                     ') ="' // TRIM( decycle_method(boundary) ) // '"'
7859             CALL message( 'salsa_boundary_conds_decycle', 'PA0626', 1, 2, 0, 6, 0 )
7860          ENDIF
7861       ENDDO
7862    ENDIF
7863
7864!
7865!-- South and north boundaries
7866     IF ( decycle_ns  .AND.  ( bc_ns_cyc  .OR. bc_ns == 'nested' ) )  THEN
7867
7868       DO  boundary = 3, 4
7869
7870          IF ( decycle_method(boundary) == 'dirichlet' )  THEN
7871!
7872!--          Initial profile is copied to ghost and first three layers
7873             ss = 1
7874             ee = 0
7875             IF ( boundary == 3  .AND.  nys == 0 )  THEN
7876                ss = nysg
7877                ee = nys+2
7878             ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
7879                ss = nyn-2
7880                ee = nyng
7881             ENDIF
7882
7883             DO  i = nxlg, nxrg
7884                DO  j = ss, ee
7885                   DO  k = nzb+1, nzt
7886                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
7887                      sq(k,j,i) = sq_init(k) * flag
7888                   ENDDO
7889                ENDDO
7890             ENDDO
7891
7892          ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
7893!
7894!--          The value at the boundary is copied to the ghost layers to simulate an outlet with
7895!--          zero gradient
7896             ss = 1
7897             ee = 0
7898             IF ( boundary == 3  .AND.  nys == 0 )  THEN
7899                ss = nysg
7900                ee = nys-1
7901                copied = nys
7902             ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
7903                ss = nyn+1
7904                ee = nyng
7905                copied = nyn
7906             ENDIF
7907
7908              DO  i = nxlg, nxrg
7909                DO  j = ss, ee
7910                   DO  k = nzb+1, nzt
7911                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
7912                      sq(k,j,i) = sq(k,copied,i) * flag
7913                   ENDDO
7914                ENDDO
7915             ENDDO
7916
7917          ELSE
7918             WRITE(message_string,*) 'unknown decycling method: decycle_method (', boundary,       &
7919                                     ') ="' // TRIM( decycle_method(boundary) ) // '"'
7920             CALL message( 'salsa_boundary_conds_decycle', 'PA0627', 1, 2, 0, 6, 0 )
7921          ENDIF
7922       ENDDO
7923    ENDIF
7924
7925 END SUBROUTINE salsa_boundary_conds_decycle
7926
7927!------------------------------------------------------------------------------!
7928! Description:
7929! ------------
7930!> Calculates the total dry or wet mass concentration for individual bins
7931!> Juha Tonttila (FMI) 2015
7932!> Tomi Raatikainen (FMI) 2016
7933!------------------------------------------------------------------------------!
7934 SUBROUTINE bin_mixrat( itype, ibin, i, j, mconc )
7935
7936    IMPLICIT NONE
7937
7938    CHARACTER(len=*), INTENT(in) ::  itype  !< 'dry' or 'wet'
7939
7940    INTEGER(iwp) ::  ic                 !< loop index for mass bin number
7941    INTEGER(iwp) ::  iend               !< end index: include water or not
7942
7943    INTEGER(iwp), INTENT(in) ::  ibin   !< index of the chemical component
7944    INTEGER(iwp), INTENT(in) ::  i      !< loop index for x-direction
7945    INTEGER(iwp), INTENT(in) ::  j      !< loop index for y-direction
7946
7947    REAL(wp), DIMENSION(:), INTENT(out) ::  mconc  !< total dry or wet mass concentration
7948
7949!-- Number of components
7950    IF ( itype == 'dry' )  THEN
7951       iend = prtcl%ncomp - 1 
7952    ELSE IF ( itype == 'wet' )  THEN
7953       iend = prtcl%ncomp
7954    ELSE
7955       message_string = 'Error in itype!'
7956       CALL message( 'salsa_mod: bin_mixrat', 'PA0628', 2, 2, 0, 6, 0 )
7957    ENDIF
7958
7959    mconc = 0.0_wp
7960
7961    DO  ic = ibin, iend*nbins_aerosol+ibin, nbins_aerosol !< every nbins'th element
7962       mconc = mconc + aerosol_mass(ic)%conc(:,j,i)
7963    ENDDO
7964
7965 END SUBROUTINE bin_mixrat
7966
7967!------------------------------------------------------------------------------!
7968! Description:
7969! ------------
7970!> Sets surface fluxes
7971!------------------------------------------------------------------------------!
7972 SUBROUTINE salsa_emission_update
7973
7974    USE control_parameters,                                                                        &
7975        ONLY:  time_since_reference_point
7976
7977    IMPLICIT NONE
7978
7979    IF ( time_since_reference_point >= skip_time_do_salsa  )  THEN
7980
7981       IF ( next_aero_emission_update <= time_since_reference_point )  THEN
7982          CALL salsa_emission_setup( .FALSE. )
7983       ENDIF
7984
7985       IF ( next_gas_emission_update <= time_since_reference_point )  THEN
7986          IF ( salsa_emission_mode == 'read_from_file'  .AND.  .NOT. salsa_gases_from_chem )  THEN
7987             CALL salsa_gas_emission_setup( .FALSE. )
7988          ENDIF
7989       ENDIF
7990
7991    ENDIF
7992
7993 END SUBROUTINE salsa_emission_update
7994
7995!------------------------------------------------------------------------------!
7996!> Description:
7997!> ------------
7998!> Define aerosol fluxes: constant or read from a from file
7999!> @todo - Emission stack height is not used yet. For default mode, emissions
8000!>         are assumed to occur on upward facing horizontal surfaces.
8001!------------------------------------------------------------------------------!
8002 SUBROUTINE salsa_emission_setup( init )
8003
8004    USE control_parameters,                                                                        &
8005        ONLY:  time_since_reference_point
8006
8007    USE date_and_time_mod,                                                                         &
8008        ONLY:  day_of_month, hour_of_day, index_dd, index_hh, index_mm, month_of_year,             &
8009               time_default_indices, time_utc_init
8010
8011    USE netcdf_data_input_mod,                                                                     &
8012        ONLY:  check_existence, get_attribute, get_variable, inquire_num_variables,                &
8013               inquire_variable_names, netcdf_data_input_get_dimension_length, open_read_file
8014
8015    USE surface_mod,                                                                               &
8016        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
8017
8018    IMPLICIT NONE
8019
8020    CHARACTER(LEN=80) ::  daytype = 'workday'  !< default day type
8021    CHARACTER(LEN=25) ::  in_name              !< name of a gas in the input file
8022    CHARACTER(LEN=25) ::  mod_name             !< name in the input file
8023
8024    INTEGER(iwp) ::  ib        !< loop index: aerosol number bins
8025    INTEGER(iwp) ::  ic        !< loop index: aerosol chemical components
8026    INTEGER(iwp) ::  id_salsa  !< NetCDF id of aerosol emission input file
8027    INTEGER(iwp) ::  in        !< loop index: emission category
8028    INTEGER(iwp) ::  inn       !< loop index
8029    INTEGER(iwp) ::  ss        !< loop index
8030
8031    INTEGER(iwp), DIMENSION(maxspec) ::  cc_i2m   !<
8032
8033    LOGICAL  ::  netcdf_extend = .FALSE.  !< NetCDF input file exists
8034
8035    LOGICAL, INTENT(in) ::  init  !< if .TRUE. --> initialisation call
8036
8037    REAL(wp), DIMENSION(:), ALLOCATABLE ::  nsect_emission  !< sectional number emission
8038
8039    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  source_array  !< temporary source array
8040
8041!
8042!-- Allocate source arrays:
8043    DO  ib = 1, nbins_aerosol
8044       IF ( init )  ALLOCATE( aerosol_number(ib)%source(nys:nyn,nxl:nxr) )
8045       aerosol_number(ib)%source = 0.0_wp
8046    ENDDO
8047
8048    DO  ic = 1, ncomponents_mass * nbins_aerosol
8049       IF ( init )  ALLOCATE( aerosol_mass(ic)%source(nys:nyn,nxl:nxr) )
8050       aerosol_mass(ic)%source = 0.0_wp
8051    ENDDO
8052
8053!
8054!-- Define emissions:
8055
8056    SELECT CASE ( salsa_emission_mode )
8057
8058       CASE ( 'uniform' )
8059
8060          IF ( init )  THEN  ! Do only once
8061!
8062!-           Form a sectional size distribution for the emissions
8063             ALLOCATE( nsect_emission(1:nbins_aerosol),                                            &
8064                       source_array(nys:nyn,nxl:nxr,1:nbins_aerosol) )
8065!
8066!--          Precalculate a size distribution for the emission based on the mean diameter, standard
8067!--          deviation and number concentration per each log-normal mode
8068             CALL size_distribution( surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag,  &
8069                                     nsect_emission )
8070             DO  ib = 1, nbins_aerosol
8071                source_array(:,:,ib) = nsect_emission(ib)
8072             ENDDO
8073!
8074!--          Check which chemical components are used
8075             cc_i2m = 0
8076             IF ( index_so4 > 0 ) cc_i2m(1) = index_so4
8077             IF ( index_oc > 0 )  cc_i2m(2) = index_oc
8078             IF ( index_bc > 0 )  cc_i2m(3) = index_bc
8079             IF ( index_du > 0 )  cc_i2m(4) = index_du
8080             IF ( index_ss > 0 )  cc_i2m(5) = index_ss
8081             IF ( index_no > 0 )  cc_i2m(6) = index_no
8082             IF ( index_nh > 0 )  cc_i2m(7) = index_nh
8083!
8084!--          Normalise mass fractions so that their sum is 1
8085             aerosol_flux_mass_fracs_a = aerosol_flux_mass_fracs_a /                               &
8086                                         SUM( aerosol_flux_mass_fracs_a(1:ncc ) )
8087!
8088!--          Set uniform fluxes of default horizontal surfaces
8089             CALL set_flux( surf_def_h(0), cc_i2m, aerosol_flux_mass_fracs_a, source_array )
8090!
8091!--          Subrange 2b:
8092             IF ( SUM( aerosol_flux_mass_fracs_b ) > 0.0_wp )  THEN
8093                CALL location_message( '   salsa_emission_setup: emissions are soluble!', .TRUE. )
8094             ENDIF
8095
8096             DEALLOCATE( nsect_emission, source_array )
8097          ENDIF
8098
8099       CASE ( 'parameterized' )
8100!
8101!--       TO DO
8102
8103       CASE ( 'read_from_file' )
8104!
8105!--       Reset surface fluxes
8106          surf_def_h(0)%answs = 0.0_wp
8107          surf_def_h(0)%amsws = 0.0_wp
8108          surf_lsm_h%answs = 0.0_wp
8109          surf_lsm_h%amsws = 0.0_wp
8110          surf_usm_h%answs = 0.0_wp
8111          surf_usm_h%amsws = 0.0_wp
8112
8113#if defined( __netcdf )
8114          IF ( init )  THEN
8115!
8116!--          Check existence of PIDS_SALSA file
8117             INQUIRE( FILE = input_file_salsa // TRIM( coupling_char ), EXIST = netcdf_extend )
8118             IF ( .NOT. netcdf_extend )  THEN
8119                message_string = 'Input file '// TRIM( input_file_salsa ) //  TRIM( coupling_char )&
8120                                 // ' missing!'
8121                CALL message( 'salsa_emission_setup', 'PA0629', 1, 2, 0, 6, 0 )
8122             ENDIF
8123!
8124!--          Open file in read-only mode
8125             CALL open_read_file( input_file_salsa // TRIM( coupling_char ), id_salsa )
8126!
8127!--          Read the index and name of chemical components
8128             CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%ncc,         &
8129                                                          'composition_index' )
8130             ALLOCATE( aero_emission_att%cc_index(1:aero_emission_att%ncc) )
8131             CALL get_variable( id_salsa, 'composition_index', aero_emission_att%cc_index )
8132             CALL get_variable( id_salsa, 'composition_name', aero_emission_att%cc_name,           &
8133                                aero_emission_att%ncc )
8134!
8135!--          Find the corresponding chemical components in the model
8136             aero_emission_att%cc_input_to_model = 0
8137             DO  ic = 1, aero_emission_att%ncc
8138                in_name = aero_emission_att%cc_name(ic)
8139                SELECT CASE ( TRIM( in_name ) )
8140                   CASE ( 'H2SO4', 'h2so4', 'SO4', 'so4' )
8141                      aero_emission_att%cc_input_to_model(1) = ic
8142                   CASE ( 'OC', 'oc', 'organics' )
8143                      aero_emission_att%cc_input_to_model(2) = ic
8144                   CASE ( 'BC', 'bc' )
8145                      aero_emission_att%cc_input_to_model(3) = ic
8146                   CASE ( 'DU', 'du' )
8147                      aero_emission_att%cc_input_to_model(4) = ic
8148                   CASE ( 'SS', 'ss' )
8149                      aero_emission_att%cc_input_to_model(5) = ic
8150                   CASE ( 'HNO3', 'hno3', 'NO', 'no' )
8151                      aero_emission_att%cc_input_to_model(6) = ic
8152                   CASE ( 'NH3', 'nh3', 'NH', 'nh' )
8153                      aero_emission_att%cc_input_to_model(7) = ic
8154                END SELECT
8155
8156             ENDDO
8157
8158             IF ( SUM( aero_emission_att%cc_input_to_model ) == 0 )  THEN
8159                message_string = 'None of the aerosol chemical components in ' // TRIM(            &
8160                                 input_file_salsa ) // ' correspond to the ones applied in SALSA.'
8161                CALL message( 'salsa_emission_setup', 'PA0630', 1, 2, 0, 6, 0 )
8162             ENDIF
8163!
8164!--          Inquire the fill value
8165             CALL get_attribute( id_salsa, '_FillValue', aero_emission%fill, .FALSE.,              &
8166                                 'aerosol_emission_values' )
8167!
8168!--          Inquire units of emissions
8169             CALL get_attribute( id_salsa, 'units', aero_emission_att%units, .FALSE.,              &
8170                                 'aerosol_emission_values' )
8171!
8172!--          Inquire the level of detail (lod)
8173             CALL get_attribute( id_salsa, 'lod', aero_emission_att%lod, .FALSE.,                  &
8174                                 'aerosol_emission_values' )
8175!
8176!--          Variable names
8177             CALL inquire_num_variables( id_salsa, aero_emission_att%num_vars )
8178             ALLOCATE( aero_emission_att%var_names(1:aero_emission_att%num_vars) )
8179             CALL inquire_variable_names( id_salsa, aero_emission_att%var_names )
8180
8181!
8182!--          Read different emission information depending on the level of detail of emissions:
8183
8184!
8185!--          Default mode:
8186             IF ( aero_emission_att%lod == 1 )  THEN
8187!
8188!--             Unit conversion factor: convert to SI units (kg/m2/s)
8189                IF ( aero_emission_att%units == 'kg/m2/yr' )  THEN
8190                   aero_emission_att%conversion_factor = 1.0_wp / 3600.0_wp
8191                ELSEIF ( aero_emission_att%units == 'g/m2/yr' )  THEN
8192                   aero_emission_att%conversion_factor = 0.001_wp / 3600.0_wp
8193                ELSE
8194                   message_string = 'unknown unit for aerosol emissions: ' //                      &
8195                                    TRIM( aero_emission_att%units ) // ' (lod1)'
8196                   CALL message( 'salsa_emission_setup','PA0631', 1, 2, 0, 6, 0 )
8197                ENDIF
8198!
8199!--             Get number of emission categories and allocate emission arrays
8200                CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%ncat,     &
8201                                                             'ncat' )
8202                ALLOCATE( aero_emission_att%cat_index(1:aero_emission_att%ncat),                   &
8203                          aero_emission_att%rho(1:aero_emission_att%ncat),                         &
8204                          aero_emission_att%time_factor(1:aero_emission_att%ncat) )
8205!
8206!--             Get emission category names and indices
8207                CALL get_variable( id_salsa, 'emission_category_name', aero_emission_att%cat_name, &
8208                                   aero_emission_att%ncat)
8209                CALL get_variable( id_salsa, 'emission_category_index', aero_emission_att%cat_index )
8210!
8211!--             Find corresponding emission categories
8212                DO  in = 1, aero_emission_att%ncat
8213                   in_name = aero_emission_att%cat_name(in)
8214                   DO  ss = 1, def_modes%ndc
8215                      mod_name = def_modes%cat_name_table(ss)
8216                      IF ( TRIM( in_name(1:4) ) == TRIM( mod_name(1:4 ) ) )  THEN
8217                         def_modes%cat_input_to_model(ss) = in
8218                      ENDIF
8219                   ENDDO
8220                ENDDO
8221
8222                IF ( SUM( def_modes%cat_input_to_model ) == 0 )  THEN
8223                   message_string = 'None of the emission categories in ' //  TRIM(                &
8224                                    input_file_salsa ) // ' match with the ones in the model.'
8225                   CALL message( 'salsa_emission_setup', 'PA0632', 1, 2, 0, 6, 0 )
8226                ENDIF
8227!
8228!--             Emission time factors: Find check whether emission time factors are given for each
8229!--             hour of year OR based on month, day and hour
8230!
8231!--             For each hour of year:
8232                IF ( check_existence( aero_emission_att%var_names, 'nhoursyear' ) )  THEN
8233                   CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%nhoursyear,&
8234                                                                'nhoursyear' )
8235                   ALLOCATE( aero_emission_att%etf(1:aero_emission_att%ncat,                       &
8236                                                   1:aero_emission_att%nhoursyear) )
8237                   CALL get_variable( id_salsa, 'emission_time_factors', aero_emission_att%etf,    &
8238                                    0, aero_emission_att%nhoursyear-1, 0, aero_emission_att%ncat-1 )
8239!
8240!--             Based on the month, day and hour:
8241                ELSEIF ( check_existence( aero_emission_att%var_names, 'nmonthdayhour' ) )  THEN
8242                   CALL netcdf_data_input_get_dimension_length( id_salsa,                          &
8243                                                                aero_emission_att%nmonthdayhour,   &
8244                                                                'nmonthdayhour' )
8245                   ALLOCATE( aero_emission_att%etf(1:aero_emission_att%ncat,                       &
8246                                                   1:aero_emission_att%nmonthdayhour) )
8247                   CALL get_variable( id_salsa, 'emission_time_factors', aero_emission_att%etf,    &
8248                                 0, aero_emission_att%nmonthdayhour-1, 0, aero_emission_att%ncat-1 )
8249                ELSE
8250                   message_string = 'emission_time_factors should be given for each nhoursyear ' //&
8251                                    'OR nmonthdayhour'
8252                   CALL message( 'salsa_emission_setup','PA0633', 1, 2, 0, 6, 0 )
8253                ENDIF
8254!
8255!--             Next emission update
8256                next_aero_emission_update = MOD( time_utc_init, 3600.0_wp ) - 3600.0_wp
8257!
8258!--             Get chemical composition (i.e. mass fraction of different species) in aerosols
8259                ALLOCATE( aero_emission%def_mass_fracs(1:aero_emission_att%ncat,                   &
8260                                                       1:aero_emission_att%ncc) )
8261                aero_emission%def_mass_fracs = 0.0_wp
8262                CALL get_variable( id_salsa, 'emission_mass_fracs', aero_emission%def_mass_fracs,  &
8263                                   0, aero_emission_att%ncc-1, 0, aero_emission_att%ncat-1 )
8264!
8265!--             If the chemical component is not activated, set its mass fraction to 0 to avoid
8266!--             inbalance between number and mass flux
8267                cc_i2m = aero_emission_att%cc_input_to_model
8268                IF ( index_so4 < 0  .AND.  cc_i2m(1) /= 0 )                                        &
8269                                                  aero_emission%def_mass_fracs(:,cc_i2m(1)) = 0.0_wp
8270                IF ( index_oc  < 0  .AND.  cc_i2m(2) /= 0 )                                        &
8271                                                  aero_emission%def_mass_fracs(:,cc_i2m(2)) = 0.0_wp
8272                IF ( index_bc  < 0  .AND.  cc_i2m(3) /= 0 )                                        &
8273                                                  aero_emission%def_mass_fracs(:,cc_i2m(3)) = 0.0_wp
8274                IF ( index_du  < 0  .AND.  cc_i2m(4) /= 0 )                                        &
8275                                                  aero_emission%def_mass_fracs(:,cc_i2m(4)) = 0.0_wp
8276                IF ( index_ss  < 0  .AND.  cc_i2m(5) /= 0 )                                        &
8277                                                  aero_emission%def_mass_fracs(:,cc_i2m(5)) = 0.0_wp
8278                IF ( index_no  < 0  .AND.  cc_i2m(6) /= 0 )                                        &
8279                                                  aero_emission%def_mass_fracs(:,cc_i2m(6)) = 0.0_wp
8280                IF ( index_nh  < 0  .AND.  cc_i2m(7) /= 0 )                                        &
8281                                                  aero_emission%def_mass_fracs(:,cc_i2m(7)) = 0.0_wp
8282!
8283!--             Then normalise the mass fraction so that SUM = 1
8284                DO  in = 1, aero_emission_att%ncat
8285                   aero_emission%def_mass_fracs(in,:) = aero_emission%def_mass_fracs(in,:) /       &
8286                                                       SUM( aero_emission%def_mass_fracs(in,:) )
8287                ENDDO
8288!
8289!--             Calculate average mass density (kg/m3)
8290                aero_emission_att%rho = 0.0_wp
8291
8292                IF ( cc_i2m(1) /= 0 )  aero_emission_att%rho = aero_emission_att%rho +  arhoh2so4 *&
8293                                                           aero_emission%def_mass_fracs(:,cc_i2m(1))
8294                IF ( cc_i2m(2) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhooc *    &
8295                                                           aero_emission%def_mass_fracs(:,cc_i2m(2))
8296                IF ( cc_i2m(3) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhobc *    &
8297                                                           aero_emission%def_mass_fracs(:,cc_i2m(3))
8298                IF ( cc_i2m(4) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhodu *    &
8299                                                           aero_emission%def_mass_fracs(:,cc_i2m(4))
8300                IF ( cc_i2m(5) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhoss *    &
8301                                                           aero_emission%def_mass_fracs(:,cc_i2m(5))
8302                IF ( cc_i2m(6) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhohno3 *  &
8303                                                           aero_emission%def_mass_fracs(:,cc_i2m(6))
8304                IF ( cc_i2m(7) /= 0 )  aero_emission_att%rho = aero_emission_att%rho + arhonh3 *   &
8305                                                           aero_emission%def_mass_fracs(:,cc_i2m(7))
8306!
8307!--             Allocate and read surface emission data (in total PM)
8308                ALLOCATE( aero_emission%def_data(nys:nyn,nxl:nxr,1:aero_emission_att%ncat) )
8309                CALL get_variable( id_salsa, 'aerosol_emission_values', aero_emission%def_data,    &
8310                                   0, aero_emission_att%ncat-1, nxl, nxr, nys, nyn )
8311
8312!
8313!--          Pre-processed mode
8314             ELSEIF ( aero_emission_att%lod == 2 )  THEN
8315!
8316!--             Unit conversion factor: convert to SI units (#/m2/s)
8317                IF ( aero_emission_att%units == '#/m2/s' )  THEN
8318                   aero_emission_att%conversion_factor = 1.0_wp
8319                ELSE
8320                   message_string = 'unknown unit for aerosol emissions: ' //                      &
8321                                    TRIM( aero_emission_att%units )
8322                   CALL message( 'salsa_emission_setup','PA0634', 1, 2, 0, 6, 0 )
8323                ENDIF
8324!
8325!--             Number of aerosol size bins in the emission data
8326                CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%nbins,    &
8327                                                             'Dmid' )
8328                IF ( aero_emission_att%nbins /= nbins_aerosol )  THEN
8329                   message_string = 'The number of size bins in aerosol input data does not ' //   &
8330                                    'correspond to the model set-up'
8331                   CALL message( 'salsa_emission_setup','PA0635', 1, 2, 0, 6, 0 )
8332                ENDIF
8333!
8334!--             Number of time steps in the emission data
8335                CALL netcdf_data_input_get_dimension_length( id_salsa, aero_emission_att%nt, 'time')
8336!
8337!--             Allocate bin diameters, time and mass fraction array
8338                ALLOCATE( aero_emission_att%dmid(1:nbins_aerosol),                                 &
8339                          aero_emission_att%time(1:aero_emission_att%nt),                          &
8340                          aero_emission%preproc_mass_fracs(1:aero_emission_att%ncc) )
8341!
8342!--             Read mean diameters
8343                CALL get_variable( id_salsa, 'Dmid', aero_emission_att%dmid )
8344!
8345!--             Check whether the sectional representation of the aerosol size distribution conform
8346!--             to the one applied in the model
8347                IF ( ANY( ABS( ( aero(1:nbins_aerosol)%dmid - aero_emission_att%dmid ) /           &
8348                               aero(1:nbins_aerosol)%dmid ) > 0.1_wp )  )  THEN
8349                   message_string = 'Mean diameters of size bins in ' // TRIM( input_file_salsa )  &
8350                                    // ' do not match with the ones in the model.'
8351                   CALL message( 'salsa_emission_setup','PA0636', 1, 2, 0, 6, 0 )
8352                ENDIF
8353!
8354!--             Read time stamps:
8355                CALL get_variable( id_salsa, 'time', aero_emission_att%time )
8356!
8357!--             Read emission mass fractions
8358                CALL get_variable( id_salsa, 'emission_mass_fracs', aero_emission%preproc_mass_fracs )
8359!
8360!--             If the chemical component is not activated, set its mass fraction to 0
8361                cc_i2m = aero_emission_att%cc_input_to_model
8362                IF ( index_so4 < 0  .AND.  cc_i2m(1) /= 0 )                                        &
8363                   aero_emission%preproc_mass_fracs(cc_i2m(1)) = 0.0_wp
8364                IF ( index_oc  < 0  .AND.  cc_i2m(2) /= 0 )                                        &
8365                   aero_emission%preproc_mass_fracs(cc_i2m(2)) = 0.0_wp
8366                IF ( index_bc  < 0  .AND.  cc_i2m(3) /= 0 )                                        &
8367                   aero_emission%preproc_mass_fracs(cc_i2m(3)) = 0.0_wp
8368                IF ( index_du  < 0  .AND.  cc_i2m(4) /= 0 )                                        &
8369                   aero_emission%preproc_mass_fracs(cc_i2m(4)) = 0.0_wp
8370                IF ( index_ss  < 0  .AND.  cc_i2m(5) /= 0 )                                        &
8371                   aero_emission%preproc_mass_fracs(cc_i2m(5)) = 0.0_wp
8372                IF ( index_no  < 0  .AND.  cc_i2m(6) /= 0 )                                        &
8373                   aero_emission%preproc_mass_fracs(cc_i2m(6)) = 0.0_wp
8374                IF ( index_nh  < 0  .AND.  cc_i2m(7) /= 0 )                                        &
8375                   aero_emission%preproc_mass_fracs(cc_i2m(7)) = 0.0_wp
8376!
8377!--             Then normalise the mass fraction so that SUM = 1
8378                aero_emission%preproc_mass_fracs = aero_emission%preproc_mass_fracs /              &
8379                                                   SUM( aero_emission%preproc_mass_fracs )
8380
8381             ELSE
8382                message_string = 'Unknown lod for aerosol_emission_values.'
8383                CALL message( 'salsa_emission','PA0637', 1, 2, 0, 6, 0 )
8384             ENDIF
8385
8386          ENDIF  ! init
8387!
8388!--       Define and set current emission values:
8389!
8390!--       Default type emissions (aerosol emission given as total mass emission per year):
8391          IF ( aero_emission_att%lod == 1 )  THEN
8392!
8393!--          Emission time factors for each emission category at current time step
8394             IF ( aero_emission_att%nhoursyear > aero_emission_att%nmonthdayhour )  THEN
8395!
8396!--             Get the index of the current hour
8397                CALL time_default_indices( month_of_year, day_of_month, hour_of_day, index_hh )
8398                aero_emission_att%time_factor = aero_emission_att%etf(:,index_hh)
8399
8400             ELSEIF ( aero_emission_att%nhoursyear < aero_emission_att%nmonthdayhour )  THEN
8401!
8402!--             Get the index of current hour (index_hh) (TODO: Now "workday" is always assumed.
8403!--             Needs to be calculated.)
8404                CALL time_default_indices( daytype, month_of_year, day_of_month, hour_of_day,      &
8405                                           index_mm, index_dd, index_hh )
8406                aero_emission_att%time_factor = aero_emission_att%etf(:,index_mm) *                &
8407                                                aero_emission_att%etf(:,index_dd) *                &
8408                                                aero_emission_att%etf(:,index_hh)
8409             ENDIF
8410
8411!
8412!--          Create a sectional number size distribution for emissions
8413             ALLOCATE( nsect_emission(1:nbins_aerosol),source_array(nys:nyn,nxl:nxr,1:nbins_aerosol) )
8414             DO  in = 1, aero_emission_att%ncat
8415
8416                inn = def_modes%cat_input_to_model(in)
8417!
8418!--             Calculate the number concentration (1/m3) of a log-normal size distribution
8419!--             following Jacobson (2005): Eq 13.25.
8420                def_modes%ntot_table = 6.0_wp * def_modes%pm_frac_table(:,inn) / ( pi *            &
8421                                       ( def_modes%dpg_table )**3 *  EXP( 4.5_wp *                 &
8422                                       LOG( def_modes%sigmag_table )**2 ) )
8423!
8424!--             Sectional size distibution (1/m3) from a log-normal one
8425                CALL size_distribution( def_modes%ntot_table, def_modes%dpg_table,                 &
8426                                        def_modes%sigmag_table, nsect_emission )
8427
8428                source_array = 0.0_wp
8429                DO  ib = 1, nbins_aerosol
8430                   source_array(:,:,ib) = aero_emission%def_data(:,:,in) *                         &
8431                                          aero_emission_att%conversion_factor /                    &
8432                                          aero_emission_att%rho(in) * nsect_emission(ib) *         &
8433                                          aero_emission_att%time_factor(in)
8434                ENDDO
8435!
8436!--             Set surface fluxes of aerosol number and mass on horizontal surfaces. Set fluxes
8437!--             only for either default, land or urban surface.
8438                IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
8439                   CALL set_flux( surf_def_h(0), aero_emission_att%cc_input_to_model,              &
8440                                  aero_emission%def_mass_fracs(in,:), source_array )
8441                ELSE
8442                   CALL set_flux( surf_usm_h, aero_emission_att%cc_input_to_model,                 &
8443                                  aero_emission%def_mass_fracs(in,:), source_array )
8444                   CALL set_flux( surf_lsm_h, aero_emission_att%cc_input_to_model,                 &
8445                                  aero_emission%def_mass_fracs(in,:), source_array )
8446                ENDIF
8447             ENDDO
8448!
8449!--          The next emission update is again after one hour
8450             next_aero_emission_update = next_aero_emission_update + 3600.0_wp
8451
8452
8453             DEALLOCATE( source_array )
8454!
8455!--       Pre-processed:
8456          ELSEIF ( aero_emission_att%lod == 2 )  THEN
8457!
8458!--          Obtain time index for current input starting at 0.
8459!--          @todo: At the moment emission data and simulated time correspond to each other.
8460             aero_emission_att%tind = MINLOC( ABS( aero_emission_att%time -                        &
8461                                                   time_since_reference_point ), DIM = 1 ) - 1
8462!
8463!--          Allocate the data input array always before reading in the data and deallocate after
8464             ALLOCATE( aero_emission%preproc_data(nys:nyn,nxl:nxr,1:nbins_aerosol) )
8465!
8466!--          Read in the next time step
8467             CALL get_variable( id_salsa, 'aerosol_emission_values', aero_emission%preproc_data,&
8468                                aero_emission_att%tind, 0, nbins_aerosol-1, nxl, nxr, nys, nyn )
8469!
8470!--          Set surface fluxes of aerosol number and mass on horizontal surfaces. Set fluxes only
8471!--          for either default, land and urban surface.
8472             IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
8473                CALL set_flux( surf_def_h(0), aero_emission_att%cc_input_to_model,                 &
8474                               aero_emission%preproc_mass_fracs, aero_emission%preproc_data )
8475             ELSE
8476                CALL set_flux( surf_usm_h, aero_emission_att%cc_input_to_model,                    &
8477                               aero_emission%preproc_mass_fracs, aero_emission%preproc_data )
8478                CALL set_flux( surf_lsm_h, aero_emission_att%cc_input_to_model,                    &
8479                               aero_emission%preproc_mass_fracs, aero_emission%preproc_data )
8480             ENDIF
8481!
8482!--          Determine the next emission update
8483             next_aero_emission_update = aero_emission_att%time(aero_emission_att%tind+2)
8484
8485             DEALLOCATE( aero_emission%preproc_data )
8486
8487          ENDIF
8488
8489#else
8490          message_string = 'salsa_emission_mode = "read_from_file", but preprocessor directive ' //&
8491                           ' __netcdf is not used in compiling!'
8492          CALL message( 'salsa_emission_setup', 'PA0638', 1, 2, 0, 6, 0 )
8493
8494#endif
8495       CASE DEFAULT
8496          message_string = 'unknown salsa_emission_mode: ' // TRIM( salsa_emission_mode )
8497          CALL message( 'salsa_emission_setup', 'PA0639', 1, 2, 0, 6, 0 )
8498
8499    END SELECT
8500
8501    CONTAINS
8502
8503!------------------------------------------------------------------------------!
8504! Description:
8505! ------------
8506!> Sets the aerosol flux to aerosol arrays in 2a and 2b.
8507!------------------------------------------------------------------------------!
8508    SUBROUTINE set_flux( surface, cc_i_mod, mass_fracs, source_array )
8509
8510       USE arrays_3d,                                                                              &
8511           ONLY:  rho_air_zw
8512
8513       USE surface_mod,                                                                            &
8514           ONLY:  surf_type
8515
8516       IMPLICIT NONE
8517
8518       INTEGER(iwp) ::  i   !< loop index
8519       INTEGER(iwp) ::  ib  !< loop index
8520       INTEGER(iwp) ::  ic  !< loop index
8521       INTEGER(iwp) ::  j   !< loop index
8522       INTEGER(iwp) ::  k   !< loop index
8523       INTEGER(iwp) ::  m   !< running index for surface elements
8524
8525       INTEGER(iwp), DIMENSION(:) ::  cc_i_mod   !< index of chemical component in the input data
8526
8527       REAL(wp) ::  so4_oc  !< mass fraction between SO4 and OC in 1a
8528
8529       REAL(wp), DIMENSION(:), INTENT(in) ::  mass_fracs  !< mass fractions of chemical components
8530
8531       REAL(wp), DIMENSION(nys:nyn,nxl:nxr,1:nbins_aerosol), INTENT(inout) ::  source_array  !<
8532
8533       TYPE(surf_type), INTENT(inout) :: surface  !< respective surface type
8534
8535       so4_oc = 0.0_wp
8536
8537       DO  m = 1, surface%ns
8538!
8539!--       Get indices of respective grid point
8540          i = surface%i(m)
8541          j = surface%j(m)
8542          k = surface%k(m)
8543
8544          DO  ib = 1, nbins_aerosol
8545             IF ( source_array(j,i,ib) < nclim )  THEN
8546                source_array(j,i,ib) = 0.0_wp
8547             ENDIF
8548!
8549!--          Set mass fluxes.  First bins include only SO4 and/or OC.
8550             IF ( ib <= end_subrange_1a )  THEN
8551!
8552!--             Both sulphate and organic carbon
8553                IF ( index_so4 > 0  .AND.  index_oc > 0 )  THEN
8554
8555                   ic = ( index_so4 - 1 ) * nbins_aerosol + ib
8556                   so4_oc = mass_fracs(cc_i_mod(1)) / ( mass_fracs(cc_i_mod(1)) +                  &
8557                                                        mass_fracs(cc_i_mod(2)) )
8558                   surface%amsws(m,ic) = surface%amsws(m,ic) + so4_oc * source_array(j,i,ib)       &
8559                                         * api6 * aero(ib)%dmid**3 * arhoh2so4 * rho_air_zw(k-1)
8560                   aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(m,ic)
8561
8562                   ic = ( index_oc - 1 ) * nbins_aerosol + ib
8563                   surface%amsws(m,ic) = surface%amsws(m,ic) + ( 1-so4_oc ) * source_array(j,i,ib) &
8564                                         * api6 * aero(ib)%dmid**3 * arhooc * rho_air_zw(k-1)
8565                   aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(m,ic)
8566!
8567!--             Only sulphates
8568                ELSEIF ( index_so4 > 0  .AND.  index_oc < 0 )  THEN
8569                   ic = ( index_so4 - 1 ) * nbins_aerosol + ib
8570                   surface%amsws(m,ic) = surface%amsws(m,ic) + source_array(j,i,ib) * api6 *       &
8571                                         aero(ib)%dmid**3 * arhoh2so4 * rho_air_zw(k-1)
8572                   aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(m,ic)
8573!
8574!--             Only organic carbon
8575                ELSEIF ( index_so4 < 0  .AND.  index_oc > 0 )  THEN
8576                   ic = ( index_oc - 1 ) * nbins_aerosol + ib
8577                   surface%amsws(m,ic) = surface%amsws(m,ic) + source_array(j,i,ib) * api6 *       &
8578                                         aero(ib)%dmid**3 * arhooc * rho_air_zw(k-1)
8579                   aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(m,ic)
8580                ENDIF
8581
8582             ELSE
8583!
8584!--             Sulphate
8585                IF ( index_so4 > 0 )  THEN
8586                   ic = cc_i_mod(1)
8587                   CALL set_mass_flux( surface, m, ib, index_so4, mass_fracs(ic), arhoh2so4,       &
8588                                       source_array(j,i,ib) )
8589                ENDIF
8590!
8591!--             Organic carbon
8592                IF ( index_oc > 0 )  THEN
8593                   ic = cc_i_mod(2)
8594                   CALL set_mass_flux( surface, m, ib, index_oc, mass_fracs(ic),arhooc,            &
8595                                       source_array(j,i,ib) )
8596                ENDIF
8597!
8598!--             Black carbon
8599                IF ( index_bc > 0 )  THEN
8600                   ic = cc_i_mod(3)
8601                   CALL set_mass_flux( surface, m, ib, index_bc, mass_fracs(ic), arhobc,           &
8602                                       source_array(j,i,ib) )
8603                ENDIF
8604!
8605!--             Dust
8606                IF ( index_du > 0 )  THEN
8607                   ic = cc_i_mod(4)
8608                   CALL set_mass_flux( surface, m, ib, index_du, mass_fracs(ic), arhodu,           &
8609                                       source_array(j,i,ib) )
8610                ENDIF
8611!
8612!--             Sea salt
8613                IF ( index_ss > 0 )  THEN
8614                   ic = cc_i_mod(5)
8615                   CALL set_mass_flux( surface, m, ib, index_ss, mass_fracs(ic), arhoss,           &
8616                                       source_array(j,i,ib) )
8617                ENDIF
8618!
8619!--             Nitric acid
8620                IF ( index_no > 0 )  THEN
8621                    ic = cc_i_mod(6)
8622                   CALL set_mass_flux( surface, m, ib, index_no, mass_fracs(ic), arhohno3,         &
8623                                       source_array(j,i,ib) )
8624                ENDIF
8625!
8626!--             Ammonia
8627                IF ( index_nh > 0 )  THEN
8628                    ic = cc_i_mod(7)
8629                   CALL set_mass_flux( surface, m, ib, index_nh, mass_fracs(ic), arhonh3,          &
8630                                       source_array(j,i,ib) )
8631                ENDIF
8632
8633             ENDIF
8634!
8635!--          Save number fluxes in the end
8636             surface%answs(m,ib) = surface%answs(m,ib) + source_array(j,i,ib) * rho_air_zw(k-1)
8637             aerosol_number(ib)%source(j,i) = aerosol_number(ib)%source(j,i) + surface%answs(m,ib)
8638
8639          ENDDO  ! ib
8640       ENDDO  ! m
8641
8642    END SUBROUTINE set_flux
8643
8644!------------------------------------------------------------------------------!
8645! Description:
8646! ------------
8647!> Sets the mass emissions to aerosol arrays in 2a and 2b.
8648!------------------------------------------------------------------------------!
8649    SUBROUTINE set_mass_flux( surface, surf_num, ib, ispec, mass_frac, prho, nsource )
8650
8651       USE arrays_3d,                                                                              &
8652           ONLY:  rho_air_zw
8653
8654       USE surface_mod,                                                                            &
8655           ONLY:  surf_type
8656
8657       IMPLICIT NONE
8658
8659       INTEGER(iwp) ::  i   !< loop index
8660       INTEGER(iwp) ::  j   !< loop index
8661       INTEGER(iwp) ::  k   !< loop index
8662       INTEGER(iwp) ::  ic  !< loop index
8663
8664       INTEGER(iwp), INTENT(in) :: ib        !< Aerosol size bin index
8665       INTEGER(iwp), INTENT(in) :: ispec     !< Aerosol species index
8666       INTEGER(iwp), INTENT(in) :: surf_num  !< index surface elements
8667
8668       REAL(wp), INTENT(in) ::  mass_frac    !< mass fraction of a chemical compound in all bins
8669       REAL(wp), INTENT(in) ::  nsource      !< number source (#/m2/s)
8670       REAL(wp), INTENT(in) ::  prho         !< Aerosol density
8671
8672       TYPE(surf_type), INTENT(inout) ::  surface  !< respective surface type
8673!
8674!--    Get indices of respective grid point
8675       i = surface%i(surf_num)
8676       j = surface%j(surf_num)
8677       k = surface%k(surf_num)
8678!
8679!--    Subrange 2a:
8680       ic = ( ispec - 1 ) * nbins_aerosol + ib
8681       surface%amsws(surf_num,ic) = surface%amsws(surf_num,ic) + mass_frac * nsource *             &
8682                                    aero(ib)%core * prho * rho_air_zw(k-1)
8683       aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(surf_num,ic)
8684!
8685!--    Subrange 2b:
8686       IF ( .NOT. no_insoluble )  THEN
8687          CALL location_message( '    salsa_mass_flux: All emissions are soluble!', .TRUE. )
8688       ENDIF
8689
8690    END SUBROUTINE set_mass_flux
8691
8692 END SUBROUTINE salsa_emission_setup
8693
8694!------------------------------------------------------------------------------!
8695! Description:
8696! ------------
8697!> Sets the gaseous fluxes
8698!------------------------------------------------------------------------------!
8699 SUBROUTINE salsa_gas_emission_setup( init )
8700
8701    USE control_parameters,                                                                        &
8702        ONLY:  time_since_reference_point
8703
8704    USE date_and_time_mod,                                                                         &
8705        ONLY:  day_of_month, hour_of_day, index_dd, index_hh, index_mm, month_of_year,             &
8706               time_default_indices, time_utc_init
8707
8708    USE netcdf_data_input_mod,                                                                     &
8709        ONLY:  check_existence, chem_emis_att_type, chem_emis_val_type, get_attribute,             &
8710               get_variable, inquire_num_variables, inquire_variable_names,                        &
8711               netcdf_data_input_get_dimension_length, open_read_file
8712
8713    USE surface_mod,                                                                               &
8714        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
8715
8716    IMPLICIT NONE
8717
8718    CHARACTER(LEN=80) ::  daytype = 'workday'  !< default day type
8719    CHARACTER(LEN=25) ::  in_name              !< name of a gas in the input file
8720
8721    CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names   !<  variable names in input data
8722
8723    INTEGER(iwp) ::  id_chem        !< NetCDF id of chemistry emission file
8724    INTEGER(iwp) ::  ig             !< loop index
8725    INTEGER(iwp) ::  in             !< running index for emission categories
8726    INTEGER(iwp) ::  num_vars       !< number of variables
8727
8728    LOGICAL  ::  netcdf_extend = .FALSE.  !< NetCDF input file exists
8729
8730    LOGICAL, INTENT(in) ::  init          !< if .TRUE. --> initialisation call
8731
8732    REAL(wp), DIMENSION(:), ALLOCATABLE ::  time_factor  !< emission time factor
8733
8734    TYPE(chem_emis_att_type) ::  chem_emission_att  !< chemistry emission attributes
8735    TYPE(chem_emis_val_type) ::  chem_emission      !< chemistry emission values
8736
8737!
8738!-- Reset surface fluxes
8739    surf_def_h(0)%gtsws = 0.0_wp
8740    surf_lsm_h%gtsws = 0.0_wp
8741    surf_usm_h%gtsws = 0.0_wp
8742
8743#if defined( __netcdf )
8744    IF ( init )  THEN
8745!
8746!--    Check existence of PIDS_CHEM file
8747       INQUIRE( FILE = 'PIDS_CHEM' // TRIM( coupling_char ), EXIST = netcdf_extend )
8748       IF ( .NOT. netcdf_extend )  THEN
8749          message_string = 'Input file PIDS_CHEM' //  TRIM( coupling_char ) // ' missing!'
8750          CALL message( 'salsa_gas_emission_setup', 'PA0640', 1, 2, 0, 6, 0 )
8751       ENDIF
8752!
8753!--    Open file in read-only mode
8754       CALL open_read_file( 'PIDS_CHEM' // TRIM( coupling_char ), id_chem )
8755!
8756!--    Read the index and name of chemical components
8757       CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%nspec,              &
8758                                                    'nspecies' )
8759       ALLOCATE( chem_emission_att%species_index(1:chem_emission_att%nspec) )
8760       CALL get_variable( id_chem, 'emission_index', chem_emission_att%species_index )
8761       CALL get_variable( id_chem, 'emission_name', chem_emission_att%species_name,                &
8762                          chem_emission_att%nspec )
8763!
8764!--    Find the corresponding indices in the model
8765       emission_index_chem = 0
8766       DO  ig = 1, chem_emission_att%nspec
8767          in_name = chem_emission_att%species_name(ig)
8768          SELECT CASE ( TRIM( in_name ) )
8769             CASE ( 'H2SO4', 'h2so4' )
8770                emission_index_chem(1) = ig
8771             CASE ( 'HNO3', 'hno3' )
8772                emission_index_chem(2) = ig
8773             CASE ( 'NH3', 'nh3' )
8774                emission_index_chem(3) = ig
8775             CASE ( 'OCNV', 'ocnv' )
8776                emission_index_chem(4) = ig
8777             CASE ( 'OCSV', 'ocsv' )
8778                emission_index_chem(5) = ig
8779          END SELECT
8780       ENDDO
8781       IF ( SUM( emission_index_chem ) == 0 )  THEN
8782          CALL location_message( '    salsa_gas_emission_setup: no gas emissions', .TRUE. )
8783       ENDIF
8784!
8785!--    Inquire the fill value
8786       CALL get_attribute( id_chem, '_FillValue', aero_emission%fill, .FALSE., 'emission_values' )
8787!
8788!--    Inquire units of emissions
8789       CALL get_attribute( id_chem, 'units', chem_emission_att%units, .FALSE., 'emission_values' )
8790!
8791!--    Inquire the level of detail (lod)
8792       CALL get_attribute( id_chem, 'lod', lod_gas_emissions, .FALSE., 'emission_values' )
8793!
8794!--    Variable names
8795       CALL inquire_num_variables( id_chem, num_vars )
8796       ALLOCATE( var_names(1:num_vars) )
8797       CALL inquire_variable_names( id_chem, var_names )
8798!
8799!--    Default mode: as total emissions per year
8800       IF ( lod_gas_emissions == 1 )  THEN
8801
8802!
8803!--       Get number of emission categories and allocate emission arrays
8804          CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%ncat, 'ncat' )
8805          ALLOCATE( chem_emission_att%cat_index(1:chem_emission_att%ncat),                         &
8806                    time_factor(1:chem_emission_att%ncat) )
8807!
8808!--       Get emission category names and indices
8809          CALL get_variable( id_chem, 'emission_category_name', chem_emission_att%cat_name,        &
8810                             chem_emission_att%ncat)
8811          CALL get_variable( id_chem, 'emission_category_index', chem_emission_att%cat_index )
8812!
8813!--       Emission time factors: Find check whether emission time factors are given for each hour
8814!--       of year OR based on month, day and hour
8815!
8816!--       For each hour of year:
8817          IF ( check_existence( var_names, 'nhoursyear' ) )  THEN
8818             CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%nhoursyear,   &
8819                                                          'nhoursyear' )
8820             ALLOCATE( chem_emission_att%hourly_emis_time_factor(1:chem_emission_att%ncat,         &
8821                                                                 1:chem_emission_att%nhoursyear) )
8822             CALL get_variable( id_chem, 'emission_time_factors',                                  &
8823                                chem_emission_att%hourly_emis_time_factor,                         &
8824                                0, chem_emission_att%nhoursyear-1, 0, chem_emission_att%ncat-1 )
8825!
8826!--       Based on the month, day and hour:
8827          ELSEIF ( check_existence( var_names, 'nmonthdayhour' ) )  THEN
8828             CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%nmonthdayhour,&
8829                                                          'nmonthdayhour' )
8830             ALLOCATE( chem_emission_att%mdh_emis_time_factor(1:chem_emission_att%ncat,            &
8831                                                              1:chem_emission_att%nmonthdayhour) )
8832             CALL get_variable( id_chem, 'emission_time_factors',                                  &
8833                                chem_emission_att%mdh_emis_time_factor,                            &
8834                                0, chem_emission_att%nmonthdayhour-1, 0, chem_emission_att%ncat-1 )
8835          ELSE
8836             message_string = 'emission_time_factors should be given for each nhoursyear OR ' //   &
8837                              'nmonthdayhour'
8838             CALL message( 'salsa_gas_emission_setup','PA0641', 1, 2, 0, 6, 0 )
8839          ENDIF
8840!
8841!--       Next emission update
8842          next_gas_emission_update = MOD( time_utc_init, 3600.0_wp ) - 3600.0_wp
8843!
8844!--       Allocate and read surface emission data (in total PM) (NOTE that "preprocessed" input data
8845!--       array is applied now here)
8846          ALLOCATE( chem_emission%preproc_emission_data(nys:nyn,nxl:nxr, 1:chem_emission_att%nspec,&
8847                                                        1:chem_emission_att%ncat) )
8848          CALL get_variable( id_chem, 'emission_values', chem_emission%preproc_emission_data,      &
8849                             0, chem_emission_att%ncat-1, 0, chem_emission_att%nspec-1,            &
8850                             nxl, nxr, nys, nyn )
8851!
8852!--    Pre-processed mode:
8853       ELSEIF ( lod_gas_emissions == 2 )  THEN
8854!
8855!--       Number of time steps in the emission data
8856          CALL netcdf_data_input_get_dimension_length( id_chem, chem_emission_att%dt_emission,     &
8857                                                       'time' )
8858!
8859!--       Allocate and read time
8860          ALLOCATE( gas_emission_time(1:chem_emission_att%dt_emission) )
8861          CALL get_variable( id_chem, 'time', gas_emission_time )
8862       ELSE
8863          message_string = 'Unknown lod for emission_values.'
8864          CALL message( 'salsa_gas_emission_setup','PA0642', 1, 2, 0, 6, 0 )
8865       ENDIF  ! lod
8866
8867    ENDIF  ! init
8868!
8869!-- Define and set current emission values:
8870
8871    IF ( lod_gas_emissions == 1 )  THEN
8872!
8873!--    Emission time factors for each emission category at current time step
8874       IF ( chem_emission_att%nhoursyear > chem_emission_att%nmonthdayhour )  THEN
8875!
8876!--       Get the index of the current hour
8877          CALL time_default_indices( month_of_year, day_of_month, hour_of_day, index_hh )
8878          time_factor = chem_emission_att%hourly_emis_time_factor(:,index_hh)
8879
8880       ELSEIF ( chem_emission_att%nhoursyear < chem_emission_att%nmonthdayhour )  THEN
8881!
8882!--       Get the index of current hour (index_hh) (TODO: Now "workday" is always assumed.
8883!--       Needs to be calculated.)
8884          CALL time_default_indices( daytype, month_of_year, day_of_month, hour_of_day,            &
8885                                     index_mm, index_dd, index_hh )
8886          time_factor = chem_emission_att%mdh_emis_time_factor(:,index_mm) *                       &
8887                        chem_emission_att%mdh_emis_time_factor(:,index_dd) *                       &
8888                        chem_emission_att%mdh_emis_time_factor(:,index_hh)
8889       ENDIF
8890!
8891!--    Set gas emissions for each emission category
8892       DO  in = 1, chem_emission_att%ncat
8893!
8894!--       Set surface fluxes only for either default, land or urban surface
8895          IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
8896             CALL set_gas_flux( surf_def_h(0), emission_index_chem, chem_emission_att%units,       &
8897                                chem_emission%preproc_emission_data(:,:,:,in), time_factor(in) )
8898          ELSE
8899             CALL set_gas_flux( surf_usm_h, emission_index_chem, chem_emission_att%units,          &
8900                                chem_emission%preproc_emission_data(:,:,:,in), time_factor(in) )
8901             CALL set_gas_flux( surf_lsm_h, emission_index_chem, chem_emission_att%units,          &
8902                                chem_emission%preproc_emission_data(:,:,:,in), time_factor(in) )
8903          ENDIF
8904       ENDDO
8905!
8906!--    The next emission update is again after one hour
8907       next_gas_emission_update = next_gas_emission_update + 3600.0_wp
8908
8909    ELSEIF ( lod_gas_emissions == 2 )  THEN
8910!
8911!--    Obtain time index for current input starting at 0.
8912!--    @todo: At the moment emission data and simulated time correspond to each other.
8913       chem_emission_att%i_hour = MINLOC( ABS( gas_emission_time - time_since_reference_point ),   &
8914                                          DIM = 1 ) - 1
8915!
8916!--    Allocate the data input array always before reading in the data and deallocate after (NOTE
8917!--    that "preprocessed" input data array is applied now here)
8918       ALLOCATE( chem_emission%default_emission_data(nys:nyn,nxl:nxr,1:nbins_aerosol) )
8919!
8920!--    Read in the next time step
8921       CALL get_variable( id_chem, 'emission_values', chem_emission%default_emission_data,         &
8922                          chem_emission_att%i_hour, 0, chem_emission_att%nspec-1, nxl, nxr, nys, nyn )
8923!
8924!--    Set surface fluxes only for either default, land or urban surface
8925       IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
8926          CALL set_gas_flux( surf_def_h(0), emission_index_chem, chem_emission_att%units,          &
8927                             chem_emission%default_emission_data )
8928       ELSE
8929          CALL set_gas_flux( surf_usm_h, emission_index_chem, chem_emission_att%units,             &
8930                             chem_emission%default_emission_data )
8931          CALL set_gas_flux( surf_lsm_h, emission_index_chem, chem_emission_att%units,             &
8932                             chem_emission%default_emission_data )
8933       ENDIF
8934!
8935!--    Determine the next emission update
8936       next_gas_emission_update = gas_emission_time(chem_emission_att%i_hour+2)
8937
8938       DEALLOCATE( chem_emission%default_emission_data )
8939    ENDIF
8940#else
8941    message_string = 'salsa_emission_mode = "read_from_file", but preprocessor directive ' //   &
8942                     ' __netcdf is not used in compiling!'
8943    CALL message( 'salsa_gas_emission_setup', 'PA0643', 1, 2, 0, 6, 0 )
8944
8945#endif
8946
8947    CONTAINS
8948!------------------------------------------------------------------------------!
8949! Description:
8950! ------------
8951!> Set gas fluxes for selected type of surfaces
8952!------------------------------------------------------------------------------!
8953    SUBROUTINE set_gas_flux( surface, cc_i_mod, unit, source_array, time_fac )
8954
8955       USE arrays_3d,                                                                              &
8956           ONLY: dzw, hyp, pt, rho_air_zw
8957
8958       USE grid_variables,                                                                         &
8959           ONLY:  dx, dy
8960
8961       USE surface_mod,                                                                            &
8962           ONLY:  surf_type
8963
8964       IMPLICIT NONE
8965
8966       CHARACTER(LEN=*), INTENT(in) ::  unit  !< flux unit in the input file
8967
8968       INTEGER(iwp) ::  ig  !< running index for gases
8969       INTEGER(iwp) ::  i   !< loop index
8970       INTEGER(iwp) ::  j   !< loop index
8971       INTEGER(iwp) ::  k   !< loop index
8972       INTEGER(iwp) ::  m   !< running index for surface elements
8973
8974       INTEGER(iwp), DIMENSION(:) ::  cc_i_mod   !< index of different gases in the input data
8975
8976       LOGICAL ::  use_time_fac  !< .TRUE. is time_fac present
8977
8978       REAL(wp), OPTIONAL ::  time_fac  !< emission time factor
8979
8980       REAL(wp), DIMENSION(ngases_salsa) ::  conv     !< unit conversion factor
8981
8982       REAL(wp), DIMENSION(nys:nyn,nxl:nxr,chem_emission_att%nspec), INTENT(in) ::  source_array  !<
8983
8984       TYPE(surf_type), INTENT(inout) :: surface  !< respective surface type
8985
8986       use_time_fac = PRESENT( time_fac )
8987
8988       DO  m = 1, surface%ns
8989!
8990!--       Get indices of respective grid point
8991          i = surface%i(m)
8992          j = surface%j(m)
8993          k = surface%k(m)
8994!
8995!--       Unit conversion factor: convert to SI units (#/m2/s)
8996          SELECT CASE ( TRIM( unit ) )
8997             CASE ( 'kg/m2/yr' )
8998                conv(1) = avo / ( amh2so4 * 3600.0_wp )
8999                conv(2) = avo / ( amhno3 * 3600.0_wp )
9000                conv(3) = avo / ( amnh3 * 3600.0_wp )
9001                conv(4) = avo / ( amoc * 3600.0_wp )
9002                conv(5) = avo / ( amoc * 3600.0_wp )
9003             CASE ( 'g/m2/yr' )
9004                conv(1) = avo / ( amh2so4 * 3.6E+6_wp )
9005                conv(2) = avo / ( amhno3 * 3.6E+6_wp )
9006                conv(3) = avo / ( amnh3 * 3.6E+6_wp )
9007                conv(4) = avo / ( amoc * 3.6E+6_wp )
9008                conv(5) = avo / ( amoc * 3.6E+6_wp )
9009             CASE ( 'g/m2/s' )
9010                conv(1) = avo / ( amh2so4 * 1000.0_wp )
9011                conv(2) = avo / ( amhno3 * 1000.0_wp )
9012                conv(3) = avo / ( amnh3 * 1000.0_wp )
9013                conv(4) = avo / ( amoc * 1000.0_wp )
9014                conv(5) = avo / ( amoc * 1000.0_wp )
9015             CASE ( '#/m2/s' )
9016                conv = 1.0_wp
9017             CASE ( 'ppm/m2/s' )
9018                conv = for_ppm_to_nconc * hyp(k) / pt(k,j,i) * ( 1.0E5_wp / hyp(k) )**0.286_wp *   &
9019                       dx * dy * dzw(k)
9020             CASE ( 'mumol/m2/s' )
9021                conv = 1.0E-6_wp * avo
9022             CASE DEFAULT
9023                message_string = 'unknown unit for gas emissions: ' // TRIM( chem_emission_att%units )
9024                CALL message( 'set_gas_flux','PA0644', 1, 2, 0, 6, 0 )
9025
9026          END SELECT
9027
9028          DO  ig = 1, ngases_salsa
9029             IF ( use_time_fac )  THEN
9030                surface%gtsws(m,ig) = surface%gtsws(m,ig) + rho_air_zw(k-1) * conv(ig) * time_fac  &
9031                                      * MAX( 0.0_wp, source_array(j,i,cc_i_mod(ig) ) )
9032             ELSE
9033                surface%gtsws(m,ig) = surface%gtsws(m,ig) + rho_air_zw(k-1) * conv(ig)             &
9034                                      * MAX( 0.0_wp, source_array(j,i,cc_i_mod(ig) ) )
9035             ENDIF
9036          ENDDO  ! ig
9037
9038       ENDDO  ! m
9039
9040    END SUBROUTINE set_gas_flux
9041
9042 END SUBROUTINE salsa_gas_emission_setup
9043
9044!------------------------------------------------------------------------------!
9045! Description:
9046! ------------
9047!> Check data output for salsa.
9048!------------------------------------------------------------------------------!
9049 SUBROUTINE salsa_check_data_output( var, unit )
9050 
9051    USE control_parameters,                                                                        &
9052        ONLY:  message_string
9053
9054    IMPLICIT NONE
9055
9056    CHARACTER(LEN=*) ::  unit     !<
9057    CHARACTER(LEN=*) ::  var      !<
9058
9059    SELECT CASE ( TRIM( var ) )
9060
9061       CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV',  'g_OCSV', 'N_bin1', 'N_bin2', 'N_bin3',     &
9062              'N_bin4',  'N_bin5',  'N_bin6', 'N_bin7', 'N_bin8', 'N_bin9', 'N_bin10', 'N_bin11',  &
9063              'N_bin12', 'Ntot' )
9064          IF (  .NOT.  salsa )  THEN
9065             message_string = 'output of "' // TRIM( var ) // '" requires salsa = .TRUE.'
9066             CALL message( 'check_parameters', 'PA0645', 1, 2, 0, 6, 0 )
9067          ENDIF
9068          unit = '#/m3'
9069
9070       CASE ( 'LDSA' )
9071          IF (  .NOT.  salsa )  THEN
9072             message_string = 'output of "' // TRIM( var ) // '" requires salsa = .TRUE.'
9073             CALL message( 'check_parameters', 'PA0646', 1, 2, 0, 6, 0 )
9074          ENDIF
9075          unit = 'mum2/cm3'
9076
9077       CASE ( 'm_bin1', 'm_bin2',  'm_bin3',  'm_bin4',  'm_bin5', 'm_bin6', 'm_bin7', 'm_bin8',   &
9078              'm_bin9', 'm_bin10', 'm_bin11', 'm_bin12', 'PM2.5',  'PM10',   's_BC',   's_DU',     &
9079              's_H2O',  's_NH',    's_NO',    's_OC',    's_SO4',  's_SS' )
9080          IF (  .NOT.  salsa )  THEN
9081             message_string = 'output of "' // TRIM( var ) // '" requires salsa = .TRUE.'
9082             CALL message( 'check_parameters', 'PA0647', 1, 2, 0, 6, 0 )
9083          ENDIF
9084          unit = 'kg/m3'
9085
9086       CASE DEFAULT
9087          unit = 'illegal'
9088
9089    END SELECT
9090
9091 END SUBROUTINE salsa_check_data_output
9092
9093!------------------------------------------------------------------------------!
9094!
9095! Description:
9096! ------------
9097!> Subroutine for averaging 3D data
9098!------------------------------------------------------------------------------!
9099 SUBROUTINE salsa_3d_data_averaging( mode, variable )
9100
9101    USE control_parameters
9102
9103    USE indices
9104
9105    USE kinds
9106
9107    IMPLICIT NONE
9108
9109    CHARACTER(LEN=*)  ::  mode       !<
9110    CHARACTER(LEN=10) ::  vari       !<
9111    CHARACTER(LEN=*)  ::  variable   !<
9112
9113    INTEGER(iwp) ::  found_index  !<
9114    INTEGER(iwp) ::  i            !<
9115    INTEGER(iwp) ::  ib           !<
9116    INTEGER(iwp) ::  ic           !<
9117    INTEGER(iwp) ::  j            !<
9118    INTEGER(iwp) ::  k            !<
9119
9120    REAL(wp) ::  df       !< For calculating LDSA: fraction of particles depositing in the alveolar
9121                          !< (or tracheobronchial) region of the lung. Depends on the particle size
9122    REAL(wp) ::  mean_d   !< Particle diameter in micrometres
9123    REAL(wp) ::  nc       !< Particle number concentration in units 1/cm**3
9124    REAL(wp) ::  temp_bin !< temporary variable
9125
9126    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !< points to selected output variable
9127
9128    temp_bin = 0.0_wp
9129
9130    IF ( mode == 'allocate' )  THEN
9131
9132       SELECT CASE ( TRIM( variable ) )
9133
9134          CASE ( 'g_H2SO4' )
9135             IF ( .NOT. ALLOCATED( g_h2so4_av ) )  THEN
9136                ALLOCATE( g_h2so4_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9137             ENDIF
9138             g_h2so4_av = 0.0_wp
9139
9140          CASE ( 'g_HNO3' )
9141             IF ( .NOT. ALLOCATED( g_hno3_av ) )  THEN
9142                ALLOCATE( g_hno3_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9143             ENDIF
9144             g_hno3_av = 0.0_wp
9145
9146          CASE ( 'g_NH3' )
9147             IF ( .NOT. ALLOCATED( g_nh3_av ) )  THEN
9148                ALLOCATE( g_nh3_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9149             ENDIF
9150             g_nh3_av = 0.0_wp
9151
9152          CASE ( 'g_OCNV' )
9153             IF ( .NOT. ALLOCATED( g_ocnv_av ) )  THEN
9154                ALLOCATE( g_ocnv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9155             ENDIF
9156             g_ocnv_av = 0.0_wp
9157
9158          CASE ( 'g_OCSV' )
9159             IF ( .NOT. ALLOCATED( g_ocsv_av ) )  THEN
9160                ALLOCATE( g_ocsv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9161             ENDIF
9162             g_ocsv_av = 0.0_wp
9163
9164          CASE ( 'LDSA' )
9165             IF ( .NOT. ALLOCATED( ldsa_av ) )  THEN
9166                ALLOCATE( ldsa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9167             ENDIF
9168             ldsa_av = 0.0_wp
9169
9170          CASE ( 'N_bin1', 'N_bin2', 'N_bin3', 'N_bin4', 'N_bin5', 'N_bin6', 'N_bin7', 'N_bin8',   &
9171                 'N_bin9', 'N_bin10', 'N_bin11', 'N_bin12' )
9172             IF ( .NOT. ALLOCATED( nbins_av ) )  THEN
9173                ALLOCATE( nbins_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
9174             ENDIF
9175             nbins_av = 0.0_wp
9176
9177          CASE ( 'Ntot' )
9178             IF ( .NOT. ALLOCATED( ntot_av ) )  THEN
9179                ALLOCATE( ntot_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9180             ENDIF
9181             ntot_av = 0.0_wp
9182
9183          CASE ( 'm_bin1', 'm_bin2', 'm_bin3', 'm_bin4', 'm_bin5', 'm_bin6', 'm_bin7', 'm_bin8',   &
9184                 'm_bin9', 'm_bin10', 'm_bin11', 'm_bin12' )
9185             IF ( .NOT. ALLOCATED( mbins_av ) )  THEN
9186                ALLOCATE( mbins_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nbins_aerosol) )
9187             ENDIF
9188             mbins_av = 0.0_wp
9189
9190          CASE ( 'PM2.5' )
9191             IF ( .NOT. ALLOCATED( pm25_av ) )  THEN
9192                ALLOCATE( pm25_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9193             ENDIF
9194             pm25_av = 0.0_wp
9195
9196          CASE ( 'PM10' )
9197             IF ( .NOT. ALLOCATED( pm10_av ) )  THEN
9198                ALLOCATE( pm10_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9199             ENDIF
9200             pm10_av = 0.0_wp
9201
9202          CASE ( 's_BC' )
9203             IF ( .NOT. ALLOCATED( s_bc_av ) )  THEN
9204                ALLOCATE( s_bc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9205             ENDIF
9206             s_bc_av = 0.0_wp
9207
9208          CASE ( 's_DU' )
9209             IF ( .NOT. ALLOCATED( s_du_av ) )  THEN
9210                ALLOCATE( s_du_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9211             ENDIF
9212             s_du_av = 0.0_wp
9213
9214          CASE ( 's_H2O' )
9215             IF ( .NOT. ALLOCATED( s_h2o_av ) )  THEN
9216                ALLOCATE( s_h2o_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9217             ENDIF
9218             s_h2o_av = 0.0_wp
9219
9220          CASE ( 's_NH' )
9221             IF ( .NOT. ALLOCATED( s_nh_av ) )  THEN
9222                ALLOCATE( s_nh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9223             ENDIF
9224             s_nh_av = 0.0_wp
9225
9226          CASE ( 's_NO' )
9227             IF ( .NOT. ALLOCATED( s_no_av ) )  THEN
9228                ALLOCATE( s_no_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9229             ENDIF
9230             s_no_av = 0.0_wp
9231
9232          CASE ( 's_OC' )
9233             IF ( .NOT. ALLOCATED( s_oc_av ) )  THEN
9234                ALLOCATE( s_oc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9235             ENDIF
9236             s_oc_av = 0.0_wp
9237
9238          CASE ( 's_SO4' )
9239             IF ( .NOT. ALLOCATED( s_so4_av ) )  THEN
9240                ALLOCATE( s_so4_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9241             ENDIF
9242             s_so4_av = 0.0_wp   
9243
9244          CASE ( 's_SS' )
9245             IF ( .NOT. ALLOCATED( s_ss_av ) )  THEN
9246                ALLOCATE( s_ss_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
9247             ENDIF
9248             s_ss_av = 0.0_wp
9249
9250          CASE DEFAULT
9251             CONTINUE
9252
9253       END SELECT
9254
9255    ELSEIF ( mode == 'sum' )  THEN
9256
9257       SELECT CASE ( TRIM( variable ) )
9258
9259          CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV', 'g_OCSV' )
9260
9261             vari = TRIM( variable(3:) )
9262
9263             SELECT CASE( vari )
9264
9265                CASE( 'H2SO4' )
9266                   found_index = 1
9267                   to_be_resorted => g_h2so4_av
9268
9269                CASE( 'HNO3' )
9270                   found_index = 2
9271                   to_be_resorted => g_hno3_av
9272
9273                CASE( 'NH3' )
9274                   found_index = 3
9275                   to_be_resorted => g_nh3_av
9276
9277                CASE( 'OCNV' )
9278                   found_index = 4
9279                   to_be_resorted => g_ocnv_av
9280
9281                CASE( 'OCSN' )
9282                   found_index = 5
9283                   to_be_resorted => g_ocsv_av
9284
9285             END SELECT
9286
9287             DO  i = nxlg, nxrg
9288                DO  j = nysg, nyng
9289                   DO  k = nzb, nzt+1
9290                      to_be_resorted(k,j,i) = to_be_resorted(k,j,i) +                              &
9291                                              salsa_gas(found_index)%conc(k,j,i)
9292                   ENDDO
9293                ENDDO
9294             ENDDO
9295
9296          CASE ( 'LDSA' )
9297             DO  i = nxlg, nxrg
9298                DO  j = nysg, nyng
9299                   DO  k = nzb, nzt+1
9300                      temp_bin = 0.0_wp
9301                      DO  ib = 1, nbins_aerosol
9302!
9303!--                      Diameter in micrometres
9304                         mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
9305!
9306!--                      Deposition factor: alveolar (use ra_dry)
9307                         df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +       &
9308                                2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -     &
9309                                1.362_wp )**2 ) )
9310!
9311!--                      Number concentration in 1/cm3
9312                         nc = 1.0E-6_wp * aerosol_number(ib)%conc(k,j,i)
9313!
9314!--                      Lung-deposited surface area LDSA (units mum2/cm3)
9315                         temp_bin = temp_bin + pi * mean_d**2 * df * nc
9316                      ENDDO
9317                      ldsa_av(k,j,i) = ldsa_av(k,j,i) + temp_bin
9318                   ENDDO
9319                ENDDO
9320             ENDDO
9321
9322          CASE ( 'N_bin1', 'N_bin2', 'N_bin3', 'N_bin4', 'N_bin5', 'N_bin6', 'N_bin7', 'N_bin8',   &
9323                 'N_bin9', 'N_bin10', 'N_bin11', 'N_bin12' )
9324             DO  i = nxlg, nxrg
9325                DO  j = nysg, nyng
9326                   DO  k = nzb, nzt+1
9327                      DO  ib = 1, nbins_aerosol
9328                         nbins_av(k,j,i,ib) = nbins_av(k,j,i,ib) + aerosol_number(ib)%conc(k,j,i)
9329                      ENDDO
9330                   ENDDO
9331                ENDDO
9332             ENDDO
9333
9334          CASE ( 'Ntot' )
9335             DO  i = nxlg, nxrg
9336                DO  j = nysg, nyng
9337                   DO  k = nzb, nzt+1
9338                      DO  ib = 1, nbins_aerosol
9339                         ntot_av(k,j,i) = ntot_av(k,j,i) + aerosol_number(ib)%conc(k,j,i)
9340                      ENDDO
9341                   ENDDO
9342                ENDDO
9343             ENDDO
9344
9345          CASE ( 'm_bin1', 'm_bin2', 'm_bin3', 'm_bin4', 'm_bin5', 'm_bin6', 'm_bin7', 'm_bin8',   &
9346                 'm_bin9', 'm_bin10', 'm_bin11', 'm_bin12' )
9347             DO  i = nxlg, nxrg
9348                DO  j = nysg, nyng
9349                   DO  k = nzb, nzt+1
9350                      DO  ib = 1, nbins_aerosol
9351                         DO  ic = ib, nbins_aerosol * ncomponents_mass, nbins_aerosol
9352                            mbins_av(k,j,i,ib) = mbins_av(k,j,i,ib) + aerosol_mass(ic)%conc(k,j,i)
9353                         ENDDO
9354                      ENDDO
9355                   ENDDO
9356                ENDDO
9357             ENDDO
9358
9359          CASE ( 'PM2.5' )
9360             DO  i = nxlg, nxrg
9361                DO  j = nysg, nyng
9362                   DO  k = nzb, nzt+1
9363                      temp_bin = 0.0_wp
9364                      DO  ib = 1, nbins_aerosol
9365                         IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
9366                            DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
9367                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
9368                            ENDDO
9369                         ENDIF
9370                      ENDDO
9371                      pm25_av(k,j,i) = pm25_av(k,j,i) + temp_bin
9372                   ENDDO
9373                ENDDO
9374             ENDDO
9375
9376          CASE ( 'PM10' )
9377             DO  i = nxlg, nxrg
9378                DO  j = nysg, nyng
9379                   DO  k = nzb, nzt+1
9380                      temp_bin = 0.0_wp
9381                      DO  ib = 1, nbins_aerosol
9382                         IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
9383                            DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
9384                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
9385                            ENDDO
9386                         ENDIF
9387                      ENDDO
9388                      pm10_av(k,j,i) = pm10_av(k,j,i) + temp_bin
9389                   ENDDO
9390                ENDDO
9391             ENDDO
9392
9393          CASE ( 's_BC', 's_DU', 's_H2O', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
9394             IF ( is_used( prtcl, TRIM( variable(3:) ) ) )  THEN
9395                found_index = get_index( prtcl, TRIM( variable(3:) ) )
9396                IF ( TRIM( variable(3:) ) == 'BC' )   to_be_resorted => s_bc_av
9397                IF ( TRIM( variable(3:) ) == 'DU' )   to_be_resorted => s_du_av
9398                IF ( TRIM( variable(3:) ) == 'NH' )   to_be_resorted => s_nh_av
9399                IF ( TRIM( variable(3:) ) == 'NO' )   to_be_resorted => s_no_av
9400                IF ( TRIM( variable(3:) ) == 'OC' )   to_be_resorted => s_oc_av
9401                IF ( TRIM( variable(3:) ) == 'SO4' )  to_be_resorted => s_so4_av
9402                IF ( TRIM( variable(3:) ) == 'SS' )   to_be_resorted => s_ss_av
9403                DO  i = nxlg, nxrg
9404                   DO  j = nysg, nyng
9405                      DO  k = nzb, nzt+1
9406                         DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
9407                            to_be_resorted(k,j,i) = to_be_resorted(k,j,i) +                        &
9408                                                    aerosol_mass(ic)%conc(k,j,i)
9409                         ENDDO
9410                      ENDDO
9411                   ENDDO
9412                ENDDO
9413             ENDIF
9414
9415          CASE DEFAULT
9416             CONTINUE
9417
9418       END SELECT
9419
9420    ELSEIF ( mode == 'average' )  THEN
9421
9422       SELECT CASE ( TRIM( variable ) )
9423
9424          CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV', 'g_OCSV' )
9425             IF ( TRIM( variable(3:) ) == 'H2SO4' )  THEN
9426                found_index = 1
9427                to_be_resorted => g_h2so4_av
9428             ELSEIF ( TRIM( variable(3:) ) == 'HNO3' )  THEN
9429                found_index = 2
9430                to_be_resorted => g_hno3_av
9431             ELSEIF ( TRIM( variable(3:) ) == 'NH3' )  THEN
9432                found_index = 3
9433                to_be_resorted => g_nh3_av
9434             ELSEIF ( TRIM( variable(3:) ) == 'OCNV' )  THEN
9435                found_index = 4
9436                to_be_resorted => g_ocnv_av
9437             ELSEIF ( TRIM( variable(3:) ) == 'OCSV' )  THEN
9438                found_index = 5
9439                to_be_resorted => g_ocsv_av
9440             ENDIF
9441             DO  i = nxlg, nxrg
9442                DO  j = nysg, nyng
9443                   DO  k = nzb, nzt+1
9444                      to_be_resorted(k,j,i) = to_be_resorted(k,j,i) /                              &
9445                                              REAL( average_count_3d, KIND=wp )
9446                   ENDDO
9447                ENDDO
9448             ENDDO
9449
9450          CASE ( 'LDSA' )
9451             DO  i = nxlg, nxrg
9452                DO  j = nysg, nyng
9453                   DO  k = nzb, nzt+1
9454                      ldsa_av(k,j,i) = ldsa_av(k,j,i) / REAL( average_count_3d, KIND=wp )
9455                   ENDDO
9456                ENDDO
9457             ENDDO
9458
9459          CASE ( 'N_bin1', 'N_bin2', 'N_bin3', 'N_bin4', 'N_bin5', 'N_bin6', 'N_bin7', 'N_bin8',   &
9460                 'N_bin9', 'N_bin10', 'N_bin11', 'N_bin12' )
9461             DO  i = nxlg, nxrg
9462                DO  j = nysg, nyng
9463                   DO  k = nzb, nzt+1
9464                      DO  ib = 1, nbins_aerosol
9465                         nbins_av(k,j,i,ib) = nbins_av(k,j,i,ib) / REAL( average_count_3d, KIND=wp )
9466                      ENDDO
9467                   ENDDO
9468                ENDDO
9469             ENDDO
9470
9471          CASE ( 'Ntot' )
9472             DO  i = nxlg, nxrg
9473                DO  j = nysg, nyng
9474                   DO  k = nzb, nzt+1
9475                      ntot_av(k,j,i) = ntot_av(k,j,i) / REAL( average_count_3d, KIND=wp )
9476                   ENDDO
9477                ENDDO
9478             ENDDO
9479
9480          CASE ( 'm_bin1', 'm_bin2', 'm_bin3', 'm_bin4', 'm_bin5', 'm_bin6', 'm_bin7', 'm_bin8',   &
9481                 'm_bin9', 'm_bin10', 'm_bin11', 'm_bin12' )
9482             DO  i = nxlg, nxrg
9483                DO  j = nysg, nyng
9484                   DO  k = nzb, nzt+1
9485                      DO  ib = 1, nbins_aerosol
9486                         DO  ic = ib, nbins_aerosol * ncomponents_mass, nbins_aerosol
9487                            mbins_av(k,j,i,ib) = mbins_av(k,j,i,ib) /                              &
9488                                                 REAL( average_count_3d, KIND=wp)
9489                         ENDDO
9490                      ENDDO
9491                   ENDDO
9492                ENDDO
9493             ENDDO
9494
9495          CASE ( 'PM2.5' )
9496             DO  i = nxlg, nxrg
9497                DO  j = nysg, nyng
9498                   DO  k = nzb, nzt+1
9499                      pm25_av(k,j,i) = pm25_av(k,j,i) / REAL( average_count_3d, KIND=wp )
9500                   ENDDO
9501                ENDDO
9502             ENDDO
9503
9504          CASE ( 'PM10' )
9505             DO  i = nxlg, nxrg
9506                DO  j = nysg, nyng
9507                   DO  k = nzb, nzt+1
9508                      pm10_av(k,j,i) = pm10_av(k,j,i) / REAL( average_count_3d, KIND=wp )
9509                   ENDDO
9510                ENDDO
9511             ENDDO
9512
9513          CASE ( 's_BC', 's_DU', 's_H2O', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
9514             IF ( is_used( prtcl, TRIM( variable(3:) ) ) )  THEN
9515                found_index = get_index( prtcl, TRIM( variable(3:) ) )
9516                IF ( TRIM( variable(3:) ) == 'BC' )   to_be_resorted => s_bc_av
9517                IF ( TRIM( variable(3:) ) == 'DU' )   to_be_resorted => s_du_av
9518                IF ( TRIM( variable(3:) ) == 'NH' )   to_be_resorted => s_nh_av
9519                IF ( TRIM( variable(3:) ) == 'NO' )   to_be_resorted => s_no_av
9520                IF ( TRIM( variable(3:) ) == 'OC' )   to_be_resorted => s_oc_av
9521                IF ( TRIM( variable(3:) ) == 'SO4' )  to_be_resorted => s_so4_av
9522                IF ( TRIM( variable(3:) ) == 'SS' )   to_be_resorted => s_ss_av 
9523                DO  i = nxlg, nxrg
9524                   DO  j = nysg, nyng
9525                      DO  k = nzb, nzt+1
9526                         to_be_resorted(k,j,i) = to_be_resorted(k,j,i) /                           &
9527                                                 REAL( average_count_3d, KIND=wp )
9528                      ENDDO
9529                   ENDDO
9530                ENDDO
9531             ENDIF
9532
9533       END SELECT
9534
9535    ENDIF
9536
9537 END SUBROUTINE salsa_3d_data_averaging
9538
9539
9540!------------------------------------------------------------------------------!
9541!
9542! Description:
9543! ------------
9544!> Subroutine defining 2D output variables
9545!------------------------------------------------------------------------------!
9546 SUBROUTINE salsa_data_output_2d( av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do )
9547
9548    USE indices
9549
9550    USE kinds
9551
9552
9553    IMPLICIT NONE
9554
9555    CHARACTER(LEN=*) ::  grid       !<
9556    CHARACTER(LEN=*) ::  mode       !<
9557    CHARACTER(LEN=*) ::  variable   !<
9558    CHARACTER(LEN=5) ::  vari       !<  trimmed format of variable
9559
9560    INTEGER(iwp) ::  av           !<
9561    INTEGER(iwp) ::  found_index  !< index of a chemical compound
9562    INTEGER(iwp) ::  i            !<
9563    INTEGER(iwp) ::  ib           !< running index: size bins
9564    INTEGER(iwp) ::  ic           !< running index: mass bins
9565    INTEGER(iwp) ::  j            !<
9566    INTEGER(iwp) ::  k            !<
9567    INTEGER(iwp) ::  nzb_do       !<
9568    INTEGER(iwp) ::  nzt_do       !<
9569
9570    LOGICAL ::  found  !<
9571    LOGICAL ::  two_d  !< flag parameter to indicate 2D variables (horizontal cross sections)
9572
9573    REAL(wp) ::  df                       !< For calculating LDSA: fraction of particles
9574                                          !< depositing in the alveolar (or tracheobronchial)
9575                                          !< region of the lung. Depends on the particle size
9576    REAL(wp) ::  fill_value = -9999.0_wp  !< value for the _FillValue attribute
9577    REAL(wp) ::  mean_d                   !< Particle diameter in micrometres
9578    REAL(wp) ::  nc                       !< Particle number concentration in units 1/cm**3
9579    REAL(wp) ::  temp_bin                 !< temporary array for calculating output variables
9580
9581    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !< output
9582
9583    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted           !< pointer
9584!
9585!-- Next statement is to avoid compiler warning about unused variable. May be removed in future.
9586    IF ( two_d )  CONTINUE
9587
9588    found = .TRUE.
9589    temp_bin  = 0.0_wp
9590
9591    SELECT CASE ( TRIM( variable( 1:LEN( TRIM( variable ) ) - 3 ) ) )  ! cut out _xy, _xz or _yz
9592
9593       CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV', 'g_OCSV' )
9594          vari = TRIM( variable( 3:LEN( TRIM( variable ) ) - 3 ) )
9595          IF ( av == 0 )  THEN
9596             IF ( vari == 'H2SO4')  found_index = 1
9597             IF ( vari == 'HNO3')   found_index = 2
9598             IF ( vari == 'NH3')    found_index = 3
9599             IF ( vari == 'OCNV')   found_index = 4
9600             IF ( vari == 'OCSV')   found_index = 5
9601             DO  i = nxl, nxr
9602                DO  j = nys, nyn
9603                   DO  k = nzb_do, nzt_do
9604                      local_pf(i,j,k) = MERGE( salsa_gas(found_index)%conc(k,j,i), REAL( fill_value, &
9605                                               KIND = wp ),  BTEST( wall_flags_0(k,j,i), 0 ) ) 
9606                   ENDDO
9607                ENDDO
9608             ENDDO
9609          ELSE
9610             IF ( vari == 'H2SO4' )  to_be_resorted => g_h2so4_av
9611             IF ( vari == 'HNO3' )   to_be_resorted => g_hno3_av
9612             IF ( vari == 'NH3' )    to_be_resorted => g_nh3_av
9613             IF ( vari == 'OCNV' )   to_be_resorted => g_ocnv_av
9614             IF ( vari == 'OCSV' )   to_be_resorted => g_ocsv_av
9615             DO  i = nxl, nxr
9616                DO  j = nys, nyn
9617                   DO  k = nzb_do, nzt_do
9618                      local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,            &
9619                                               KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
9620                   ENDDO
9621                ENDDO
9622             ENDDO
9623          ENDIF
9624
9625          IF ( mode == 'xy' )  grid = 'zu'
9626
9627       CASE ( 'LDSA' )
9628          IF ( av == 0 )  THEN
9629             DO  i = nxl, nxr
9630                DO  j = nys, nyn
9631                   DO  k = nzb_do, nzt_do
9632                      temp_bin = 0.0_wp
9633                      DO  ib = 1, nbins_aerosol
9634!
9635!--                      Diameter in micrometres
9636                         mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp 
9637!
9638!--                      Deposition factor: alveolar
9639                         df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +       &
9640                                2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -     &
9641                                1.362_wp )**2 ) )
9642!
9643!--                      Number concentration in 1/cm3
9644                         nc = 1.0E-6_wp * aerosol_number(ib)%conc(k,j,i)
9645!
9646!--                      Lung-deposited surface area LDSA (units mum2/cm3)
9647                         temp_bin = temp_bin + pi * mean_d**2 * df * nc
9648                      ENDDO
9649
9650                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
9651                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9652                   ENDDO
9653                ENDDO
9654             ENDDO
9655          ELSE
9656             DO  i = nxl, nxr
9657                DO  j = nys, nyn
9658                   DO  k = nzb_do, nzt_do
9659                      local_pf(i,j,k) = MERGE( ldsa_av(k,j,i), REAL( fill_value, KIND = wp ),      &
9660                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9661                   ENDDO
9662                ENDDO
9663             ENDDO
9664          ENDIF
9665
9666          IF ( mode == 'xy' )  grid = 'zu'
9667
9668       CASE ( 'N_bin1', 'N_bin2', 'N_bin3', 'N_bin4',   'N_bin5',  'N_bin6', 'N_bin7', 'N_bin8',   &
9669              'N_bin9', 'N_bin10' , 'N_bin11', 'N_bin12' )
9670          vari = TRIM( variable( 6:LEN( TRIM( variable ) ) - 3 ) )
9671
9672          IF ( vari == '1' ) ib = 1
9673          IF ( vari == '2' ) ib = 2
9674          IF ( vari == '3' ) ib = 3
9675          IF ( vari == '4' ) ib = 4
9676          IF ( vari == '5' ) ib = 5
9677          IF ( vari == '6' ) ib = 6
9678          IF ( vari == '7' ) ib = 7
9679          IF ( vari == '8' ) ib = 8
9680          IF ( vari == '9' ) ib = 9
9681          IF ( vari == '10' ) ib = 10
9682          IF ( vari == '11' ) ib = 11
9683          IF ( vari == '12' ) ib = 12
9684
9685          IF ( av == 0 )  THEN
9686             DO  i = nxl, nxr
9687                DO  j = nys, nyn
9688                   DO  k = nzb_do, nzt_do
9689                      local_pf(i,j,k) = MERGE( aerosol_number(ib)%conc(k,j,i), REAL( fill_value,   &
9690                                               KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
9691                   ENDDO
9692                ENDDO
9693             ENDDO
9694          ELSE
9695             DO  i = nxl, nxr
9696                DO  j = nys, nyn
9697                   DO  k = nzb_do, nzt_do
9698                      local_pf(i,j,k) = MERGE( nbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
9699                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9700                   ENDDO
9701                ENDDO
9702             ENDDO
9703          ENDIF
9704
9705          IF ( mode == 'xy' )  grid = 'zu'
9706
9707       CASE ( 'Ntot' )
9708
9709          IF ( av == 0 )  THEN
9710             DO  i = nxl, nxr
9711                DO  j = nys, nyn
9712                   DO  k = nzb_do, nzt_do
9713                      temp_bin = 0.0_wp
9714                      DO  ib = 1, nbins_aerosol
9715                         temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
9716                      ENDDO
9717                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
9718                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9719                   ENDDO
9720                ENDDO
9721             ENDDO
9722          ELSE
9723             DO  i = nxl, nxr
9724                DO  j = nys, nyn
9725                   DO  k = nzb_do, nzt_do
9726                      local_pf(i,j,k) = MERGE( ntot_av(k,j,i), REAL( fill_value, KIND = wp ),      &
9727                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9728                   ENDDO
9729                ENDDO
9730             ENDDO
9731          ENDIF
9732
9733          IF ( mode == 'xy' )  grid = 'zu'
9734
9735       CASE ( 'm_bin1', 'm_bin2', 'm_bin3', 'm_bin4',   'm_bin5',  'm_bin6', 'm_bin7', 'm_bin8',   &
9736              'm_bin9', 'm_bin10' , 'm_bin11', 'm_bin12' )
9737          vari = TRIM( variable( 6:LEN( TRIM( variable ) ) - 3 ) )
9738
9739          IF ( vari == '1' ) ib = 1
9740          IF ( vari == '2' ) ib = 2
9741          IF ( vari == '3' ) ib = 3
9742          IF ( vari == '4' ) ib = 4
9743          IF ( vari == '5' ) ib = 5
9744          IF ( vari == '6' ) ib = 6
9745          IF ( vari == '7' ) ib = 7
9746          IF ( vari == '8' ) ib = 8
9747          IF ( vari == '9' ) ib = 9
9748          IF ( vari == '10' ) ib = 10
9749          IF ( vari == '11' ) ib = 11
9750          IF ( vari == '12' ) ib = 12
9751
9752          IF ( av == 0 )  THEN
9753             DO  i = nxl, nxr
9754                DO  j = nys, nyn
9755                   DO  k = nzb_do, nzt_do
9756                      temp_bin = 0.0_wp
9757                      DO  ic = ib, ncomponents_mass * nbins_aerosol, nbins_aerosol
9758                         temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
9759                      ENDDO
9760                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
9761                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9762                   ENDDO
9763                ENDDO
9764             ENDDO
9765          ELSE
9766             DO  i = nxl, nxr
9767                DO  j = nys, nyn
9768                   DO  k = nzb_do, nzt_do
9769                      local_pf(i,j,k) = MERGE( mbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
9770                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9771                   ENDDO
9772                ENDDO
9773             ENDDO
9774          ENDIF
9775
9776          IF ( mode == 'xy' )  grid = 'zu'
9777
9778       CASE ( 'PM2.5' )
9779          IF ( av == 0 )  THEN
9780             DO  i = nxl, nxr
9781                DO  j = nys, nyn
9782                   DO  k = nzb_do, nzt_do
9783                      temp_bin = 0.0_wp
9784                      DO  ib = 1, nbins_aerosol
9785                         IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
9786                            DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
9787                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
9788                            ENDDO
9789                         ENDIF
9790                      ENDDO
9791                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
9792                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9793                   ENDDO
9794                ENDDO
9795             ENDDO
9796          ELSE
9797             DO  i = nxl, nxr
9798                DO  j = nys, nyn
9799                   DO  k = nzb_do, nzt_do
9800                      local_pf(i,j,k) = MERGE( pm25_av(k,j,i), REAL( fill_value, KIND = wp ),      &
9801                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9802                   ENDDO
9803                ENDDO
9804             ENDDO
9805          ENDIF
9806
9807          IF ( mode == 'xy' )  grid = 'zu'
9808
9809       CASE ( 'PM10' )
9810          IF ( av == 0 )  THEN
9811             DO  i = nxl, nxr
9812                DO  j = nys, nyn
9813                   DO  k = nzb_do, nzt_do
9814                      temp_bin = 0.0_wp
9815                      DO  ib = 1, nbins_aerosol
9816                         IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
9817                            DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
9818                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
9819                            ENDDO
9820                         ENDIF
9821                      ENDDO
9822                      local_pf(i,j,k) = MERGE( temp_bin,  REAL( fill_value, KIND = wp ),           &
9823                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9824                   ENDDO
9825                ENDDO
9826             ENDDO
9827          ELSE
9828             DO  i = nxl, nxr
9829                DO  j = nys, nyn
9830                   DO  k = nzb_do, nzt_do
9831                      local_pf(i,j,k) = MERGE( pm10_av(k,j,i), REAL( fill_value, KIND = wp ),      &
9832                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9833                   ENDDO
9834                ENDDO
9835             ENDDO
9836          ENDIF
9837
9838          IF ( mode == 'xy' )  grid = 'zu'
9839
9840       CASE ( 's_BC', 's_DU', 's_H2O', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
9841          vari = TRIM( variable( 3:LEN( TRIM( variable ) ) - 3 ) )
9842          IF ( is_used( prtcl, vari ) )  THEN
9843             found_index = get_index( prtcl, vari )
9844             IF ( av == 0 )  THEN
9845                DO  i = nxl, nxr
9846                   DO  j = nys, nyn
9847                      DO  k = nzb_do, nzt_do
9848                         temp_bin = 0.0_wp
9849                         DO  ic = ( found_index-1 ) * nbins_aerosol+1, found_index * nbins_aerosol
9850                            temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
9851                         ENDDO
9852                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
9853                                                  BTEST( wall_flags_0(k,j,i), 0 ) )
9854                      ENDDO
9855                   ENDDO
9856                ENDDO
9857             ELSE
9858                IF ( vari == 'BC' )   to_be_resorted => s_bc_av
9859                IF ( vari == 'DU' )   to_be_resorted => s_du_av
9860                IF ( vari == 'NH' )   to_be_resorted => s_nh_av
9861                IF ( vari == 'NO' )   to_be_resorted => s_no_av
9862                IF ( vari == 'OC' )   to_be_resorted => s_oc_av
9863                IF ( vari == 'SO4' )  to_be_resorted => s_so4_av
9864                IF ( vari == 'SS' )   to_be_resorted => s_ss_av
9865                DO  i = nxl, nxr
9866                   DO  j = nys, nyn
9867                      DO  k = nzb_do, nzt_do
9868                         local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,         &
9869                                                  KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
9870                      ENDDO
9871                   ENDDO
9872                ENDDO
9873             ENDIF
9874          ELSE
9875             local_pf = fill_value
9876          ENDIF
9877
9878          IF ( mode == 'xy' )  grid = 'zu'
9879
9880       CASE DEFAULT
9881          found = .FALSE.
9882          grid  = 'none'
9883
9884    END SELECT
9885
9886 END SUBROUTINE salsa_data_output_2d
9887
9888!------------------------------------------------------------------------------!
9889!
9890! Description:
9891! ------------
9892!> Subroutine defining 3D output variables
9893!------------------------------------------------------------------------------!
9894 SUBROUTINE salsa_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
9895
9896    USE indices
9897
9898    USE kinds
9899
9900
9901    IMPLICIT NONE
9902
9903    CHARACTER(LEN=*), INTENT(in) ::  variable   !<
9904
9905    INTEGER(iwp) ::  av           !<
9906    INTEGER(iwp) ::  found_index  !< index of a chemical compound
9907    INTEGER(iwp) ::  ib           !< running index: size bins
9908    INTEGER(iwp) ::  ic           !< running index: mass bins
9909    INTEGER(iwp) ::  i            !<
9910    INTEGER(iwp) ::  j            !<
9911    INTEGER(iwp) ::  k            !<
9912    INTEGER(iwp) ::  nzb_do       !<
9913    INTEGER(iwp) ::  nzt_do       !<
9914
9915    LOGICAL ::  found      !<
9916
9917    REAL(wp) ::  df                       !< For calculating LDSA: fraction of particles
9918                                          !< depositing in the alveolar (or tracheobronchial)
9919                                          !< region of the lung. Depends on the particle size
9920    REAL(wp) ::  fill_value = -9999.0_wp  !< value for the _FillValue attribute
9921    REAL(wp) ::  mean_d                   !< Particle diameter in micrometres
9922    REAL(wp) ::  nc                       !< Particle number concentration in units 1/cm**3
9923    REAL(wp) ::  temp_bin                 !< temporary array for calculating output variables
9924
9925    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !< local
9926
9927    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !< pointer
9928
9929    found     = .TRUE.
9930    temp_bin  = 0.0_wp
9931
9932    SELECT CASE ( TRIM( variable ) )
9933
9934       CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV',  'g_OCSV' )
9935          IF ( av == 0 )  THEN
9936             IF ( TRIM( variable ) == 'g_H2SO4')  found_index = 1
9937             IF ( TRIM( variable ) == 'g_HNO3')   found_index = 2
9938             IF ( TRIM( variable ) == 'g_NH3')    found_index = 3
9939             IF ( TRIM( variable ) == 'g_OCNV')   found_index = 4
9940             IF ( TRIM( variable ) == 'g_OCSV')   found_index = 5
9941
9942             DO  i = nxl, nxr
9943                DO  j = nys, nyn
9944                   DO  k = nzb_do, nzt_do
9945                      local_pf(i,j,k) = MERGE( salsa_gas(found_index)%conc(k,j,i),                 &
9946                                               REAL( fill_value, KIND = wp ),                      &
9947                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9948                   ENDDO
9949                ENDDO
9950             ENDDO
9951          ELSE
9952             IF ( TRIM( variable(3:) ) == 'H2SO4' ) to_be_resorted => g_h2so4_av
9953             IF ( TRIM( variable(3:) ) == 'HNO3' )  to_be_resorted => g_hno3_av
9954             IF ( TRIM( variable(3:) ) == 'NH3' )   to_be_resorted => g_nh3_av
9955             IF ( TRIM( variable(3:) ) == 'OCNV' )  to_be_resorted => g_ocnv_av
9956             IF ( TRIM( variable(3:) ) == 'OCSV' )  to_be_resorted => g_ocsv_av
9957             DO  i = nxl, nxr
9958                DO  j = nys, nyn
9959                   DO  k = nzb_do, nzt_do
9960                      local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,            &
9961                                               KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
9962                   ENDDO
9963                ENDDO
9964             ENDDO
9965          ENDIF
9966
9967       CASE ( 'LDSA' )
9968          IF ( av == 0 )  THEN
9969             DO  i = nxl, nxr
9970                DO  j = nys, nyn
9971                   DO  k = nzb_do, nzt_do
9972                      temp_bin = 0.0_wp
9973                      DO  ib = 1, nbins_aerosol
9974!
9975!--                      Diameter in micrometres
9976                         mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
9977!
9978!--                      Deposition factor: alveolar
9979                         df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +       &
9980                                2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -     &
9981                                1.362_wp )**2 ) )
9982!
9983!--                      Number concentration in 1/cm3
9984                         nc = 1.0E-6_wp * aerosol_number(ib)%conc(k,j,i)
9985!
9986!--                      Lung-deposited surface area LDSA (units mum2/cm3)
9987                         temp_bin = temp_bin + pi * mean_d**2 * df * nc 
9988                      ENDDO
9989                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
9990                                               BTEST( wall_flags_0(k,j,i), 0 ) )
9991                   ENDDO
9992                ENDDO
9993             ENDDO
9994          ELSE
9995             DO  i = nxl, nxr
9996                DO  j = nys, nyn
9997                   DO  k = nzb_do, nzt_do
9998                      local_pf(i,j,k) = MERGE( ldsa_av(k,j,i), REAL( fill_value, KIND = wp ),      &
9999                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
10000                   ENDDO
10001                ENDDO
10002             ENDDO
10003          ENDIF
10004
10005       CASE ( 'N_bin1', 'N_bin2', 'N_bin3', 'N_bin4', 'N_bin5', 'N_bin6', 'N_bin7', 'N_bin8',      &
10006              'N_bin9', 'N_bin10', 'N_bin11', 'N_bin12' )
10007          IF ( TRIM( variable(6:) ) == '1' ) ib = 1
10008          IF ( TRIM( variable(6:) ) == '2' ) ib = 2
10009          IF ( TRIM( variable(6:) ) == '3' ) ib = 3
10010          IF ( TRIM( variable(6:) ) == '4' ) ib = 4
10011          IF ( TRIM( variable(6:) ) == '5' ) ib = 5
10012          IF ( TRIM( variable(6:) ) == '6' ) ib = 6
10013          IF ( TRIM( variable(6:) ) == '7' ) ib = 7
10014          IF ( TRIM( variable(6:) ) == '8' ) ib = 8
10015          IF ( TRIM( variable(6:) ) == '9' ) ib = 9
10016          IF ( TRIM( variable(6:) ) == '10' ) ib = 10
10017          IF ( TRIM( variable(6:) ) == '11' ) ib = 11
10018          IF ( TRIM( variable(6:) ) == '12' ) ib = 12
10019
10020          IF ( av == 0 )  THEN
10021             DO  i = nxl, nxr
10022                DO  j = nys, nyn
10023                   DO  k = nzb_do, nzt_do
10024                      local_pf(i,j,k) = MERGE( aerosol_number(ib)%conc(k,j,i), REAL( fill_value,   &
10025                                               KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
10026                   ENDDO
10027                ENDDO
10028             ENDDO
10029          ELSE
10030             DO  i = nxl, nxr
10031                DO  j = nys, nyn
10032                   DO  k = nzb_do, nzt_do
10033                      local_pf(i,j,k) = MERGE( nbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
10034                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
10035                   ENDDO
10036                ENDDO
10037             ENDDO
10038          ENDIF
10039
10040       CASE ( 'Ntot' )
10041          IF ( av == 0 )  THEN
10042             DO  i = nxl, nxr
10043                DO  j = nys, nyn
10044                   DO  k = nzb_do, nzt_do
10045                      temp_bin = 0.0_wp
10046                      DO  ib = 1, nbins_aerosol
10047                         temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
10048                      ENDDO
10049                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
10050                                               BTEST( wall_flags_0(k,j,i), 0 ) )
10051                   ENDDO
10052                ENDDO
10053             ENDDO
10054          ELSE
10055             DO  i = nxl, nxr
10056                DO  j = nys, nyn
10057                   DO  k = nzb_do, nzt_do
10058                      local_pf(i,j,k) = MERGE( ntot_av(k,j,i), REAL( fill_value, KIND = wp ),      &
10059                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
10060                   ENDDO
10061                ENDDO
10062             ENDDO
10063          ENDIF
10064
10065       CASE ( 'm_bin1', 'm_bin2', 'm_bin3', 'm_bin4', 'm_bin5', 'm_bin6', 'm_bin7', 'm_bin8',      &
10066              'm_bin9', 'm_bin10' , 'm_bin11', 'm_bin12' )
10067          IF ( TRIM( variable(6:) ) == '1' ) ib = 1
10068          IF ( TRIM( variable(6:) ) == '2' ) ib = 2
10069          IF ( TRIM( variable(6:) ) == '3' ) ib = 3
10070          IF ( TRIM( variable(6:) ) == '4' ) ib = 4
10071          IF ( TRIM( variable(6:) ) == '5' ) ib = 5
10072          IF ( TRIM( variable(6:) ) == '6' ) ib = 6
10073          IF ( TRIM( variable(6:) ) == '7' ) ib = 7
10074          IF ( TRIM( variable(6:) ) == '8' ) ib = 8
10075          IF ( TRIM( variable(6:) ) == '9' ) ib = 9
10076          IF ( TRIM( variable(6:) ) == '10' ) ib = 10
10077          IF ( TRIM( variable(6:) ) == '11' ) ib = 11
10078          IF ( TRIM( variable(6:) ) == '12' ) ib = 12
10079
10080          IF ( av == 0 )  THEN
10081             DO  i = nxl, nxr
10082                DO  j = nys, nyn
10083                   DO  k = nzb_do, nzt_do
10084                      temp_bin = 0.0_wp
10085                      DO  ic = ib, ncomponents_mass * nbins_aerosol, nbins_aerosol
10086                         temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10087                      ENDDO
10088                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
10089                                               BTEST( wall_flags_0(k,j,i), 0 ) )
10090                   ENDDO
10091                ENDDO
10092             ENDDO
10093          ELSE
10094             DO  i = nxl, nxr
10095                DO  j = nys, nyn
10096                   DO  k = nzb_do, nzt_do
10097                      local_pf(i,j,k) = MERGE( mbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
10098                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
10099                   ENDDO
10100                ENDDO
10101             ENDDO
10102          ENDIF
10103
10104       CASE ( 'PM2.5' )
10105          IF ( av == 0 )  THEN
10106             DO  i = nxl, nxr
10107                DO  j = nys, nyn
10108                   DO  k = nzb_do, nzt_do
10109                      temp_bin = 0.0_wp
10110                      DO  ib = 1, nbins_aerosol
10111                         IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
10112                            DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10113                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10114                            ENDDO
10115                         ENDIF
10116                      ENDDO
10117                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
10118                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
10119                   ENDDO
10120                ENDDO
10121             ENDDO
10122          ELSE
10123             DO  i = nxl, nxr
10124                DO  j = nys, nyn
10125                   DO  k = nzb_do, nzt_do
10126                      local_pf(i,j,k) = MERGE( pm25_av(k,j,i), REAL( fill_value, KIND = wp ),      &
10127                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
10128                   ENDDO
10129                ENDDO
10130             ENDDO
10131          ENDIF
10132
10133       CASE ( 'PM10' )
10134          IF ( av == 0 )  THEN
10135             DO  i = nxl, nxr
10136                DO  j = nys, nyn
10137                   DO  k = nzb_do, nzt_do
10138                      temp_bin = 0.0_wp
10139                      DO  ib = 1, nbins_aerosol
10140                         IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
10141                            DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10142                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10143                            ENDDO
10144                         ENDIF
10145                      ENDDO
10146                      local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),            &
10147                                               BTEST( wall_flags_0(k,j,i), 0 ) ) 
10148                   ENDDO
10149                ENDDO
10150             ENDDO
10151          ELSE
10152             DO  i = nxl, nxr
10153                DO  j = nys, nyn
10154                   DO  k = nzb_do, nzt_do
10155                      local_pf(i,j,k) = MERGE( pm10_av(k,j,i), REAL( fill_value, KIND = wp ),      &
10156                                               BTEST( wall_flags_0(k,j,i), 0 ) )
10157                   ENDDO
10158                ENDDO
10159             ENDDO
10160          ENDIF
10161
10162       CASE ( 's_BC', 's_DU', 's_H2O', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
10163          IF ( is_used( prtcl, TRIM( variable(3:) ) ) )  THEN
10164             found_index = get_index( prtcl, TRIM( variable(3:) ) )
10165             IF ( av == 0 )  THEN
10166                DO  i = nxl, nxr
10167                   DO  j = nys, nyn
10168                      DO  k = nzb_do, nzt_do
10169                         temp_bin = 0.0_wp
10170                         DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
10171                            temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10172                         ENDDO
10173                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
10174                                                  BTEST( wall_flags_0(k,j,i), 0 ) ) 
10175                      ENDDO
10176                   ENDDO
10177                ENDDO
10178             ELSE
10179                IF ( TRIM( variable(3:) ) == 'BC' )   to_be_resorted => s_bc_av
10180                IF ( TRIM( variable(3:) ) == 'DU' )   to_be_resorted => s_du_av
10181                IF ( TRIM( variable(3:) ) == 'NH' )   to_be_resorted => s_nh_av
10182                IF ( TRIM( variable(3:) ) == 'NO' )   to_be_resorted => s_no_av
10183                IF ( TRIM( variable(3:) ) == 'OC' )   to_be_resorted => s_oc_av
10184                IF ( TRIM( variable(3:) ) == 'SO4' )  to_be_resorted => s_so4_av
10185                IF ( TRIM( variable(3:) ) == 'SS' )   to_be_resorted => s_ss_av
10186                DO  i = nxl, nxr
10187                   DO  j = nys, nyn
10188                      DO  k = nzb_do, nzt_do
10189                         local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i), REAL( fill_value,         &
10190                                                  KIND = wp ), BTEST( wall_flags_0(k,j,i), 0 ) )
10191                      ENDDO
10192                   ENDDO
10193                ENDDO
10194             ENDIF
10195          ENDIF
10196
10197       CASE DEFAULT
10198          found = .FALSE.
10199
10200    END SELECT
10201
10202 END SUBROUTINE salsa_data_output_3d
10203
10204!------------------------------------------------------------------------------!
10205!
10206! Description:
10207! ------------
10208!> Subroutine defining mask output variables
10209!------------------------------------------------------------------------------!
10210 SUBROUTINE salsa_data_output_mask( av, variable, found, local_pf )
10211
10212    USE arrays_3d,                                                                                 &
10213        ONLY:  tend
10214
10215    USE control_parameters,                                                                        &
10216        ONLY:  mask_size_l, mask_surface, mid
10217
10218    USE surface_mod,                                                                               &
10219        ONLY:  get_topography_top_index_ji
10220
10221    IMPLICIT NONE
10222
10223    CHARACTER(LEN=5) ::  grid      !< flag to distinquish between staggered grid
10224    CHARACTER(LEN=*) ::  variable  !<
10225    CHARACTER(LEN=7) ::  vari      !< trimmed format of variable
10226
10227    INTEGER(iwp) ::  av              !<
10228    INTEGER(iwp) ::  found_index     !< index of a chemical compound
10229    INTEGER(iwp) ::  ib              !< loop index for aerosol size number bins
10230    INTEGER(iwp) ::  ic              !< loop index for chemical components
10231    INTEGER(iwp) ::  i               !< loop index in x-direction
10232    INTEGER(iwp) ::  j               !< loop index in y-direction
10233    INTEGER(iwp) ::  k               !< loop index in z-direction
10234    INTEGER(iwp) ::  topo_top_ind    !< k index of highest horizontal surface
10235
10236    LOGICAL ::  found      !<
10237    LOGICAL ::  resorted   !<
10238
10239    REAL(wp) ::  df        !< For calculating LDSA: fraction of particles
10240                           !< depositing in the alveolar (or tracheobronchial)
10241                           !< region of the lung. Depends on the particle size
10242    REAL(wp) ::  mean_d    !< Particle diameter in micrometres
10243    REAL(wp) ::  nc        !< Particle number concentration in units 1/cm**3
10244    REAL(wp) ::  temp_bin  !< temporary array for calculating output variables
10245
10246    REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  local_pf   !<
10247
10248    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !< pointer
10249
10250    found     = .TRUE.
10251    resorted  = .FALSE.
10252    grid      = 's'
10253    temp_bin  = 0.0_wp
10254
10255    SELECT CASE ( TRIM( variable ) )
10256
10257       CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV',  'g_OCSV' )
10258          vari = TRIM( variable )
10259          IF ( av == 0 )  THEN
10260             IF ( vari == 'g_H2SO4')  to_be_resorted => salsa_gas(1)%conc
10261             IF ( vari == 'g_HNO3')   to_be_resorted => salsa_gas(2)%conc
10262             IF ( vari == 'g_NH3')    to_be_resorted => salsa_gas(3)%conc
10263             IF ( vari == 'g_OCNV')   to_be_resorted => salsa_gas(4)%conc
10264             IF ( vari == 'g_OCSV')   to_be_resorted => salsa_gas(5)%conc
10265          ELSE
10266             IF ( vari == 'g_H2SO4') to_be_resorted => g_h2so4_av
10267             IF ( vari == 'g_HNO3')  to_be_resorted => g_hno3_av
10268             IF ( vari == 'g_NH3')   to_be_resorted => g_nh3_av
10269             IF ( vari == 'g_OCNV')  to_be_resorted => g_ocnv_av
10270             IF ( vari == 'g_OCSV')  to_be_resorted => g_ocsv_av
10271          ENDIF
10272
10273       CASE ( 'LDSA' )
10274          IF ( av == 0 )  THEN
10275             DO  i = nxl, nxr
10276                DO  j = nys, nyn
10277                   DO  k = nzb, nz_do3d
10278                      temp_bin = 0.0_wp
10279                      DO  ib = 1, nbins_aerosol
10280!
10281!--                      Diameter in micrometres
10282                         mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
10283!
10284!--                      Deposition factor: alveolar
10285                         df = ( 0.01555_wp / mean_d ) * ( EXP( -0.416_wp * ( LOG( mean_d ) +       &
10286                                2.84_wp )**2 ) + 19.11_wp * EXP( -0.482_wp * ( LOG( mean_d ) -     &
10287                                1.362_wp )**2 ) )
10288!
10289!--                      Number concentration in 1/cm3
10290                         nc = 1.0E-6_wp * aerosol_number(ib)%conc(k,j,i)
10291!
10292!--                      Lung-deposited surface area LDSA (units mum2/cm3)
10293                         temp_bin = temp_bin + pi * mean_d**2 * df * nc
10294                      ENDDO
10295                      tend(k,j,i) = temp_bin
10296                   ENDDO
10297                ENDDO
10298             ENDDO
10299             IF ( .NOT. mask_surface(mid) )  THEN   
10300                DO  i = 1, mask_size_l(mid,1)
10301                   DO  j = 1, mask_size_l(mid,2)
10302                      DO  k = 1, mask_size_l(mid,3)
10303                         local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
10304                      ENDDO
10305                   ENDDO
10306                ENDDO
10307             ELSE
10308                DO  i = 1, mask_size_l(mid,1)
10309                   DO  j = 1, mask_size_l(mid,2)
10310                      topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), mask_i(mid,i),    &
10311                                                                  grid )
10312                      DO  k = 1, mask_size_l(mid,3)
10313                         local_pf(i,j,k) = tend( MIN( topo_top_ind+mask_k(mid,k), nzt+1 ),         &
10314                                                 mask_j(mid,j), mask_i(mid,i) )
10315                      ENDDO
10316                   ENDDO
10317                ENDDO
10318             ENDIF
10319             resorted = .TRUE.
10320          ELSE
10321             to_be_resorted => ldsa_av
10322          ENDIF
10323
10324       CASE ( 'N_bin1', 'N_bin2', 'N_bin3', 'N_bin4',   'N_bin5',  'N_bin6', 'N_bin7', 'N_bin8',   &
10325              'N_bin9', 'N_bin10' , 'N_bin11', 'N_bin12' )
10326          IF ( TRIM( variable(6:) ) == '1' ) ib = 1
10327          IF ( TRIM( variable(6:) ) == '2' ) ib = 2
10328          IF ( TRIM( variable(6:) ) == '3' ) ib = 3
10329          IF ( TRIM( variable(6:) ) == '4' ) ib = 4
10330          IF ( TRIM( variable(6:) ) == '5' ) ib = 5
10331          IF ( TRIM( variable(6:) ) == '6' ) ib = 6
10332          IF ( TRIM( variable(6:) ) == '7' ) ib = 7
10333          IF ( TRIM( variable(6:) ) == '8' ) ib = 8
10334          IF ( TRIM( variable(6:) ) == '9' ) ib = 9
10335          IF ( TRIM( variable(6:) ) == '10' ) ib = 10
10336          IF ( TRIM( variable(6:) ) == '11' ) ib = 11
10337          IF ( TRIM( variable(6:) ) == '12' ) ib = 12
10338
10339          IF ( av == 0 )  THEN
10340             IF ( .NOT. mask_surface(mid) )  THEN
10341                DO  i = 1, mask_size_l(mid,1)
10342                   DO  j = 1, mask_size_l(mid,2)
10343                      DO  k = 1, mask_size_l(mid,3)
10344                         local_pf(i,j,k) = aerosol_number(ib)%conc( mask_k(mid,k), mask_j(mid,j),  &
10345                                                                    mask_i(mid,i) )
10346                      ENDDO
10347                   ENDDO
10348                ENDDO
10349             ELSE
10350                DO  i = 1, mask_size_l(mid,1)
10351                   DO  j = 1, mask_size_l(mid,2)
10352                      topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), mask_i(mid,i),    &
10353                                                                  grid )
10354                      DO  k = 1, mask_size_l(mid,3)
10355                         local_pf(i,j,k) = aerosol_number(ib)%conc(MIN( topo_top_ind+mask_k(mid,k),&
10356                                                                        nzt+1 ),                   &
10357                                                                   mask_j(mid,j), mask_i(mid,i) )
10358                      ENDDO
10359                   ENDDO
10360                ENDDO
10361             ENDIF
10362             resorted = .TRUE.
10363          ELSE
10364             to_be_resorted => nbins_av(:,:,:,ib)
10365          ENDIF
10366
10367       CASE ( 'Ntot' )
10368          IF ( av == 0 )  THEN
10369             DO  i = nxl, nxr
10370                DO  j = nys, nyn
10371                   DO  k = nzb, nz_do3d
10372                      temp_bin = 0.0_wp
10373                      DO  ib = 1, nbins_aerosol
10374                         temp_bin = temp_bin + aerosol_number(ib)%conc(k,j,i)
10375                      ENDDO
10376                      tend(k,j,i) = temp_bin
10377                   ENDDO
10378                ENDDO
10379             ENDDO 
10380             IF ( .NOT. mask_surface(mid) )  THEN   
10381                DO  i = 1, mask_size_l(mid,1)
10382                   DO  j = 1, mask_size_l(mid,2)
10383                      DO  k = 1, mask_size_l(mid,3)
10384                         local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
10385                      ENDDO
10386                   ENDDO
10387                ENDDO
10388             ELSE
10389                DO  i = 1, mask_size_l(mid,1)
10390                   DO  j = 1, mask_size_l(mid,2)
10391                      topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), mask_i(mid,i),    &
10392                                                                  grid )
10393                      DO  k = 1, mask_size_l(mid,3)
10394                         local_pf(i,j,k) = tend( MIN( topo_top_ind+mask_k(mid,k), nzt+1 ),         &
10395                                                 mask_j(mid,j), mask_i(mid,i) )
10396                      ENDDO
10397                   ENDDO
10398                ENDDO
10399             ENDIF
10400             resorted = .TRUE.
10401          ELSE
10402             to_be_resorted => ntot_av
10403          ENDIF
10404
10405       CASE ( 'm_bin1', 'm_bin2', 'm_bin3', 'm_bin4', 'm_bin5', 'm_bin6', 'm_bin7', 'm_bin8',      &
10406              'm_bin9', 'm_bin10', 'm_bin11', 'm_bin12' )
10407          IF ( TRIM( variable(6:) ) == '1' ) ib = 1
10408          IF ( TRIM( variable(6:) ) == '2' ) ib = 2
10409          IF ( TRIM( variable(6:) ) == '3' ) ib = 3
10410          IF ( TRIM( variable(6:) ) == '4' ) ib = 4
10411          IF ( TRIM( variable(6:) ) == '5' ) ib = 5
10412          IF ( TRIM( variable(6:) ) == '6' ) ib = 6
10413          IF ( TRIM( variable(6:) ) == '7' ) ib = 7
10414          IF ( TRIM( variable(6:) ) == '8' ) ib = 8
10415          IF ( TRIM( variable(6:) ) == '9' ) ib = 9
10416          IF ( TRIM( variable(6:) ) == '10' ) ib = 10
10417          IF ( TRIM( variable(6:) ) == '11' ) ib = 11
10418          IF ( TRIM( variable(6:) ) == '12' ) ib = 12
10419
10420          IF ( av == 0 )  THEN
10421             DO  i = nxl, nxr
10422                DO  j = nys, nyn
10423                   DO  k = nzb, nz_do3d
10424                      temp_bin = 0.0_wp
10425                      DO  ic = ib, ncomponents_mass * nbins_aerosol, nbins_aerosol
10426                         temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10427                      ENDDO
10428                      tend(k,j,i) = temp_bin
10429                   ENDDO
10430                ENDDO
10431             ENDDO
10432             IF ( .NOT. mask_surface(mid) )  THEN
10433                DO  i = 1, mask_size_l(mid,1)
10434                   DO  j = 1, mask_size_l(mid,2)
10435                      DO  k = 1, mask_size_l(mid,3)
10436                         local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
10437                      ENDDO
10438                   ENDDO
10439                ENDDO
10440             ELSE
10441                DO  i = 1, mask_size_l(mid,1)
10442                   DO  j = 1, mask_size_l(mid,2)
10443                      topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), mask_i(mid,i),    &
10444                                                                  grid )
10445                      DO  k = 1, mask_size_l(mid,3)
10446                         local_pf(i,j,k) = tend( MIN( topo_top_ind+mask_k(mid,k), nzt+1 ),         &
10447                                                 mask_j(mid,j), mask_i(mid,i) )
10448                      ENDDO
10449                   ENDDO
10450                ENDDO
10451             ENDIF
10452             resorted = .TRUE.
10453          ELSE
10454             to_be_resorted => mbins_av(:,:,:,ib)
10455          ENDIF
10456
10457       CASE ( 'PM2.5' )
10458          IF ( av == 0 )  THEN
10459             DO  i = nxl, nxr
10460                DO  j = nys, nyn
10461                   DO  k = nzb, nz_do3d
10462                      temp_bin = 0.0_wp
10463                      DO  ib = 1, nbins_aerosol
10464                         IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 2.5E-6_wp )  THEN
10465                            DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10466                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10467                            ENDDO
10468                         ENDIF
10469                      ENDDO
10470                      tend(k,j,i) = temp_bin
10471                   ENDDO
10472                ENDDO
10473             ENDDO 
10474             IF ( .NOT. mask_surface(mid) )  THEN
10475                DO  i = 1, mask_size_l(mid,1)
10476                   DO  j = 1, mask_size_l(mid,2)
10477                      DO  k = 1, mask_size_l(mid,3)
10478                         local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
10479                      ENDDO
10480                   ENDDO
10481                ENDDO
10482             ELSE
10483                DO  i = 1, mask_size_l(mid,1)
10484                   DO  j = 1, mask_size_l(mid,2)
10485                      topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), mask_i(mid,i),    &
10486                                                                  grid )
10487                      DO  k = 1, mask_size_l(mid,3)
10488                         local_pf(i,j,k) = tend( MIN( topo_top_ind+mask_k(mid,k), nzt+1 ),         &
10489                                                 mask_j(mid,j), mask_i(mid,i) )
10490                      ENDDO
10491                   ENDDO
10492                ENDDO
10493             ENDIF
10494             resorted = .TRUE.
10495          ELSE
10496             to_be_resorted => pm25_av
10497          ENDIF
10498
10499       CASE ( 'PM10' )
10500          IF ( av == 0 )  THEN
10501             DO  i = nxl, nxr
10502                DO  j = nys, nyn
10503                   DO  k = nzb, nz_do3d
10504                      temp_bin = 0.0_wp
10505                      DO  ib = 1, nbins_aerosol
10506                         IF ( 2.0_wp * ra_dry(k,j,i,ib) <= 10.0E-6_wp )  THEN
10507                            DO  ic = ib, nbins_aerosol * ncc, nbins_aerosol
10508                               temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10509                            ENDDO
10510                         ENDIF
10511                      ENDDO
10512                      tend(k,j,i) = temp_bin
10513                   ENDDO
10514                ENDDO
10515             ENDDO 
10516             IF ( .NOT. mask_surface(mid) )  THEN
10517                DO  i = 1, mask_size_l(mid,1)
10518                   DO  j = 1, mask_size_l(mid,2)
10519                      DO  k = 1, mask_size_l(mid,3)
10520                         local_pf(i,j,k) = tend( mask_k(mid,k),  mask_j(mid,j), mask_i(mid,i) )
10521                      ENDDO
10522                   ENDDO
10523                ENDDO
10524             ELSE
10525                DO  i = 1, mask_size_l(mid,1)
10526                   DO  j = 1, mask_size_l(mid,2)
10527                      topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), mask_i(mid,i),    &
10528                                                                  grid )
10529                      DO  k = 1, mask_size_l(mid,3)
10530                         local_pf(i,j,k) = tend( MIN( topo_top_ind+mask_k(mid,k), nzt+1 ),         &
10531                                                 mask_j(mid,j), mask_i(mid,i) )
10532                      ENDDO
10533                   ENDDO
10534                ENDDO
10535             ENDIF
10536             resorted = .TRUE.
10537          ELSE
10538             to_be_resorted => pm10_av
10539          ENDIF
10540
10541       CASE ( 's_BC', 's_DU', 's_NH', 's_NO', 's_OC', 's_SO4', 's_SS' )
10542          IF ( av == 0 )  THEN
10543             IF ( is_used( prtcl, TRIM( variable(3:) ) ) )  THEN
10544                found_index = get_index( prtcl, TRIM( variable(3:) ) )
10545                DO  i = nxl, nxr
10546                   DO  j = nys, nyn
10547                      DO  k = nzb, nz_do3d
10548                         temp_bin = 0.0_wp
10549                         DO  ic = ( found_index-1 ) * nbins_aerosol + 1, found_index * nbins_aerosol
10550                            temp_bin = temp_bin + aerosol_mass(ic)%conc(k,j,i)
10551                         ENDDO
10552                         tend(k,j,i) = temp_bin
10553                      ENDDO
10554                   ENDDO
10555                ENDDO
10556             ELSE
10557                tend = 0.0_wp
10558             ENDIF
10559             IF ( .NOT. mask_surface(mid) )  THEN
10560                DO  i = 1, mask_size_l(mid,1)
10561                   DO  j = 1, mask_size_l(mid,2)
10562                      DO  k = 1, mask_size_l(mid,3)
10563                         local_pf(i,j,k) = tend( mask_k(mid,k), mask_j(mid,j), mask_i(mid,i) )
10564                      ENDDO
10565                   ENDDO
10566                ENDDO
10567             ELSE
10568                DO  i = 1, mask_size_l(mid,1)
10569                   DO  j = 1, mask_size_l(mid,2)
10570                      topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), mask_i(mid,i),    &
10571                                                                  grid )
10572                      DO  k = 1, mask_size_l(mid,3)
10573                         local_pf(i,j,k) = tend( MIN( topo_top_ind+mask_k(mid,k), nzt+1 ),         &
10574                                                 mask_j(mid,j), mask_i(mid,i) )
10575                      ENDDO
10576                   ENDDO
10577                ENDDO
10578             ENDIF
10579             resorted = .TRUE.
10580          ELSE
10581             IF ( TRIM( variable(3:) ) == 'BC' )   to_be_resorted => s_bc_av
10582             IF ( TRIM( variable(3:) ) == 'DU' )   to_be_resorted => s_du_av
10583             IF ( TRIM( variable(3:) ) == 'NH' )   to_be_resorted => s_nh_av
10584             IF ( TRIM( variable(3:) ) == 'NO' )   to_be_resorted => s_no_av
10585             IF ( TRIM( variable(3:) ) == 'OC' )   to_be_resorted => s_oc_av
10586             IF ( TRIM( variable(3:) ) == 'SO4' )  to_be_resorted => s_so4_av
10587             IF ( TRIM( variable(3:) ) == 'SS' )   to_be_resorted => s_ss_av
10588          ENDIF
10589
10590       CASE DEFAULT
10591          found = .FALSE.
10592
10593    END SELECT
10594
10595    IF ( .NOT. resorted )  THEN
10596       IF ( .NOT. mask_surface(mid) )  THEN
10597!
10598!--       Default masked output
10599          DO  i = 1, mask_size_l(mid,1)
10600             DO  j = 1, mask_size_l(mid,2)
10601                DO  k = 1, mask_size_l(mid,3)
10602                   local_pf(i,j,k) = to_be_resorted( mask_k(mid,k), mask_j(mid,j),mask_i(mid,i) )
10603                ENDDO
10604             ENDDO
10605          ENDDO
10606       ELSE
10607!
10608!--       Terrain-following masked output
10609          DO  i = 1, mask_size_l(mid,1)
10610             DO  j = 1, mask_size_l(mid,2)
10611!
10612!--             Get k index of highest horizontal surface
10613                topo_top_ind = get_topography_top_index_ji( mask_j(mid,j), mask_i(mid,i), grid )
10614!
10615!--             Save output array
10616                DO  k = 1, mask_size_l(mid,3)
10617                   local_pf(i,j,k) = to_be_resorted( MIN( topo_top_ind+mask_k(mid,k), nzt+1 ),     &
10618                                                     mask_j(mid,j), mask_i(mid,i) )
10619                ENDDO
10620             ENDDO
10621          ENDDO
10622       ENDIF
10623    ENDIF
10624
10625 END SUBROUTINE salsa_data_output_mask
10626
10627 END MODULE salsa_mod
Note: See TracBrowser for help on using the repository browser.