source: palm/trunk/SOURCE/chemistry_model_mod.f90 @ 4650

Last change on this file since 4650 was 4637, checked in by suehring, 5 years ago

Avoid usage of omp_lib, instead declare omp_get_thread_num explicitly

  • Property svn:keywords set to Id
File size: 266.3 KB
Line 
1!> @file chemistry_model_mod.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 2017-2020 Leibniz Universitaet Hannover
17! Copyright 2017-2020 Karlsruhe Institute of Technology
18! Copyright 2017-2020 Freie Universitaet Berlin
19!--------------------------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: chemistry_model_mod.f90 4637 2020-08-07 07:49:33Z raasch $
28! Avoid usage of omp_lib, instead declare omp_get_thread_num explicitly
29!
30! 4636 2020-08-06 14:10:12Z resler
31! Fix bugs in OpenMP directives
32!
33! 4636 2020-08-06 14:10:12Z suehring
34! - Bugfix in variable name separation in profile-output initialization
35! - Bugfix in counting the number of chemistry profiles
36!
37! 4581 2020-06-29 08:49:58Z suehring
38! Enable output of resolved-scale vertical fluxes of chemical species.
39!
40! 4577 2020-06-25 09:53:58Z raasch
41! further re-formatting to follow the PALM coding standard
42!
43! 4559 2020-06-11 08:51:48Z raasch
44! file re-formatted to follow the PALM coding standard
45!
46! 4550 2020-05-29 15:22:13Z raasch
47! bugfix for reading local restart data
48!
49! 4544 2020-05-21 14:43:05Z raasch
50! conc_av changed from pointer to allocatable array, array spec_conc_av removed
51!
52! 4542 2020-05-19 15:45:12Z raasch
53! redundant if statement removed
54!
55! 4535 2020-05-15 12:07:23Z raasch
56! bugfix for restart data format query
57!
58! 4517 2020-05-03 14:29:30Z raasch
59! added restart with MPI-IO
60!
61! 4511 2020-04-30 12:20:40Z raasch
62! decycling replaced by explicit setting of lateral boundary conditions
63!
64! 4487 2020-04-03 09:38:20Z raasch
65! bugfix for subroutine calls that contain the decycle_chem switches as arguments
66!
67! 4481 2020-03-31 18:55:54Z maronga
68! use statement for exchange horiz added,
69! bugfix for call of exchange horiz 2d
70!
71! 4442 2020-03-04 19:21:13Z suehring
72! Change order of dimension in surface array %frac to allow for better
73! vectorization.
74!
75! 4441 2020-03-04 19:20:35Z suehring
76! in subroutine chem_init (ECC)
77! - allows different init paths emission data for legacy mode emission and on-demand mode in
78!   subroutine chem_init_internal (ECC)
79! - reads netcdf file only when legacy mode is activated (i.e., emiss_read_legacy_mode = .TRUE.)
80!   otherwise file is read once at the beginning to obtain header information, and emission data
81!   are extracted on an on-demand basis
82!
83! 4372 2020-01-14 10:20:35Z banzhafs
84! chem_parin : added handler for new namelist item emiss_legacy_read_mode (ECC) added messages
85! CM0465 - legacy read mode selection
86! CM0466 - legacy read mode force selection
87! CM0467 - new read mode selection
88!
89! 4370 2020-01-10 14:00:44Z raasch
90! vector directives added to force vectorization on Intel19 compiler
91!
92! 4346 2019-12-18 11:55:56Z motisi
93! Introduction of wall_flags_total_0, which currently sets bits based on static topography
94! information used in wall_flags_static_0
95!
96! 4329 2019-12-10 15:46:36Z motisi
97! Renamed wall_flags_0 to wall_flags_static_0
98!
99! 4306 2019-11-25 12:04:48Z banzhafs
100! Corretion for r4304 commit
101!
102! 4304 2019-11-25 10:43:03Z banzhafs
103! Precision clean-up in drydepo_aero_zhang_vd subroutine
104!
105! 4292 2019-11-11 13:04:50Z banzhafs
106! Bugfix for r4290
107!
108! 4290 2019-11-11 12:06:14Z banzhafs
109! Bugfix in sedimentation resistance calculation in drydepo_aero_zhang_vd subroutine
110!
111! 4273 2019-10-24 13:40:54Z monakurppa
112! Add logical switches nesting_chem and nesting_offline_chem (both .TRUE. by default)
113!
114! 4272 2019-10-23 15:18:57Z schwenkel
115! Further modularization of boundary conditions: moved boundary conditions to respective modules
116!
117! 4268 2019-10-17 11:29:38Z schwenkel
118! Moving module specific boundary conditions from time_integration to module
119!
120! 4230 2019-09-11 13:58:14Z suehring
121! Bugfix, initialize mean profiles also in restart runs. Also initialize array used for Runge-Kutta
122! tendecies in restart runs.
123!
124! 4227 2019-09-10 18:04:34Z gronemeier
125! implement new palm_date_time_mod
126!
127! 4182 2019-08-22 15:20:23Z scharf
128! Corrected "Former revisions" section
129!
130! 4167 2019-08-16 11:01:48Z suehring
131! Changed behaviour of masked output over surface to follow terrain and ignore buildings
132! (J.Resler, T.Gronemeier)
133!
134! 4166 2019-08-16 07:54:21Z resler
135! Bugfix in decycling
136!
137! 4115 2019-07-24 12:50:49Z suehring
138! Fix faulty IF statement in decycling initialization
139!
140! 4110 2019-07-22 17:05:21Z suehring
141! - Decycling boundary conditions are only set at the ghost points not on the prognostic grid points
142! - Allocation and initialization of special advection flags cs_advc_flags_s used for chemistry.
143!   These are exclusively used for chemical species in order to distinguish from the usually-used
144!   flags which might be different when decycling is applied in combination with cyclic boundary
145!   conditions.
146!   Moreover, cs_advc_flags_s considers extended zones around buildings where first-order upwind
147!   scheme is applied for the horizontal advection terms, in order to overcome high concentration
148!   peaks due to stationary numerical oscillations caused by horizontal advection discretization.
149!
150! 4109 2019-07-22 17:00:34Z suehring
151! Slightly revise setting of boundary conditions at horizontal walls, use data-structure offset
152! index instead of pre-calculate it for each facing
153!
154! 4080 2019-07-09 18:17:37Z suehring
155! Restore accidantly removed limitation to positive values
156!
157! 4079 2019-07-09 18:04:41Z suehring
158! Application of monotonic flux limiter for the vertical scalar advection up to the topography top
159! (only for the cache-optimized version at the moment).
160!
161! 4069 2019-07-01 14:05:51Z Giersch
162! Masked output running index mid has been introduced as a local variable to avoid runtime error
163! (Loop variable has been modified) in time_integration
164!
165! 4029 2019-06-14 14:04:35Z raasch
166! nest_chemistry option removed
167!
168! 4004 2019-05-24 11:32:38Z suehring
169! in subroutine chem_parin check emiss_lod / mod_emis only when emissions_anthropogenic is activated
170! in namelist (E.C. Chan)
171!
172! 3968 2019-05-13 11:04:01Z suehring
173! - added "emiss_lod" which serves the same function as "mode_emis" both will be synchronized with
174!   emiss_lod having pirority over mode_emis (see informational messages)
175! - modified existing error message and introduced new informational messages
176!    - CM0436 - now also applies to invalid LOD settings
177!    - CM0463 - emiss_lod take precedence in case of conflict with mod_emis
178!    - CM0464 - emiss_lod valued assigned based on mode_emis if undefined
179!
180! 3930 2019-04-24 14:57:18Z forkel
181! Changed chem_non_transport_physics to chem_non_advective_processes
182!
183! 3929 2019-04-24 12:52:08Z banzhafs
184! Correct/complete module_interface introduction for chemistry model
185! Add subroutine chem_exchange_horiz_bounds
186! Bug fix deposition
187!
188! 3784 2019-03-05 14:16:20Z banzhafs
189! 2D output of emission fluxes
190!
191! 3784 2019-03-05 14:16:20Z banzhafs
192! Bugfix, uncomment erroneous commented variable used for dry deposition.
193! Bugfix in 3D emission output.
194!
195! 3784 2019-03-05 14:16:20Z banzhafs
196! Changes related to global restructuring of location messages and introduction
197! of additional debug messages
198!
199! 3784 2019-03-05 14:16:20Z banzhafs
200! some formatting of the deposition code
201!
202! 3784 2019-03-05 14:16:20Z banzhafs
203! some formatting
204!
205! 3784 2019-03-05 14:16:20Z banzhafs
206! added cs_mech to USE chem_gasphase_mod
207!
208! 3784 2019-03-05 14:16:20Z banzhafs
209! renamed get_mechanismname to get_mechanism_name
210! renamed do_emiss to emissions_anthropogenic and do_depo to deposition_dry (ecc)
211!
212! 3784 2019-03-05 14:16:20Z banzhafs
213! Unused variables removed/taken care of
214!
215! 3784 2019-03-05 14:16:20Z forkel
216! Replaced READ from unit 10 by CALL get_mechanismname also in chem_header
217!
218! 3783 2019-03-05 13:23:50Z forkel
219! Removed forgotte write statements an some unused variables (did not touch the parts related to
220! deposition)
221!
222! 3780 2019-03-05 11:19:45Z forkel
223! Removed READ from unit 10, added CALL get_mechanismname
224!
225! 3767 2019-02-27 08:18:02Z raasch
226! unused variable for file index removed from rrd-subroutines parameter list
227!
228! 3738 2019-02-12 17:00:45Z suehring
229! Clean-up debug prints
230!
231! 3737 2019-02-12 16:57:06Z suehring
232! Enable mesoscale offline nesting for chemistry variables as well as initialization of chemistry
233! via dynamic input file.
234!
235! 3719 2019-02-06 13:10:18Z kanani
236! Resolved cpu logpoint overlap with all progn.equations, moved cpu_log call to prognostic_equations
237! for better overview
238!
239! 3700 2019-01-26 17:03:42Z knoop
240! Some interface calls moved to module_interface + cleanup
241!
242! 3664 2019-01-09 14:00:37Z forkel
243! Replaced misplaced location message by @todo
244!
245! 3654 2019-01-07 16:31:57Z suehring
246! Disable misplaced location message
247!
248! 3652 2019-01-07 15:29:59Z forkel
249! Checks added for chemistry mechanism, parameter chem_mechanism added (basit)
250!
251! 2718 2018-01-02 08:49:38Z maronga
252! Initial revision
253!
254!
255!
256!
257! Authors:
258! --------
259! @author Renate Forkel
260! @author Farah Kanani-Suehring
261! @author Klaus Ketelsen
262! @author Basit Khan
263! @author Sabine Banzhaf
264!
265!
266!--------------------------------------------------------------------------------------------------!
267! Description:
268! ------------
269!> Chemistry model for PALM-4U
270!> @todo Extend chem_species type by nspec and nvar as addititional elements (RF)
271!> @todo Check possibility to reduce dimension of chem_species%conc from nspec to nvar (RF)
272!> @todo Adjust chem_rrd_local to CASE structure of others modules. It is not allowed to use the
273!>       chemistry model in a precursor run and additionally not using it in a main run
274!> @todo Implement turbulent inflow of chem spcs in inflow_turbulence.
275!> @todo Separate boundary conditions for each chem spcs to be implemented
276!> @todo Currently only total concentration are calculated. Resolved, parameterized and chemistry
277!>       fluxes although partially and some completely coded but are not operational/activated in
278!>       this version. bK.
279!> @todo slight differences in passive scalar and chem spcs when chem reactions turned off. Need to
280!>       be fixed. bK
281!> @todo test nesting for chem spcs, was implemented by suehring (kanani)
282!> @todo chemistry error messages
283!
284!--------------------------------------------------------------------------------------------------!
285
286 MODULE chemistry_model_mod
287
288    USE advec_s_pw_mod,                                                                            &
289         ONLY:  advec_s_pw
290
291    USE advec_s_up_mod,                                                                            &
292         ONLY:  advec_s_up
293
294    USE advec_ws,                                                                                  &
295         ONLY:  advec_s_ws, ws_init_flags_scalar
296
297    USE diffusion_s_mod,                                                                           &
298         ONLY:  diffusion_s
299
300    USE kinds,                                                                                     &
301         ONLY:  iwp, wp
302
303    USE indices,                                                                                   &
304         ONLY:  advc_flags_s,                                                                      &
305                nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz, nzb, nzt,            &
306                wall_flags_total_0
307
308    USE pegrid,                                                                                    &
309         ONLY: myid, threads_per_task
310
311    USE bulk_cloud_model_mod,                                                                      &
312         ONLY:  bulk_cloud_model
313
314    USE control_parameters,                                                                        &
315         ONLY:  air_chemistry,                                                                     &
316                bc_dirichlet_l,                                                                    &
317                bc_dirichlet_n,                                                                    &
318                bc_dirichlet_r,                                                                    &
319                bc_dirichlet_s,                                                                    &
320                bc_radiation_l,                                                                    &
321                bc_lr_cyc,                                                                         &
322                bc_ns_cyc,                                                                         &
323                bc_radiation_n,                                                                    &
324                bc_radiation_r,                                                                    &
325                bc_radiation_s,                                                                    &
326                debug_output,                                                                      &
327                dt_3d,                                                                             &
328                humidity,                                                                          &
329                initializing_actions,                                                              &
330                intermediate_timestep_count,                                                       &
331                intermediate_timestep_count_max,                                                   &
332                max_pr_user,                                                                       &
333                message_string,                                                                    &
334                monotonic_limiter_z,                                                               &
335                omega,                                                                             &
336                restart_data_format_output,                                                        &
337                scalar_advec,                                                                      &
338                timestep_scheme,                                                                   &
339                tsc,                                                                               &
340                use_prescribed_profile_data,                                                       &
341                ws_scheme_sca
342
343    USE arrays_3d,                                                                                 &
344         ONLY:  exner, hyp, pt, q, ql, rdf_sc, tend, zu
345
346    USE chem_gasphase_mod,                                                                         &
347         ONLY:  atol, chem_gasphase_integrate, cs_mech, get_mechanism_name, nkppctrl,              &
348         nmaxfixsteps, nphot, nreact, nspec, nvar, phot_names, rtol, spc_names, t_steps, vl_dim
349
350    USE chem_modules
351
352    USE chem_photolysis_mod,                                                                       &
353        ONLY:  photolysis_control
354
355    USE cpulog,                                                                                    &
356        ONLY:  cpu_log, log_point_s
357
358    USE restart_data_mpi_io_mod,                                                                   &
359        ONLY:  rrd_mpi_io, rd_mpi_io_check_array, wrd_mpi_io
360
361    USE statistics
362
363    USE surface_mod,                                                                               &
364         ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
365
366    IMPLICIT NONE
367
368    PRIVATE
369    SAVE
370
371    INTEGER, DIMENSION(nkppctrl)                           ::  icntrl       !< 20 integer parameters for fine tuning KPP code
372
373    REAL(kind=wp), PUBLIC ::  cs_time_step = 0._wp
374
375    REAL(kind=wp), DIMENSION(nkppctrl)                     ::  rcntrl       !< 20 real parameters for fine tuning of KPP code
376                                                                            !< (e.g starting internal timestep of solver)
377
378    REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET ::  spec_conc_1  !< pointer for swapping of timelevels for conc
379    REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET ::  spec_conc_2  !< pointer for swapping of timelevels for conc
380    REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET ::  spec_conc_3  !< pointer for swapping of timelevels for conc
381    REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET ::  freq_1       !< pointer for phtolysis frequncies
382                                                                            !< (only 1 timelevel required) (e.g. solver type)
383
384!
385!-- Parameter needed for Deposition calculation using DEPAC model (van Zanten et al., 2010)
386    INTEGER(iwp), PARAMETER ::  nlu_dep = 15            !< Number of DEPAC landuse classes (lu's)
387    INTEGER(iwp), PARAMETER ::  ncmp = 10               !< Number of DEPAC gas components
388    INTEGER(iwp), PARAMETER ::  nposp = 69              !< Number of possible species for deposition
389!
390!-- DEPAC landuse classes as defined in LOTOS-EUROS model v2.1
391    INTEGER(iwp) ::  ilu_grass              = 1
392    INTEGER(iwp) ::  ilu_arable             = 2
393    INTEGER(iwp) ::  ilu_permanent_crops    = 3
394    INTEGER(iwp) ::  ilu_coniferous_forest  = 4
395    INTEGER(iwp) ::  ilu_deciduous_forest   = 5
396    INTEGER(iwp) ::  ilu_water_sea          = 6
397    INTEGER(iwp) ::  ilu_urban              = 7
398    INTEGER(iwp) ::  ilu_other              = 8
399    INTEGER(iwp) ::  ilu_desert             = 9
400    INTEGER(iwp) ::  ilu_ice                = 10
401    INTEGER(iwp) ::  ilu_savanna            = 11
402    INTEGER(iwp) ::  ilu_tropical_forest    = 12
403    INTEGER(iwp) ::  ilu_water_inland       = 13
404    INTEGER(iwp) ::  ilu_mediterrean_scrub  = 14
405    INTEGER(iwp) ::  ilu_semi_natural_veg   = 15
406
407!
408!-- NH3/SO2 ratio regimes:
409    INTEGER(iwp), PARAMETER ::  iratns_low      = 1       !< low ratio NH3/SO2
410    INTEGER(iwp), PARAMETER ::  iratns_high     = 2       !< high ratio NH3/SO2
411    INTEGER(iwp), PARAMETER ::  iratns_very_low = 3       !< very low ratio NH3/SO2
412!
413!-- Default:
414    INTEGER, PARAMETER ::  iratns_default = iratns_low
415!
416!-- Set alpha for f_light (4.57 is conversion factor from 1./(mumol m-2 s-1) to W m-2
417    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  alpha   = (/ 0.009, 0.009, 0.009, 0.006, 0.006,    &
418                    -999.0, -999., 0.009, -999.0, -999.0, 0.009, 0.006, -999.0, 0.009, 0.008 /)*4.57
419!
420!-- Set temperatures per land use for f_temp
421    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  tmin = (/ 12.0,  12.0,  12.0,  0.0,  0.0, -999.0,  &
422                                      -999.0, 12.0, -999.0, -999.0, 12.0,  0.0, -999.0, 12.0,  8.0/)
423    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  topt = (/ 26.0, 26.0,  26.0, 18.0, 20.0, -999.0,   &
424                                     -999.0, 26.0, -999.0, -999.0, 26.0, 20.0, -999.0, 26.0, 24.0 /)
425    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  tmax = (/ 40.0, 40.0,  40.0, 36.0, 35.0, -999.0,   &
426                                    -999.0, 40.0, -999.0, -999.0,  40.0, 35.0, -999.0, 40.0, 39.0 /)
427!
428!-- Set f_min:
429    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  f_min = (/ 0.01, 0.01, 0.01, 0.1, 0.1, -999.0,     &
430                                       -999.0, 0.01, -999.0, -999.0, 0.01, 0.1, -999.0, 0.01, 0.04/)
431
432!
433!-- Set maximal conductance (m/s)
434!-- (R T/P) = 1/41000 mmol/m3 is given for 20 deg C to go from  mmol O3/m2/s to m/s
435    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  g_max = (/ 270.0, 300.0, 300.0, 140.0, 150.0,      &
436              -999.0, -999.0, 270.0, -999.0, -999.0, 270.0, 150.0, -999.0, 300.0, 422.0 /) / 41000.0
437!
438!-- Set max, min for vapour pressure deficit vpd
439    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  vpd_max = (/ 1.3, 0.9, 0.9, 0.5, 1.0, -999.0,      &
440                                           -999.0, 1.3, -999.0, -999.0, 1.3, 1.0, -999.0, 0.9, 2.8/)
441    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  vpd_min = (/ 3.0, 2.8, 2.8, 3.0, 3.25, -999.0,     &
442                                         -999.0, 3.0, -999.0, -999.0, 3.0,  3.25, -999.0, 2.8, 4.5/)
443
444    PUBLIC nreact
445    PUBLIC nspec               !< number of gas phase chemical species including constant compound (e.g. N2)
446    PUBLIC nvar                !< number of variable gas phase chemical species (nvar <= nspec)
447    PUBLIC spc_names           !< names of gas phase chemical species (come from KPP) (come from KPP)
448    PUBLIC spec_conc_2
449!
450!-- Interface section
451    INTERFACE chem_actions
452       MODULE PROCEDURE chem_actions
453       MODULE PROCEDURE chem_actions_ij
454    END INTERFACE chem_actions
455
456    INTERFACE chem_3d_data_averaging
457       MODULE PROCEDURE chem_3d_data_averaging
458    END INTERFACE chem_3d_data_averaging
459
460    INTERFACE chem_boundary_conditions
461       MODULE PROCEDURE chem_boundary_conditions
462    END INTERFACE chem_boundary_conditions
463
464    INTERFACE chem_check_data_output
465       MODULE PROCEDURE chem_check_data_output
466    END INTERFACE chem_check_data_output
467
468    INTERFACE chem_data_output_2d
469       MODULE PROCEDURE chem_data_output_2d
470    END INTERFACE chem_data_output_2d
471
472    INTERFACE chem_data_output_3d
473       MODULE PROCEDURE chem_data_output_3d
474    END INTERFACE chem_data_output_3d
475
476    INTERFACE chem_data_output_mask
477       MODULE PROCEDURE chem_data_output_mask
478    END INTERFACE chem_data_output_mask
479
480    INTERFACE chem_check_data_output_pr
481       MODULE PROCEDURE chem_check_data_output_pr
482    END INTERFACE chem_check_data_output_pr
483
484    INTERFACE chem_check_parameters
485       MODULE PROCEDURE chem_check_parameters
486    END INTERFACE chem_check_parameters
487
488    INTERFACE chem_define_netcdf_grid
489       MODULE PROCEDURE chem_define_netcdf_grid
490    END INTERFACE chem_define_netcdf_grid
491
492    INTERFACE chem_header
493       MODULE PROCEDURE chem_header
494    END INTERFACE chem_header
495
496    INTERFACE chem_init_arrays
497       MODULE PROCEDURE chem_init_arrays
498    END INTERFACE chem_init_arrays
499
500    INTERFACE chem_init
501       MODULE PROCEDURE chem_init
502    END INTERFACE chem_init
503
504    INTERFACE chem_init_profiles
505       MODULE PROCEDURE chem_init_profiles
506    END INTERFACE chem_init_profiles
507
508    INTERFACE chem_integrate
509       MODULE PROCEDURE chem_integrate_ij
510    END INTERFACE chem_integrate
511
512    INTERFACE chem_parin
513       MODULE PROCEDURE chem_parin
514    END INTERFACE chem_parin
515
516    INTERFACE chem_non_advective_processes
517       MODULE PROCEDURE chem_non_advective_processes
518       MODULE PROCEDURE chem_non_advective_processes_ij
519    END INTERFACE chem_non_advective_processes
520
521    INTERFACE chem_exchange_horiz_bounds
522       MODULE PROCEDURE chem_exchange_horiz_bounds
523    END INTERFACE chem_exchange_horiz_bounds
524
525    INTERFACE chem_prognostic_equations
526       MODULE PROCEDURE chem_prognostic_equations
527       MODULE PROCEDURE chem_prognostic_equations_ij
528    END INTERFACE chem_prognostic_equations
529
530    INTERFACE chem_rrd_local
531       MODULE PROCEDURE chem_rrd_local_ftn
532       MODULE PROCEDURE chem_rrd_local_mpi
533    END INTERFACE chem_rrd_local
534
535    INTERFACE chem_statistics
536       MODULE PROCEDURE chem_statistics
537    END INTERFACE chem_statistics
538
539    INTERFACE chem_swap_timelevel
540       MODULE PROCEDURE chem_swap_timelevel
541    END INTERFACE chem_swap_timelevel
542
543    INTERFACE chem_wrd_local
544       MODULE PROCEDURE chem_wrd_local
545    END INTERFACE chem_wrd_local
546
547    INTERFACE chem_depo
548       MODULE PROCEDURE chem_depo
549    END INTERFACE chem_depo
550
551    INTERFACE drydepos_gas_depac
552       MODULE PROCEDURE drydepos_gas_depac
553    END INTERFACE drydepos_gas_depac
554
555    INTERFACE rc_special
556       MODULE PROCEDURE rc_special
557    END INTERFACE rc_special
558
559    INTERFACE  rc_gw
560       MODULE PROCEDURE rc_gw
561    END INTERFACE rc_gw
562
563    INTERFACE rw_so2
564       MODULE PROCEDURE rw_so2
565    END INTERFACE rw_so2
566
567    INTERFACE rw_nh3_sutton
568       MODULE PROCEDURE rw_nh3_sutton
569    END INTERFACE rw_nh3_sutton
570
571    INTERFACE rw_constant
572       MODULE PROCEDURE rw_constant
573    END INTERFACE rw_constant
574
575    INTERFACE rc_gstom
576       MODULE PROCEDURE rc_gstom
577    END INTERFACE rc_gstom
578
579    INTERFACE rc_gstom_emb
580       MODULE PROCEDURE rc_gstom_emb
581    END INTERFACE rc_gstom_emb
582
583    INTERFACE par_dir_diff
584       MODULE PROCEDURE par_dir_diff
585    END INTERFACE par_dir_diff
586
587    INTERFACE rc_get_vpd
588       MODULE PROCEDURE rc_get_vpd
589    END INTERFACE rc_get_vpd
590
591    INTERFACE rc_gsoil_eff
592       MODULE PROCEDURE rc_gsoil_eff
593    END INTERFACE rc_gsoil_eff
594
595    INTERFACE rc_rinc
596       MODULE PROCEDURE rc_rinc
597    END INTERFACE rc_rinc
598
599    INTERFACE rc_rctot
600       MODULE PROCEDURE rc_rctot
601    END INTERFACE rc_rctot
602
603    INTERFACE drydepo_aero_zhang_vd
604       MODULE PROCEDURE drydepo_aero_zhang_vd
605    END INTERFACE drydepo_aero_zhang_vd
606
607    INTERFACE get_rb_cell
608       MODULE PROCEDURE  get_rb_cell
609    END INTERFACE get_rb_cell
610
611
612
613    PUBLIC chem_3d_data_averaging, chem_boundary_conditions, chem_check_data_output,               &
614           chem_check_data_output_pr, chem_check_parameters, chem_data_output_2d,                  &
615           chem_data_output_3d, chem_data_output_mask, chem_define_netcdf_grid, chem_header,       &
616           chem_init, chem_init_arrays, chem_init_profiles, chem_integrate, chem_parin,            &
617           chem_actions, chem_prognostic_equations, chem_rrd_local, chem_statistics,               &
618           chem_swap_timelevel, chem_wrd_local, chem_depo, chem_non_advective_processes,           &
619           chem_exchange_horiz_bounds
620
621 CONTAINS
622
623
624!--------------------------------------------------------------------------------------------------!
625! Description:
626! ------------
627!> Subroutine for averaging 3D data of chemical species. Due to the fact that the averaged chem
628!> arrays are allocated in chem_init, no if-query concerning the allocation is required (in any
629!> mode). Attention: If you just specify an averaged output quantity in the _p3dr file during
630!> restarts the first output includes the time between the beginning of the restart run and the
631!> first output time (not necessarily the whole averaging_interval you have specified in your
632!> _p3d/_p3dr file ).
633!--------------------------------------------------------------------------------------------------!
634 SUBROUTINE chem_3d_data_averaging( mode, variable )
635
636    USE control_parameters
637
638    USE exchange_horiz_mod,                                                                        &
639        ONLY:  exchange_horiz_2d
640
641
642    CHARACTER (LEN=*) ::  mode     !<
643    CHARACTER (LEN=*) ::  variable !<
644
645    LOGICAL ::  match_def  !< flag indicating default-type surface
646    LOGICAL ::  match_lsm  !< flag indicating natural-type surface
647    LOGICAL ::  match_usm  !< flag indicating urban-type surface
648
649    INTEGER(iwp) ::  i                  !< grid index x direction
650    INTEGER(iwp) ::  j                  !< grid index y direction
651    INTEGER(iwp) ::  k                  !< grid index z direction
652    INTEGER(iwp) ::  lsp                !< running index for chem spcs
653    INTEGER(iwp) ::  m                  !< running index surface type
654
655    IF ( ( variable(1:3) == 'kc_'  .OR.  variable(1:3) == 'em_' )  )  THEN
656
657       IF ( mode == 'allocate' )  THEN
658
659          DO  lsp = 1, nspec
660             IF ( TRIM( variable(1:3) ) == 'kc_'  .AND.                                            &
661                  TRIM( variable(4:) )  == TRIM( chem_species(lsp)%name ) )  THEN
662                IF ( .NOT. ALLOCATED( chem_species(lsp)%conc_av ) )  THEN
663                   ALLOCATE( chem_species(lsp)%conc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
664                   chem_species(lsp)%conc_av = 0.0_wp
665                ENDIF
666             ENDIF
667          ENDDO
668
669       ELSEIF ( mode == 'sum' )  THEN
670
671          DO  lsp = 1, nspec
672             IF ( TRIM( variable(1:3) ) == 'kc_'  .AND.                                            &
673                  TRIM( variable(4:) )  == TRIM( chem_species(lsp)%name ) )  THEN
674                DO  i = nxlg, nxrg
675                   DO  j = nysg, nyng
676                      DO  k = nzb, nzt+1
677                         chem_species(lsp)%conc_av(k,j,i) = chem_species(lsp)%conc_av(k,j,i) +     &
678                                                            chem_species(lsp)%conc(k,j,i)
679                      ENDDO
680                   ENDDO
681                ENDDO
682             ELSEIF ( TRIM( variable(4:) ) == TRIM( 'cssws*' ) )  THEN
683                DO  i = nxl, nxr
684                   DO  j = nys, nyn
685                      match_def = surf_def_h(0)%start_index(j,i) <= surf_def_h(0)%end_index(j,i)
686                      match_lsm = surf_lsm_h%start_index(j,i)    <= surf_lsm_h%end_index(j,i)
687                      match_usm = surf_usm_h%start_index(j,i)    <= surf_usm_h%end_index(j,i)
688
689                      IF ( match_def )  THEN
690                         m = surf_def_h(0)%end_index(j,i)
691                         chem_species(lsp)%cssws_av(j,i) = chem_species(lsp)%cssws_av(j,i) +       &
692                                                           surf_def_h(0)%cssws(lsp,m)
693                      ELSEIF ( match_lsm  .AND.  .NOT. match_usm )  THEN
694                         m = surf_lsm_h%end_index(j,i)
695                         chem_species(lsp)%cssws_av(j,i) = chem_species(lsp)%cssws_av(j,i) +       &
696                                                           surf_lsm_h%cssws(lsp,m)
697                      ELSEIF ( match_usm )  THEN
698                         m = surf_usm_h%end_index(j,i)
699                         chem_species(lsp)%cssws_av(j,i) = chem_species(lsp)%cssws_av(j,i) +       &
700                                                           surf_usm_h%cssws(lsp,m)
701                      ENDIF
702                   ENDDO
703                ENDDO
704             ENDIF
705          ENDDO
706
707       ELSEIF ( mode == 'average' )  THEN
708
709          DO  lsp = 1, nspec
710             IF ( TRIM( variable(1:3) ) == 'kc_'  .AND.                                            &
711                  TRIM( variable(4:) )  == TRIM( chem_species(lsp)%name ) )  THEN
712                DO  i = nxlg, nxrg
713                   DO  j = nysg, nyng
714                      DO  k = nzb, nzt+1
715                         chem_species(lsp)%conc_av(k,j,i) = chem_species(lsp)%conc_av(k,j,i) /     &
716                                                            REAL( average_count_3d, KIND = wp )
717                      ENDDO
718                   ENDDO
719                ENDDO
720
721             ELSEIF ( TRIM( variable(4:) ) == TRIM( 'cssws*' ) )  THEN
722                DO  i = nxlg, nxrg
723                   DO  j = nysg, nyng
724                      chem_species(lsp)%cssws_av(j,i) = chem_species(lsp)%cssws_av(j,i) /          &
725                                                        REAL( average_count_3d, KIND = wp )
726                   ENDDO
727                ENDDO
728                CALL exchange_horiz_2d( chem_species(lsp)%cssws_av )
729             ENDIF
730          ENDDO
731       ENDIF
732
733    ENDIF
734
735 END SUBROUTINE chem_3d_data_averaging
736
737
738!--------------------------------------------------------------------------------------------------!
739! Description:
740! ------------
741!> Subroutine to initialize and set all boundary conditions for chemical species
742!--------------------------------------------------------------------------------------------------!
743 SUBROUTINE chem_boundary_conditions( horizontal_conditions_only )
744
745    USE arrays_3d,                                                                                 &
746        ONLY:  dzu
747
748    USE surface_mod,                                                                               &
749        ONLY:  bc_h
750
751    INTEGER(iwp) ::  i                            !< grid index x direction.
752    INTEGER(iwp) ::  j                            !< grid index y direction.
753    INTEGER(iwp) ::  k                            !< grid index z direction.
754    INTEGER(iwp) ::  l                            !< running index boundary type, for up- and downward-facing walls.
755    INTEGER(iwp) ::  lsp                          !< running index for chem spcs.
756    INTEGER(iwp) ::  m                            !< running index surface elements.
757
758    LOGICAL, OPTIONAL ::  horizontal_conditions_only  !< switch to set horizontal bc only
759
760
761    IF ( .NOT. PRESENT( horizontal_conditions_only ) )  THEN
762!
763!--    Boundary condtions for chemical species at horizontal walls
764       DO  lsp = 1, nspec
765
766          IF ( ibc_cs_b == 0 )  THEN
767             DO  l = 0, 1
768                !$OMP PARALLEL DO PRIVATE( i, j, k )
769                DO  m = 1, bc_h(l)%ns
770                    i = bc_h(l)%i(m)
771                    j = bc_h(l)%j(m)
772                    k = bc_h(l)%k(m)
773                   chem_species(lsp)%conc_p(k+bc_h(l)%koff,j,i) =                                  &
774                                                          chem_species(lsp)%conc(k+bc_h(l)%koff,j,i)
775                ENDDO
776             ENDDO
777
778          ELSEIF ( ibc_cs_b == 1 )  THEN
779!
780!--          In boundary_conds there is som extra loop over m here for passive tracer
781!>           TODO: clarify the meaning of the above comment. Explain in more detail or remove it. (Siggi)
782             DO  l = 0, 1
783                !$OMP PARALLEL DO PRIVATE( i, j, k )
784                DO m = 1, bc_h(l)%ns
785                   i = bc_h(l)%i(m)
786                   j = bc_h(l)%j(m)
787                   k = bc_h(l)%k(m)
788                   chem_species(lsp)%conc_p(k+bc_h(l)%koff,j,i) = chem_species(lsp)%conc_p(k,j,i)
789                ENDDO
790             ENDDO
791          ENDIF
792
793       ENDDO    ! end lsp loop
794
795!
796!--    Top boundary conditions for chemical species - Should this not be done for all species?
797!>     TODO: This question also needs to be clarified. I guess it can be removed because the loop
798!>           already runs over all species? (Siggi)
799       DO  lsp = 1, nspec
800          IF ( ibc_cs_t == 0 )  THEN
801             chem_species(lsp)%conc_p(nzt+1,:,:) = chem_species(lsp)%conc(nzt+1,:,:)
802          ELSEIF ( ibc_cs_t == 1 )  THEN
803             chem_species(lsp)%conc_p(nzt+1,:,:) = chem_species(lsp)%conc_p(nzt,:,:)
804          ELSEIF ( ibc_cs_t == 2 )  THEN
805             chem_species(lsp)%conc_p(nzt+1,:,:) = chem_species(lsp)%conc_p(nzt,:,:) +             &
806                                                   bc_cs_t_val(lsp) * dzu(nzt+1)
807          ENDIF
808       ENDDO
809
810!
811!--    Lateral boundary conditions.
812!--    Dirichlet conditions have been already set when chem_species concentration is initialized.
813!--    The initially set value is not touched during time integration, hence, this boundary value
814!--    remains at a constant value.
815!--    Neumann conditions:
816       IF ( bc_radiation_cs_s )  THEN
817          DO  lsp = 1, nspec
818             chem_species(lsp)%conc_p(:,nys-1,:) = chem_species(lsp)%conc_p(:,nys,:)
819          ENDDO
820       ENDIF
821       IF ( bc_radiation_cs_n )  THEN
822          DO  lsp = 1, nspec
823             chem_species(lsp)%conc_p(:,nyn+1,:) = chem_species(lsp)%conc_p(:,nyn,:)
824          ENDDO
825       ENDIF
826       IF ( bc_radiation_cs_l )  THEN
827          DO  lsp = 1, nspec
828             chem_species(lsp)%conc_p(:,:,nxl-1) = chem_species(lsp)%conc_p(:,:,nxl)
829          ENDDO
830       ENDIF
831       IF ( bc_radiation_cs_r )  THEN
832          DO  lsp = 1, nspec
833             chem_species(lsp)%conc_p(:,:,nxr+1) = chem_species(lsp)%conc_p(:,:,nxr)
834          ENDDO
835       ENDIF
836
837!--    For testing: set Dirichlet conditions for all boundaries
838!      IF ( bc_dirichlet_cs_s )  THEN
839!         DO  lsp = 1, nspec
840!            DO  i = nxlg, nxrg
841!               DO  j = nysg, nys-1
842!                  DO  k = nzb, nzt
843!                     IF ( k /= nzb )  THEN
844!                        flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
845!                     ELSE
846!                        flag = 1.0
847!                     ENDIF
848!                     chem_species(lsp)%conc_p(k,j,i) = chem_species(lsp)%conc_pr_init(k) * flag
849!                  ENDDO
850!               ENDDO
851!            ENDDO
852!         ENDDO
853!      ENDIF
854!      IF ( bc_dirichlet_cs_n )  THEN
855!         DO  lsp = 1, nspec
856!            DO  i = nxlg, nxrg
857!               DO  j = nyn+1, nyng
858!                  DO  k = nzb, nzt
859!                     IF ( k /= nzb )  THEN
860!                        flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
861!                     ELSE
862!                        flag = 1.0
863!                     ENDIF
864!                     chem_species(lsp)%conc_p(k,j,i) = chem_species(lsp)%conc_pr_init(k) * flag
865!                  ENDDO
866!               ENDDO
867!            ENDDO
868!         ENDDO
869!      ENDIF
870!      IF ( bc_dirichlet_cs_l )  THEN
871!         DO  lsp = 1, nspec
872!            DO  i = nxlg, nxl-1
873!               DO  j = nysg, nyng
874!                  DO  k = nzb, nzt
875!                     IF ( k /= nzb )  THEN
876!                        flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
877!                     ELSE
878!                        flag = 1.0
879!                     ENDIF
880!                     chem_species(lsp)%conc_p(k,j,i) = chem_species(lsp)%conc_pr_init(k) * flag
881!                  ENDDO
882!               ENDDO
883!            ENDDO
884!         ENDDO
885!      ENDIF
886!      IF ( bc_dirichlet_cs_r )  THEN
887!         DO  lsp = 1, nspec
888!            DO  i = nxr+1, nxrg
889!               DO  j = nysg, nyng
890!                  DO  k = nzb, nzt
891!                     IF ( k /= nzb )  THEN
892!                        flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
893!                     ELSE
894!                        flag = 1.0
895!                     ENDIF
896!                     chem_species(lsp)%conc_p(k,j,i) = chem_species(lsp)%conc_pr_init(k) * flag
897!                  ENDDO
898!               ENDDO
899!            ENDDO
900!         ENDDO
901!      ENDIF
902
903    ELSE
904!
905!--    Lateral Neumann booundary conditions for timelevel t.
906!--    This branch is executed when routine is called after the non-advective processes / before the
907!--    prognostic equations.
908       IF ( bc_radiation_cs_s )  THEN
909          DO  lsp = 1, nspec
910             chem_species(lsp)%conc(:,nys-1,:) = chem_species(lsp)%conc(:,nys,:)
911          ENDDO
912       ENDIF
913       IF ( bc_radiation_cs_n )  THEN
914          DO  lsp = 1, nspec
915             chem_species(lsp)%conc(:,nyn+1,:) = chem_species(lsp)%conc(:,nyn,:)
916          ENDDO
917       ENDIF
918       IF ( bc_radiation_cs_l )  THEN
919          DO  lsp = 1, nspec
920             chem_species(lsp)%conc(:,:,nxl-1) = chem_species(lsp)%conc(:,:,nxl)
921          ENDDO
922       ENDIF
923       IF ( bc_radiation_cs_r )  THEN
924          DO  lsp = 1, nspec
925             chem_species(lsp)%conc(:,:,nxr+1) = chem_species(lsp)%conc(:,:,nxr)
926          ENDDO
927       ENDIF
928
929!--    For testing: set Dirichlet conditions for all boundaries
930!      IF ( bc_dirichlet_cs_s )  THEN
931!         DO  lsp = 1, nspec
932!            DO  i = nxlg, nxrg
933!               DO  j = nysg, nys-1
934!                  DO  k = nzb, nzt
935!                     IF ( k /= nzb )  THEN
936!                        flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
937!                     ELSE
938!                        flag = 1.0
939!                     ENDIF
940!                     chem_species(lsp)%conc(k,j,i) = chem_species(lsp)%conc_pr_init(k) * flag
941!                  ENDDO
942!               ENDDO
943!            ENDDO
944!         ENDDO
945!      ENDIF
946!      IF ( bc_dirichlet_cs_n )  THEN
947!         DO  lsp = 1, nspec
948!            DO  i = nxlg, nxrg
949!               DO  j = nyn+1, nyng
950!                  DO  k = nzb, nzt
951!                     IF ( k /= nzb )  THEN
952!                        flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
953!                     ELSE
954!                        flag = 1.0
955!                     ENDIF
956!                     chem_species(lsp)%conc(k,j,i) = chem_species(lsp)%conc_pr_init(k) * flag
957!                  ENDDO
958!               ENDDO
959!            ENDDO
960!         ENDDO
961!      ENDIF
962!      IF ( bc_dirichlet_cs_l )  THEN
963!         DO  lsp = 1, nspec
964!            DO  i = nxlg, nxl-1
965!               DO  j = nysg, nyng
966!                  DO  k = nzb, nzt
967!                     IF ( k /= nzb )  THEN
968!                        flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
969!                     ELSE
970!                        flag = 1.0
971!                     ENDIF
972!                     chem_species(lsp)%conc(k,j,i) = chem_species(lsp)%conc_pr_init(k) * flag
973!                  ENDDO
974!               ENDDO
975!            ENDDO
976!         ENDDO
977!      ENDIF
978!      IF ( bc_dirichlet_cs_r )  THEN
979!         DO  lsp = 1, nspec
980!            DO  i = nxr+1, nxrg
981!               DO  j = nysg, nyng
982!                  DO  k = nzb, nzt
983!                     IF ( k /= nzb )  THEN
984!                        flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
985!                     ELSE
986!                        flag = 1.0
987!                     ENDIF
988!                     chem_species(lsp)%conc(k,j,i) = chem_species(lsp)%conc_pr_init(k) * flag
989!                  ENDDO
990!               ENDDO
991!            ENDDO
992!         ENDDO
993!      ENDIF
994
995    ENDIF
996
997 END SUBROUTINE chem_boundary_conditions
998
999
1000!--------------------------------------------------------------------------------------------------!
1001! Description:
1002! ------------
1003!> Subroutine for checking data output for chemical species
1004!--------------------------------------------------------------------------------------------------!
1005 SUBROUTINE chem_check_data_output( var, unit, i, ilen, k )
1006
1007
1008    CHARACTER (LEN=*) ::  unit     !<
1009    CHARACTER (LEN=*) ::  var      !<
1010
1011    INTEGER(iwp) ::  i
1012    INTEGER(iwp) ::  ilen
1013    INTEGER(iwp) ::  lsp
1014    INTEGER(iwp) ::  k
1015
1016    CHARACTER(LEN=16)    ::  spec_name
1017
1018!
1019!-- Next statement is to avoid compiler warnings about unused variables
1020    IF ( ( i + ilen + k ) > 0  .OR.  var(1:1) == ' ' )  CONTINUE
1021
1022    unit = 'illegal'
1023
1024    spec_name = TRIM( var(4:) )             !< var 1:3 is 'kc_' or 'em_'.
1025
1026    IF ( TRIM( var(1:3) ) == 'em_' )  THEN
1027       DO  lsp=1,nspec
1028          IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
1029             unit = 'mol m-2 s-1'
1030          ENDIF
1031!
1032!--       It is possible to plant PM10 and PM25 into the gasphase chemistry code as passive species
1033!--       (e.g. 'passive' in GASPHASE_PREPROC/mechanisms): set unit to micrograms per m**3 for PM10
1034!--       and PM25 (PM2.5)
1035          IF (spec_name(1:2) == 'PM')  THEN
1036             unit = 'kg m-2 s-1'
1037          ENDIF
1038       ENDDO
1039
1040    ELSE
1041
1042       DO  lsp=1,nspec
1043          IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
1044             unit = 'ppm'
1045          ENDIF
1046!
1047!--       It is possible to plant PM10 and PM25 into the gasphase chemistry code as passive species
1048!--       (e.g. 'passive' in GASPHASE_PREPROC/mechanisms): set unit to kilograms per m**3 for PM10
1049!--       and PM25 (PM2.5)
1050          IF (spec_name(1:2) == 'PM')  THEN
1051            unit = 'kg m-3'
1052          ENDIF
1053       ENDDO
1054
1055       DO  lsp=1,nphot
1056          IF ( TRIM( spec_name ) == TRIM( phot_frequen(lsp)%name ) )  THEN
1057             unit = 'sec-1'
1058          ENDIF
1059       ENDDO
1060    ENDIF
1061
1062
1063    RETURN
1064 END SUBROUTINE chem_check_data_output
1065
1066
1067!--------------------------------------------------------------------------------------------------!
1068! Description:
1069! ------------
1070!> Subroutine for checking data output of profiles for chemistry model
1071!--------------------------------------------------------------------------------------------------!
1072 SUBROUTINE chem_check_data_output_pr( variable, var_count, unit, dopr_unit )
1073
1074    USE arrays_3d
1075
1076    USE control_parameters,                                                                        &
1077        ONLY:  data_output_pr, message_string
1078
1079    USE profil_parameter
1080
1081    USE statistics
1082
1083
1084    CHARACTER (LEN=*)  ::  unit      !< unit
1085    CHARACTER (LEN=*)  ::  variable  !< variable name
1086    CHARACTER (LEN=*)  ::  dopr_unit !< unit
1087    CHARACTER (LEN=16) ::  spec_name !< species name extracted from output string
1088
1089    INTEGER(iwp) ::  index_start     !< start index of the species name in data-output string
1090    INTEGER(iwp) ::  index_end       !< end index of the species name in data-output string
1091    INTEGER(iwp) ::  var_count       !< number of data-output quantity
1092    INTEGER(iwp) ::  lsp             !< running index over species
1093
1094    SELECT CASE ( TRIM( variable(1:3 ) ) )
1095
1096       CASE ( 'kc_' )
1097
1098          IF ( .NOT. air_chemistry )  THEN
1099             message_string = 'data_output_pr = ' // TRIM( data_output_pr(var_count) ) //          &
1100                              ' is not implemented for air_chemistry = .FALSE.'
1101             CALL message( 'chem_check_parameters', 'CM0433', 1, 2, 0, 6, 0 )
1102
1103          ENDIF
1104!
1105!--       Output of total fluxes is not allowed to date.
1106          IF ( TRIM( variable(1:4) ) == 'kc_w' )  THEN
1107             IF ( TRIM( variable(1:5) ) /= 'kc_w*'  .AND.  TRIM( variable(1:5) ) /= 'kc_w"' )  THEN
1108                message_string = 'data_output_pr = ' // TRIM( data_output_pr(var_count) ) //       &
1109                              ' is currently not implemented. Please output resolved- and '//      &
1110                              'subgrid-scale fluxes individually to obtain the total flux.'
1111                CALL message( 'chem_check_parameters', 'CM0498', 1, 2, 0, 6, 0 )
1112             ENDIF
1113          ENDIF
1114!
1115!--       Check for profile output of first-order moments, i.e. variable(4:) equals a species name.
1116          spec_name = TRIM( variable(4:) )
1117          DO  lsp = 1, nspec
1118             IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
1119                cs_pr_count_sp                 = cs_pr_count_sp + 1
1120                cs_pr_index_sp(cs_pr_count_sp) = lsp
1121                dopr_index(var_count)          = pr_palm + cs_pr_count_sp +                        &
1122                                                 cs_pr_count_fl_sgs + cs_pr_count_fl_res
1123                dopr_unit                      = 'ppm'
1124                IF ( spec_name(1:2) == 'PM')  THEN
1125                   dopr_unit = 'kg m-3'
1126                ENDIF
1127                hom(:,2,dopr_index(var_count),:) = SPREAD( zu, 2, statistic_regions+1 )
1128                unit                              = dopr_unit
1129
1130                hom_index_spec(cs_pr_count_sp)    = dopr_index(var_count)
1131             ENDIF
1132          ENDDO
1133!
1134!--       Check for profile output of fluxes. variable(index_start:index_end) equals a species name.
1135!--       Start with SGS components.
1136          IF ( TRIM( variable(1:5) ) == 'kc_w"' )  THEN
1137             DO  lsp = 1, nspec
1138                index_end   = LEN( TRIM( variable ) ) - 1
1139                index_start = 6
1140                spec_name = TRIM( variable(index_start:index_end) )
1141                IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
1142                   cs_pr_count_fl_sgs                     = cs_pr_count_fl_sgs + 1
1143                   cs_pr_index_fl_sgs(cs_pr_count_fl_sgs) = lsp
1144                   dopr_index(var_count)                  = pr_palm + cs_pr_count_sp +          &
1145                                                            cs_pr_count_fl_sgs +                &
1146                                                            cs_pr_count_fl_res
1147                   dopr_unit                              = 'm ppm s-1'
1148                   IF ( spec_name(1:2) == 'PM')  THEN
1149                      dopr_unit = 'kg m-2 s-1'
1150                   ENDIF
1151                   hom(:,2,dopr_index(var_count),:)     = SPREAD( zu, 2, statistic_regions+1 )
1152                   unit                                 = dopr_unit
1153
1154                   hom_index_fl_sgs(cs_pr_count_fl_sgs) = dopr_index(var_count)
1155                ENDIF
1156             ENDDO
1157          ENDIF
1158!
1159!--       Proceed with resolved-scale fluxes.
1160          IF ( TRIM( variable(1:5) ) == 'kc_w*' )  THEN
1161             spec_name = TRIM( variable(6:) )
1162             DO  lsp = 1, nspec
1163                index_start = 6
1164                index_end   = LEN( TRIM( variable ) ) - 1
1165                spec_name = TRIM( variable(index_start:index_end) )
1166                IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name ) )  THEN
1167                   cs_pr_count_fl_res                     = cs_pr_count_fl_res + 1
1168                   cs_pr_index_fl_res(cs_pr_count_fl_res) = lsp
1169                   dopr_index(var_count)                  = pr_palm + cs_pr_count_sp +             &
1170                                                            cs_pr_count_fl_sgs +                   &
1171                                                            cs_pr_count_fl_res
1172                   dopr_unit                              = 'm ppm s-1'
1173                   IF ( spec_name(1:2) == 'PM')  THEN
1174                      dopr_unit = 'kg m-2 s-1'
1175                   ENDIF
1176                   hom(:,2, dopr_index(var_count),:)    = SPREAD( zu, 2, statistic_regions+1 )
1177                   unit                                 = dopr_unit
1178
1179                   hom_index_fl_res(cs_pr_count_fl_res) = dopr_index(var_count)
1180                ENDIF
1181             ENDDO
1182          ENDIF
1183       CASE DEFAULT
1184          unit = 'illegal'
1185
1186    END SELECT
1187
1188 END SUBROUTINE chem_check_data_output_pr
1189
1190
1191!--------------------------------------------------------------------------------------------------!
1192! Description:
1193! ------------
1194!> Check parameters routine for chemistry_model_mod
1195!--------------------------------------------------------------------------------------------------!
1196 SUBROUTINE chem_check_parameters
1197
1198    USE control_parameters,                                                                        &
1199        ONLY:  bc_lr, bc_ns
1200
1201    INTEGER (iwp) ::  lsp          !< running index for chem spcs.
1202    INTEGER (iwp) ::  lsp_usr      !< running index for user defined chem spcs
1203
1204    LOGICAL  ::  found
1205
1206!
1207!-- Check for chemical reactions status
1208    IF ( chem_gasphase_on )  THEN
1209       message_string = 'Chemical reactions: ON'
1210       CALL message( 'chem_check_parameters', 'CM0421', 0, 0, 0, 6, 0 )
1211    ELSEIF ( .NOT. (chem_gasphase_on) )  THEN
1212       message_string = 'Chemical reactions: OFF'
1213       CALL message( 'chem_check_parameters', 'CM0422', 0, 0, 0, 6, 0 )
1214    ENDIF
1215!
1216!-- Check for chemistry time-step
1217    IF ( call_chem_at_all_substeps )  THEN
1218       message_string = 'Chemistry is calculated at all meteorology time-step'
1219       CALL message( 'chem_check_parameters', 'CM0423', 0, 0, 0, 6, 0 )
1220    ELSEIF ( .not. (call_chem_at_all_substeps) )  THEN
1221       message_string = 'Sub-time-steps are skipped for chemistry time-steps'
1222       CALL message( 'chem_check_parameters', 'CM0424', 0, 0, 0, 6, 0 )
1223    ENDIF
1224!
1225!-- Check for photolysis scheme
1226    IF ( (photolysis_scheme /= 'simple') .AND. (photolysis_scheme /= 'constant')  )  THEN
1227       message_string = 'Incorrect photolysis scheme selected, please check spelling'
1228       CALL message( 'chem_check_parameters', 'CM0425', 1, 2, 0, 6, 0 )
1229    ENDIF
1230!
1231!-- Check for chemical mechanism used
1232    CALL get_mechanism_name
1233    IF ( chem_mechanism /= TRIM( cs_mech ) )  THEN
1234       message_string =                                                                            &
1235       'Incorrect chemistry mechanism selected, check spelling in namelist and/or chem_gasphase_mod'
1236       CALL message( 'chem_check_parameters', 'CM0462', 1, 2, 0, 6, 0 )
1237    ENDIF
1238
1239!
1240!-- Check bottom boundary condition and set internal steering parameter
1241    IF ( bc_cs_b == 'dirichlet' )  THEN
1242       ibc_cs_b = 0
1243    ELSEIF ( bc_cs_b == 'neumann' )  THEN
1244       ibc_cs_b = 1
1245    ELSE
1246       message_string = 'unknown boundary condition: bc_cs_b ="' // TRIM( bc_cs_b ) // '"'
1247       CALL message( 'chem_boundary_conds', 'CM0429', 1, 2, 0, 6, 0 )
1248    ENDIF
1249!
1250!-- Check top boundary condition and set internal steering parameter
1251    IF ( bc_cs_t == 'dirichlet' )  THEN
1252       ibc_cs_t = 0
1253    ELSEIF ( bc_cs_t == 'neumann' )  THEN
1254       ibc_cs_t = 1
1255    ELSEIF ( bc_cs_t == 'initial_gradient' )  THEN
1256       ibc_cs_t = 2
1257    ELSEIF ( bc_cs_t == 'nested' )  THEN
1258       ibc_cs_t = 3
1259    ELSE
1260       message_string = 'unknown boundary condition: bc_c_t ="' // TRIM( bc_cs_t ) // '"'
1261       CALL message( 'check_parameters', 'CM0430', 1, 2, 0, 6, 0 )
1262    ENDIF
1263
1264!
1265!-- If nesting_chem = .F., set top boundary condition to its default value
1266    IF ( .NOT. nesting_chem  .AND.  ibc_cs_t == 3  )  THEN
1267       ibc_cs_t = 2
1268       bc_cs_t = 'initial_gradient'
1269    ENDIF
1270
1271!
1272!-- Check left and right boundary conditions. First set default value if not set by user.
1273    IF ( bc_cs_l == 'undefined' )  THEN
1274       IF ( bc_lr == 'cyclic' )  THEN
1275          bc_cs_l = 'cyclic'
1276       ELSEIF ( bc_lr == 'dirichlet/radiation' )  THEN
1277          bc_cs_l = 'dirichlet'
1278       ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
1279          bc_cs_l = 'neumann'
1280       ENDIF
1281    ENDIF
1282    IF ( bc_cs_r == 'undefined' )  THEN
1283       IF ( bc_lr == 'cyclic' )  THEN
1284          bc_cs_r = 'cyclic'
1285       ELSEIF ( bc_lr == 'dirichlet/radiation' )  THEN
1286          bc_cs_r = 'neumann'
1287       ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
1288          bc_cs_r = 'dirichlet'
1289       ENDIF
1290    ENDIF
1291    IF ( bc_cs_l /= 'dirichlet'  .AND.  bc_cs_l /= 'neumann'  .AND.  bc_cs_l /= 'cyclic' )  THEN
1292       message_string = 'unknown boundary condition: bc_cs_l = "' // TRIM( bc_cs_l ) // '"'
1293       CALL message( 'chem_check_parameters','PA0505', 1, 2, 0, 6, 0 )
1294    ENDIF
1295    IF ( bc_cs_r /= 'dirichlet'  .AND.  bc_cs_r /= 'neumann'  .AND.  bc_cs_r /= 'cyclic' )  THEN
1296       message_string = 'unknown boundary condition: bc_cs_r = "' // TRIM( bc_cs_r ) // '"'
1297       CALL message( 'chem_check_parameters','PA0551', 1, 2, 0, 6, 0 )
1298    ENDIF
1299!
1300!-- Check north and south boundary conditions. First set default value if not set by user.
1301    IF ( bc_cs_n == 'undefined' )  THEN
1302       IF ( bc_ns == 'cyclic' )  THEN
1303          bc_cs_n = 'cyclic'
1304       ELSEIF ( bc_ns == 'dirichlet/radiation' )  THEN
1305          bc_cs_n = 'dirichlet'
1306       ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
1307          bc_cs_n = 'neumann'
1308       ENDIF
1309    ENDIF
1310    IF ( bc_cs_s == 'undefined' )  THEN
1311       IF ( bc_ns == 'cyclic' )  THEN
1312          bc_cs_s = 'cyclic'
1313       ELSEIF ( bc_ns == 'dirichlet/radiation' )  THEN
1314          bc_cs_s = 'neumann'
1315       ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
1316          bc_cs_s = 'dirichlet'
1317       ENDIF
1318    ENDIF
1319    IF ( bc_cs_n /= 'dirichlet'  .AND.  bc_cs_n /= 'neumann'  .AND.  bc_cs_n /= 'cyclic' )  THEN
1320       message_string = 'unknown boundary condition: bc_cs_n = "' // TRIM( bc_cs_n ) // '"'
1321       CALL message( 'chem_check_parameters','PA0714', 1, 2, 0, 6, 0 )
1322    ENDIF
1323    IF ( bc_cs_s /= 'dirichlet'  .AND.  bc_cs_s /= 'neumann'  .AND.  bc_cs_s /= 'cyclic' )  THEN
1324       message_string = 'unknown boundary condition: bc_cs_s = "' // TRIM( bc_cs_s ) // '"'
1325       CALL message( 'chem_check_parameters','PA0715', 1, 2, 0, 6, 0 )
1326    ENDIF
1327!
1328!-- Cyclic conditions must be set identically at opposing boundaries
1329    IF ( ( bc_cs_l == 'cyclic' .AND. bc_cs_r /= 'cyclic' )  .OR.                                   &
1330         ( bc_cs_r == 'cyclic' .AND. bc_cs_l /= 'cyclic' ) )  THEN
1331       message_string = 'boundary conditions bc_cs_l and bc_cs_r must both be cyclic or non-cyclic'
1332       CALL message( 'chem_check_parameters','PA0716', 1, 2, 0, 6, 0 )
1333    ENDIF
1334    IF ( ( bc_cs_n == 'cyclic' .AND. bc_cs_s /= 'cyclic' )  .OR.                                   &
1335         ( bc_cs_s == 'cyclic' .AND. bc_cs_n /= 'cyclic' ) )  THEN
1336       message_string = 'boundary conditions bc_cs_n and bc_cs_s must both be cyclic or non-cyclic'
1337       CALL message( 'chem_check_parameters','PA0717', 1, 2, 0, 6, 0 )
1338    ENDIF
1339!
1340!-- Set the switches that control application of horizontal boundary conditions at the boundaries
1341!-- of the total domain
1342    IF ( bc_cs_n == 'dirichlet'  .AND.  nyn == ny )  bc_dirichlet_cs_n = .TRUE.
1343    IF ( bc_cs_n == 'neumann'    .AND.  nyn == ny )  bc_radiation_cs_n = .TRUE.
1344    IF ( bc_cs_s == 'dirichlet'  .AND.  nys ==  0 )  bc_dirichlet_cs_s = .TRUE.
1345    IF ( bc_cs_s == 'neumann'    .AND.  nys ==  0 )  bc_radiation_cs_s = .TRUE.
1346    IF ( bc_cs_l == 'dirichlet'  .AND.  nxl ==  0 )  bc_dirichlet_cs_l = .TRUE.
1347    IF ( bc_cs_l == 'neumann'    .AND.  nxl ==  0 )  bc_radiation_cs_l = .TRUE.
1348    IF ( bc_cs_r == 'dirichlet'  .AND.  nxr == nx )  bc_dirichlet_cs_r = .TRUE.
1349    IF ( bc_cs_r == 'neumann'    .AND.  nxr == nx )  bc_radiation_cs_r = .TRUE.
1350
1351!
1352!-- Set the communicator to be used for ghost layer data exchange
1353!-- 1: cyclic, 2: cyclic along x, 3: cyclic along y, 4: non-cyclic
1354    IF ( bc_cs_l == 'cyclic' )  THEN
1355       IF ( bc_cs_s == 'cyclic' )  THEN
1356          communicator_chem = 1
1357       ELSE
1358          communicator_chem = 2
1359       ENDIF
1360    ELSE
1361       IF ( bc_cs_s == 'cyclic' )  THEN
1362          communicator_chem = 3
1363       ELSE
1364          communicator_chem = 4
1365       ENDIF
1366    ENDIF
1367
1368!
1369!-- chem_check_parameters is called before the array chem_species is allocated!
1370!-- temporary switch of this part of the check
1371!    RETURN                !bK commented
1372!> TODO: this workaround definitely needs to be removed from here!!!
1373    CALL chem_init_internal
1374!
1375!-- Check for initial chem species input
1376    lsp_usr = 1
1377    lsp     = 1
1378    DO WHILE ( cs_name (lsp_usr) /= 'novalue')
1379       found = .FALSE.
1380       DO  lsp = 1, nvar
1381          IF ( TRIM( cs_name (lsp_usr) ) == TRIM( chem_species(lsp)%name) )  THEN
1382             found = .TRUE.
1383             EXIT
1384          ENDIF
1385       ENDDO
1386       IF ( .NOT.  found )  THEN
1387          message_string = 'Unused/incorrect input for initial surface value: ' //     &
1388                            TRIM( cs_name(lsp_usr) )
1389          CALL message( 'chem_check_parameters', 'CM0427', 1, 2, 0, 6, 0 )
1390       ENDIF
1391       lsp_usr = lsp_usr + 1
1392    ENDDO
1393!
1394!-- Check for surface  emission flux chem species
1395    lsp_usr = 1
1396    lsp     = 1
1397    DO WHILE ( surface_csflux_name (lsp_usr) /= 'novalue')
1398       found = .FALSE.
1399       DO  lsp = 1, nvar
1400          IF ( TRIM( surface_csflux_name (lsp_usr) ) == TRIM( chem_species(lsp)%name ) )  THEN
1401             found = .TRUE.
1402             EXIT
1403          ENDIF
1404       ENDDO
1405       IF ( .NOT.  found )  THEN
1406          message_string = 'Unused/incorrect input of chemical species for surface emission fluxes: '  &
1407                            // TRIM( surface_csflux_name(lsp_usr) )
1408          CALL message( 'chem_check_parameters', 'CM0428', 1, 2, 0, 6, 0 )
1409       ENDIF
1410       lsp_usr = lsp_usr + 1
1411    ENDDO
1412
1413 END SUBROUTINE chem_check_parameters
1414
1415
1416!--------------------------------------------------------------------------------------------------!
1417! Description:
1418! ------------
1419!> Subroutine defining 2D output variables for chemical species
1420!> @todo: Remove "mode" from argument list, not used.
1421!--------------------------------------------------------------------------------------------------!
1422 SUBROUTINE chem_data_output_2d( av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do, &
1423                                 fill_value )
1424
1425
1426    CHARACTER (LEN=*) ::  grid       !<
1427    CHARACTER (LEN=*) ::  mode       !<
1428    CHARACTER (LEN=*) ::  variable   !<
1429
1430    INTEGER(iwp) ::  av              !< flag to control data output of instantaneous or
1431                                     !< time-averaged data
1432    INTEGER(iwp) ::  nzb_do          !< lower limit of the domain (usually nzb)
1433    INTEGER(iwp) ::  nzt_do          !< upper limit of the domain (usually nzt+1)
1434
1435    LOGICAL      ::  found           !<
1436    LOGICAL      ::  two_d           !< flag parameter that indicates 2D variables (horizontal cross
1437                                     !< sections)
1438
1439    REAL(wp)     ::  fill_value
1440
1441    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf
1442
1443!
1444!-- local variables.
1445    CHARACTER(LEN=16)    ::  spec_name
1446    INTEGER(iwp) ::  lsp
1447    INTEGER(iwp) ::  i               !< grid index along x-direction
1448    INTEGER(iwp) ::  j               !< grid index along y-direction
1449    INTEGER(iwp) ::  k               !< grid index along z-direction
1450    INTEGER(iwp) ::  m               !< running indices for surfaces
1451    INTEGER(iwp) ::  char_len        !< length of a character string
1452!
1453!-- Next statement is to avoid compiler warnings about unused variables
1454    IF ( mode(1:1) == ' '  .OR.  two_d )  CONTINUE
1455
1456    found = .FALSE.
1457    char_len  = LEN_TRIM( variable )
1458
1459    spec_name = TRIM( variable(4:char_len-3) )
1460!
1461!-- Output of emission values, i.e. surface fluxes cssws.
1462    IF ( variable(1:3) == 'em_' )  THEN
1463
1464       local_pf = 0.0_wp
1465
1466       DO  lsp = 1, nvar
1467          IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name) )  THEN
1468!
1469!--          No average output for now.
1470             DO  m = 1, surf_lsm_h%ns
1471                local_pf(surf_lsm_h%i(m),surf_lsm_h%j(m),nzb+1) =                                  &
1472                                                   local_pf(surf_lsm_h%i(m),surf_lsm_h%j(m),nzb+1) &
1473                                                   + surf_lsm_h%cssws(lsp,m)
1474             ENDDO
1475             DO  m = 1, surf_usm_h%ns
1476                   local_pf(surf_usm_h%i(m),surf_usm_h%j(m),nzb+1) =                               &
1477                                                   local_pf(surf_usm_h%i(m),surf_usm_h%j(m),nzb+1) &
1478                                                   + surf_usm_h%cssws(lsp,m)
1479             ENDDO
1480             grid = 'zu'
1481             found = .TRUE.
1482          ENDIF
1483       ENDDO
1484
1485    ELSE
1486
1487       DO  lsp=1,nspec
1488          IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name )  .AND.                          &
1489                ( (variable(char_len-2:) == '_xy')  .OR.                                           &
1490                  (variable(char_len-2:) == '_xz')  .OR.                                           &
1491                  (variable(char_len-2:) == '_yz') ) )  THEN
1492!
1493!--   todo: remove or replace by "CALL message" mechanism (kanani)
1494!                    IF(myid == 0)  WRITE(6,*) 'Output of species ' // TRIM( variable )  //       &
1495!                                                             TRIM( chem_species(lsp)%name )
1496             IF (av == 0)  THEN
1497                DO  i = nxl, nxr
1498                   DO  j = nys, nyn
1499                      DO  k = nzb_do, nzt_do
1500                           local_pf(i,j,k) = MERGE(                                                &
1501                                              chem_species(lsp)%conc(k,j,i),                       &
1502                                              REAL( fill_value, KIND = wp ),                       &
1503                                              BTEST( wall_flags_total_0(k,j,i), 0 ) )
1504                      ENDDO
1505                   ENDDO
1506                ENDDO
1507
1508             ELSE
1509                DO  i = nxl, nxr
1510                   DO  j = nys, nyn
1511                      DO  k = nzb_do, nzt_do
1512                           local_pf(i,j,k) = MERGE(                                                &
1513                                              chem_species(lsp)%conc_av(k,j,i),                    &
1514                                              REAL( fill_value, KIND = wp ),                       &
1515                                              BTEST( wall_flags_total_0(k,j,i), 0 ) )
1516                      ENDDO
1517                   ENDDO
1518                ENDDO
1519             ENDIF
1520             grid = 'zu'
1521             found = .TRUE.
1522          ENDIF
1523       ENDDO
1524    ENDIF
1525
1526    RETURN
1527
1528 END SUBROUTINE chem_data_output_2d
1529
1530
1531!--------------------------------------------------------------------------------------------------!
1532! Description:
1533! ------------
1534!> Subroutine defining 3D output variables for chemical species
1535!--------------------------------------------------------------------------------------------------!
1536 SUBROUTINE chem_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1537
1538
1539    USE surface_mod
1540
1541    CHARACTER (LEN=*)    ::  variable     !<
1542
1543    INTEGER(iwp)         ::  av         !<
1544    INTEGER(iwp) ::  nzb_do             !< lower limit of the data output (usually 0)
1545    INTEGER(iwp) ::  nzt_do             !< vertical upper limit of the data output (usually nz_do3d)
1546
1547    LOGICAL      ::  found                !<
1548
1549    REAL(wp)             ::  fill_value   !<
1550
1551    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf
1552!
1553!-- Local variables
1554    CHARACTER(LEN=16)    ::  spec_name
1555
1556    INTEGER(iwp)         ::  i
1557    INTEGER(iwp)         ::  j
1558    INTEGER(iwp)         ::  k
1559    INTEGER(iwp)         ::  m       !< running indices for surfaces
1560    INTEGER(iwp)         ::  l
1561    INTEGER(iwp)         ::  lsp     !< running index for chem spcs
1562
1563
1564    found = .FALSE.
1565    IF ( .NOT. (variable(1:3) == 'kc_' .OR. variable(1:3) == 'em_' ) )  THEN
1566       RETURN
1567    ENDIF
1568
1569    spec_name = TRIM( variable(4:) )
1570
1571    IF ( variable(1:3) == 'em_' )  THEN
1572
1573       DO  lsp = 1, nvar   !!! cssws - nvar species, chem_species - nspec species !!!
1574          IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name) )  THEN
1575
1576             local_pf = 0.0_wp
1577!
1578!--          no average for now
1579             DO  m = 1, surf_usm_h%ns
1580                local_pf(surf_usm_h%i(m),surf_usm_h%j(m),surf_usm_h%k(m)) =                        &
1581                                         local_pf(surf_usm_h%i(m),surf_usm_h%j(m),surf_usm_h%k(m)) &
1582                                         + surf_usm_h%cssws(lsp,m)
1583             ENDDO
1584             DO  m = 1, surf_lsm_h%ns
1585                local_pf(surf_lsm_h%i(m),surf_lsm_h%j(m),surf_lsm_h%k(m)) =                        &
1586                                         local_pf(surf_lsm_h%i(m),surf_lsm_h%j(m),surf_lsm_h%k(m)) &
1587                                         + surf_lsm_h%cssws(lsp,m)
1588             ENDDO
1589             DO  l = 0, 3
1590                DO  m = 1, surf_usm_v(l)%ns
1591                   local_pf(surf_usm_v(l)%i(m),surf_usm_v(l)%j(m),surf_usm_v(l)%k(m)) =            &
1592                                local_pf(surf_usm_v(l)%i(m),surf_usm_v(l)%j(m),surf_usm_v(l)%k(m)) &
1593                                + surf_usm_v(l)%cssws(lsp,m)
1594                ENDDO
1595                DO  m = 1, surf_lsm_v(l)%ns
1596                   local_pf(surf_lsm_v(l)%i(m),surf_lsm_v(l)%j(m),surf_lsm_v(l)%k(m)) =            &
1597                                local_pf(surf_lsm_v(l)%i(m),surf_lsm_v(l)%j(m),surf_lsm_v(l)%k(m)) &
1598                                + surf_lsm_v(l)%cssws(lsp,m)
1599                ENDDO
1600             ENDDO
1601             found = .TRUE.
1602          ENDIF
1603       ENDDO
1604    ELSE
1605      DO  lsp = 1, nspec
1606         IF ( TRIM( spec_name ) == TRIM( chem_species(lsp)%name) )  THEN
1607!
1608!--   todo: remove or replace by "CALL message" mechanism (kanani)
1609!              IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ' // TRIM( variable )  // &
1610!                                                           TRIM( chem_species(lsp)%name )
1611            IF (av == 0)  THEN
1612               DO  i = nxl, nxr
1613                  DO  j = nys, nyn
1614                     DO  k = nzb_do, nzt_do
1615                         local_pf(i,j,k) = MERGE(                                                  &
1616                                             chem_species(lsp)%conc(k,j,i),                        &
1617                                             REAL( fill_value, KIND = wp ),                        &
1618                                             BTEST( wall_flags_total_0(k,j,i), 0 ) )
1619                     ENDDO
1620                  ENDDO
1621               ENDDO
1622
1623            ELSE
1624
1625               DO  i = nxl, nxr
1626                  DO  j = nys, nyn
1627                     DO  k = nzb_do, nzt_do
1628                         local_pf(i,j,k) = MERGE(                                                  &
1629                                             chem_species(lsp)%conc_av(k,j,i),                     &
1630                                             REAL( fill_value, KIND = wp ),                        &
1631                                             BTEST( wall_flags_total_0(k,j,i), 0 ) )
1632                     ENDDO
1633                  ENDDO
1634               ENDDO
1635            ENDIF
1636            found = .TRUE.
1637         ENDIF
1638      ENDDO
1639    ENDIF
1640
1641    RETURN
1642
1643 END SUBROUTINE chem_data_output_3d
1644
1645
1646!--------------------------------------------------------------------------------------------------!
1647! Description:
1648! ------------
1649!> Subroutine defining mask output variables for chemical species
1650!--------------------------------------------------------------------------------------------------!
1651 SUBROUTINE chem_data_output_mask( av, variable, found, local_pf, mid )
1652
1653
1654    USE control_parameters
1655
1656    REAL(wp), PARAMETER ::  fill_value = -9999.0_wp    !< value for the _FillValue attribute
1657
1658    CHARACTER(LEN=16) ::  spec_name
1659    CHARACTER(LEN=*)  ::  variable    !<
1660
1661    INTEGER(iwp) ::  av              !< flag to control data output of instantaneous or
1662                                     !< time-averaged data
1663    INTEGER(iwp) ::  i               !< grid index along x-direction
1664    INTEGER(iwp) ::  im              !< loop index for masked variables
1665    INTEGER(iwp) ::  j               !< grid index along y-direction
1666    INTEGER(iwp) ::  jm              !< loop index for masked variables
1667    INTEGER(iwp) ::  k               !< grid index along z-direction
1668    INTEGER(iwp) ::  kk              !< masked output index along z-direction
1669    INTEGER(iwp) ::  ktt             !< k index of highest terrain surface
1670    INTEGER(iwp) ::  lsp
1671    INTEGER(iwp) ::  mid             !< masked output running index
1672
1673    LOGICAL ::  found
1674
1675    REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  local_pf   !<
1676
1677
1678!
1679!-- Local variables.
1680
1681    spec_name = TRIM( variable(4:) )
1682    found = .FALSE.
1683
1684    DO  lsp=1,nspec
1685       IF (TRIM( spec_name ) == TRIM( chem_species(lsp)%name) )  THEN
1686!
1687!-- todo: remove or replace by "CALL message" mechanism (kanani)
1688!              IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ' // TRIM( variable )  // &
1689!                                                        TRIM( chem_species(lsp)%name )
1690          IF (av == 0)  THEN
1691             IF ( .NOT. mask_surface(mid) )  THEN
1692
1693                DO  i = 1, mask_size_l(mid,1)
1694                   DO  j = 1, mask_size_l(mid,2)
1695                      DO  k = 1, mask_size(mid,3)
1696                          local_pf(i,j,k) = chem_species(lsp)%conc( mask_k(mid,k),                 &
1697                                                                    mask_j(mid,j),                 &
1698                                                                    mask_i(mid,i)      )
1699                      ENDDO
1700                   ENDDO
1701                ENDDO
1702
1703             ELSE
1704!
1705!--             Terrain-following masked output
1706                DO  i = 1, mask_size_l(mid,1)
1707                   DO  j = 1, mask_size_l(mid,2)
1708!
1709!--                   Get k index of the highest terraing surface
1710                      im = mask_i(mid,i)
1711                      jm = mask_j(mid,j)
1712                      ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 ) ),        &
1713                                    DIM = 1 ) - 1
1714                      DO  k = 1, mask_size_l(mid,3)
1715                         kk = MIN( ktt+mask_k(mid,k), nzt+1 )
1716!
1717!--                      Set value if not in building
1718                         IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
1719                            local_pf(i,j,k) = fill_value
1720                         ELSE
1721                            local_pf(i,j,k) = chem_species(lsp)%conc(kk,jm,im)
1722                         ENDIF
1723                      ENDDO
1724                   ENDDO
1725                ENDDO
1726
1727             ENDIF
1728          ELSE
1729             IF ( .NOT. mask_surface(mid) )  THEN
1730
1731                DO  i = 1, mask_size_l(mid,1)
1732                   DO  j = 1, mask_size_l(mid,2)
1733                      DO  k =  1, mask_size_l(mid,3)
1734                          local_pf(i,j,k) = chem_species(lsp)%conc_av(  mask_k(mid,k),             &
1735                                                                        mask_j(mid,j),             &
1736                                                                        mask_i(mid,i)         )
1737                      ENDDO
1738                   ENDDO
1739                ENDDO
1740
1741             ELSE
1742!
1743!--             Terrain-following masked output
1744                DO  i = 1, mask_size_l(mid,1)
1745                   DO  j = 1, mask_size_l(mid,2)
1746!
1747!--                   Get k index of the highest terraing surface
1748                      im = mask_i(mid,i)
1749                      jm = mask_j(mid,j)
1750                      ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),         &
1751                                    DIM = 1 ) - 1
1752                      DO  k = 1, mask_size_l(mid,3)
1753                         kk = MIN( ktt+mask_k(mid,k), nzt+1 )
1754!
1755!--                      Set value if not in building
1756                         IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
1757                            local_pf(i,j,k) = fill_value
1758                         ELSE
1759                            local_pf(i,j,k) = chem_species(lsp)%conc_av(kk,jm,im)
1760                         ENDIF
1761                      ENDDO
1762                   ENDDO
1763                ENDDO
1764
1765             ENDIF
1766
1767          ENDIF
1768          found = .TRUE.
1769          EXIT
1770       ENDIF
1771    ENDDO
1772
1773    RETURN
1774
1775 END SUBROUTINE chem_data_output_mask
1776
1777
1778!--------------------------------------------------------------------------------------------------!
1779! Description:
1780! ------------
1781!> Subroutine defining appropriate grid for netcdf variables.
1782!> It is called out from subroutine netcdf.
1783!--------------------------------------------------------------------------------------------------!
1784 SUBROUTINE chem_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
1785
1786
1787    CHARACTER (LEN=*), INTENT(IN)  ::  var          !<
1788
1789    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x       !<
1790    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y       !<
1791    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z       !<
1792
1793    LOGICAL, INTENT(OUT)           ::  found        !<
1794
1795    found  = .TRUE.
1796
1797    IF ( var(1:3) == 'kc_' .OR. var(1:3) == 'em_' )  THEN                !< always the same grid for
1798                                                                         !< chemistry variables
1799       grid_x = 'x'
1800       grid_y = 'y'
1801       grid_z = 'zu'
1802    ELSE
1803       found  = .FALSE.
1804       grid_x = 'none'
1805       grid_y = 'none'
1806       grid_z = 'none'
1807    ENDIF
1808
1809
1810 END SUBROUTINE chem_define_netcdf_grid
1811
1812
1813!--------------------------------------------------------------------------------------------------!
1814! Description:
1815! ------------
1816!> Subroutine defining header output for chemistry model
1817!--------------------------------------------------------------------------------------------------!
1818 SUBROUTINE chem_header( io )
1819
1820    CHARACTER (LEN=80)  :: docsflux_chr
1821    CHARACTER (LEN=80)  :: docsinit_chr
1822
1823    INTEGER(iwp), INTENT(IN) ::  io            !< Unit of the output file
1824
1825    INTEGER(iwp)  :: cs_fixed
1826    INTEGER(iwp)  :: lsp                       !< running index for chem spcs
1827
1828!
1829!-- Get name of chemical mechanism from chem_gasphase_mod
1830    CALL get_mechanism_name
1831!
1832!-- Write chemistry model  header
1833    WRITE( io, 1 )
1834!
1835!-- Gasphase reaction status
1836    IF ( chem_gasphase_on )  THEN
1837       WRITE( io, 2 )
1838    ELSE
1839       WRITE( io, 3 )
1840    ENDIF
1841!
1842!-- Chemistry time-step
1843    WRITE ( io, 4 ) cs_time_step
1844!
1845!-- Emission mode info
1846!-- At the moment the evaluation is done with both emiss_lod and mode_emis but once salsa has been
1847!-- migrated to emiss_lod the .OR. mode_emis conditions can be removed (ecc 20190513)
1848    IF     ( ( emiss_lod == 1 )  .OR.  ( mode_emis == 'DEFAULT' ) )        THEN
1849        WRITE ( io, 5 )
1850    ELSEIF ( ( emiss_lod == 0 )  .OR.  ( mode_emis == 'PARAMETERIZED' ) )  THEN
1851        WRITE ( io, 6 )
1852    ELSEIF ( ( emiss_lod == 2 )  .OR.  ( mode_emis == 'PRE-PROCESSED' ) )  THEN
1853        WRITE ( io, 7 )
1854    ENDIF
1855!
1856!-- Photolysis scheme info
1857    IF ( photolysis_scheme == "simple" )  THEN
1858       WRITE( io, 8 )
1859    ELSEIF (photolysis_scheme == "constant" )  THEN
1860       WRITE( io, 9 )
1861    ENDIF
1862!
1863!-- Emission flux info
1864    lsp = 1
1865    docsflux_chr ='Chemical species for surface emission flux: '
1866    DO WHILE ( surface_csflux_name(lsp) /= 'novalue' )
1867       docsflux_chr = TRIM( docsflux_chr ) // ' ' // TRIM( surface_csflux_name(lsp) ) // ','
1868       IF ( LEN_TRIM( docsflux_chr ) >= 75 )  THEN
1869          WRITE ( io, 10 )  docsflux_chr
1870          docsflux_chr = '       '
1871       ENDIF
1872       lsp = lsp + 1
1873    ENDDO
1874
1875    IF ( docsflux_chr /= '' )  THEN
1876       WRITE ( io, 10 )  docsflux_chr
1877    ENDIF
1878!
1879!-- Initialization of Surface and profile chemical species
1880    lsp = 1
1881    docsinit_chr ='Chemical species for initial surface and profile emissions: '
1882    DO WHILE ( cs_name(lsp) /= 'novalue' )
1883       docsinit_chr = TRIM( docsinit_chr ) // ' ' // TRIM( cs_name(lsp) ) // ','
1884       IF ( LEN_TRIM( docsinit_chr ) >= 75 )  THEN
1885          WRITE ( io, 11 )  docsinit_chr
1886          docsinit_chr = '       '
1887       ENDIF
1888       lsp = lsp + 1
1889    ENDDO
1890
1891    IF ( docsinit_chr /= '' )  THEN
1892       WRITE ( io, 11 )  docsinit_chr
1893    ENDIF
1894
1895    IF ( nesting_chem )  WRITE( io, 12 )  nesting_chem
1896    IF ( nesting_offline_chem )  WRITE( io, 13 )  nesting_offline_chem
1897
1898    WRITE( io, 14 )  TRIM( bc_cs_b ), TRIM( bc_cs_t ), TRIM( bc_cs_s ), TRIM( bc_cs_n ),           &
1899                     TRIM( bc_cs_l ), TRIM( bc_cs_r )
1900
1901!
1902!-- Number of variable and fix chemical species and number of reactions
1903    cs_fixed = nspec - nvar
1904    WRITE ( io, * ) '   --> Chemical Mechanism        : ', cs_mech
1905    WRITE ( io, * ) '   --> Chemical species, variable: ', nvar
1906    WRITE ( io, * ) '   --> Chemical species, fixed   : ', cs_fixed
1907    WRITE ( io, * ) '   --> Total number of reactions : ', nreact
1908
1909
19101   FORMAT (//' Chemistry model information:'/' ----------------------------'/)
19112   FORMAT ('    --> Chemical reactions are turned on')
19123   FORMAT ('    --> Chemical reactions are turned off')
19134   FORMAT ('    --> Time-step for chemical species: ',F6.2, ' s')
19145   FORMAT ('    --> Emission mode = DEFAULT ')
19156   FORMAT ('    --> Emission mode = PARAMETERIZED ')
19167   FORMAT ('    --> Emission mode = PRE-PROCESSED ')
19178   FORMAT ('    --> Photolysis scheme used =  simple ')
19189   FORMAT ('    --> Photolysis scheme used =  constant ')
191910  FORMAT (/'    ',A)
192011  FORMAT (/'    ',A)
192112  FORMAT (/'   Nesting for chemistry variables: ', L1 )
192213  FORMAT (/'   Offline nesting for chemistry variables: ', L1 )
192314  FORMAT (/'   Boundary conditions for chemical species:', /                                     &
1924             '      bottom/top:   ',A10,' / ',A10, /                                               &
1925             '      north/south:  ',A10,' / ',A10, /                                               &
1926             '      left/right:   ',A10,' / ',A10)
1927
1928 END SUBROUTINE chem_header
1929
1930
1931!--------------------------------------------------------------------------------------------------!
1932! Description:
1933! ------------
1934!> Subroutine initializating chemistry_model_mod specific arrays
1935!--------------------------------------------------------------------------------------------------!
1936 SUBROUTINE chem_init_arrays
1937!
1938!-- Please use this place to allocate required arrays
1939
1940 END SUBROUTINE chem_init_arrays
1941
1942
1943!--------------------------------------------------------------------------------------------------!
1944! Description:
1945! ------------
1946!> Subroutine initializating chemistry_model_mod
1947!--------------------------------------------------------------------------------------------------!
1948 SUBROUTINE chem_init
1949
1950!
1951!-- 20200203 (ECC)
1952!-- introduced additional interfaces for on-demand emission update
1953
1954!    USE chem_emissions_mod,                                                                        &
1955!        ONLY:  chem_emissions_init
1956
1957    USE chem_emissions_mod,                                                                        &
1958        ONLY:  chem_emissions_header_init, chem_emissions_init
1959
1960    USE netcdf_data_input_mod,                                                                     &
1961        ONLY:  init_3d
1962
1963
1964    INTEGER(iwp) ::  i !< running index x dimension
1965    INTEGER(iwp) ::  j !< running index y dimension
1966    INTEGER(iwp) ::  n !< running index for chemical species
1967
1968
1969    IF ( debug_output )  CALL debug_message( 'chem_init', 'start' )
1970!
1971!-- Next statement is to avoid compiler warning about unused variables
1972    IF ( ( ilu_arable + ilu_coniferous_forest + ilu_deciduous_forest + ilu_mediterrean_scrub +     &
1973           ilu_permanent_crops + ilu_savanna + ilu_semi_natural_veg + ilu_tropical_forest +        &
1974           ilu_urban ) == 0 )  CONTINUE
1975
1976!
1977!-- 20200203 (ECC)
1978!-- Calls specific emisisons initialization subroutines for legacy mode and on-demand mode
1979
1980!    IF ( emissions_anthropogenic )  CALL chem_emissions_init
1981
1982    IF  ( emissions_anthropogenic )  THEN
1983
1984       IF  ( emiss_read_legacy_mode )  THEN
1985          CALL chem_emissions_init
1986       ELSE
1987          CALL chem_emissions_header_init
1988       ENDIF
1989
1990    ENDIF
1991
1992
1993!
1994!-- Chemistry variables will be initialized if availabe from dynamic input file. Note, it is
1995!-- possible to initialize only part of the chemistry variables from dynamic input.
1996    IF ( INDEX( initializing_actions, 'inifor' ) /= 0 )  THEN
1997       DO  n = 1, nspec
1998          IF ( init_3d%from_file_chem(n) )  THEN
1999             DO  i = nxlg, nxrg
2000                DO  j = nysg, nyng
2001                   chem_species(n)%conc(:,j,i) = init_3d%chem_init(:,n)
2002                ENDDO
2003             ENDDO
2004          ENDIF
2005       ENDDO
2006    ENDIF
2007
2008    IF ( debug_output )  CALL debug_message( 'chem_init', 'end' )
2009
2010 END SUBROUTINE chem_init
2011
2012
2013!--------------------------------------------------------------------------------------------------!
2014! Description:
2015! ------------
2016!> Subroutine initializating chemistry_model_mod
2017!> internal workaround for chem_species dependency in chem_check_parameters
2018!--------------------------------------------------------------------------------------------------!
2019 SUBROUTINE chem_init_internal
2020
2021    USE pegrid
2022
2023    USE netcdf_data_input_mod,                                                                     &
2024        ONLY:  chem_emis, chem_emis_att, input_pids_dynamic, init_3d,                              &
2025               netcdf_data_input_chemistry_data
2026
2027!
2028!-- Local variables
2029    INTEGER(iwp) ::  i                 !< running index for for horiz numerical grid points
2030    INTEGER(iwp) ::  j                 !< running index for for horiz numerical grid points
2031    INTEGER(iwp) ::  lpr_lev           !< running index for chem spcs profile level
2032    INTEGER(iwp) ::  lsp               !< running index for chem spcs
2033
2034    REAL(wp)     ::  flag              !< flag for masking topography/building grid points
2035!
2036!-- 20200203 ECC
2037!-- reads netcdf data only under legacy mode
2038
2039!    IF ( emissions_anthropogenic )  THEN
2040!       CALL netcdf_data_input_chemistry_data( chem_emis_att, chem_emis )
2041!    ENDIF
2042
2043    IF ( emissions_anthropogenic )  THEN
2044       IF ( emiss_read_legacy_mode )  THEN
2045          CALL netcdf_data_input_chemistry_data( chem_emis_att, chem_emis )
2046       ENDIF
2047    ENDIF
2048
2049!
2050!-- Allocate memory for chemical species
2051    ALLOCATE( chem_species(nspec) )
2052    ALLOCATE( spec_conc_1 (nzb:nzt+1,nysg:nyng,nxlg:nxrg,nspec) )
2053    ALLOCATE( spec_conc_2 (nzb:nzt+1,nysg:nyng,nxlg:nxrg,nspec) )
2054    ALLOCATE( spec_conc_3 (nzb:nzt+1,nysg:nyng,nxlg:nxrg,nspec) )
2055    ALLOCATE( phot_frequen(nphot) )
2056    ALLOCATE( freq_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg,nphot) )
2057    ALLOCATE( bc_cs_t_val(nspec) )
2058!
2059!-- Initialize arrays
2060    spec_conc_1 (:,:,:,:) = 0.0_wp
2061    spec_conc_2 (:,:,:,:) = 0.0_wp
2062    spec_conc_3 (:,:,:,:) = 0.0_wp
2063
2064!
2065!-- Allocate array to store locally summed-up resolved-scale vertical fluxes.
2066    IF ( scalar_advec == 'ws-scheme' )  THEN
2067       ALLOCATE( sums_ws_l(nzb:nzt+1,0:threads_per_task-1,nspec) )
2068       sums_ws_l = 0.0_wp
2069    ENDIF
2070
2071    DO  lsp = 1, nspec
2072       chem_species(lsp)%name    = spc_names(lsp)
2073
2074       chem_species(lsp)%conc   (nzb:nzt+1,nysg:nyng,nxlg:nxrg)       => spec_conc_1 (:,:,:,lsp)
2075       chem_species(lsp)%conc_p (nzb:nzt+1,nysg:nyng,nxlg:nxrg)       => spec_conc_2 (:,:,:,lsp)
2076       chem_species(lsp)%tconc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg)       => spec_conc_3 (:,:,:,lsp)
2077
2078       ALLOCATE (chem_species(lsp)%cssws_av(nysg:nyng,nxlg:nxrg))
2079       chem_species(lsp)%cssws_av    = 0.0_wp
2080!
2081!--    The following block can be useful when emission module is not applied. &
2082!--    If emission module is applied the following block will be overwritten.
2083       ALLOCATE (chem_species(lsp)%flux_s_cs(nzb+1:nzt,0:threads_per_task-1))
2084       ALLOCATE (chem_species(lsp)%diss_s_cs(nzb+1:nzt,0:threads_per_task-1))
2085       ALLOCATE (chem_species(lsp)%flux_l_cs(nzb+1:nzt,nys:nyn,0:threads_per_task-1))
2086       ALLOCATE (chem_species(lsp)%diss_l_cs(nzb+1:nzt,nys:nyn,0:threads_per_task-1))
2087       chem_species(lsp)%flux_s_cs = 0.0_wp
2088       chem_species(lsp)%flux_l_cs = 0.0_wp
2089       chem_species(lsp)%diss_s_cs = 0.0_wp
2090       chem_species(lsp)%diss_l_cs = 0.0_wp
2091!
2092!--   Allocate memory for initial concentration profiles (concentration values come from namelist)
2093!--   (@todo (FK): Because of this, chem_init is called in palm before check_parameters, since
2094!--                conc_pr_init is used there.
2095!--                We have to find another solution since chem_init should eventually be called from
2096!--                init_3d_model!!)
2097       ALLOCATE ( chem_species(lsp)%conc_pr_init(0:nz+1) )
2098       chem_species(lsp)%conc_pr_init(:) = 0.0_wp
2099
2100    ENDDO
2101
2102!
2103!-- For some passive scalars decycling may be enabled. This case, the lateral boundary conditions
2104!-- are non-cyclic for these scalars (chemical species and aerosols), while the other scalars may
2105!-- have cyclic boundary conditions. However, large gradients near the boundaries may produce
2106!-- stationary numerical oscillations near the lateral boundaries when a higher-order scheme is
2107!-- applied near these boundaries.
2108!-- To get rid-off this, set-up additional flags that control the order of the scalar advection
2109!-- scheme near the lateral boundaries for passive scalars with decycling.
2110    IF ( scalar_advec == 'ws-scheme' )  THEN
2111       ALLOCATE( cs_advc_flags_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2112!
2113!--    In case of decyling, set Neumann boundary conditions for wall_flags_total_0 bit 31 instead of
2114!--    cyclic boundary conditions.
2115!--    Bit 31 is used to identify extended degradation zones (please see following comment).
2116!--    Note, since several also other modules like Salsa or other future one may access this bit but
2117!--    may have other boundary conditions, the original value of wall_flags_total_0 bit 31 must not
2118!--    be modified. Hence, store the boundary conditions directly on cs_advc_flags_s.
2119!--    cs_advc_flags_s will be later overwritten in ws_init_flags_scalar and bit 31 won't be used to
2120!--    control the numerical order.
2121!--    Initialize with flag 31 only.
2122       cs_advc_flags_s = 0
2123       cs_advc_flags_s = MERGE( IBSET( cs_advc_flags_s, 31 ), 0, BTEST( wall_flags_total_0, 31 ) )
2124
2125       IF ( bc_dirichlet_cs_n .OR. bc_dirichlet_cs_s )  THEN
2126          IF ( nys == 0  )  THEN
2127             DO  i = 1, nbgp
2128                cs_advc_flags_s(:,nys-i,:) = MERGE(                                                &
2129                                                    IBSET( cs_advc_flags_s(:,nys,:), 31 ),         &
2130                                                    IBCLR( cs_advc_flags_s(:,nys,:), 31 ),         &
2131                                                    BTEST( cs_advc_flags_s(:,nys,:), 31 )          &
2132                                                  )
2133             ENDDO
2134          ENDIF
2135          IF ( nyn == ny )  THEN
2136             DO  i = 1, nbgp
2137                cs_advc_flags_s(:,nyn+i,:) = MERGE(                                                &
2138                                                    IBSET( cs_advc_flags_s(:,nyn,:), 31 ),         &
2139                                                    IBCLR( cs_advc_flags_s(:,nyn,:), 31 ),         &
2140                                                    BTEST( cs_advc_flags_s(:,nyn,:), 31 )          &
2141                                                  )
2142             ENDDO
2143          ENDIF
2144       ENDIF
2145       IF ( bc_dirichlet_cs_l .OR. bc_dirichlet_cs_r )  THEN
2146          IF ( nxl == 0  )  THEN
2147             DO  i = 1, nbgp
2148                cs_advc_flags_s(:,:,nxl-i) = MERGE(                                                &
2149                                                    IBSET( cs_advc_flags_s(:,:,nxl), 31 ),         &
2150                                                    IBCLR( cs_advc_flags_s(:,:,nxl), 31 ),         &
2151                                                    BTEST( cs_advc_flags_s(:,:,nxl), 31 )          &
2152                                                  )
2153             ENDDO
2154          ENDIF
2155          IF ( nxr == nx )  THEN
2156             DO  i = 1, nbgp
2157                cs_advc_flags_s(:,:,nxr+i) = MERGE(                                                &
2158                                                    IBSET( cs_advc_flags_s(:,:,nxr), 31 ), &
2159                                                    IBCLR( cs_advc_flags_s(:,:,nxr), 31 ), &
2160                                                    BTEST( cs_advc_flags_s(:,:,nxr), 31 )  &
2161                                                  )
2162             ENDDO
2163          ENDIF
2164
2165       ENDIF
2166!
2167!--    To initialize advection flags appropriately, pass the boundary flags.
2168!--    The last argument indicates that a passive scalar is treated, where the horizontal advection
2169!--    terms are degraded already 2 grid points before the lateral boundary to avoid stationary
2170!--    oscillations at large-gradients.
2171!--    Also, extended degradation zones are applied, where horizontal advection of passive scalars
2172!--    is discretized by first-order scheme at all grid points that in the vicinity of buildings
2173!--    (<= 3 grid points). Even though no building is within the numerical stencil, first-order
2174!--    scheme is used.
2175!--    At fourth and fifth grid point the order of the horizontal advection scheme
2176!--    is successively upgraded.
2177!--    These extended degradation zones are used to avoid stationary numerical oscillations, which
2178!--    are responsible for high concentration maxima that may appear under shear-free stable
2179!--    conditions.
2180       CALL ws_init_flags_scalar( bc_dirichlet_cs_l  .OR.  bc_radiation_cs_l,                      &
2181                                  bc_dirichlet_cs_n  .OR.  bc_radiation_cs_n,                      &
2182                                  bc_dirichlet_cs_r  .OR.  bc_radiation_cs_r,                      &
2183                                  bc_dirichlet_cs_s  .OR.  bc_radiation_cs_s,                      &
2184                                  cs_advc_flags_s, .TRUE. )
2185    ENDIF
2186!
2187!-- Initial concentration of profiles is prescribed by parameters cs_profile and cs_heights in the
2188!-- namelist &chemistry_parameters.
2189    CALL chem_init_profiles
2190!
2191!-- In case there is dynamic input file, create a list of names for chemistry initial input files.
2192!-- Also, initialize array that indicates whether the respective variable is on file or not.
2193    IF ( input_pids_dynamic )  THEN
2194       ALLOCATE( init_3d%var_names_chem(1:nspec) )
2195       ALLOCATE( init_3d%from_file_chem(1:nspec) )
2196       init_3d%from_file_chem(:) = .FALSE.
2197
2198       DO  lsp = 1, nspec
2199          init_3d%var_names_chem(lsp) = init_3d%init_char // TRIM( chem_species(lsp)%name )
2200       ENDDO
2201    ENDIF
2202!
2203!-- Initialize model variables
2204    IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.                                &
2205         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
2206!
2207!--    First model run of a possible job queue.
2208!--    Initial profiles of the variables must be computed.
2209       IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
2210!
2211!--       Transfer initial profiles to the arrays of the 3D model
2212!--       Concentrations within buildings are set to zero.
2213          DO  lsp = 1, nspec
2214             DO  i = nxlg, nxrg
2215                DO  j = nysg, nyng
2216                   DO lpr_lev = 1, nz + 1
2217                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(lpr_lev,j,i), 0 ) )
2218                      chem_species(lsp)%conc(lpr_lev,j,i) = chem_species(lsp)%conc_pr_init(lpr_lev)&
2219                                                            * flag
2220                   ENDDO
2221                ENDDO
2222             ENDDO
2223          ENDDO
2224
2225       ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles') /= 0 )  THEN
2226
2227          DO  lsp = 1, nspec
2228             DO  i = nxlg, nxrg
2229                DO  j = nysg, nyng
2230                   DO  lpr_lev = nzb, nz+1
2231                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(lpr_lev,j,i), 0 ) )
2232                      chem_species(lsp)%conc(lpr_lev,j,i) = chem_species(lsp)%conc_pr_init(lpr_lev)&
2233                                                            * flag
2234                   ENDDO
2235                ENDDO
2236             ENDDO
2237          ENDDO
2238
2239       ENDIF
2240!
2241!--    If required, change the surface chem spcs at the start of the 3D run
2242       IF ( cs_surface_initial_change(1) /= 0.0_wp )  THEN
2243          DO  lsp = 1, nspec
2244             DO  i = nxlg, nxrg
2245                DO  j = nysg, nyng
2246                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(nzb,j,i), 0 ) )
2247                   chem_species(lsp)%conc(nzb,j,i) = chem_species(lsp)%conc(nzb,j,i) +             &
2248                                                     cs_surface_initial_change(lsp) * flag
2249                ENDDO
2250             ENDDO
2251          ENDDO
2252       ENDIF
2253
2254    ENDIF
2255!
2256!-- Initial old and new time levels. Note, this has to be done also in restart runs
2257    DO  lsp = 1, nvar
2258       chem_species(lsp)%tconc_m = 0.0_wp
2259       chem_species(lsp)%conc_p  = chem_species(lsp)%conc
2260    ENDDO
2261
2262    DO  lsp = 1, nphot
2263       phot_frequen(lsp)%name = phot_names(lsp)
2264!
2265!-- todo: remove or replace by "CALL message" mechanism (kanani)
2266!--       IF( myid == 0 )  THEN
2267!--          WRITE(6,'(a,i4,3x,a)')  'Photolysis: ',lsp,TRIM( phot_names(lsp) )
2268!--       ENDIF
2269       phot_frequen(lsp)%freq(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  =>  freq_1(:,:,:,lsp)
2270    ENDDO
2271
2272!    CALL photolysis_init   ! probably also required for restart
2273
2274    RETURN
2275
2276 END SUBROUTINE chem_init_internal
2277
2278
2279!--------------------------------------------------------------------------------------------------!
2280! Description:
2281! ------------
2282!> Subroutine defining initial vertical profiles of chemical species (given by namelist parameters
2283!> chem_profiles and chem_heights)  --> which should work analogically to parameters u_profile,
2284!> v_profile and uv_heights)
2285!--------------------------------------------------------------------------------------------------!
2286 SUBROUTINE chem_init_profiles
2287
2288    USE chem_modules
2289
2290!
2291!-- Local variables
2292    INTEGER ::  lpr_lev    !< running index for profile level for each chem spcs.
2293    INTEGER ::  lsp        !< running index for number of species in derived data type species_def
2294    INTEGER ::  lsp_usr    !< running index for number of species (user defined)  in cs_names,
2295                           !< cs_profiles etc
2296    INTEGER ::  npr_lev    !< the next available profile lev
2297!
2298!-- Parameter "cs_profile" and "cs_heights" are used to prescribe user defined initial profiles
2299!-- and heights. If parameter "cs_profile" is not prescribed then initial surface values
2300!-- "cs_surface" are used as constant initial profiles for each species. If "cs_profile" and
2301!-- "cs_heights" are prescribed, their values will!override the constant profile given by
2302!-- "cs_surface".
2303!     IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
2304    lsp_usr = 1
2305    DO  WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )   !'novalue' is the default
2306       DO  lsp = 1, nspec                                !
2307!
2308!--       Create initial profile (conc_pr_init) for each chemical species
2309          IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
2310             IF ( cs_profile(lsp_usr,1) == 9999999.9_wp )  THEN
2311!
2312!--            Set a vertically constant profile based on the surface conc (cs_surface(lsp_usr)) of
2313!--            each species
2314                DO lpr_lev = 0, nzt+1
2315                   chem_species(lsp)%conc_pr_init(lpr_lev) = cs_surface(lsp_usr)
2316                ENDDO
2317             ELSE
2318                IF ( cs_heights(1,1) /= 0.0_wp )  THEN
2319                   message_string = 'The surface value of cs_heights must be 0.0'
2320                   CALL message( 'chem_check_parameters', 'CM0434', 1, 2, 0, 6, 0 )
2321                ENDIF
2322
2323                use_prescribed_profile_data = .TRUE.
2324
2325                npr_lev = 1
2326!                chem_species(lsp)%conc_pr_init(0) = 0.0_wp
2327                DO  lpr_lev = 1, nz+1
2328                   IF ( npr_lev < 100 )  THEN
2329                      DO  WHILE ( cs_heights(lsp_usr, npr_lev+1) <= zu(lpr_lev) )
2330                         npr_lev = npr_lev + 1
2331                         IF ( npr_lev == 100 )  THEN
2332                            message_string = 'number of chem spcs exceeding the limit'
2333                            CALL message( 'chem_check_parameters', 'CM0435', 1, 2, 0, 6, 0 )
2334                            EXIT
2335                         ENDIF
2336                      ENDDO
2337                   ENDIF
2338                   IF ( npr_lev < 100  .AND.  cs_heights(lsp_usr,npr_lev+1) /= 9999999.9_wp )  THEN
2339                      chem_species(lsp)%conc_pr_init(lpr_lev) = cs_profile(lsp_usr, npr_lev) +     &
2340                           ( zu(lpr_lev) - cs_heights(lsp_usr, npr_lev) ) /                        &
2341                           ( cs_heights(lsp_usr, (npr_lev + 1)) - cs_heights(lsp_usr, npr_lev ) ) *&
2342                           ( cs_profile(lsp_usr, (npr_lev + 1)) - cs_profile(lsp_usr, npr_lev ) )
2343                   ELSE
2344                      chem_species(lsp)%conc_pr_init(lpr_lev) = cs_profile(lsp_usr, npr_lev)
2345                   ENDIF
2346                ENDDO
2347             ENDIF
2348!
2349!--       If a profile is prescribed explicity using cs_profiles and cs_heights, then
2350!--       chem_species(lsp)%conc_pr_init is populated with the specific "lsp" based on the
2351!--       cs_profiles(lsp_usr,:)  and cs_heights(lsp_usr,:).
2352          ENDIF
2353
2354       ENDDO
2355
2356       lsp_usr = lsp_usr + 1
2357    ENDDO
2358!     ENDIF
2359
2360 END SUBROUTINE chem_init_profiles
2361
2362
2363!--------------------------------------------------------------------------------------------------!
2364! Description:
2365! ------------
2366!> Subroutine to integrate chemical species in the given chemical mechanism
2367!--------------------------------------------------------------------------------------------------!
2368 SUBROUTINE chem_integrate_ij( i, j )
2369
2370    USE statistics,                                                                                &
2371        ONLY:  weight_pres
2372
2373    USE control_parameters,                                                                        &
2374        ONLY:  dt_3d, intermediate_timestep_count, time_since_reference_point
2375
2376    REAL(wp), PARAMETER              ::  fr2ppm  = 1.0e6_wp              !< Conversion factor fraction to ppm
2377!    REAL(wp), PARAMETER              ::  xm_air  = 28.96_wp              !< Mole mass of dry air
2378!    REAL(wp), PARAMETER              ::  xm_h2o  = 18.01528_wp           !< Mole mass of water vapor
2379    REAL(wp), PARAMETER              ::  p_std   = 101325.0_wp           !< standard pressure (Pa)
2380    REAL(wp), PARAMETER              ::  ppm2fr  = 1.0e-6_wp             !< Conversion factor ppm to fraction
2381    REAL(wp), PARAMETER              ::  t_std   = 273.15_wp             !< standard pressure (Pa)
2382    REAL(wp), PARAMETER              ::  vmolcm  = 22.414e3_wp           !< Mole volume (22.414 l) in cm^3
2383    REAL(wp), PARAMETER              ::  xna     = 6.022e23_wp           !< Avogadro number (molecules/mol)
2384
2385    INTEGER,INTENT(IN)       :: i
2386    INTEGER,INTENT(IN)       :: j
2387!
2388!-- Local variables
2389    INTEGER(iwp) ::  lph                                 !< running index for photolysis frequencies
2390    INTEGER(iwp) ::  lsp                                 !< running index for chem spcs.
2391
2392    INTEGER, DIMENSION(20)        :: istatus
2393
2394    INTEGER,DIMENSION(nzb+1:nzt)  :: nacc          !< Number of accepted steps
2395    INTEGER,DIMENSION(nzb+1:nzt)  :: nrej          !< Number of rejected steps
2396
2397    REAL(wp)                         ::  conv                                !< conversion factor
2398    REAL(kind=wp)                    ::  dt_chem
2399
2400    REAL(wp),DIMENSION(size(rcntrl)) :: rcntrl_local
2401
2402    REAL(kind=wp), DIMENSION(nzb+1:nzt)                      :: tmp_fact
2403    REAL(kind=wp), DIMENSION(nzb+1:nzt)                      :: tmp_fact_i    !< conversion factor between
2404                                                                              !< molecules cm^{-3} and ppm
2405    REAL(kind=wp), DIMENSION(nzb+1:nzt)                      :: tmp_qvap
2406    REAL(kind=wp), DIMENSION(nzb+1:nzt)                      :: tmp_temp
2407
2408    REAL(kind=wp), DIMENSION(nzb+1:nzt,nspec)                :: tmp_conc
2409    REAL(kind=wp), DIMENSION(nzb+1:nzt,nphot)                :: tmp_phot
2410
2411!
2412!-- Set chem_gasphase_on to .FALSE. if you want to skip computation of gas phase chemistry
2413    IF (chem_gasphase_on)  THEN
2414       nacc = 0
2415       nrej = 0
2416
2417       tmp_temp(:) = pt(nzb+1:nzt,j,i) * exner(nzb+1:nzt)
2418!
2419!--    Convert ppm to molecules/cm**3
2420!--    tmp_fact = 1.e-6_wp*6.022e23_wp/(22.414_wp*1000._wp) * 273.15_wp *
2421!--               hyp(nzb+1:nzt)/( 101300.0_wp * tmp_temp )
2422       conv = ppm2fr * xna / vmolcm
2423       tmp_fact(:) = conv * t_std * hyp(nzb+1:nzt) / (tmp_temp(:) * p_std)
2424       tmp_fact_i = 1.0_wp/tmp_fact
2425
2426       IF ( humidity )  THEN
2427          IF ( bulk_cloud_model )  THEN
2428             tmp_qvap(:) = ( q(nzb+1:nzt,j,i) - ql(nzb+1:nzt,j,i) ) *                              &
2429                             xm_air/xm_h2o * fr2ppm * tmp_fact(:)
2430          ELSE
2431             tmp_qvap(:) = q(nzb+1:nzt,j,i) * xm_air/xm_h2o * fr2ppm * tmp_fact(:)
2432          ENDIF
2433       ELSE
2434          tmp_qvap(:) = 0.01 * xm_air/xm_h2o * fr2ppm * tmp_fact(:)   !< Constant value for q if
2435                                                                      !< water vapor is not computed
2436       ENDIF
2437
2438       DO  lsp = 1,nspec
2439          tmp_conc(:,lsp) = chem_species(lsp)%conc(nzb+1:nzt,j,i) * tmp_fact(:)
2440       ENDDO
2441
2442       DO lph = 1,nphot
2443          tmp_phot(:,lph) = phot_frequen(lph)%freq(nzb+1:nzt,j,i)
2444       ENDDO
2445!
2446!--    Compute length of time step
2447       IF ( call_chem_at_all_substeps )  THEN
2448          dt_chem = dt_3d * weight_pres(intermediate_timestep_count)
2449       ELSE
2450          dt_chem = dt_3d
2451       ENDIF
2452
2453       cs_time_step = dt_chem
2454
2455       IF ( MAXVAL( rcntrl ) > 0.0 )  THEN    ! Only if rcntrl is set
2456          IF( time_since_reference_point <= 2*dt_3d)  THEN
2457             rcntrl_local = 0
2458          ELSE
2459             rcntrl_local = rcntrl
2460          ENDIF
2461       ELSE
2462          rcntrl_local = 0
2463       END IF
2464
2465       CALL chem_gasphase_integrate ( dt_chem, tmp_conc, tmp_temp, tmp_qvap, tmp_fact, tmp_phot,   &
2466            icntrl_i = icntrl, rcntrl_i = rcntrl_local, xnacc = nacc, xnrej = nrej, istatus=istatus )
2467
2468       DO  lsp = 1,nspec
2469          chem_species(lsp)%conc (nzb+1:nzt,j,i) = tmp_conc(:,lsp) * tmp_fact_i(:)
2470       ENDDO
2471
2472
2473    ENDIF
2474
2475    RETURN
2476 END SUBROUTINE chem_integrate_ij
2477
2478
2479!--------------------------------------------------------------------------------------------------!
2480! Description:
2481! ------------
2482!> Subroutine defining parin for &chemistry_parameters for chemistry model
2483!--------------------------------------------------------------------------------------------------!
2484 SUBROUTINE chem_parin
2485
2486    USE chem_modules
2487    USE control_parameters
2488
2489    USE pegrid
2490    USE statistics
2491
2492
2493    CHARACTER (LEN=80) ::  line                        !< dummy string that contains the current
2494                                                       !< line of the parameter file
2495
2496    INTEGER(iwp) ::  i                                 !<
2497    INTEGER(iwp) ::  max_pr_cs_tmp                     !<
2498
2499    REAL(wp), DIMENSION(nmaxfixsteps) ::   my_steps    !< List of fixed timesteps   my_step(1) = 0.0
2500                                                       !< automatic stepping
2501
2502
2503    NAMELIST /chemistry_parameters/                                                                &
2504         bc_cs_b,                                                                                  &
2505         bc_cs_l,                                                                                  &
2506         bc_cs_n,                                                                                  &
2507         bc_cs_r,                                                                                  &
2508         bc_cs_s,                                                                                  &
2509         bc_cs_t,                                                                                  &
2510         call_chem_at_all_substeps,                                                                &
2511         chem_debug0,                                                                              &
2512         chem_debug1,                                                                              &
2513         chem_debug2,                                                                              &
2514         chem_gasphase_on,                                                                         &
2515         chem_mechanism,                                                                           &
2516         cs_heights,                                                                               &
2517         cs_name,                                                                                  &
2518         cs_profile,                                                                               &
2519         cs_surface,                                                                               &
2520         cs_surface_initial_change,                                                                &
2521         cs_vertical_gradient_level,                                                               &
2522         daytype_mdh,                                                                              &
2523         deposition_dry,                                                                           &
2524         emissions_anthropogenic,                                                                  &
2525         emiss_lod,                                                                                &
2526         emiss_factor_main,                                                                        &
2527         emiss_factor_side,                                                                        &
2528         emiss_read_legacy_mode,                                                                   &
2529         icntrl,                                                                                   &
2530         main_street_id,                                                                           &
2531         max_street_id,                                                                            &
2532         mode_emis,                                                                                &
2533         my_steps,                                                                                 &
2534         nesting_chem,                                                                             &
2535         nesting_offline_chem,                                                                     &
2536         rcntrl,                                                                                   &
2537         side_street_id,                                                                           &
2538         photolysis_scheme,                                                                        &
2539         wall_csflux,                                                                              &
2540         cs_vertical_gradient,                                                                     &
2541         top_csflux,                                                                               &
2542         surface_csflux,                                                                           &
2543         surface_csflux_name,                                                                      &
2544         time_fac_type
2545!
2546!-- Analogically to chem_names(nspj) we could invent chem_surfaceflux(nspj) and chem_topflux(nspj)
2547!-- so this way we could prescribe a specific flux value for each species
2548    !>  chemistry_parameters for initial profiles
2549    !>  cs_names = 'O3', 'NO2', 'NO', ...   to set initial profiles)
2550    !>  cs_heights(1,:) = 0.0, 100.0, 500.0, 2000.0, .... (height levels where concs will be prescribed for O3)
2551    !>  cs_heights(2,:) = 0.0, 200.0, 400.0, 1000.0, .... (same for NO2 etc.)
2552    !>  cs_profiles(1,:) = 10.0, 20.0, 20.0, 30.0, .....  (chem spcs conc at height lvls chem_heights(1,:)) etc.
2553    !>  If the respective concentration profile should be constant with height, then use "cs_surface( number of spcs)"
2554    !>  then write these cs_surface values to chem_species(lsp)%conc_pr_init(:)
2555!
2556!-- Read chem namelist
2557    CHARACTER(LEN=8)    :: solver_type
2558
2559    icntrl    = 0
2560    rcntrl    = 0.0_wp
2561    my_steps  = 0.0_wp
2562    photolysis_scheme = 'simple'
2563    atol = 1.0_wp
2564    rtol = 0.01_wp
2565!
2566!-- Try to find chemistry package
2567    REWIND ( 11 )
2568    line = ' '
2569    DO   WHILE ( INDEX( line, '&chemistry_parameters' ) == 0 )
2570       READ ( 11, '(A)', END=20 )  line
2571    ENDDO
2572    BACKSPACE ( 11 )
2573!
2574!-- Read chemistry namelist
2575    READ ( 11, chemistry_parameters, ERR = 10, END = 20 )
2576!
2577!-- Enable chemistry model
2578    air_chemistry = .TRUE.
2579    GOTO 20
2580
2581 10 BACKSPACE( 11 )
2582    READ( 11 , '(A)') line
2583    CALL parin_fail_message( 'chemistry_parameters', line )
2584
2585 20 CONTINUE
2586
2587
2588
2589!
2590!-- Synchronize emiss_lod and mod_emis only if emissions_anthropogenic is activated in the namelist.
2591!-- Otherwise their values are "don't care"
2592    IF ( emissions_anthropogenic )  THEN
2593
2594!
2595!--    Check for emission mode for chem species
2596       IF ( emiss_lod < 0 )  THEN   !- if LOD not defined in namelist
2597          IF ( ( mode_emis /= 'PARAMETERIZED'  )    .AND.                                          &
2598               ( mode_emis /= 'DEFAULT'        )    .AND.                                          &
2599               ( mode_emis /= 'PRE-PROCESSED'  ) )  THEN
2600             message_string = 'Incorrect mode_emiss  option select. Please check spelling'
2601             CALL message( 'chem_check_parameters', 'CM0436', 1, 2, 0, 6, 0 )
2602          ENDIF
2603       ELSE
2604          IF ( ( emiss_lod /= 0 )    .AND.                                                         &
2605               ( emiss_lod /= 1 )    .AND.                                                         &
2606               ( emiss_lod /= 2 ) )  THEN
2607             message_string = 'Invalid value for emiss_lod (0, 1, or 2)'
2608             CALL message( 'chem_check_parameters', 'CM0436', 1, 2, 0, 6, 0 )
2609          ENDIF
2610       ENDIF
2611
2612!
2613! For reference (ecc)
2614!    IF ( (mode_emis /= 'PARAMETERIZED')  .AND. ( mode_emis /= 'DEFAULT' ) .AND. ( mode_emis /= 'PRE-PROCESSED'  ) )  THEN
2615!       message_string = 'Incorrect mode_emiss  option select. Please check spelling'
2616!       CALL message( 'chem_check_parameters', 'CM0436', 1, 2, 0, 6, 0 )
2617!    ENDIF
2618
2619!
2620!-- Conflict resolution for emiss_lod and mode_emis
2621!-- 1) if emiss_lod is defined, have mode_emis assume same setting as emiss_lod
2622!-- 2) if emiss_lod it not defined, have emiss_lod assuem same setting as mode_emis
2623!-- this check is in place to retain backward compatibility with salsa until the code is migrated
2624!-- completed to emiss_lod
2625!-- note that
2626       IF  ( emiss_lod >= 0 ) THEN
2627
2628          SELECT CASE  ( emiss_lod )
2629             CASE (0)  !- parameterized mode
2630                mode_emis = 'PARAMETERIZED'
2631             CASE (1)  !- default mode
2632                mode_emis = 'DEFAULT'
2633             CASE (2)  !- preprocessed mode
2634                mode_emis = 'PRE-PROCESSED'
2635          END SELECT
2636
2637          message_string = 'Synchronizing mode_emis to defined emiss_lod'               //         &
2638                           CHAR( 10 )  //  '                    '                       //         &
2639                           'NOTE - mode_emis will be depreciated in future releases'    //         &
2640                           CHAR( 10 )  //  '                    '                       //         &
2641                           'please use emiss_lod to define emission mode'
2642
2643          CALL message ( 'parin_chem', 'CM0463', 0, 0, 0, 6, 0 )
2644
2645       ELSE ! if emiss_lod is not set
2646
2647          SELECT CASE ( mode_emis )
2648             CASE ('PARAMETERIZED')
2649                emiss_lod = 0
2650             CASE ('DEFAULT')
2651                emiss_lod = 1
2652             CASE ('PRE-PROCESSED')
2653                emiss_lod = 2
2654          END SELECT
2655
2656          message_string = 'emiss_lod undefined.  Using existing mod_emiss setting'     //         &
2657                           CHAR( 10 )  //  '                    '                       //         &
2658                           'NOTE - mode_emis will be depreciated in future releases'    //         &
2659                           CHAR( 10 )  //  '                    '                       //         &
2660                           'please use emiss_lod to define emission mode'
2661
2662          CALL message ( 'parin_chem', 'CM0464', 0, 0, 0, 6, 0 )
2663       ENDIF
2664
2665!
2666!-- (ECC) input check for emission read mode.
2667!--    legacy : business as usual (everything read / set up at start of run)
2668!--    new    : emission based on timestamp, and for lod2 data is loaded on an hourly basis
2669
2670!
2671!-- (ECC) handler for emiss_read_legacy_mode
2672!-- * emiss_read_legacy_mode is defaulted to TRUE
2673!-- * if emiss_read_legacy_mode is TRUE and LOD is 0 or 1,
2674!--       force emission_read_legacy_mode to TRUE (not yet implemented)
2675
2676       IF ( emiss_read_legacy_mode )  THEN       !< notify legacy read mode
2677
2678          message_string = 'Legacy emission read mode activated'            //                     &
2679                           CHAR( 10 )  //  '                    '           //                     &
2680                           'All emissions data will be loaded '             //                     &
2681                           'prior to start of simulation'
2682          CALL message ( 'parin_chem', 'CM0465', 0, 0, 0, 6, 0 )
2683
2684       ELSE                                     !< if new read mode selected
2685
2686          IF ( emiss_lod < 2 )  THEN            !< check LOD compatibility
2687
2688             message_string = 'New emission read mode '                    //                      &
2689                              'currently unavailable for LODs 0 and 1.'    //                      &
2690                              CHAR( 10 )  //  '                    '       //                      &
2691                              'Reverting to legacy emission read mode'
2692             CALL message ( 'parin_chem', 'CM0466', 0, 0, 0, 6, 0 )
2693
2694             emiss_read_legacy_mode = .TRUE.
2695
2696          ELSE                                  !< notify new read mode
2697
2698             message_string = 'New emission read mode activated'           //                      &
2699                              CHAR( 10 )  //  '                    '       //                      &
2700                              'LOD 2 emissions will be updated on-demand ' //                      &
2701                              'according to indicated timestamps'
2702             CALL message ( 'parin_chem', 'CM0467', 0, 0, 0, 6, 0 )
2703
2704          ENDIF
2705
2706       ENDIF ! if emiss_read_legacy_mode
2707
2708
2709    ENDIF  ! if emissions_anthropengic
2710
2711
2712    t_steps = my_steps
2713!
2714!-- Determine the number of user-defined profiles and append them to the standard data output
2715!-- (data_output_pr)
2716    max_pr_cs_tmp = 0
2717    i = 1
2718
2719    DO  WHILE ( data_output_pr(i)  /= ' '  .AND.  i <= SIZE( data_output_pr ) )
2720       IF ( TRIM( data_output_pr(i)(1:3) ) == 'kc_' )  THEN
2721          max_pr_cs_tmp = max_pr_cs_tmp+1
2722       ENDIF
2723       i = i +1
2724    ENDDO
2725
2726    IF ( max_pr_cs_tmp > 0 )  THEN
2727       cs_pr_namelist_found = .TRUE.
2728       max_pr_cs = max_pr_cs_tmp
2729    ENDIF
2730!
2731!-- Set Solver Type
2732    IF(icntrl(3) == 0)  THEN
2733       solver_type = 'rodas3'           !Default
2734    ELSE IF(icntrl(3) == 1)  THEN
2735       solver_type = 'ros2'
2736    ELSE IF(icntrl(3) == 2)  THEN
2737       solver_type = 'ros3'
2738    ELSE IF(icntrl(3) == 3)  THEN
2739       solver_type = 'ro4'
2740    ELSE IF(icntrl(3) == 4)  THEN
2741       solver_type = 'rodas3'
2742    ELSE IF(icntrl(3) == 5)  THEN
2743       solver_type = 'rodas4'
2744    ELSE IF(icntrl(3) == 6)  THEN
2745       solver_type = 'Rang3'
2746    ELSE
2747       message_string = 'illegal Rosenbrock-solver type'
2748       CALL message( 'chem_parin', 'PA0506', 1, 2, 0, 6, 0 )
2749    END IF
2750
2751!
2752!--   todo: remove or replace by "CALL message" mechanism (kanani)
2753!       write(text,*) 'gas_phase chemistry: solver_type = ',TRIM( solver_type )
2754!kk    Has to be changed to right calling sequence
2755!        IF(myid == 0)  THEN
2756!           write(9,*) ' '
2757!           write(9,*) 'kpp setup '
2758!           write(9,*) ' '
2759!           write(9,*) '    gas_phase chemistry: solver_type = ',TRIM( solver_type )
2760!           write(9,*) ' '
2761!           write(9,*) '    Hstart  = ',rcntrl(3)
2762!           write(9,*) '    FacMin  = ',rcntrl(4)
2763!           write(9,*) '    FacMax  = ',rcntrl(5)
2764!           write(9,*) ' '
2765!           IF(vl_dim > 1)  THEN
2766!              write(9,*) '    Vector mode                   vektor length = ',vl_dim
2767!           ELSE
2768!              write(9,*) '    Scalar mode'
2769!           ENDIF
2770!           write(9,*) ' '
2771!        END IF
2772
2773    RETURN
2774
2775 END SUBROUTINE chem_parin
2776
2777
2778!--------------------------------------------------------------------------------------------------!
2779! Description:
2780! ------------
2781!> Call for all grid points
2782!--------------------------------------------------------------------------------------------------!
2783    SUBROUTINE chem_actions( location )
2784
2785
2786    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
2787
2788    SELECT CASE ( location )
2789
2790       CASE ( 'before_prognostic_equations' )
2791!
2792!--       Chemical reactions and deposition
2793          IF ( chem_gasphase_on )  THEN
2794!
2795!--          If required, calculate photolysis frequencies -
2796!--          UNFINISHED: Why not before the intermediate timestep loop?
2797             IF ( intermediate_timestep_count ==  1 )  THEN
2798                CALL photolysis_control
2799             ENDIF
2800
2801          ENDIF
2802
2803       CASE ( 'before_timestep' )
2804!
2805!--       Set array used to sum-up resolved scale fluxes to zero.
2806          IF ( ws_scheme_sca )  THEN
2807             sums_ws_l = 0.0_wp
2808          ENDIF
2809
2810       CASE DEFAULT
2811          CONTINUE
2812
2813    END SELECT
2814
2815    END SUBROUTINE chem_actions
2816
2817
2818!--------------------------------------------------------------------------------------------------!
2819! Description:
2820! ------------
2821!> Call for grid points i,j
2822!--------------------------------------------------------------------------------------------------!
2823
2824    SUBROUTINE chem_actions_ij( i, j, location )
2825
2826    CHARACTER (LEN=*), INTENT(IN) ::  location  !< call location string
2827
2828    INTEGER(iwp)  ::  dummy                     !< call location string
2829
2830    INTEGER(iwp),      INTENT(IN) ::  i         !< grid index in x-direction
2831    INTEGER(iwp),      INTENT(IN) ::  j         !< grid index in y-direction
2832
2833    IF ( air_chemistry    )   dummy = i + j
2834
2835    SELECT CASE ( location )
2836
2837       CASE DEFAULT
2838          CONTINUE
2839
2840    END SELECT
2841
2842
2843    END SUBROUTINE chem_actions_ij
2844
2845
2846!--------------------------------------------------------------------------------------------------!
2847! Description:
2848! ------------
2849!> Call for all grid points
2850!--------------------------------------------------------------------------------------------------!
2851    SUBROUTINE chem_non_advective_processes()
2852
2853
2854      INTEGER(iwp) ::  i  !<
2855      INTEGER(iwp) ::  j  !<
2856
2857!
2858!--   Calculation of chemical reactions and deposition.
2859      IF ( intermediate_timestep_count == 1  .OR.  call_chem_at_all_substeps )  THEN
2860
2861         IF ( chem_gasphase_on )  THEN
2862            CALL cpu_log( log_point_s(19), 'chem.reactions', 'start' )
2863            !$OMP PARALLEL PRIVATE (i,j)
2864            !$OMP DO schedule(static,1)
2865            DO  i = nxl, nxr
2866               DO  j = nys, nyn
2867                  CALL chem_integrate( i, j )
2868               ENDDO
2869            ENDDO
2870            !$OMP END PARALLEL
2871            CALL cpu_log( log_point_s(19), 'chem.reactions', 'stop' )
2872         ENDIF
2873
2874         IF ( deposition_dry )  THEN
2875            CALL cpu_log( log_point_s(24), 'chem.deposition', 'start' )
2876            DO  i = nxl, nxr
2877               DO  j = nys, nyn
2878                  CALL chem_depo( i, j )
2879               ENDDO
2880            ENDDO
2881            CALL cpu_log( log_point_s(24), 'chem.deposition', 'stop' )
2882         ENDIF
2883
2884      ENDIF
2885
2886
2887
2888    END SUBROUTINE chem_non_advective_processes
2889
2890
2891!--------------------------------------------------------------------------------------------------!
2892! Description:
2893! ------------
2894!> Call for grid points i,j
2895!--------------------------------------------------------------------------------------------------!
2896 SUBROUTINE chem_non_advective_processes_ij( i, j )
2897
2898
2899   INTEGER(iwp), INTENT(IN) ::  i  !< grid index in x-direction
2900   INTEGER(iwp), INTENT(IN) ::  j  !< grid index in y-direction
2901
2902!
2903!-- Calculation of chemical reactions and deposition.
2904   IF ( intermediate_timestep_count == 1  .OR.  call_chem_at_all_substeps )  THEN
2905
2906      IF ( chem_gasphase_on )  THEN
2907         CALL cpu_log( log_point_s(19), 'chem.reactions', 'start' )
2908         CALL chem_integrate( i, j )
2909         CALL cpu_log( log_point_s(19), 'chem.reactions', 'stop' )
2910      ENDIF
2911
2912      IF ( deposition_dry )  THEN
2913         CALL cpu_log( log_point_s(24), 'chem.deposition', 'start' )
2914         CALL chem_depo( i, j )
2915         CALL cpu_log( log_point_s(24), 'chem.deposition', 'stop' )
2916      ENDIF
2917
2918   ENDIF
2919
2920
2921
2922 END SUBROUTINE chem_non_advective_processes_ij
2923
2924!--------------------------------------------------------------------------------------------------!
2925! Description:
2926! ------------
2927!> routine for exchange horiz of chemical quantities
2928!--------------------------------------------------------------------------------------------------!
2929 SUBROUTINE chem_exchange_horiz_bounds
2930
2931    USE exchange_horiz_mod,                                                                        &
2932        ONLY:  exchange_horiz
2933
2934   INTEGER(iwp) ::  lsp       !<
2935
2936!
2937!--    Loop over chemical species
2938       CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'start' )
2939       DO  lsp = 1, nvar
2940          CALL exchange_horiz( chem_species(lsp)%conc, nbgp,                                       &
2941                               alternative_communicator = communicator_chem )
2942       ENDDO
2943
2944       CALL chem_boundary_conditions( horizontal_conditions_only = .TRUE. )
2945
2946       CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' )
2947
2948
2949 END SUBROUTINE chem_exchange_horiz_bounds
2950
2951
2952!--------------------------------------------------------------------------------------------------!
2953! Description:
2954! ------------
2955!> Subroutine calculating prognostic equations for chemical species (vector-optimized).
2956!> Routine is called separately for each chemical species over a loop from prognostic_equations.
2957!--------------------------------------------------------------------------------------------------!
2958 SUBROUTINE chem_prognostic_equations()
2959
2960
2961    INTEGER ::  i   !< running index
2962    INTEGER ::  j   !< running index
2963    INTEGER ::  k   !< running index
2964
2965    INTEGER(iwp) ::  ilsp   !<
2966
2967
2968    CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'start' )
2969
2970    DO  ilsp = 1, nvar
2971!
2972!--    Tendency terms for chemical species
2973       tend = 0.0_wp
2974!
2975!--    Advection terms
2976       IF ( timestep_scheme(1:5) == 'runge' )  THEN
2977          IF ( ws_scheme_sca )  THEN
2978             sums_wschs_ws_l(nzb:,0:) => sums_ws_l(:,:,ilsp)
2979             CALL advec_s_ws( cs_advc_flags_s, chem_species(ilsp)%conc, 'kc',                      &
2980                              bc_dirichlet_cs_l  .OR.  bc_radiation_cs_l,                          &
2981                              bc_dirichlet_cs_n  .OR.  bc_radiation_cs_n,                          &
2982                              bc_dirichlet_cs_r  .OR.  bc_radiation_cs_r,                          &
2983                              bc_dirichlet_cs_s  .OR.  bc_radiation_cs_s )
2984          ELSE
2985             CALL advec_s_pw( chem_species(ilsp)%conc )
2986          ENDIF
2987       ELSE
2988          CALL advec_s_up( chem_species(ilsp)%conc )
2989       ENDIF
2990!
2991!--    Diffusion terms  (the last three arguments are zero)
2992       CALL diffusion_s( chem_species(ilsp)%conc,                                                  &
2993            surf_def_h(0)%cssws(ilsp,:),                                                           &
2994            surf_def_h(1)%cssws(ilsp,:),                                                           &
2995            surf_def_h(2)%cssws(ilsp,:),                                                           &
2996            surf_lsm_h%cssws(ilsp,:),                                                              &
2997            surf_usm_h%cssws(ilsp,:),                                                              &
2998            surf_def_v(0)%cssws(ilsp,:),                                                           &
2999            surf_def_v(1)%cssws(ilsp,:),                                                           &
3000            surf_def_v(2)%cssws(ilsp,:),                                                           &
3001            surf_def_v(3)%cssws(ilsp,:),                                                           &
3002            surf_lsm_v(0)%cssws(ilsp,:),                                                           &
3003            surf_lsm_v(1)%cssws(ilsp,:),                                                           &
3004            surf_lsm_v(2)%cssws(ilsp,:),                                                           &
3005            surf_lsm_v(3)%cssws(ilsp,:),                                                           &
3006            surf_usm_v(0)%cssws(ilsp,:),                                                           &
3007            surf_usm_v(1)%cssws(ilsp,:),                                                           &
3008            surf_usm_v(2)%cssws(ilsp,:),                                                           &
3009            surf_usm_v(3)%cssws(ilsp,:) )
3010!
3011!--    Prognostic equation for chemical species
3012       DO  i = nxl, nxr
3013          DO  j = nys, nyn
3014             !following directive is required to vectorize on Intel19
3015             !DIR$ IVDEP
3016             DO  k = nzb+1, nzt
3017                chem_species(ilsp)%conc_p(k,j,i) =   chem_species(ilsp)%conc(k,j,i)                &
3018                     + ( dt_3d  *                                                                  &
3019                     (   tsc(2) * tend(k,j,i)                                                      &
3020                     + tsc(3) * chem_species(ilsp)%tconc_m(k,j,i)                                  &
3021                     )                                                                             &
3022                     - tsc(5) * rdf_sc(k)                                                          &
3023                     * ( chem_species(ilsp)%conc(k,j,i) - chem_species(ilsp)%conc_pr_init(k) )     &
3024                     )                                                                             &
3025                     * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
3026
3027                IF ( chem_species(ilsp)%conc_p(k,j,i) < 0.0_wp )  THEN
3028                   chem_species(ilsp)%conc_p(k,j,i) = 0.1_wp * chem_species(ilsp)%conc(k,j,i)
3029                ENDIF
3030             ENDDO
3031          ENDDO
3032       ENDDO
3033!
3034!--    Calculate tendencies for the next Runge-Kutta step
3035       IF ( timestep_scheme(1:5) == 'runge' )  THEN
3036          IF ( intermediate_timestep_count == 1 )  THEN
3037             DO  i = nxl, nxr
3038                DO  j = nys, nyn
3039                   DO  k = nzb+1, nzt
3040                      chem_species(ilsp)%tconc_m(k,j,i) = tend(k,j,i)
3041                   ENDDO
3042                ENDDO
3043             ENDDO
3044          ELSEIF ( intermediate_timestep_count < &
3045               intermediate_timestep_count_max )  THEN
3046             DO  i = nxl, nxr
3047                DO  j = nys, nyn
3048                   DO  k = nzb+1, nzt
3049                      chem_species(ilsp)%tconc_m(k,j,i) = - 9.5625_wp * tend(k,j,i)                &
3050                                                     + 5.3125_wp * chem_species(ilsp)%tconc_m(k,j,i)
3051                   ENDDO
3052                ENDDO
3053             ENDDO
3054          ENDIF
3055       ENDIF
3056
3057    ENDDO
3058
3059    CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'stop' )
3060
3061 END SUBROUTINE chem_prognostic_equations
3062
3063
3064!--------------------------------------------------------------------------------------------------!
3065! Description:
3066! ------------
3067!> Subroutine calculating prognostic equations for chemical species (cache-optimized).
3068!> Routine is called separately for each chemical species over a loop from prognostic_equations.
3069!--------------------------------------------------------------------------------------------------!
3070 SUBROUTINE chem_prognostic_equations_ij( i, j, i_omp_start, tn )
3071
3072
3073    INTEGER(iwp),INTENT(IN) :: i, j, i_omp_start, tn
3074
3075    INTEGER(iwp) :: ilsp
3076!
3077!-- local variables
3078
3079    INTEGER :: k
3080
3081    DO  ilsp = 1, nvar
3082!
3083!--    Tendency-terms for chem spcs.
3084       tend(:,j,i) = 0.0_wp
3085!
3086!--    Advection terms
3087       IF ( timestep_scheme(1:5) == 'runge' )  THEN
3088          IF ( ws_scheme_sca )  THEN
3089             sums_wschs_ws_l(nzb:,0:) => sums_ws_l(nzb:nzt+1,0:threads_per_task-1,ilsp)
3090             CALL advec_s_ws( cs_advc_flags_s,                                                     &
3091                              i,                                                                   &
3092                              j,                                                                   &
3093                              chem_species(ilsp)%conc,                                             &
3094                              'kc',                                                                &
3095                              chem_species(ilsp)%flux_s_cs,                                        &
3096                              chem_species(ilsp)%diss_s_cs,                                        &
3097                              chem_species(ilsp)%flux_l_cs,                                        &
3098                              chem_species(ilsp)%diss_l_cs,                                        &
3099                              i_omp_start,                                                         &
3100                              tn,                                                                  &
3101                              bc_dirichlet_cs_l  .OR.  bc_radiation_cs_l,                          &
3102                              bc_dirichlet_cs_n  .OR.  bc_radiation_cs_n,                          &
3103                              bc_dirichlet_cs_r  .OR.  bc_radiation_cs_r,                          &
3104                              bc_dirichlet_cs_s  .OR.  bc_radiation_cs_s,                          &
3105                              monotonic_limiter_z )
3106          ELSE
3107             CALL advec_s_pw( i, j, chem_species(ilsp)%conc )
3108          ENDIF
3109       ELSE
3110          CALL advec_s_up( i, j, chem_species(ilsp)%conc )
3111       ENDIF
3112!
3113!--    Diffusion terms (the last three arguments are zero)
3114       CALL diffusion_s( i, j, chem_species(ilsp)%conc,                                            &
3115            surf_def_h(0)%cssws(ilsp,:), surf_def_h(1)%cssws(ilsp,:),                              &
3116            surf_def_h(2)%cssws(ilsp,:),                                                           &
3117            surf_lsm_h%cssws(ilsp,:), surf_usm_h%cssws(ilsp,:),                                    &
3118            surf_def_v(0)%cssws(ilsp,:), surf_def_v(1)%cssws(ilsp,:),                              &
3119            surf_def_v(2)%cssws(ilsp,:), surf_def_v(3)%cssws(ilsp,:),                              &
3120            surf_lsm_v(0)%cssws(ilsp,:), surf_lsm_v(1)%cssws(ilsp,:),                              &
3121            surf_lsm_v(2)%cssws(ilsp,:), surf_lsm_v(3)%cssws(ilsp,:),                              &
3122            surf_usm_v(0)%cssws(ilsp,:), surf_usm_v(1)%cssws(ilsp,:),                              &
3123            surf_usm_v(2)%cssws(ilsp,:), surf_usm_v(3)%cssws(ilsp,:) )
3124!
3125!--    Prognostic equation for chem spcs
3126       DO  k = nzb+1, nzt
3127          chem_species(ilsp)%conc_p(k,j,i) = chem_species(ilsp)%conc(k,j,i) + ( dt_3d  *           &
3128               ( tsc(2) * tend(k,j,i) +                                                            &
3129               tsc(3) * chem_species(ilsp)%tconc_m(k,j,i) )                                        &
3130               - tsc(5) * rdf_sc(k)                                                                &
3131               * ( chem_species(ilsp)%conc(k,j,i) - chem_species(ilsp)%conc_pr_init(k) )           &
3132               )                                                                                   &
3133               * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 )                      &
3134               )
3135
3136          IF ( chem_species(ilsp)%conc_p(k,j,i) < 0.0_wp )  THEN
3137             chem_species(ilsp)%conc_p(k,j,i) = 0.1_wp * chem_species(ilsp)%conc(k,j,i)    !FKS6
3138          ENDIF
3139       ENDDO
3140!
3141!--    Calculate tendencies for the next Runge-Kutta step
3142       IF ( timestep_scheme(1:5) == 'runge' )  THEN
3143          IF ( intermediate_timestep_count == 1 )  THEN
3144             DO  k = nzb+1, nzt
3145                chem_species(ilsp)%tconc_m(k,j,i) = tend(k,j,i)
3146             ENDDO
3147          ELSEIF ( intermediate_timestep_count < &
3148               intermediate_timestep_count_max )  THEN
3149             DO  k = nzb+1, nzt
3150                chem_species(ilsp)%tconc_m(k,j,i) = -9.5625_wp * tend(k,j,i) +                     &
3151                                                     5.3125_wp * chem_species(ilsp)%tconc_m(k,j,i)
3152             ENDDO
3153          ENDIF
3154       ENDIF
3155
3156    ENDDO
3157
3158 END SUBROUTINE chem_prognostic_equations_ij
3159
3160
3161!--------------------------------------------------------------------------------------------------!
3162! Description:
3163! ------------
3164!> Read module-specific local restart data arrays (Fortran binary format).
3165!--------------------------------------------------------------------------------------------------!
3166 SUBROUTINE chem_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,   &
3167                                nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
3168
3169    USE control_parameters
3170
3171    INTEGER(iwp) ::  k               !<
3172    INTEGER(iwp) ::  lsp             !<
3173    INTEGER(iwp) ::  nxlc            !<
3174    INTEGER(iwp) ::  nxlf            !<
3175    INTEGER(iwp) ::  nxl_on_file     !<
3176    INTEGER(iwp) ::  nxrc            !<
3177    INTEGER(iwp) ::  nxrf            !<
3178    INTEGER(iwp) ::  nxr_on_file     !<
3179    INTEGER(iwp) ::  nync            !<
3180    INTEGER(iwp) ::  nynf            !<
3181    INTEGER(iwp) ::  nyn_on_file     !<
3182    INTEGER(iwp) ::  nysc            !<
3183    INTEGER(iwp) ::  nysf            !<
3184    INTEGER(iwp) ::  nys_on_file     !<
3185
3186    LOGICAL, INTENT(OUT) :: found
3187
3188    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) &
3189                 :: tmp_3d   !< 3D array to temp store data
3190
3191
3192    found = .FALSE.
3193
3194
3195    IF ( ALLOCATED( chem_species ) )  THEN
3196
3197       DO  lsp = 1, nspec
3198
3199          IF ( restart_string(1:length) == TRIM( chem_species(lsp)%name) )  THEN
3200
3201             IF ( k == 1 )  READ ( 13 )  tmp_3d
3202             chem_species(lsp)%conc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                   &
3203                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3204             found = .TRUE.
3205
3206          ELSEIF (restart_string(1:length) == TRIM( chem_species(lsp)%name ) // '_av' )  THEN
3207
3208             IF ( .NOT. ALLOCATED( chem_species(lsp)%conc_av ) )  THEN
3209                ALLOCATE( chem_species(lsp)%conc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ) )
3210             ENDIF
3211             IF ( k == 1 )  READ ( 13 )  tmp_3d
3212             chem_species(lsp)%conc_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                &
3213                                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3214             found = .TRUE.
3215
3216          ENDIF
3217
3218       ENDDO
3219
3220    ENDIF
3221
3222 END SUBROUTINE chem_rrd_local_ftn
3223
3224
3225!--------------------------------------------------------------------------------------------------!
3226! Description:
3227! ------------
3228!> Read module-specific local restart data arrays (Fortran binary format).
3229!--------------------------------------------------------------------------------------------------!
3230 SUBROUTINE chem_rrd_local_mpi
3231
3232    IMPLICIT NONE
3233
3234    INTEGER(iwp) ::  lsp  !<
3235
3236    LOGICAL      ::  array_found  !<
3237
3238
3239    DO  lsp = 1, nspec
3240
3241       CALL rrd_mpi_io( TRIM( chem_species(lsp)%name ), chem_species(lsp)%conc )
3242
3243       CALL rd_mpi_io_check_array( TRIM( chem_species(lsp)%name )//'_av' , found = array_found )
3244       IF ( array_found )  THEN
3245          IF ( .NOT. ALLOCATED( chem_species(lsp)%conc_av ) )  THEN
3246             ALLOCATE( chem_species(lsp)%conc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
3247          ENDIF
3248          CALL rrd_mpi_io( TRIM( chem_species(lsp)%name )//'_av', chem_species(lsp)%conc_av )
3249       ENDIF
3250
3251    ENDDO
3252
3253 END SUBROUTINE chem_rrd_local_mpi
3254
3255
3256!--------------------------------------------------------------------------------------------------!
3257!> Description:
3258!> Calculation of horizontally averaged profiles
3259!> This routine is called for every statistic region (sr) defined by the user,
3260!> but at least for the region "total domain" (sr=0).
3261!> quantities.
3262!--------------------------------------------------------------------------------------------------!
3263 SUBROUTINE chem_statistics( mode, sr, tn )
3264
3265
3266    USE arrays_3d
3267
3268    USE statistics
3269
3270    CHARACTER (LEN=*) ::  mode   !<
3271
3272    INTEGER(iwp) ::  i                   !< running index on x-axis
3273    INTEGER(iwp) ::  j                   !< running index on y-axis
3274    INTEGER(iwp) ::  k                   !< vertical index counter
3275    INTEGER(iwp) ::  lpr                 !< running index chem spcs
3276    INTEGER(iwp) ::  m                   !< running index for surface elements
3277!$  INTEGER(iwp) ::  omp_get_thread_num  !< intrinsic OMP function
3278    INTEGER(iwp) ::  sr                  !< statistical region
3279    INTEGER(iwp) ::  surf_e              !< end surface index
3280    INTEGER(iwp) ::  surf_s              !< start surface index
3281    INTEGER(iwp) ::  tn                  !< thread number
3282
3283    REAL(wp)                                            ::  flag     !< topography masking flag
3284    REAL(wp), DIMENSION(nzb:nzt+1,0:threads_per_task-1) ::  sums_tmp !< temporary array used to sum-up profiles
3285
3286    IF ( mode == 'profiles' )  THEN
3287!
3288!--    Sum-up profiles for the species
3289       tn = 0
3290       !$OMP PARALLEL PRIVATE( i, j, k, tn, lpr, sums_tmp )
3291       !$ tn = omp_get_thread_num()
3292       !$OMP DO
3293       DO  lpr = 1, cs_pr_count_sp
3294          sums_tmp(:,tn) = 0.0_wp
3295          DO  i = nxl, nxr
3296             DO  j = nys, nyn
3297                DO  k = nzb, nzt+1
3298                   sums_tmp(k,tn) = sums_tmp(k,tn) +                                               &
3299                        chem_species(cs_pr_index_sp(lpr))%conc(k,j,i) *                            &
3300                        rmask(j,i,sr)  *                                                           &
3301                        MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 22 ) )
3302                ENDDO
3303             ENDDO
3304          ENDDO
3305          sums_l(nzb:nzt+1,hom_index_spec(lpr),tn) = sums_tmp(nzb:nzt+1,tn)
3306       ENDDO
3307       !$OMP END PARALLEL
3308!
3309!--    Sum-up profiles for vertical fluxes of the the species. Note, in case of WS5 scheme the
3310!--    profiles of resolved-scale fluxes have been already summed-up, while resolved-scale fluxes
3311!--    need to be calculated in case of PW scheme.
3312!--    For summation employ a temporary array.
3313       !$OMP PARALLEL PRIVATE( i, j, k, tn, lpr, sums_tmp, flag )
3314       !$ tn = omp_get_thread_num()
3315       !$OMP DO
3316       DO  lpr = 1, cs_pr_count_fl_sgs
3317          sums_tmp(:,tn) = 0.0_wp
3318          DO  i = nxl, nxr
3319             DO  j = nys, nyn
3320                DO  k = nzb, nzt
3321                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 23 ) ) *        &
3322                          MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 9  ) )
3323                   sums_tmp(k,tn) = sums_tmp(k,tn) -                                               &
3324                        0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )                                       &
3325                               * ( chem_species(cs_pr_index_fl_sgs(lpr))%conc(k+1,j,i) -           &
3326                                   chem_species(cs_pr_index_fl_sgs(lpr))%conc(k,j,i) ) *           &
3327                        ddzu(k+1) * rmask(j,i,sr)  * flag
3328                ENDDO
3329!
3330!--             Add surface fluxes
3331                surf_s = surf_def_h(0)%start_index(j,i)
3332                surf_e = surf_def_h(0)%end_index(j,i)
3333                DO  m = surf_s, surf_e
3334                   k   = surf_def_h(0)%k(m) + surf_def_h(0)%koff
3335                   sums_tmp(k,tn) = sums_tmp(k,tn) + surf_def_h(0)%cssws(cs_pr_index_fl_sgs(lpr),m)
3336                ENDDO
3337                surf_s = surf_def_h(1)%start_index(j,i)
3338                surf_e = surf_def_h(1)%end_index(j,i)
3339                DO  m = surf_s, surf_e
3340                   k   = surf_def_h(1)%k(m)  + surf_def_h(1)%koff
3341                   sums_tmp(k,tn) = sums_tmp(k,tn) + surf_def_h(1)%cssws(cs_pr_index_fl_sgs(lpr),m)
3342                ENDDO
3343                surf_s = surf_lsm_h%start_index(j,i)
3344                surf_e = surf_lsm_h%end_index(j,i)
3345                DO  m = surf_s, surf_e
3346                   k   = surf_lsm_h%k(m) + surf_lsm_h%koff
3347                   sums_tmp(k,tn) = sums_tmp(k,tn) + surf_lsm_h%cssws(cs_pr_index_fl_sgs(lpr),m)
3348                ENDDO
3349                surf_s = surf_usm_h%start_index(j,i)
3350                surf_e = surf_usm_h%end_index(j,i)
3351                DO  m = surf_s, surf_e
3352                   k   = surf_usm_h%k(m) + surf_usm_h%koff
3353                   sums_tmp(k,tn) = sums_tmp(k,tn) + surf_usm_h%cssws(cs_pr_index_fl_sgs(lpr),m)
3354                ENDDO
3355             ENDDO
3356          ENDDO
3357          sums_l(nzb:nzt+1,hom_index_fl_sgs(lpr),tn) = sums_tmp(nzb:nzt+1,tn)
3358       ENDDO
3359       !$OMP END PARALLEL
3360!
3361!--    Resolved-scale fluxes from the WS5 scheme
3362       IF ( ws_scheme_sca )  THEN
3363          !$OMP PARALLEL PRIVATE( tn, lpr )
3364          !$ tn = omp_get_thread_num()
3365          !$OMP DO
3366          DO  lpr = 1, cs_pr_count_fl_res
3367             sums_l(nzb:nzt+1,hom_index_fl_res(lpr),tn) =                                           &
3368                                                      sums_ws_l(nzb:nzt+1,tn,cs_pr_index_fl_res(lpr))
3369          ENDDO
3370          !$OMP END PARALLEL
3371       ENDIF
3372
3373    ELSEIF ( mode == 'time_series' )  THEN
3374!      @todo
3375    ENDIF
3376
3377 END SUBROUTINE chem_statistics
3378
3379
3380!--------------------------------------------------------------------------------------------------!
3381! Description:
3382! ------------
3383!> Subroutine for swapping of timelevels for chemical species called out from subroutine
3384!> swap_timelevel
3385!--------------------------------------------------------------------------------------------------!
3386
3387
3388 SUBROUTINE chem_swap_timelevel( level )
3389
3390
3391    INTEGER(iwp), INTENT(IN) ::  level
3392!
3393!-- Local variables
3394    INTEGER(iwp)             ::  lsp
3395
3396
3397    IF ( level == 0 )  THEN
3398       DO  lsp=1, nvar
3399          chem_species(lsp)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    => spec_conc_1(:,:,:,lsp)
3400          chem_species(lsp)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => spec_conc_2(:,:,:,lsp)
3401       ENDDO
3402    ELSE
3403       DO  lsp=1, nvar
3404          chem_species(lsp)%conc(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    => spec_conc_2(:,:,:,lsp)
3405          chem_species(lsp)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => spec_conc_1(:,:,:,lsp)
3406       ENDDO
3407    ENDIF
3408
3409    RETURN
3410 END SUBROUTINE chem_swap_timelevel
3411
3412
3413!--------------------------------------------------------------------------------------------------!
3414! Description:
3415! ------------
3416!> Subroutine to write restart data for chemistry model
3417!--------------------------------------------------------------------------------------------------!
3418 SUBROUTINE chem_wrd_local
3419
3420
3421    INTEGER(iwp) ::  lsp  !< running index for chem spcs.
3422
3423    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
3424
3425       DO  lsp = 1, nspec
3426          CALL wrd_write_string( TRIM( chem_species(lsp)%name ) )
3427          WRITE ( 14 )  chem_species(lsp)%conc
3428          IF ( ALLOCATED( chem_species(lsp)%conc_av ) )  THEN
3429             CALL wrd_write_string( TRIM( chem_species(lsp)%name )//'_av' )
3430             WRITE ( 14 )  chem_species(lsp)%conc_av
3431          ENDIF
3432       ENDDO
3433
3434    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
3435
3436       DO  lsp = 1, nspec
3437          CALL wrd_mpi_io( TRIM( chem_species(lsp)%name ), chem_species(lsp)%conc )
3438          IF ( ALLOCATED( chem_species(lsp)%conc_av ) )  THEN
3439             CALL wrd_mpi_io( TRIM( chem_species(lsp)%name ) // '_av', chem_species(lsp)%conc_av )
3440          ENDIF
3441       ENDDO
3442
3443    ENDIF
3444
3445 END SUBROUTINE chem_wrd_local
3446
3447
3448!--------------------------------------------------------------------------------------------------!
3449! Description:
3450! ------------
3451!> Subroutine to calculate the deposition of gases and PMs. For now deposition only takes place on
3452!> lsm and usm horizontal surfaces. Default surfaces are NOT considered. The deposition of particles
3453!> is derived following Zhang et al., 2001, gases are deposited using the DEPAC module
3454!> (van Zanten et al., 2010).
3455!>
3456!> @TODO: Consider deposition on vertical surfaces
3457!> @TODO: Consider overlaying horizontal surfaces
3458!> @TODO: Consider resolved vegetation
3459!> @TODO: Check error messages
3460!--------------------------------------------------------------------------------------------------!
3461 SUBROUTINE chem_depo( i, j )
3462
3463    USE control_parameters,                                                                        &
3464         ONLY:  dt_3d, intermediate_timestep_count, latitude, time_since_reference_point
3465
3466    USE arrays_3d,                                                                                 &
3467         ONLY:  dzw, rho_air_zw
3468
3469    USE palm_date_time_mod,                                                                        &
3470         ONLY:  get_date_time
3471
3472    USE surface_mod,                                                                               &
3473         ONLY:  ind_pav_green, ind_veg_wall, ind_wat_win, surf_lsm_h, surf_type, surf_usm_h
3474
3475    USE radiation_model_mod,                                                                       &
3476         ONLY:  cos_zenith
3477
3478
3479    INTEGER(iwp) ::  day_of_year                   !< current day of the year
3480    INTEGER(iwp), INTENT(IN) ::  i
3481    INTEGER(iwp) ::  i_pspec                       !< index for matching depac gas component
3482    INTEGER(iwp), INTENT(IN) ::  j
3483    INTEGER(iwp) ::  k                             !< matching k to surface m at i,j
3484    INTEGER(iwp) ::  lsp                           !< running index for chem spcs.
3485    INTEGER(iwp) ::  luv_palm                      !< index of PALM LSM vegetation_type at current
3486                                                   !< surface element
3487    INTEGER(iwp) ::  lup_palm                      !< index of PALM LSM pavement_type at current
3488                                                   !< surface element
3489    INTEGER(iwp) ::  luw_palm                      !< index of PALM LSM water_type at current
3490                                                   !< surface element
3491    INTEGER(iwp) ::  luu_palm                      !< index of PALM USM walls/roofs at current
3492                                                   !< surface element
3493    INTEGER(iwp) ::  lug_palm                      !< index of PALM USM green walls/roofs at current
3494                                                   !< surface element
3495    INTEGER(iwp) ::  lud_palm                      !< index of PALM USM windows at current surface
3496                                                   !< element
3497    INTEGER(iwp) ::  luv_dep                       !< matching DEPAC LU to luv_palm
3498    INTEGER(iwp) ::  lup_dep                       !< matching DEPAC LU to lup_palm
3499    INTEGER(iwp) ::  luw_dep                       !< matching DEPAC LU to luw_palm
3500    INTEGER(iwp) ::  luu_dep                       !< matching DEPAC LU to luu_palm
3501    INTEGER(iwp) ::  lug_dep                       !< matching DEPAC LU to lug_palm
3502    INTEGER(iwp) ::  lud_dep                       !< matching DEPAC LU to lud_palm
3503    INTEGER(iwp) ::  m                             !< index for horizontal surfaces
3504    INTEGER(iwp) ::  pspec                         !< running index
3505!
3506!-- Vegetation                                               !<  Assign PALM classes to DEPAC land
3507                                                             !<  use classes
3508    INTEGER(iwp) ::  ind_luv_user = 0                        !<  ERROR as no class given in PALM
3509    INTEGER(iwp) ::  ind_luv_b_soil = 1                      !<  assigned to ilu_desert
3510    INTEGER(iwp) ::  ind_luv_mixed_crops = 2                 !<  assigned to ilu_arable
3511    INTEGER(iwp) ::  ind_luv_s_grass = 3                     !<  assigned to ilu_grass
3512    INTEGER(iwp) ::  ind_luv_ev_needle_trees = 4             !<  assigned to ilu_coniferous_forest
3513    INTEGER(iwp) ::  ind_luv_de_needle_trees = 5             !<  assigned to ilu_coniferous_forest
3514    INTEGER(iwp) ::  ind_luv_ev_broad_trees = 6              !<  assigned to ilu_tropical_forest
3515    INTEGER(iwp) ::  ind_luv_de_broad_trees = 7              !<  assigned to ilu_deciduous_forest
3516    INTEGER(iwp) ::  ind_luv_t_grass = 8                     !<  assigned to ilu_grass
3517    INTEGER(iwp) ::  ind_luv_desert = 9                      !<  assigned to ilu_desert
3518    INTEGER(iwp) ::  ind_luv_tundra = 10                     !<  assigned to ilu_other
3519    INTEGER(iwp) ::  ind_luv_irr_crops = 11                  !<  assigned to ilu_arable
3520    INTEGER(iwp) ::  ind_luv_semidesert = 12                 !<  assigned to ilu_other
3521    INTEGER(iwp) ::  ind_luv_ice = 13                        !<  assigned to ilu_ice
3522    INTEGER(iwp) ::  ind_luv_marsh = 14                      !<  assigned to ilu_other
3523    INTEGER(iwp) ::  ind_luv_ev_shrubs = 15                  !<  assigned to ilu_mediterrean_scrub
3524    INTEGER(iwp) ::  ind_luv_de_shrubs = 16                  !<  assigned to ilu_mediterrean_scrub
3525    INTEGER(iwp) ::  ind_luv_mixed_forest = 17               !<  assigned to ilu_coniferous_forest(ave(decid+conif))
3526    INTEGER(iwp) ::  ind_luv_intrup_forest = 18              !<  assigned to ilu_other (ave(other+decid))
3527!
3528!-- Water
3529    INTEGER(iwp) ::  ind_luw_user = 0                        !<  ERROR as no class given in PALM
3530    INTEGER(iwp) ::  ind_luw_lake = 1                        !<  assigned to ilu_water_inland
3531    INTEGER(iwp) ::  ind_luw_river = 2                       !<  assigned to ilu_water_inland
3532    INTEGER(iwp) ::  ind_luw_ocean = 3                       !<  assigned to ilu_water_sea
3533    INTEGER(iwp) ::  ind_luw_pond = 4                        !<  assigned to ilu_water_inland
3534    INTEGER(iwp) ::  ind_luw_fountain = 5                    !<  assigned to ilu_water_inland
3535!
3536!-- Pavement
3537    INTEGER(iwp) ::  ind_lup_user = 0                        !<  ERROR as no class given in PALM
3538    INTEGER(iwp) ::  ind_lup_asph_conc = 1                   !<  assigned to ilu_desert
3539    INTEGER(iwp) ::  ind_lup_asph = 2                        !<  assigned to ilu_desert
3540    INTEGER(iwp) ::  ind_lup_conc = 3                        !<  assigned to ilu_desert
3541    INTEGER(iwp) ::  ind_lup_sett = 4                        !<  assigned to ilu_desert
3542    INTEGER(iwp) ::  ind_lup_pav_stones = 5                  !<  assigned to ilu_desert
3543    INTEGER(iwp) ::  ind_lup_cobblest = 6                    !<  assigned to ilu_desert
3544    INTEGER(iwp) ::  ind_lup_metal = 7                       !<  assigned to ilu_desert
3545    INTEGER(iwp) ::  ind_lup_wood = 8                        !<  assigned to ilu_desert
3546    INTEGER(iwp) ::  ind_lup_gravel = 9                      !<  assigned to ilu_desert
3547    INTEGER(iwp) ::  ind_lup_f_gravel = 10                   !<  assigned to ilu_desert
3548    INTEGER(iwp) ::  ind_lup_pebblest = 11                   !<  assigned to ilu_desert
3549    INTEGER(iwp) ::  ind_lup_woodchips = 12                  !<  assigned to ilu_desert
3550    INTEGER(iwp) ::  ind_lup_tartan = 13                     !<  assigned to ilu_desert
3551    INTEGER(iwp) ::  ind_lup_art_turf = 14                   !<  assigned to ilu_desert
3552    INTEGER(iwp) ::  ind_lup_clay = 15                       !<  assigned to ilu_desert
3553!
3554!-- Particle parameters according to the respective aerosol classes (PM25, PM10)
3555    INTEGER(iwp) ::  ind_p_size = 1     !< index for partsize in particle_pars
3556    INTEGER(iwp) ::  ind_p_dens = 2     !< index for rhopart in particle_pars
3557    INTEGER(iwp) ::  ind_p_slip = 3     !< index for slipcor in particle_pars
3558    INTEGER(iwp) ::  nwet               !< wetness indicator dor DEPAC; nwet=0 -> dry; nwet=1 -> wet; nwet=9 -> snow
3559    INTEGER(iwp) ::  part_type          !< index for particle type (PM10 or PM25) in particle_pars
3560
3561
3562    REAL(wp) ::  conc_ijk_ugm3     !< concentration at i, j, k in ug/m3
3563    REAL(wp) ::  dens              !< density at layer k at i,j
3564    REAL(wp) ::  dh                !< vertical grid size
3565    REAL(wp) ::  diffusivity       !< diffusivity
3566    REAL(wp) ::  dt_chem           !< length of chem time step
3567    REAL(wp) ::  dt_dh             !< dt_chem/dh
3568    REAL(wp) ::  inv_dh            !< inverse of vertical grid size
3569    REAL(wp) ::  lai               !< leaf area index at current surface element
3570    REAL(wp) ::  ppm2ugm3          !< conversion factor from ppm to ug/m3
3571    REAL(wp) ::  qv_tmp            !< surface mixing ratio at current surface element
3572    REAL(wp) ::  r_aero_surf       !< aerodynamic resistance (s/m) at current surface element
3573    REAL(wp) ::  rb                !< quasi-laminar boundary layer resistance (s/m)
3574    REAL(wp) ::  rc_tot            !< total canopy resistance (s/m)
3575    REAL(wp) ::  rh_surf           !< relative humidity at current surface element
3576    REAL(wp) ::  rs                !< Sedimentaion resistance (s/m)
3577    REAL(wp) ::  sai               !< surface area index at current surface element assumed to be
3578                                   !< lai + 1
3579    REAL(wp) ::  slinnfac
3580    REAL(wp) ::  solar_rad         !< solar radiation, direct and diffuse, at current surface
3581                                   !< element
3582    REAL(wp) ::  temp_tmp          !< temperatur at i,j,k
3583    REAL(wp) ::  ts                !< surface temperatur in degrees celsius
3584    REAL(wp) ::  ustar_surf        !< ustar at current surface element
3585    REAL(wp) ::  vd_lu             !< deposition velocity (m/s)
3586    REAL(wp) ::  visc              !< Viscosity
3587    REAL(wp) ::  vs                !< Sedimentation velocity
3588    REAL(wp) ::  z0h_surf          !< roughness length for heat at current surface element
3589
3590    REAL(wp), DIMENSION(nspec) ::  bud          !< overall budget at current surface element
3591    REAL(wp), DIMENSION(nspec) ::  bud_lud      !< budget for USM windows at current surface element
3592    REAL(wp), DIMENSION(nspec) ::  bud_lug      !< budget for USM green surfaces at current surface
3593                                                !< element
3594    REAL(wp), DIMENSION(nspec) ::  bud_lup      !< budget for LSM pavement type at current surface
3595                                                !< element
3596    REAL(wp), DIMENSION(nspec) ::  bud_luu      !< budget for USM walls/roofs at current surface
3597                                                !< element
3598    REAL(wp), DIMENSION(nspec) ::  bud_luv      !< budget for LSM vegetation type at current surface
3599                                                !< element
3600    REAL(wp), DIMENSION(nspec) ::  bud_luw      !< budget for LSM water type at current surface
3601                                                !< element
3602    REAL(wp), DIMENSION(nspec) ::  ccomp_tot    !< total compensation point (ug/m3), for now kept to
3603                                                !< zero for all species!
3604    REAL(wp), DIMENSION(nspec) ::  conc_ijk     !< concentration at i,j,k
3605
3606
3607!
3608!-- Particle parameters (PM10 (1), PM25 (2)) partsize (diameter in m), rhopart (density in kg/m3),
3609!-- slipcor (slip correction factor dimensionless, Seinfeld and Pandis 2006, Table 9.3)
3610    REAL(wp), DIMENSION(1:3,1:2), PARAMETER ::  particle_pars = RESHAPE( (/                        &
3611                                                         8.0e-6_wp, 1.14e3_wp, 1.016_wp, &   !<  1
3612                                                         0.7e-6_wp, 1.14e3_wp, 1.082_wp  &   !<  2
3613                                                         /), (/ 3, 2 /) )
3614
3615    LOGICAL ::  match_lsm     !< flag indicating natural-type surface
3616    LOGICAL ::  match_usm     !< flag indicating urban-type surface
3617
3618!
3619!-- List of names of possible tracers
3620    CHARACTER(LEN=*), PARAMETER ::  pspecnames(nposp) = (/                                         &
3621         'NO2           ', &    !< NO2
3622         'NO            ', &    !< NO
3623         'O3            ', &    !< O3
3624         'CO            ', &    !< CO
3625         'form          ', &    !< FORM
3626         'ald           ', &    !< ALD
3627         'pan           ', &    !< PAN
3628         'mgly          ', &    !< MGLY
3629         'par           ', &    !< PAR
3630         'ole           ', &    !< OLE
3631         'eth           ', &    !< ETH
3632         'tol           ', &    !< TOL
3633         'cres          ', &    !< CRES
3634         'xyl           ', &    !< XYL
3635         'SO4a_f        ', &    !< SO4a_f
3636         'SO2           ', &    !< SO2
3637         'HNO2          ', &    !< HNO2
3638         'CH4           ', &    !< CH4
3639         'NH3           ', &    !< NH3
3640         'NO3           ', &    !< NO3
3641         'OH            ', &    !< OH
3642         'HO2           ', &    !< HO2
3643         'N2O5          ', &    !< N2O5
3644         'SO4a_c        ', &    !< SO4a_c
3645         'NH4a_f        ', &    !< NH4a_f
3646         'NO3a_f        ', &    !< NO3a_f
3647         'NO3a_c        ', &    !< NO3a_c
3648         'C2O3          ', &    !< C2O3
3649         'XO2           ', &    !< XO2
3650         'XO2N          ', &    !< XO2N
3651         'cro           ', &    !< CRO
3652         'HNO3          ', &    !< HNO3
3653         'H2O2          ', &    !< H2O2
3654         'iso           ', &    !< ISO
3655         'ispd          ', &    !< ISPD
3656         'to2           ', &    !< TO2
3657         'open          ', &    !< OPEN
3658         'terp          ', &    !< TERP
3659         'ec_f          ', &    !< EC_f
3660         'ec_c          ', &    !< EC_c
3661         'pom_f         ', &    !< POM_f
3662         'pom_c         ', &    !< POM_c
3663         'ppm_f         ', &    !< PPM_f
3664         'ppm_c         ', &    !< PPM_c
3665         'na_ff         ', &    !< Na_ff
3666         'na_f          ', &    !< Na_f
3667         'na_c          ', &    !< Na_c
3668         'na_cc         ', &    !< Na_cc
3669         'na_ccc        ', &    !< Na_ccc
3670         'dust_ff       ', &    !< dust_ff
3671         'dust_f        ', &    !< dust_f
3672         'dust_c        ', &    !< dust_c
3673         'dust_cc       ', &    !< dust_cc
3674         'dust_ccc      ', &    !< dust_ccc
3675         'tpm10         ', &    !< tpm10
3676         'tpm25         ', &    !< tpm25
3677         'tss           ', &    !< tss
3678         'tdust         ', &    !< tdust
3679         'tc            ', &    !< tc
3680         'tcg           ', &    !< tcg
3681         'tsoa          ', &    !< tsoa
3682         'tnmvoc        ', &    !< tnmvoc
3683         'SOxa          ', &    !< SOxa
3684         'NOya          ', &    !< NOya
3685         'NHxa          ', &    !< NHxa
3686         'NO2_obs       ', &    !< NO2_obs
3687         'tpm10_biascorr', &    !< tpm10_biascorr
3688         'tpm25_biascorr', &    !< tpm25_biascorr
3689         'O3_biascorr   ' /)    !< o3_biascorr
3690!
3691!-- Tracer mole mass:
3692    REAL(wp), PARAMETER ::  specmolm(nposp) = (/                                                   &
3693         xm_O * 2 + xm_N, &                         !< NO2
3694         xm_O + xm_N, &                             !< NO
3695         xm_O * 3, &                                !< O3
3696         xm_C + xm_O, &                             !< CO
3697         xm_H * 2 + xm_C + xm_O, &                  !< FORM
3698         xm_H * 3 + xm_C * 2 + xm_O, &              !< ALD
3699         xm_H * 3 + xm_C * 2 + xm_O * 5 + xm_N, &   !< PAN
3700         xm_H * 4 + xm_C * 3 + xm_O * 2, &          !< MGLY
3701         xm_H * 3 + xm_C, &                         !< PAR
3702         xm_H * 3 + xm_C * 2, &                     !< OLE
3703         xm_H * 4 + xm_C * 2, &                     !< ETH
3704         xm_H * 8 + xm_C * 7, &                     !< TOL
3705         xm_H * 8 + xm_C * 7 + xm_O, &              !< CRES
3706         xm_H * 10 + xm_C * 8, &                    !< XYL
3707         xm_S + xm_O * 4, &                         !< SO4a_f
3708         xm_S + xm_O * 2, &                         !< SO2
3709         xm_H + xm_O * 2 + xm_N, &                  !< HNO2
3710         xm_H * 4 + xm_C, &                         !< CH4
3711         xm_H * 3 + xm_N, &                         !< NH3
3712         xm_O * 3 + xm_N, &                         !< NO3
3713         xm_H + xm_O, &                             !< OH
3714         xm_H + xm_O * 2, &                         !< HO2
3715         xm_O * 5 + xm_N * 2, &                     !< N2O5
3716         xm_S + xm_O * 4, &                         !< SO4a_c
3717         xm_H * 4 + xm_N, &                         !< NH4a_f
3718         xm_O * 3 + xm_N, &                         !< NO3a_f
3719         xm_O * 3 + xm_N, &                         !< NO3a_c
3720         xm_C * 2 + xm_O * 3, &                     !< C2O3
3721         xm_dummy, &                                !< XO2
3722         xm_dummy, &                                !< XO2N
3723         xm_dummy, &                                !< CRO
3724         xm_H + xm_O * 3 + xm_N, &                  !< HNO3
3725         xm_H * 2 + xm_O * 2, &                     !< H2O2
3726         xm_H * 8 + xm_C * 5, &                     !< ISO
3727         xm_dummy, &                                !< ISPD
3728         xm_dummy, &                                !< TO2
3729         xm_dummy, &                                !< OPEN
3730         xm_H * 16 + xm_C * 10, &                   !< TERP
3731         xm_dummy, &                                !< EC_f
3732         xm_dummy, &                                !< EC_c
3733         xm_dummy, &                                !< POM_f
3734         xm_dummy, &                                !< POM_c
3735         xm_dummy, &                                !< PPM_f
3736         xm_dummy, &                                !< PPM_c
3737         xm_Na, &                                   !< Na_ff
3738         xm_Na, &                                   !< Na_f
3739         xm_Na, &                                   !< Na_c
3740         xm_Na, &                                   !< Na_cc
3741         xm_Na, &                                   !< Na_ccc
3742         xm_dummy, &                                !< dust_ff
3743         xm_dummy, &                                !< dust_f
3744         xm_dummy, &                                !< dust_c
3745         xm_dummy, &                                !< dust_cc
3746         xm_dummy, &                                !< dust_ccc
3747         xm_dummy, &                                !< tpm10
3748         xm_dummy, &                                !< tpm25
3749         xm_dummy, &                                !< tss
3750         xm_dummy, &                                !< tdust
3751         xm_dummy, &                                !< tc
3752         xm_dummy, &                                !< tcg
3753         xm_dummy, &                                !< tsoa
3754         xm_dummy, &                                !< tnmvoc
3755         xm_dummy, &                                !< SOxa
3756         xm_dummy, &                                !< NOya
3757         xm_dummy, &                                !< NHxa
3758         xm_O * 2 + xm_N, &                         !< NO2_obs
3759         xm_dummy, &                                !< tpm10_biascorr
3760         xm_dummy, &                                !< tpm25_biascorr
3761         xm_O * 3 /)                                !< o3_biascorr
3762!
3763!-- Get current day of the year
3764    CALL get_date_time( time_since_reference_point, day_of_year = day_of_year )
3765!
3766!-- Initialize surface element m
3767    m = 0
3768    k = 0
3769!
3770!-- LSM or USM surface present at i,j:
3771!-- Default surfaces are NOT considered for deposition
3772    match_lsm = surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i)
3773    match_usm = surf_usm_h%start_index(j,i) <= surf_usm_h%end_index(j,i)
3774!
3775!--For LSM surfaces
3776    IF ( match_lsm )  THEN
3777!
3778!--    Get surface element information at i,j:
3779       m = surf_lsm_h%start_index(j,i)
3780       k = surf_lsm_h%k(m)
3781!
3782!--    Get needed variables for surface element m
3783       ustar_surf  = surf_lsm_h%us(m)
3784       z0h_surf    = surf_lsm_h%z0h(m)
3785       r_aero_surf = surf_lsm_h%r_a(m)
3786       solar_rad   = surf_lsm_h%rad_sw_dir(m) + surf_lsm_h%rad_sw_dif(m)
3787
3788       lai = surf_lsm_h%lai(m)
3789       sai = lai + 1
3790!
3791!--    For small grid spacing neglect R_a
3792       IF ( dzw(k) <= 1.0 )  THEN
3793          r_aero_surf = 0.0_wp
3794       ENDIF
3795!
3796!--    Initialize lu's
3797       luv_palm = 0
3798       luv_dep = 0
3799       lup_palm = 0
3800       lup_dep = 0
3801       luw_palm = 0
3802       luw_dep = 0
3803!
3804!--    Initialize budgets
3805       bud_luv = 0.0_wp
3806       bud_lup = 0.0_wp
3807       bud_luw = 0.0_wp
3808!
3809!--    Get land use for i,j and assign to DEPAC lu
3810       IF ( surf_lsm_h%frac(m,ind_veg_wall) > 0 )  THEN
3811          luv_palm = surf_lsm_h%vegetation_type(m)
3812          IF ( luv_palm == ind_luv_user )  THEN
3813             message_string = 'No vegetation type defined. Please define vegetation type to enable deposition calculation'
3814             CALL message( 'chem_depo', 'CM0451', 1, 2, 0, 6, 0 )
3815          ELSEIF ( luv_palm == ind_luv_b_soil )  THEN
3816             luv_dep = 9
3817          ELSEIF ( luv_palm == ind_luv_mixed_crops )  THEN
3818             luv_dep = 2
3819          ELSEIF ( luv_palm == ind_luv_s_grass )  THEN
3820             luv_dep = 1
3821          ELSEIF ( luv_palm == ind_luv_ev_needle_trees )  THEN
3822             luv_dep = 4
3823          ELSEIF ( luv_palm == ind_luv_de_needle_trees )  THEN
3824             luv_dep = 4
3825          ELSEIF ( luv_palm == ind_luv_ev_broad_trees )  THEN
3826             luv_dep = 12
3827          ELSEIF ( luv_palm == ind_luv_de_broad_trees )  THEN
3828             luv_dep = 5
3829          ELSEIF ( luv_palm == ind_luv_t_grass )  THEN
3830             luv_dep = 1
3831          ELSEIF ( luv_palm == ind_luv_desert )  THEN
3832             luv_dep = 9
3833          ELSEIF ( luv_palm == ind_luv_tundra )  THEN
3834             luv_dep = 8
3835          ELSEIF ( luv_palm == ind_luv_irr_crops )  THEN
3836             luv_dep = 2
3837          ELSEIF ( luv_palm == ind_luv_semidesert )  THEN
3838             luv_dep = 8
3839          ELSEIF ( luv_palm == ind_luv_ice )  THEN
3840             luv_dep = 10
3841          ELSEIF ( luv_palm == ind_luv_marsh )  THEN
3842             luv_dep = 8
3843          ELSEIF ( luv_palm == ind_luv_ev_shrubs )  THEN
3844             luv_dep = 14
3845          ELSEIF ( luv_palm == ind_luv_de_shrubs )  THEN
3846             luv_dep = 14
3847          ELSEIF ( luv_palm == ind_luv_mixed_forest )  THEN
3848             luv_dep = 4
3849          ELSEIF ( luv_palm == ind_luv_intrup_forest )  THEN
3850             luv_dep = 8
3851          ENDIF
3852       ENDIF
3853
3854       IF ( surf_lsm_h%frac(m,ind_pav_green) > 0 )  THEN
3855          lup_palm = surf_lsm_h%pavement_type(m)
3856          IF ( lup_palm == ind_lup_user )  THEN
3857             message_string = 'No pavement type defined. Please define pavement type to enable deposition calculation'
3858             CALL message( 'chem_depo', 'CM0452', 1, 2, 0, 6, 0 )
3859          ELSEIF ( lup_palm == ind_lup_asph_conc )  THEN
3860             lup_dep = 9
3861          ELSEIF ( lup_palm == ind_lup_asph )  THEN
3862             lup_dep = 9
3863          ELSEIF ( lup_palm == ind_lup_conc )  THEN
3864             lup_dep = 9
3865          ELSEIF ( lup_palm == ind_lup_sett )  THEN
3866             lup_dep = 9
3867          ELSEIF ( lup_palm == ind_lup_pav_stones )  THEN
3868             lup_dep = 9
3869          ELSEIF ( lup_palm == ind_lup_cobblest )  THEN
3870             lup_dep = 9
3871          ELSEIF ( lup_palm == ind_lup_metal )  THEN
3872             lup_dep = 9
3873          ELSEIF ( lup_palm == ind_lup_wood )  THEN
3874             lup_dep = 9
3875          ELSEIF ( lup_palm == ind_lup_gravel )  THEN
3876             lup_dep = 9
3877          ELSEIF ( lup_palm == ind_lup_f_gravel )  THEN
3878             lup_dep = 9
3879          ELSEIF ( lup_palm == ind_lup_pebblest )  THEN
3880             lup_dep = 9
3881          ELSEIF ( lup_palm == ind_lup_woodchips )  THEN
3882             lup_dep = 9
3883          ELSEIF ( lup_palm == ind_lup_tartan )  THEN
3884             lup_dep = 9
3885          ELSEIF ( lup_palm == ind_lup_art_turf )  THEN
3886             lup_dep = 9
3887          ELSEIF ( lup_palm == ind_lup_clay )  THEN
3888             lup_dep = 9
3889          ENDIF
3890       ENDIF
3891
3892       IF ( surf_lsm_h%frac(m,ind_wat_win) > 0 )  THEN
3893          luw_palm = surf_lsm_h%water_type(m)
3894          IF ( luw_palm == ind_luw_user )  THEN
3895             message_string = 'No water type defined. Please define water type to enable deposition calculation'
3896             CALL message( 'chem_depo', 'CM0453', 1, 2, 0, 6, 0 )
3897          ELSEIF ( luw_palm ==  ind_luw_lake )  THEN
3898             luw_dep = 13
3899          ELSEIF ( luw_palm == ind_luw_river )  THEN
3900             luw_dep = 13
3901          ELSEIF ( luw_palm == ind_luw_ocean )  THEN
3902             luw_dep = 6
3903          ELSEIF ( luw_palm == ind_luw_pond )  THEN
3904             luw_dep = 13
3905          ELSEIF ( luw_palm == ind_luw_fountain )  THEN
3906             luw_dep = 13
3907          ENDIF
3908       ENDIF
3909!
3910!--    Set wetness indicator to dry or wet for lsm vegetation or pavement
3911       IF ( surf_lsm_h%c_liq(m) > 0 )  THEN
3912          nwet = 1
3913       ELSE
3914          nwet = 0
3915       ENDIF
3916!
3917!--    Compute length of time step
3918       IF ( call_chem_at_all_substeps )  THEN
3919          dt_chem = dt_3d * weight_pres(intermediate_timestep_count)
3920       ELSE
3921          dt_chem = dt_3d
3922       ENDIF
3923
3924       dh = dzw(k)
3925       inv_dh = 1.0_wp / dh
3926       dt_dh = dt_chem/dh
3927!
3928!--    Concentration at i,j,k
3929       DO  lsp = 1, nspec
3930          conc_ijk(lsp) = chem_species(lsp)%conc(k,j,i)
3931       ENDDO
3932
3933!--    Temperature at i,j,k
3934       temp_tmp = pt(k,j,i) * ( hyp(k) / 100000.0_wp )**0.286_wp
3935
3936       ts       = temp_tmp - 273.15  !< in degrees celcius
3937!
3938!--    Viscosity of air
3939       visc = 1.496e-6 * temp_tmp**1.5 / (temp_tmp + 120.0)
3940!
3941!--    Air density at k
3942       dens = rho_air_zw(k)
3943!
3944!--    Calculate relative humidity from specific humidity for DEPAC
3945       qv_tmp = MAX( q(k,j,i), 0.0_wp)
3946       rh_surf = relativehumidity_from_specifichumidity(qv_tmp, temp_tmp, hyp(k) )
3947!
3948!-- Check if surface fraction (vegetation, pavement or water) > 0 and calculate vd and budget
3949!-- for each surface fraction. Then derive overall budget taking into account the surface fractions.
3950!
3951!--    Vegetation
3952       IF ( surf_lsm_h%frac(m,ind_veg_wall) > 0 )  THEN
3953
3954!
3955!--       No vegetation on bare soil, desert or ice:
3956          IF ( ( luv_palm == ind_luv_b_soil )  .OR.  ( luv_palm == ind_luv_desert )  .OR.          &
3957               ( luv_palm == ind_luv_ice ) ) THEN
3958
3959             lai = 0.0_wp
3960             sai = 0.0_wp
3961
3962          ENDIF
3963
3964          slinnfac = 1.0_wp
3965!
3966!--       Get deposition velocity vd
3967          DO  lsp = 1, nvar
3968!
3969!--          Initialize
3970             vs = 0.0_wp
3971             vd_lu = 0.0_wp
3972             rs = 0.0_wp
3973             rb = 0.0_wp
3974             rc_tot = 0.0_wp
3975             IF ( spc_names(lsp) == 'PM10' )  THEN
3976                part_type = 1
3977!
3978!--             Sedimentation velocity
3979                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
3980                                                        particle_pars(ind_p_size, part_type),      &
3981                                                        particle_pars(ind_p_slip, part_type),      &
3982                                                        visc)
3983
3984                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
3985                                            vs,                                                    &
3986                                            particle_pars(ind_p_size, part_type),                  &
3987                                            particle_pars(ind_p_slip, part_type),                  &
3988                                            nwet, temp_tmp, dens, visc,                            &
3989                                            luv_dep,                                               &
3990                                            r_aero_surf, ustar_surf )
3991
3992                bud_luv(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
3993
3994
3995             ELSEIF ( spc_names(lsp) == 'PM25' )  THEN
3996                part_type = 2
3997!
3998!--             Sedimentation velocity
3999                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4000                                                        particle_pars(ind_p_size, part_type),      &
4001                                                        particle_pars(ind_p_slip, part_type),      &
4002                                                        visc)
4003
4004                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4005                                            vs,                                                    &
4006                                            particle_pars(ind_p_size, part_type),                  &
4007                                            particle_pars(ind_p_slip, part_type),                  &
4008                                            nwet, temp_tmp, dens, visc,                            &
4009                                            luv_dep ,                                              &
4010                                            r_aero_surf, ustar_surf )
4011
4012                bud_luv(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4013
4014             ELSE !< GASES
4015!
4016!--             Read spc_name of current species for gas parameter
4017                IF ( ANY( pspecnames(:) == spc_names(lsp) ) )  THEN
4018                   i_pspec = 0
4019                   DO  pspec = 1, nposp
4020                      IF ( pspecnames(pspec) == spc_names(lsp) )  THEN
4021                         i_pspec = pspec
4022                      END IF
4023                   ENDDO
4024
4025                ELSE
4026!
4027!--             For now species not deposited
4028                   CYCLE
4029                ENDIF
4030!
4031!--             Factor used for conversion from ppb to ug/m3 :
4032!--             ppb (mole tr)/(mole air)/ppb (kg tr)/(mole tr) (ug tr)/(kg tr) &
4033!--                 (mole air)/(kg air) (kg air)/(m3 air) (kg air(ug/m3)/ppb/(kg/mole) = / (kg/mole)
4034!--                 c           1e-9              xm_tracer         1e9       /       xm_air            dens
4035!--             thus:
4036!--                 c_in_ppb * xm_tracer * [ dens / xm_air ] = c_in_ugm3
4037!--             Use density at k:
4038                ppm2ugm3 =  (dens/xm_air) * 0.001_wp  !< (mole air)/m3
4039!
4040!--             Atmospheric concentration in DEPAC is requested in ug/m3:
4041                !   ug/m3              ppm          (ug/m3)/ppm/(kg/mole)     kg/mole
4042                conc_ijk_ugm3 = conc_ijk(lsp)         * ppm2ugm3 *   specmolm(i_pspec)  ! in ug/m3
4043!
4044!--             Diffusivity for DEPAC relevant gases
4045!--             Use default value
4046                diffusivity            = 0.11e-4
4047!
4048!--             Overwrite with known coefficients of diffusivity from Massman (1998)
4049                IF ( spc_names(lsp) == 'NO2' ) diffusivity = 0.136e-4
4050                IF ( spc_names(lsp) == 'NO'  ) diffusivity = 0.199e-4
4051                IF ( spc_names(lsp) == 'O3'  ) diffusivity = 0.144e-4
4052                IF ( spc_names(lsp) == 'CO'  ) diffusivity = 0.176e-4
4053                IF ( spc_names(lsp) == 'SO2' ) diffusivity = 0.112e-4
4054                IF ( spc_names(lsp) == 'CH4' ) diffusivity = 0.191e-4
4055                IF ( spc_names(lsp) == 'NH3' ) diffusivity = 0.191e-4
4056!
4057!--             Get quasi-laminar boundary layer resistance rb:
4058                CALL get_rb_cell( ( luv_dep == ilu_water_sea )  .OR.                               &
4059                                  ( luv_dep == ilu_water_inland ), z0h_surf, ustar_surf,           &
4060                                  diffusivity, rb )
4061!
4062!--             Get rc_tot
4063                CALL drydepos_gas_depac( spc_names(lsp), day_of_year, latitude, ts, ustar_surf,    &
4064                                         solar_rad, cos_zenith, rh_surf, lai, sai, nwet, luv_dep,  &
4065                                         2, rc_tot, ccomp_tot(lsp), hyp(nzb), conc_ijk_ugm3,       &
4066                                         diffusivity, r_aero_surf , rb )
4067!
4068!--             Calculate budget
4069                IF ( rc_tot <= 0.0 )  THEN
4070
4071                   bud_luv(lsp) = 0.0_wp
4072
4073                ELSE
4074
4075                   vd_lu = 1.0_wp / ( r_aero_surf + rb + rc_tot )
4076
4077                   bud_luv(lsp) = - ( conc_ijk(lsp) - ccomp_tot(lsp) ) *                           &
4078                                    ( 1.0_wp - EXP( -vd_lu * dt_dh ) ) * dh
4079                ENDIF
4080
4081             ENDIF
4082          ENDDO
4083       ENDIF
4084!
4085!--    Pavement
4086       IF ( surf_lsm_h%frac(m,ind_pav_green) > 0 )  THEN
4087!
4088!--       No vegetation on pavements:
4089          lai = 0.0_wp
4090          sai = 0.0_wp
4091
4092          slinnfac = 1.0_wp
4093!
4094!--       Get vd
4095          DO  lsp = 1, nvar
4096!
4097!--       Initialize
4098             vs = 0.0_wp
4099             vd_lu = 0.0_wp
4100             rs = 0.0_wp
4101             rb = 0.0_wp
4102             rc_tot = 0.0_wp
4103             IF ( spc_names(lsp) == 'PM10' )  THEN
4104                part_type = 1
4105!
4106!--             Sedimentation velocity:
4107                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4108                                                        particle_pars(ind_p_size, part_type),      &
4109                                                        particle_pars(ind_p_slip, part_type),      &
4110                                                        visc)
4111
4112                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4113                                            vs,                                                    &
4114                                            particle_pars(ind_p_size, part_type),                  &
4115                                            particle_pars(ind_p_slip, part_type),                  &
4116                                            nwet, temp_tmp, dens, visc,                            &
4117                                            lup_dep,                                               &
4118                                            r_aero_surf, ustar_surf )
4119
4120                bud_lup(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4121
4122
4123             ELSEIF ( spc_names(lsp) == 'PM25' )  THEN
4124                part_type = 2
4125!
4126!--             Sedimentation velocity:
4127                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4128                                                        particle_pars(ind_p_size, part_type),      &
4129                                                        particle_pars(ind_p_slip, part_type),      &
4130                                                        visc)
4131
4132                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4133                                            vs,                                                    &
4134                                            particle_pars(ind_p_size, part_type),                  &
4135                                            particle_pars(ind_p_slip, part_type),                  &
4136                                            nwet, temp_tmp, dens, visc,                            &
4137                                            lup_dep,                                               &
4138                                            r_aero_surf, ustar_surf )
4139
4140                bud_lup(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4141
4142             ELSE  !<GASES
4143!
4144!--             Read spc_name of current species for gas parameter
4145                IF ( ANY( pspecnames(:) == spc_names(lsp) ) )  THEN
4146                   i_pspec = 0
4147                   DO  pspec = 1, nposp
4148                      IF ( pspecnames(pspec) == spc_names(lsp) )  THEN
4149                         i_pspec = pspec
4150                      END IF
4151                   ENDDO
4152
4153                ELSE
4154!
4155!--                For now species not deposited
4156                   CYCLE
4157                ENDIF
4158!
4159!--             Factor used for conversion from ppb to ug/m3 :
4160!--                 ppb (mole tr)/(mole air)/ppb (kg tr)/(mole tr) (ug tr)/(kg tr) &
4161!--                 (mole air)/(kg air) (kg air)/(m3 air) (kg air(ug/m3)/ppb/(kg/mole) = / (kg/mole)
4162!--                 c           1e-9               xm_tracer         1e9       /       xm_air            dens
4163!--             thus:
4164!--                 c_in_ppb * xm_tracer * [ dens / xm_air ] = c_in_ugm3
4165!--             Use density at lowest layer:
4166                ppm2ugm3 =  (dens/xm_air) * 0.001_wp  !< (mole air)/m3
4167!
4168!--             Atmospheric concentration in DEPAC is requested in ug/m3:
4169                !   ug/m3              ppm          (ug/m3)/ppm/(kg/mole)     kg/mole
4170                conc_ijk_ugm3 = conc_ijk(lsp)         * ppm2ugm3 *   specmolm(i_pspec)  ! in ug/m3
4171!
4172!--             Diffusivity for DEPAC relevant gases
4173!--             Use default value
4174                diffusivity            = 0.11e-4
4175!
4176!--             Overwrite with known coefficients of diffusivity from Massman (1998)
4177                IF ( spc_names(lsp) == 'NO2' ) diffusivity = 0.136e-4
4178                IF ( spc_names(lsp) == 'NO'  ) diffusivity = 0.199e-4
4179                IF ( spc_names(lsp) == 'O3'  ) diffusivity = 0.144e-4
4180                IF ( spc_names(lsp) == 'CO'  ) diffusivity = 0.176e-4
4181                IF ( spc_names(lsp) == 'SO2' ) diffusivity = 0.112e-4
4182                IF ( spc_names(lsp) == 'CH4' ) diffusivity = 0.191e-4
4183                IF ( spc_names(lsp) == 'NH3' ) diffusivity = 0.191e-4
4184!
4185!--             Get quasi-laminar boundary layer resistance rb:
4186                CALL get_rb_cell( ( lup_dep == ilu_water_sea )  .OR.                               &
4187                                  ( lup_dep == ilu_water_inland ), z0h_surf, ustar_surf,           &
4188                                    diffusivity, rb )
4189!
4190!--             Get rc_tot
4191                CALL drydepos_gas_depac( spc_names(lsp), day_of_year, latitude, ts, ustar_surf,    &
4192                                         solar_rad, cos_zenith, rh_surf, lai, sai, nwet, lup_dep,  &
4193                                         2, rc_tot, ccomp_tot(lsp), hyp(nzb), conc_ijk_ugm3,       &
4194                                         diffusivity, r_aero_surf , rb )
4195!
4196!--             Calculate budget
4197                IF ( rc_tot <= 0.0 )  THEN
4198                   bud_lup(lsp) = 0.0_wp
4199                ELSE
4200                   vd_lu = 1.0_wp / (r_aero_surf + rb + rc_tot )
4201                   bud_lup(lsp) = - ( conc_ijk(lsp) - ccomp_tot(lsp) ) *                           &
4202                                  ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4203                ENDIF
4204
4205             ENDIF
4206          ENDDO
4207       ENDIF
4208!
4209!--    Water
4210       IF ( surf_lsm_h%frac(m,ind_wat_win) > 0 )  THEN
4211!
4212!--       No vegetation on water:
4213          lai = 0.0_wp
4214          sai = 0.0_wp
4215          slinnfac = 1.0_wp
4216!
4217!--       Get vd
4218          DO  lsp = 1, nvar
4219!
4220!--          Initialize
4221             vs = 0.0_wp
4222             vd_lu = 0.0_wp
4223             rs = 0.0_wp
4224             rb = 0.0_wp
4225             rc_tot = 0.0_wp
4226             IF ( spc_names(lsp) == 'PM10' )  THEN
4227                part_type = 1
4228!
4229!--             Sedimentation velocity:
4230                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4231                                                        particle_pars(ind_p_size, part_type),      &
4232                                                        particle_pars(ind_p_slip, part_type),      &
4233                                                        visc)
4234
4235                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4236                                            vs,                                                    &
4237                                            particle_pars(ind_p_size, part_type),                  &
4238                                            particle_pars(ind_p_slip, part_type),                  &
4239                                            nwet, temp_tmp, dens, visc,                            &
4240                                            luw_dep,                                               &
4241                                            r_aero_surf, ustar_surf )
4242
4243                bud_luw(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4244
4245             ELSEIF ( spc_names(lsp) == 'PM25' )  THEN
4246                part_type = 2
4247!
4248!--             Sedimentation velocity:
4249                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4250                                                        particle_pars(ind_p_size, part_type), &
4251                                                        particle_pars(ind_p_slip, part_type), &
4252                                                        visc)
4253
4254                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4255                                            vs,                                                    &
4256                                            particle_pars(ind_p_size, part_type),                  &
4257                                            particle_pars(ind_p_slip, part_type),                  &
4258                                            nwet, temp_tmp, dens, visc,                            &
4259                                            luw_dep,                                               &
4260                                            r_aero_surf, ustar_surf )
4261
4262                bud_luw(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4263
4264             ELSE  !<GASES
4265!
4266!--             Read spc_name of current species for gas PARAMETER
4267                IF ( ANY(pspecnames(:) == spc_names(lsp) ) )  THEN
4268                   i_pspec = 0
4269                   DO  pspec = 1, nposp
4270                      IF ( pspecnames(pspec) == spc_names(lsp) )  THEN
4271                         i_pspec = pspec
4272                      END IF
4273                   ENDDO
4274
4275                ELSE
4276!
4277!--                For now species not deposited
4278                   CYCLE
4279                ENDIF
4280!
4281!--             Factor used for conversion from ppb to ug/m3 :
4282!--                 ppb (mole tr)/(mole air)/ppb (kg tr)/(mole tr) (ug tr)/(kg tr) &
4283!--                 (mole air)/(kg air) (kg air)/(m3 air) (kg air(ug/m3)/ppb/(kg/mole) = / (kg/mole)
4284!--                 c           1e-9               xm_tracer         1e9       /       xm_air            dens
4285!--             thus:
4286!--                 c_in_ppb * xm_tracer * [ dens / xm_air ] = c_in_ugm3
4287!--             Use density at lowest layer:
4288                ppm2ugm3 = (dens/xm_air) * 0.001_wp  !< (mole air)/m3
4289!
4290!--             Atmospheric concentration in DEPAC is requested in ug/m3:
4291!--                 ug/m3        ppm          (ug/m3)/ppm/(kg/mole)     kg/mole
4292                conc_ijk_ugm3 = conc_ijk(lsp) * ppm2ugm3 *  specmolm(i_pspec)  ! in ug/m3
4293!
4294!--             Diffusivity for DEPAC relevant gases
4295!--             Use default value
4296                diffusivity            = 0.11e-4
4297!
4298!--             Overwrite with known coefficients of diffusivity from Massman (1998)
4299                IF ( spc_names(lsp) == 'NO2' ) diffusivity = 0.136e-4
4300                IF ( spc_names(lsp) == 'NO'  ) diffusivity = 0.199e-4
4301                IF ( spc_names(lsp) == 'O3'  ) diffusivity = 0.144e-4
4302                IF ( spc_names(lsp) == 'CO'  ) diffusivity = 0.176e-4
4303                IF ( spc_names(lsp) == 'SO2' ) diffusivity = 0.112e-4
4304                IF ( spc_names(lsp) == 'CH4' ) diffusivity = 0.191e-4
4305                IF ( spc_names(lsp) == 'NH3' ) diffusivity = 0.191e-4
4306!
4307!--             Get quasi-laminar boundary layer resistance rb:
4308                CALL get_rb_cell( ( luw_dep == ilu_water_sea )  .OR.                               &
4309                                  ( luw_dep == ilu_water_inland ), z0h_surf, ustar_surf,           &
4310                                    diffusivity, rb )
4311
4312!--             Get rc_tot
4313                CALL drydepos_gas_depac( spc_names(lsp), day_of_year, latitude, ts, ustar_surf,    &
4314                                         solar_rad, cos_zenith, rh_surf, lai, sai, nwet, luw_dep,  &
4315                                         2, rc_tot, ccomp_tot(lsp), hyp(nzb), conc_ijk_ugm3,       &
4316                                         diffusivity, r_aero_surf , rb )
4317!
4318!--             Calculate budget
4319                IF ( rc_tot <= 0.0 )  THEN
4320
4321                   bud_luw(lsp) = 0.0_wp
4322
4323                ELSE
4324
4325                   vd_lu = 1.0_wp / (r_aero_surf + rb + rc_tot )
4326
4327                   bud_luw(lsp) = - ( conc_ijk(lsp) - ccomp_tot(lsp) ) *                           &
4328                                  ( 1.0_wp - EXP(-vd_lu * dt_dh ) ) * dh
4329                ENDIF
4330
4331             ENDIF
4332          ENDDO
4333       ENDIF
4334
4335
4336       bud = 0.0_wp
4337!
4338!--    Calculate overall budget for surface m and adapt concentration
4339       DO  lsp = 1, nspec
4340
4341          bud(lsp) = surf_lsm_h%frac(m,ind_veg_wall)  * bud_luv(lsp) +                             &
4342                     surf_lsm_h%frac(m,ind_pav_green) * bud_lup(lsp) +                             &
4343                     surf_lsm_h%frac(m,ind_wat_win)   * bud_luw(lsp)
4344!
4345!--       Compute new concentration:
4346          conc_ijk(lsp) = conc_ijk(lsp) + bud(lsp) * inv_dh
4347
4348          chem_species(lsp)%conc(k,j,i) = MAX( 0.0_wp, conc_ijk(lsp) )
4349
4350       ENDDO
4351
4352    ENDIF
4353!
4354!-- For USM surfaces
4355    IF ( match_usm )  THEN
4356!
4357!--    Get surface element information at i,j:
4358       m = surf_usm_h%start_index(j,i)
4359       k = surf_usm_h%k(m)
4360!
4361!--    Get needed variables for surface element m
4362       ustar_surf  = surf_usm_h%us(m)
4363       z0h_surf    = surf_usm_h%z0h(m)
4364       r_aero_surf = surf_usm_h%r_a(m)
4365       solar_rad   = surf_usm_h%rad_sw_dir(m) + surf_usm_h%rad_sw_dif(m)
4366       lai = surf_usm_h%lai(m)
4367       sai = lai + 1
4368!
4369!--    For small grid spacing neglect R_a
4370       IF ( dzw(k) <= 1.0 )  THEN
4371          r_aero_surf = 0.0_wp
4372       ENDIF
4373!
4374!--    Initialize lu's
4375       luu_palm = 0
4376       luu_dep = 0
4377       lug_palm = 0
4378       lug_dep = 0
4379       lud_palm = 0
4380       lud_dep = 0
4381!
4382!--    Initialize budgets
4383       bud_luu  = 0.0_wp
4384       bud_lug = 0.0_wp
4385       bud_lud = 0.0_wp
4386!
4387!--    Get land use for i,j and assign to DEPAC lu
4388       IF ( surf_usm_h%frac(m,ind_pav_green) > 0 )  THEN
4389!
4390!--       For green urban surfaces (e.g. green roofs assume LU short grass
4391          lug_palm = ind_luv_s_grass
4392          IF ( lug_palm == ind_luv_user )  THEN
4393             message_string = 'No vegetation type defined. Please define vegetation type to enable deposition calculation'
4394             CALL message( 'chem_depo', 'CM0454', 1, 2, 0, 6, 0 )
4395          ELSEIF ( lug_palm == ind_luv_b_soil )  THEN
4396             lug_dep = 9
4397          ELSEIF ( lug_palm == ind_luv_mixed_crops )  THEN
4398             lug_dep = 2
4399          ELSEIF ( lug_palm == ind_luv_s_grass )  THEN
4400             lug_dep = 1
4401          ELSEIF ( lug_palm == ind_luv_ev_needle_trees )  THEN
4402             lug_dep = 4
4403          ELSEIF ( lug_palm == ind_luv_de_needle_trees )  THEN
4404             lug_dep = 4
4405          ELSEIF ( lug_palm == ind_luv_ev_broad_trees )  THEN
4406             lug_dep = 12
4407          ELSEIF ( lug_palm == ind_luv_de_broad_trees )  THEN
4408             lug_dep = 5
4409          ELSEIF ( lug_palm == ind_luv_t_grass )  THEN
4410             lug_dep = 1
4411          ELSEIF ( lug_palm == ind_luv_desert )  THEN
4412             lug_dep = 9
4413          ELSEIF ( lug_palm == ind_luv_tundra  )  THEN
4414             lug_dep = 8
4415          ELSEIF ( lug_palm == ind_luv_irr_crops )  THEN
4416             lug_dep = 2
4417          ELSEIF ( lug_palm == ind_luv_semidesert )  THEN
4418             lug_dep = 8
4419          ELSEIF ( lug_palm == ind_luv_ice )  THEN
4420             lug_dep = 10
4421          ELSEIF ( lug_palm == ind_luv_marsh )  THEN
4422             lug_dep = 8
4423          ELSEIF ( lug_palm == ind_luv_ev_shrubs )  THEN
4424             lug_dep = 14
4425          ELSEIF ( lug_palm == ind_luv_de_shrubs  )  THEN
4426             lug_dep = 14
4427          ELSEIF ( lug_palm == ind_luv_mixed_forest )  THEN
4428             lug_dep = 4
4429          ELSEIF ( lug_palm == ind_luv_intrup_forest )  THEN
4430             lug_dep = 8
4431          ENDIF
4432       ENDIF
4433
4434       IF ( surf_usm_h%frac(m,ind_veg_wall) > 0 )  THEN
4435!
4436!--       For walls in USM assume concrete walls/roofs,
4437!--       assumed LU class desert as also assumed for pavements in LSM
4438          luu_palm = ind_lup_conc
4439          IF ( luu_palm == ind_lup_user )  THEN
4440             message_string = 'No pavement type defined. Please define pavement type to enable deposition calculation'
4441             CALL message( 'chem_depo', 'CM0455', 1, 2, 0, 6, 0 )
4442          ELSEIF ( luu_palm == ind_lup_asph_conc )  THEN
4443             luu_dep = 9
4444          ELSEIF ( luu_palm == ind_lup_asph )  THEN
4445             luu_dep = 9
4446          ELSEIF ( luu_palm ==  ind_lup_conc )  THEN
4447             luu_dep = 9
4448          ELSEIF ( luu_palm ==  ind_lup_sett )  THEN
4449             luu_dep = 9
4450          ELSEIF ( luu_palm == ind_lup_pav_stones )  THEN
4451             luu_dep = 9
4452          ELSEIF ( luu_palm == ind_lup_cobblest )  THEN
4453             luu_dep = 9
4454          ELSEIF ( luu_palm == ind_lup_metal )  THEN
4455             luu_dep = 9
4456          ELSEIF ( luu_palm == ind_lup_wood )  THEN
4457             luu_dep = 9
4458          ELSEIF ( luu_palm == ind_lup_gravel )  THEN
4459             luu_dep = 9
4460          ELSEIF ( luu_palm == ind_lup_f_gravel )  THEN
4461             luu_dep = 9
4462          ELSEIF ( luu_palm == ind_lup_pebblest )  THEN
4463             luu_dep = 9
4464          ELSEIF ( luu_palm == ind_lup_woodchips )  THEN
4465             luu_dep = 9
4466          ELSEIF ( luu_palm == ind_lup_tartan )  THEN
4467             luu_dep = 9
4468          ELSEIF ( luu_palm == ind_lup_art_turf )  THEN
4469             luu_dep = 9
4470          ELSEIF ( luu_palm == ind_lup_clay )  THEN
4471             luu_dep = 9
4472          ENDIF
4473       ENDIF
4474
4475       IF ( surf_usm_h%frac(m,ind_wat_win) > 0 )  THEN
4476!
4477!--       For windows in USM assume metal as this is as close as we get, assumed LU class desert as
4478!--       also assumed for pavements in LSM.
4479          lud_palm = ind_lup_metal
4480          IF ( lud_palm == ind_lup_user )  THEN
4481             message_string = 'No pavement type defined. Please define pavement type to enable deposition calculation'
4482             CALL message( 'chem_depo', 'CM0456', 1, 2, 0, 6, 0 )
4483          ELSEIF ( lud_palm == ind_lup_asph_conc )  THEN
4484             lud_dep = 9
4485          ELSEIF ( lud_palm == ind_lup_asph )  THEN
4486             lud_dep = 9
4487          ELSEIF ( lud_palm ==  ind_lup_conc )  THEN
4488             lud_dep = 9
4489          ELSEIF ( lud_palm ==  ind_lup_sett )  THEN
4490             lud_dep = 9
4491          ELSEIF ( lud_palm == ind_lup_pav_stones )  THEN
4492             lud_dep = 9
4493          ELSEIF ( lud_palm == ind_lup_cobblest )  THEN
4494             lud_dep = 9
4495          ELSEIF ( lud_palm == ind_lup_metal )  THEN
4496             lud_dep = 9
4497          ELSEIF ( lud_palm == ind_lup_wood )  THEN
4498             lud_dep = 9
4499          ELSEIF ( lud_palm == ind_lup_gravel )  THEN
4500             lud_dep = 9
4501          ELSEIF ( lud_palm == ind_lup_f_gravel )  THEN
4502             lud_dep = 9
4503          ELSEIF ( lud_palm == ind_lup_pebblest )  THEN
4504             lud_dep = 9
4505          ELSEIF ( lud_palm == ind_lup_woodchips )  THEN
4506             lud_dep = 9
4507          ELSEIF ( lud_palm == ind_lup_tartan )  THEN
4508             lud_dep = 9
4509          ELSEIF ( lud_palm == ind_lup_art_turf )  THEN
4510             lud_dep = 9
4511          ELSEIF ( lud_palm == ind_lup_clay )  THEN
4512             lud_dep = 9
4513          ENDIF
4514       ENDIF
4515!
4516!--    @TODO: Activate these lines as soon as new ebsolver branch is merged:
4517!--    Set wetness indicator to dry or wet for usm vegetation or pavement
4518       !IF ( surf_usm_h%c_liq(m) > 0 )  THEN
4519       !   nwet = 1
4520       !ELSE
4521       nwet = 0
4522       !ENDIF
4523!
4524!--    Compute length of time step
4525       IF ( call_chem_at_all_substeps )  THEN
4526          dt_chem = dt_3d * weight_pres(intermediate_timestep_count)
4527       ELSE
4528          dt_chem = dt_3d
4529       ENDIF
4530
4531       dh = dzw(k)
4532       inv_dh = 1.0_wp / dh
4533       dt_dh = dt_chem / dh
4534!
4535!--    Concentration at i,j,k
4536       DO  lsp = 1, nspec
4537          conc_ijk(lsp) = chem_species(lsp)%conc(k,j,i)
4538       ENDDO
4539!
4540!--    Temperature at i,j,k
4541       temp_tmp = pt(k,j,i) * ( hyp(k) / 100000.0_wp )**0.286_wp
4542
4543       ts       = temp_tmp - 273.15  !< in degrees celcius
4544!
4545!--    Viscosity of air
4546       visc = 1.496e-6 * temp_tmp**1.5 / ( temp_tmp + 120.0 )
4547!
4548!--    Air density at k
4549       dens = rho_air_zw(k)
4550!
4551!--    Calculate relative humidity from specific humidity for DEPAC
4552       qv_tmp = MAX( q(k,j,i), 0.0_wp )
4553       rh_surf = relativehumidity_from_specifichumidity( qv_tmp, temp_tmp, hyp(k) )
4554!
4555!--    Check if surface fraction (vegetation, pavement or water) > 0 and calculate vd and budget for
4556!--    each surface fraction. Then derive overall budget taking into account the surface fractions.
4557
4558!--    Walls/roofs
4559       IF ( surf_usm_h%frac(m,ind_veg_wall) > 0 )  THEN
4560!
4561!--       No vegetation on non-green walls:
4562          lai = 0.0_wp
4563          sai = 0.0_wp
4564
4565          slinnfac = 1.0_wp
4566!
4567!--       Get vd
4568          DO  lsp = 1, nvar
4569!
4570!--          Initialize
4571             vs = 0.0_wp
4572             vd_lu = 0.0_wp
4573             rs = 0.0_wp
4574             rb = 0.0_wp
4575             rc_tot = 0.0_wp
4576             IF (spc_names(lsp) == 'PM10' )  THEN
4577                part_type = 1
4578!
4579!--             Sedimentation velocity
4580                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4581                                                        particle_pars(ind_p_size, part_type),      &
4582                                                        particle_pars(ind_p_slip, part_type),      &
4583                                                        visc)
4584
4585                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4586                                            vs,                                                    &
4587                                            particle_pars(ind_p_size, part_type),                  &
4588                                            particle_pars(ind_p_slip, part_type),                  &
4589                                            nwet, temp_tmp, dens, visc,                            &
4590                                            luu_dep,                                               &
4591                                            r_aero_surf, ustar_surf )
4592
4593                bud_luu(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4594
4595             ELSEIF ( spc_names(lsp) == 'PM25' )  THEN
4596                part_type = 2
4597!
4598!--             Sedimentation velocity
4599                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4600                                                        particle_pars(ind_p_size, part_type),      &
4601                                                        particle_pars(ind_p_slip, part_type),      &
4602                                                        visc)
4603
4604                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4605                                            vs,                                                    &
4606                                            particle_pars(ind_p_size, part_type),                  &
4607                                            particle_pars(ind_p_slip, part_type),                  &
4608                                            nwet, temp_tmp, dens, visc,                            &
4609                                            luu_dep ,                                              &
4610                                            r_aero_surf, ustar_surf )
4611
4612                bud_luu(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4613
4614             ELSE  !< GASES
4615!
4616!--             Read spc_name of current species for gas parameter
4617                IF ( ANY( pspecnames(:) == spc_names(lsp) ) )  THEN
4618                   i_pspec = 0
4619                   DO  pspec = 1, nposp
4620                      IF ( pspecnames(pspec) == spc_names(lsp) )  THEN
4621                         i_pspec = pspec
4622                      END IF
4623                   ENDDO
4624                ELSE
4625!
4626!--                For now species not deposited
4627                   CYCLE
4628                ENDIF
4629!
4630!--             Factor used for conversion from ppb to ug/m3 :
4631!--                 ppb (mole tr)/(mole air)/ppb (kg tr)/(mole tr) (ug tr)/(kg tr) &
4632!--                 (mole air)/(kg air) (kg air)/(m3 air) (kg air(ug/m3)/ppb/(kg/mole) = / (kg/mole)
4633!--                 c           1e-9              xm_tracer         1e9       /       xm_air            dens
4634!--             thus:
4635!--                 c_in_ppb * xm_tracer * [ dens / xm_air ] = c_in_ugm3
4636!--             Use density at k:
4637                ppm2ugm3 =  (dens/xm_air) * 0.001_wp  !< (mole air)/m3
4638
4639                !
4640!--             Atmospheric concentration in DEPAC is requested in ug/m3:
4641!--                 ug/m3              ppm          (ug/m3)/ppm/(kg/mole)     kg/mole
4642                conc_ijk_ugm3 = conc_ijk(lsp)         * ppm2ugm3 *   specmolm(i_pspec)  ! in ug/m3
4643!
4644!--             Diffusivity for DEPAC relevant gases
4645!--             Use default value
4646                diffusivity            = 0.11e-4
4647!
4648!--             Overwrite with known coefficients of diffusivity from Massman (1998)
4649                IF ( spc_names(lsp) == 'NO2' ) diffusivity = 0.136e-4
4650                IF ( spc_names(lsp) == 'NO'  ) diffusivity = 0.199e-4
4651                IF ( spc_names(lsp) == 'O3'  ) diffusivity = 0.144e-4
4652                IF ( spc_names(lsp) == 'CO'  ) diffusivity = 0.176e-4
4653                IF ( spc_names(lsp) == 'SO2' ) diffusivity = 0.112e-4
4654                IF ( spc_names(lsp) == 'CH4' ) diffusivity = 0.191e-4
4655                IF ( spc_names(lsp) == 'NH3' ) diffusivity = 0.191e-4
4656!
4657!--             Get quasi-laminar boundary layer resistance rb:
4658                CALL get_rb_cell( ( luu_dep == ilu_water_sea )  .OR.                               &
4659                                  ( luu_dep == ilu_water_inland ), z0h_surf, ustar_surf,           &
4660                                    diffusivity, rb )
4661!
4662!--             Get rc_tot
4663                CALL drydepos_gas_depac( spc_names(lsp), day_of_year, latitude, ts, ustar_surf,    &
4664                                         solar_rad, cos_zenith, rh_surf, lai, sai, nwet, luu_dep,  &
4665                                         2, rc_tot, ccomp_tot(lsp), hyp(nzb), conc_ijk_ugm3,       &
4666                                         diffusivity, r_aero_surf, rb )
4667!
4668!--             Calculate budget
4669                IF ( rc_tot <= 0.0 )  THEN
4670
4671                   bud_luu(lsp) = 0.0_wp
4672
4673                ELSE
4674
4675                   vd_lu = 1.0_wp / (r_aero_surf + rb + rc_tot )
4676
4677                   bud_luu(lsp) = - ( conc_ijk(lsp) - ccomp_tot(lsp) ) *                           &
4678                                  ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4679                ENDIF
4680
4681             ENDIF
4682          ENDDO
4683       ENDIF
4684!
4685!--    Green usm surfaces
4686       IF ( surf_usm_h%frac(m,ind_pav_green) > 0 )  THEN
4687
4688!
4689!--       No vegetation on bare soil, desert or ice:
4690          IF ( ( lug_palm == ind_luv_b_soil )  .OR.  ( lug_palm == ind_luv_desert ) .OR.           &
4691               ( lug_palm == ind_luv_ice ) ) THEN
4692
4693             lai = 0.0_wp
4694             sai = 0.0_wp
4695
4696          ENDIF
4697
4698
4699          slinnfac = 1.0_wp
4700!
4701!--       Get vd
4702          DO  lsp = 1, nvar
4703!
4704!--          Initialize
4705             vs = 0.0_wp
4706             vd_lu = 0.0_wp
4707             rs = 0.0_wp
4708             rb = 0.0_wp
4709             rc_tot = 0.0_wp
4710             IF ( spc_names(lsp) == 'PM10' )  THEN
4711                part_type = 1
4712!
4713!--             Sedimentation velocity
4714                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4715                                                        particle_pars(ind_p_size, part_type),      &
4716                                                        particle_pars(ind_p_slip, part_type),      &
4717                                                        visc)
4718
4719                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4720                                            vs,                                                    &
4721                                            particle_pars(ind_p_size, part_type),                  &
4722                                            particle_pars(ind_p_slip, part_type),                  &
4723                                            nwet, temp_tmp, dens, visc,                            &
4724                                            lug_dep,                                               &
4725                                            r_aero_surf, ustar_surf )
4726
4727                bud_lug(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4728
4729             ELSEIF ( spc_names(lsp) == 'PM25' )  THEN
4730                part_type = 2
4731!
4732!--             Sedimentation velocity
4733                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4734                                                        particle_pars(ind_p_size, part_type),      &
4735                                                        particle_pars(ind_p_slip, part_type),      &
4736                                                        visc)
4737
4738                CALL drydepo_aero_zhang_vd( vd_lu, rs,                                             &
4739                                            vs,                                                    &
4740                                            particle_pars(ind_p_size, part_type),                  &
4741                                            particle_pars(ind_p_slip, part_type),                  &
4742                                            nwet, temp_tmp, dens, visc,                            &
4743                                            lug_dep,                                               &
4744                                            r_aero_surf, ustar_surf )
4745
4746                bud_lug(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4747
4748             ELSE  !< GASES
4749!
4750!--             Read spc_name of current species for gas parameter
4751                IF ( ANY( pspecnames(:) == spc_names(lsp) ) )  THEN
4752                   i_pspec = 0
4753                   DO  pspec = 1, nposp
4754                      IF ( pspecnames(pspec) == spc_names(lsp) )  THEN
4755                         i_pspec = pspec
4756                      END IF
4757                   ENDDO
4758                ELSE
4759!
4760!--                For now species not deposited
4761                   CYCLE
4762                ENDIF
4763!
4764!--             Factor used for conversion from ppb to ug/m3 :
4765!--                 ppb (mole tr)/(mole air)/ppb (kg tr)/(mole tr) (ug tr)/(kg tr) &
4766!--                 (mole air)/(kg air) (kg air)/(m3 air) (kg air(ug/m3)/ppb/(kg/mole) = / (kg/mole)
4767!--                 c           1e-9               xm_tracer         1e9       /       xm_air            dens
4768!--             thus:
4769!--                  c_in_ppb * xm_tracer * [ dens / xm_air ] = c_in_ugm3
4770!--             Use density at k:
4771                ppm2ugm3 =  (dens/xm_air) * 0.001_wp  ! (mole air)/m3
4772!
4773!--             Atmospheric concentration in DEPAC is requested in ug/m3:
4774                !   ug/m3              ppm          (ug/m3)/ppm/(kg/mole)     kg/mole
4775                conc_ijk_ugm3 = conc_ijk(lsp)         * ppm2ugm3 *   specmolm(i_pspec)  ! in ug/m3
4776!
4777!--             Diffusivity for DEPAC relevant gases
4778!--             Use default value
4779                diffusivity            = 0.11e-4
4780!
4781!--             Overwrite with known coefficients of diffusivity from Massman (1998)
4782                IF ( spc_names(lsp) == 'NO2' ) diffusivity = 0.136e-4
4783                IF ( spc_names(lsp) == 'NO'  ) diffusivity = 0.199e-4
4784                IF ( spc_names(lsp) == 'O3'  ) diffusivity = 0.144e-4
4785                IF ( spc_names(lsp) == 'CO'  ) diffusivity = 0.176e-4
4786                IF ( spc_names(lsp) == 'SO2' ) diffusivity = 0.112e-4
4787                IF ( spc_names(lsp) == 'CH4' ) diffusivity = 0.191e-4
4788                IF ( spc_names(lsp) == 'NH3' ) diffusivity = 0.191e-4
4789!
4790!--             Get quasi-laminar boundary layer resistance rb:
4791                CALL get_rb_cell( ( lug_dep == ilu_water_sea )  .OR.                               &
4792                                  ( lug_dep == ilu_water_inland ), z0h_surf, ustar_surf,           &
4793                                    diffusivity, rb )
4794!
4795!--             Get rc_tot
4796                CALL drydepos_gas_depac( spc_names(lsp), day_of_year, latitude, ts, ustar_surf,    &
4797                                         solar_rad, cos_zenith, rh_surf, lai, sai, nwet, lug_dep,  &
4798                                         2, rc_tot, ccomp_tot(lsp), hyp(nzb), conc_ijk_ugm3,       &
4799                                         diffusivity, r_aero_surf , rb )
4800!
4801!--             Calculate budget
4802                IF ( rc_tot <= 0.0 )  THEN
4803
4804                   bud_lug(lsp) = 0.0_wp
4805
4806                ELSE
4807
4808                   vd_lu = 1.0_wp / ( r_aero_surf + rb + rc_tot )
4809
4810                   bud_lug(lsp) = - ( conc_ijk(lsp) - ccomp_tot(lsp) ) *                           &
4811                                  ( 1.0_wp - EXP( - vd_lu * dt_dh ) )  * dh
4812                ENDIF
4813
4814             ENDIF
4815          ENDDO
4816       ENDIF
4817!
4818!--    Windows
4819       IF ( surf_usm_h%frac(m,ind_wat_win) > 0 )  THEN
4820!
4821!--       No vegetation on windows:
4822          lai = 0.0_wp
4823          sai = 0.0_wp
4824
4825          slinnfac = 1.0_wp
4826!
4827!--       Get vd
4828          DO  lsp = 1, nvar
4829!
4830!--          Initialize
4831             vs = 0.0_wp
4832             vd_lu = 0.0_wp
4833             rs = 0.0_wp
4834             rb = 0.0_wp
4835             rc_tot = 0.0_wp
4836             IF ( spc_names(lsp) == 'PM10' )  THEN
4837                part_type = 1
4838!
4839!--             Sedimentation velocity
4840                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4841                                                        particle_pars(ind_p_size, part_type),      &
4842                                                        particle_pars(ind_p_slip, part_type),      &
4843                                                        visc)
4844
4845                CALL drydepo_aero_zhang_vd( vd_lu, rs, vs,                                         &
4846                                            particle_pars(ind_p_size, part_type),                  &
4847                                            particle_pars(ind_p_slip, part_type),                  &
4848                                            nwet, temp_tmp, dens, visc,                            &
4849                                            lud_dep, r_aero_surf, ustar_surf )
4850
4851                bud_lud(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4852
4853             ELSEIF ( spc_names(lsp) == 'PM25' )  THEN
4854                part_type = 2
4855!
4856!--             Sedimentation velocity
4857                vs = slinnfac * sedimentation_velocity( particle_pars(ind_p_dens, part_type),      &
4858                                                        particle_pars(ind_p_size, part_type),      &
4859                                                        particle_pars(ind_p_slip, part_type),      &
4860                                                        visc)
4861
4862                CALL drydepo_aero_zhang_vd( vd_lu, rs, vs,                                         &
4863                                            particle_pars(ind_p_size, part_type),                  &
4864                                            particle_pars(ind_p_slip, part_type),                  &
4865                                            nwet, temp_tmp, dens, visc,                            &
4866                                            lud_dep,                                               &
4867                                            r_aero_surf, ustar_surf )
4868
4869                bud_lud(lsp) = - conc_ijk(lsp) * ( 1.0_wp - EXP( - vd_lu * dt_dh ) ) * dh
4870
4871             ELSE  !< GASES
4872!
4873!--             Read spc_name of current species for gas PARAMETER
4874                IF ( ANY( pspecnames(:) == spc_names(lsp) ) )  THEN
4875                   i_pspec = 0
4876                   DO  pspec = 1, nposp
4877                      IF ( pspecnames(pspec) == spc_names(lsp) )  THEN
4878                         i_pspec = pspec
4879                      END IF
4880                   ENDDO
4881                ELSE
4882!
4883!--                For now species not deposited
4884                   CYCLE
4885                ENDIF
4886!
4887!--             Factor used for conversion from ppb to ug/m3 :
4888!--                 ppb (mole tr)/(mole air)/ppb (kg tr)/(mole tr) (ug tr)/(kg tr) &
4889!--                 (mole air)/(kg air) (kg air)/(m3 air) (kg air(ug/m3)/ppb/(kg/mole) = / (kg/mole)
4890!--                 c           1e-9               xm_tracer         1e9       /       xm_air            dens
4891!--             thus:
4892!--                  c_in_ppb * xm_tracer * [ dens / xm_air ] = c_in_ugm3
4893!--             Use density at k:
4894
4895                ppm2ugm3 =  (dens/xm_air) * 0.001_wp  ! (mole air)/m3
4896!
4897!--             Atmospheric concentration in DEPAC is requested in ug/m3:
4898!--                 ug/m3              ppm          (ug/m3)/ppm/(kg/mole)     kg/mole
4899                conc_ijk_ugm3 = conc_ijk(lsp)         * ppm2ugm3 *   specmolm(i_pspec)  ! in ug/m3
4900!
4901!--             Diffusivity for DEPAC relevant gases
4902!--             Use default value
4903                diffusivity = 0.11e-4
4904!
4905!--             Overwrite with known coefficients of diffusivity from Massman (1998)
4906                IF ( spc_names(lsp) == 'NO2' ) diffusivity = 0.136e-4
4907                IF ( spc_names(lsp) == 'NO'  ) diffusivity = 0.199e-4
4908                IF ( spc_names(lsp) == 'O3'  ) diffusivity = 0.144e-4
4909                IF ( spc_names(lsp) == 'CO'  ) diffusivity = 0.176e-4
4910                IF ( spc_names(lsp) == 'SO2' ) diffusivity = 0.112e-4
4911                IF ( spc_names(lsp) == 'CH4' ) diffusivity = 0.191e-4
4912                IF ( spc_names(lsp) == 'NH3' ) diffusivity = 0.191e-4
4913!
4914!--             Get quasi-laminar boundary layer resistance rb:
4915                CALL get_rb_cell( ( lud_dep == ilu_water_sea )  .OR.                               &
4916                                  ( lud_dep == ilu_water_inland ), z0h_surf, ustar_surf,           &
4917                                    diffusivity, rb )
4918!
4919!--             Get rc_tot
4920                CALL drydepos_gas_depac( spc_names(lsp), day_of_year, latitude, ts, ustar_surf,    &
4921                                         solar_rad, cos_zenith, rh_surf, lai, sai, nwet, lud_dep,  &
4922                                         2, rc_tot, ccomp_tot(lsp), hyp(nzb), conc_ijk_ugm3,       &
4923                                         diffusivity, r_aero_surf , rb )
4924!
4925!--             Calculate budget
4926                IF ( rc_tot <= 0.0 )  THEN
4927
4928                   bud_lud(lsp) = 0.0_wp
4929
4930                ELSE
4931
4932                   vd_lu = 1.0_wp / (r_aero_surf + rb + rc_tot )
4933
4934                   bud_lud(lsp) = - ( conc_ijk(lsp) - ccomp_tot(lsp) ) *                           &
4935                                  ( 1.0_wp - EXP( - vd_lu * dt_dh ) )  * dh
4936                ENDIF
4937
4938             ENDIF
4939          ENDDO
4940       ENDIF
4941
4942
4943       bud = 0.0_wp
4944!
4945!--    Calculate overall budget for surface m and adapt concentration
4946       DO  lsp = 1, nspec
4947
4948
4949          bud(lsp) = surf_usm_h%frac(m,ind_veg_wall)  * bud_luu(lsp) +                             &
4950                     surf_usm_h%frac(m,ind_pav_green) * bud_lug(lsp) +                             &
4951                     surf_usm_h%frac(m,ind_wat_win)   * bud_lud(lsp)
4952!
4953!--       Compute new concentration
4954          conc_ijk(lsp) = conc_ijk(lsp) + bud(lsp) * inv_dh
4955
4956          chem_species(lsp)%conc(k,j,i) = MAX( 0.0_wp, conc_ijk(lsp) )
4957
4958       ENDDO
4959
4960    ENDIF
4961
4962
4963 END SUBROUTINE chem_depo
4964
4965
4966!--------------------------------------------------------------------------------------------------!
4967! Description:
4968! ------------
4969!> Subroutine to compute total canopy (or surface) resistance Rc for gases
4970!>
4971!> DEPAC:
4972!> Code of the DEPAC routine and corresponding subroutines below from the DEPAC module of the
4973!> LOTOS-EUROS model (Manders et al., 2017)
4974!>
4975!> Original DEPAC routines by RIVM and TNO (2015), for Documentation see van Zanten et al., 2010.
4976!--------------------------------------------------------------------------------------------------!
4977 SUBROUTINE drydepos_gas_depac( compnam, day_of_year, lat, t, ust, solar_rad, sinphi, rh, lai, sai,&
4978                                nwet, lu, iratns, rc_tot, ccomp_tot, p, conc_ijk_ugm3, diffusivity,&
4979                                ra, rb )
4980!
4981!--   Some of depac arguments are OPTIONAL:
4982!--    A. compute Rc_tot without compensation points (ccomp_tot will be zero):
4983!--        CALL depac (compnam, day_of_year, lat, t, ust, glrad, sinphi, rh, nwet, lu, iratns, rc_tot,&
4984!--                    ccomp_tot, [smi])
4985!--    B. compute Rc_tot with compensation points (used for LOTOS-EUROS):
4986!--        CALL depac (compnam, day_of_year, lat, t, ust, glrad, sinphi, rh, nwet, lu, iratns, rc_tot,&
4987!--                    ccomp_tot, [smi], c_ave_prev_nh3, c_ave_prev_so2, catm, gamma_soil_water)
4988!--
4989!--    C. compute effective Rc based on compensation points (used for OPS):
4990!--        CALL depac (compnam, day_of_year, lat, t, ust, glrad, sinphi, rh, nwet, lu, iratns, rc_tot,&
4991!--                    ccomp_tot, [smi], c_ave_prev_nh3, c_ave_prev_so2, catm, gamma_soil_water, ra,  &
4992!--                    rb, rc_eff)
4993!--    X1. Extra (OPTIONAL) output variables:
4994!--        CALL depac (compnam, day_of_year, lat, t, ust, glrad, sinphi, rh, nwet, lu, iratns, rc_tot,&
4995!--                    ccomp_tot, [smi], c_ave_prev_nh3, c_ave_prev_so2, catm, gamma_soil_water, ra,  &
4996!--                    rb, rc_eff, gw_out, gstom_out, gsoil_eff_out, cw_out, cstom_out, csoil_out,    &
4997!--                    lai_out, sai_out)
4998!--    X2. Extra (OPTIONAL) needed for stomatal ozone flux calculation (only sunlit leaves):
4999!--        CALL depac (compnam, day_of_year, lat, t, ust, glrad, sinphi, rh, nwet, lu, iratns, rc_tot,&
5000!--                    ccomp_tot, [smi], c_ave_prev_nh3, c_ave_prev_so2, catm, gamma_soil_water, ra,  &
5001!--                    rb, rc_eff, gw_out, gstom_out, gsoil_eff_out, cw_out, cstom_out, csoil_out,    &
5002!--                    lai_out, sai_out, calc_stom_o3flux, frac_sto_o3_lu, fac_surface_area_2_PLA)
5003
5004
5005    CHARACTER(LEN=*), INTENT(IN) ::  compnam         !< component name
5006                                                     !< 'HNO3','NO','NO2','O3','SO2','NH3'
5007    INTEGER(iwp), INTENT(IN) ::  day_of_year         !< day of year, 1 ... 365 (366)
5008    INTEGER(iwp), INTENT(IN) ::  iratns              !< index for NH3/SO2 ratio used for SO2:
5009                                                     !< iratns = 1: low NH3/SO2
5010                                                     !< iratns = 2: high NH3/SO2
5011                                                     !< iratns = 3: very low NH3/SO2
5012    INTEGER(iwp), INTENT(IN) ::  lu                  !< land use type, lu = 1,...,nlu
5013    INTEGER(iwp), INTENT(IN) ::  nwet                !< wetness indicator; nwet=0 -> dry; nwet=1 -> wet; nwet=9 -> snow
5014
5015    REAL(wp), INTENT(IN) ::  conc_ijk_ugm3           !< actual atmospheric concentration (ug/m3), in
5016                                                     !< DEPAC=Catm
5017    REAL(wp), INTENT(IN) ::  diffusivity             !< diffusivity
5018    REAL(wp), INTENT(IN) ::  lai                     !< one-sidedleaf area index (-)
5019    REAL(wp), INTENT(IN) ::  lat                     !< latitude Northern hemisphere (degrees) (S.
5020                                                     !< hemisphere not possible)
5021    REAL(wp), INTENT(IN) ::  p                       !< pressure (Pa)
5022    REAL(wp), INTENT(IN) ::  ra                      !< aerodynamic resistance (s/m)
5023    REAL(wp), INTENT(IN) ::  rb                      !< boundary layer resistance (s/m)
5024    REAL(wp), INTENT(IN) ::  rh                      !< relative humidity (%)
5025    REAL(wp), INTENT(IN) ::  sai                     !< surface area index (-) (lai + branches and
5026                                                     !< stems)
5027    REAL(wp), INTENT(IN) ::  sinphi                  !< sin of solar elevation angle
5028    REAL(wp), INTENT(IN) ::  solar_rad               !< solar radiation, dirict+diffuse (W/m2)
5029    REAL(wp), INTENT(IN) ::  t                       !< temperature (C)
5030    REAL(wp), INTENT(IN) ::  ust                     !< friction velocity (m/s)
5031
5032    REAL(wp), INTENT(OUT) ::  ccomp_tot              !< total compensation point (ug/m3)
5033!                                                    !< [= 0 for species that don't have a compensation
5034    REAL(wp), INTENT(OUT) ::  rc_tot                 !< total canopy resistance Rc (s/m)
5035
5036!-- Local variables:
5037!
5038!-- Component number taken from component name, paramteres matched with include files
5039    INTEGER(iwp) ::  icmp
5040!
5041!-- Component numbers:
5042    INTEGER(iwp), PARAMETER ::  icmp_o3   = 1
5043    INTEGER(iwp), PARAMETER ::  icmp_so2  = 2
5044    INTEGER(iwp), PARAMETER ::  icmp_no2  = 3
5045    INTEGER(iwp), PARAMETER ::  icmp_no   = 4
5046    INTEGER(iwp), PARAMETER ::  icmp_nh3  = 5
5047    INTEGER(iwp), PARAMETER ::  icmp_co   = 6
5048    INTEGER(iwp), PARAMETER ::  icmp_no3  = 7
5049    INTEGER(iwp), PARAMETER ::  icmp_hno3 = 8
5050    INTEGER(iwp), PARAMETER ::  icmp_n2o5 = 9
5051    INTEGER(iwp), PARAMETER ::  icmp_h2o2 = 10
5052
5053    LOGICAL ::  ready                                !< Rc has been set:
5054                                                     !< = 1 -> constant Rc
5055                                                     !< = 2 -> temperature dependent Rc
5056!
5057!-- Vegetation indicators:
5058    LOGICAL ::  lai_present                          !< leaves are present for current land use type
5059    LOGICAL ::  sai_present                          !< vegetation is present for current land use
5060                                                     !< type
5061
5062    REAL(wp) ::  csoil                               !< soil compensation point (ug/m3)
5063    REAL(wp) ::  cstom                               !< stomatal compensation point (ug/m3)
5064    REAL(wp) ::  cw                                  !< external leaf surface compensation point
5065                                                     !< (ug/m3)
5066    REAL(wp) ::  gc_tot                              !< total canopy conductance (m/s)
5067    REAL(wp) ::  gsoil_eff                           !< effective soil conductance (m/s)
5068    REAL(wp) ::  gstom                               !< stomatal conductance (m/s)
5069    REAL(wp) ::  gw                                  !< external leaf conductance (m/s)
5070!    REAL(wp) ::  laimax                              !< maximum leaf area index (-)
5071!
5072!-- Next statement is just to avoid compiler warning about unused variable
5073    IF ( day_of_year == 0  .OR.  ( conc_ijk_ugm3 + lat + ra + rb ) > 0.0_wp )  CONTINUE
5074!
5075!-- Define component number
5076    SELECT CASE ( TRIM( compnam ) )
5077
5078    CASE ( 'O3', 'o3' )
5079       icmp = icmp_o3
5080
5081    CASE ( 'SO2', 'so2' )
5082       icmp = icmp_so2
5083
5084    CASE ( 'NO2', 'no2' )
5085       icmp = icmp_no2
5086
5087    CASE ( 'NO', 'no' )
5088       icmp = icmp_no
5089
5090    CASE ( 'NH3', 'nh3' )
5091       icmp = icmp_nh3
5092
5093    CASE ( 'CO', 'co' )
5094       icmp = icmp_co
5095
5096    CASE ( 'NO3', 'no3' )
5097       icmp = icmp_no3
5098
5099    CASE ( 'HNO3', 'hno3' )
5100       icmp = icmp_hno3
5101
5102    CASE ( 'N2O5', 'n2o5' )
5103       icmp = icmp_n2o5
5104
5105    CASE ( 'H2O2', 'h2o2' )
5106       icmp = icmp_h2o2
5107
5108    CASE default
5109!
5110!--    Component not part of DEPAC --> not deposited
5111       RETURN
5112
5113    END SELECT
5114
5115!
5116!-- Inititalize
5117    gw        = 0.0_wp
5118    gstom     = 0.0_wp
5119    gsoil_eff = 0.0_wp
5120    gc_tot    = 0.0_wp
5121    cw        = 0.0_wp
5122    cstom     = 0.0_wp
5123    csoil     = 0.0_wp
5124!
5125!-- Check whether vegetation is present:
5126    lai_present = ( lai > 0.0 )
5127    sai_present = ( sai > 0.0 )
5128!
5129!-- Set Rc (i.e. rc_tot) in special cases:
5130    CALL rc_special( icmp, compnam, lu, t, nwet, rc_tot, ready, ccomp_tot )
5131!
5132!-- If Rc is not set:
5133    IF ( .NOT. ready ) then
5134!
5135!--    External conductance:
5136       CALL rc_gw( compnam, iratns, t, rh, nwet, sai_present, sai,gw )
5137!
5138!--    Stomatal conductance:
5139       CALL rc_gstom( icmp, compnam, lu, lai_present, lai, solar_rad, sinphi, t, rh, diffusivity,  &
5140                      gstom, p )
5141!
5142!--    Effective soil conductance:
5143       CALL rc_gsoil_eff( icmp, lu, sai, ust, nwet, t, gsoil_eff )
5144!
5145!--    Total canopy conductance (gc_tot) and resistance Rc (rc_tot):
5146       CALL rc_rctot( gstom, gsoil_eff, gw, gc_tot, rc_tot )
5147!
5148!--    Needed to include compensation point for NH3
5149!--    Compensation points (always returns ccomp_tot; currently ccomp_tot != 0 only for NH3):
5150!--    CALL rc_comp_point( compnam,lu,day_of_year,t,gw,gstom,gsoil_eff,gc_tot,&
5151!--          lai_present, sai_present, &
5152!--          ccomp_tot, &
5153!--          conc_ijk_ugm3=conc_ijk_ugm3,c_ave_prev_nh3=c_ave_prev_nh3, &
5154!--          c_ave_prev_so2=c_ave_prev_so2,gamma_soil_water=gamma_soil_water, &
5155!--          tsea=tsea,cw=cw,cstom=cstom,csoil=csoil )
5156!
5157!--    Effective Rc based on compensation points:
5158!--        IF ( PRESENT( rc_eff ) )  THEN
5159!--          check on required arguments:
5160!--           IF ( ( .NOT. PRESENT( conc_ijk_ugm3 ) )  .OR.  ( .NOT. PRESENT( ra ) )  .OR.         &
5161!--                ( .NOT. PRESENT( rb ) ) )  THEN
5162!--              STOP 'output argument rc_eff requires input arguments conc_ijk_ugm3, ra and rb'
5163!--           ENDIF
5164!
5165!--           Compute rc_eff :
5166!--           CALL rc_comp_point_rc_eff(ccomp_tot,conc_ijk_ugm3,ra,rb,rc_tot,rc_eff)
5167!--        ENDIF
5168    ENDIF
5169
5170 END SUBROUTINE drydepos_gas_depac
5171
5172
5173!--------------------------------------------------------------------------------------------------!
5174! Description:
5175! ------------
5176!> Subroutine to compute total canopy resistance in special cases
5177!--------------------------------------------------------------------------------------------------!
5178 SUBROUTINE rc_special( icmp, compnam, lu, t, nwet, rc_tot, ready, ccomp_tot )
5179
5180
5181    CHARACTER(LEN=*), INTENT(IN)  ::  compnam     !< component name
5182
5183    INTEGER(iwp), INTENT(IN)  ::  icmp            !< component index
5184    INTEGER(iwp), INTENT(IN)  ::  lu              !< land use type, lu = 1,...,nlu
5185    INTEGER(iwp), INTENT(IN)  ::  nwet            !< wetness indicator; nwet=0 -> dry; nwet=1 -> wet; nwet=9 -> snow
5186
5187    LOGICAL, INTENT(OUT) ::  ready               !< Rc has been set
5188                                                 !< = 1 -> constant Rc
5189
5190    REAL(wp), INTENT(IN)  ::  t                   !< temperature (C)
5191
5192    REAL(wp), INTENT(OUT) ::  ccomp_tot          !< total compensation point (ug/m3)
5193    REAL(wp), INTENT(OUT) ::  rc_tot             !< total canopy resistance Rc (s/m)
5194
5195!
5196!-- Next line is to avoid compiler warning about unused variable
5197    IF ( icmp == 0 )  CONTINUE
5198!
5199!-- rc_tot is not yet set:
5200    ready = .FALSE.
5201!
5202!-- Default compensation point in special CASEs = 0:
5203    ccomp_tot = 0.0_wp
5204
5205    SELECT CASE( TRIM( compnam ) )
5206    CASE( 'HNO3', 'N2O5', 'NO3', 'H2O2' )
5207!
5208!--    No separate resistances for HNO3; just one total canopy resistance:
5209       IF ( t < -5.0_wp .AND. nwet == 9 )  THEN
5210!
5211!--       T < 5 C and snow:
5212          rc_tot = 50.0_wp
5213       ELSE
5214!
5215!--       All other circumstances:
5216          rc_tot = 10.0_wp
5217       ENDIF
5218       ready = .TRUE.
5219
5220    CASE( 'NO', 'CO' )
5221       IF ( lu == ilu_water_sea .OR. lu == ilu_water_inland )  THEN       ! water
5222          rc_tot = 2000.0_wp
5223          ready = .TRUE.
5224       ELSEIF ( nwet == 1 )  THEN  !< wet
5225          rc_tot = 2000.0_wp
5226          ready = .TRUE.
5227       ENDIF
5228    CASE( 'NO2', 'O3', 'SO2', 'NH3' )
5229!
5230!--    snow surface:
5231       IF ( nwet == 9 )  THEN
5232!
5233!--       To be activated when snow is implemented
5234          !CALL rc_snow(ipar_snow(icmp),t,rc_tot)
5235          ready = .TRUE.
5236       ENDIF
5237    CASE default
5238       message_string = 'Component '// TRIM( compnam ) // ' not supported'
5239       CALL message( 'rc_special', 'CM0457', 1, 2, 0, 6, 0 )
5240    END SELECT
5241
5242 END SUBROUTINE rc_special
5243
5244
5245!--------------------------------------------------------------------------------------------------!
5246! Description:
5247! ------------
5248!> Subroutine to compute external conductance
5249!--------------------------------------------------------------------------------------------------!
5250 SUBROUTINE rc_gw( compnam, iratns, t, rh, nwet, sai_present, sai, gw )
5251
5252!
5253!-- Input/output variables:
5254    CHARACTER(LEN=*), INTENT(IN) ::  compnam      !< component name
5255    INTEGER(iwp), INTENT(IN) ::  iratns           !< index for NH3/SO2 ratio;
5256                                                  !< iratns = 1: low NH3/SO2
5257                                                  !< iratns = 2: high NH3/SO2
5258                                                  !< iratns = 3: very low NH3/SO2
5259
5260    INTEGER(iwp), INTENT(IN) ::  nwet             !< wetness indicator; nwet=0 -> dry; nwet=1 -> wet; nwet=9 -> snow
5261
5262    LOGICAL, INTENT(IN) ::  sai_present
5263
5264    REAL(wp), INTENT(IN) ::  rh                   !< relative humidity (%)
5265    REAL(wp), INTENT(IN) ::  sai                  !< one-sided leaf area index (-)
5266    REAL(wp), INTENT(IN) ::  t                    !< temperature (C)
5267
5268    REAL(wp), INTENT(OUT) ::  gw                  !< external leaf conductance (m/s)
5269
5270    SELECT CASE( TRIM( compnam ) )
5271
5272    CASE( 'NO2' )
5273       CALL rw_constant( 2000.0_wp, sai_present, gw )
5274
5275    CASE( 'NO', 'CO' )
5276       CALL rw_constant( -9999.0_wp, sai_present, gw )   !< see Erisman et al, 1994 section 3.2.3
5277
5278    CASE( 'O3' )
5279       CALL rw_constant( 2500.0_wp, sai_present, gw )
5280
5281    CASE( 'SO2' )
5282       CALL rw_so2( t, nwet, rh, iratns, sai_present, gw )
5283
5284    CASE( 'NH3' )
5285       CALL rw_nh3_sutton( t, rh, sai_present, gw )
5286!
5287!--    Conversion from leaf resistance to canopy resistance by multiplying with sai:
5288       gw = sai * gw
5289
5290    CASE default
5291       message_string = 'Component '// TRIM( compnam ) // ' not supported'
5292       CALL message( 'rc_gw', 'CM0458', 1, 2, 0, 6, 0 )
5293    END SELECT
5294
5295 END SUBROUTINE rc_gw
5296
5297
5298!--------------------------------------------------------------------------------------------------!
5299! Description:
5300! ------------
5301!> Subroutine to compute external leaf conductance for SO2
5302!--------------------------------------------------------------------------------------------------!
5303 SUBROUTINE rw_so2( t, nwet, rh, iratns, sai_present, gw )
5304
5305!
5306!-- Input/output variables:
5307    INTEGER(iwp), INTENT(IN) ::  iratns      !< index for NH3/SO2 ratio:
5308                                             !< iratns = 1: low NH3/SO2
5309                                             !< iratns = 2: high NH3/SO2
5310                                             !< iratns = 3: very low NH3/SO2
5311    INTEGER(iwp), INTENT(IN) ::  nwet        !< wetness indicator; nwet=0 -> dry; nwet=1 -> wet; nwet=9 -> snow
5312
5313    LOGICAL, INTENT(IN) ::  sai_present
5314
5315    REAL(wp), INTENT(IN) ::  rh              !< relative humidity (%)
5316    REAL(wp), INTENT(IN) ::  t               !< temperature (C)
5317
5318    REAL(wp), INTENT(OUT) ::  gw             !< external leaf conductance (m/s)
5319!
5320!-- Local variables:
5321    REAL(wp) ::  rw                          !< external leaf resistance (s/m)
5322!
5323!-- Check if vegetation present:
5324    IF ( sai_present )  THEN
5325
5326       IF ( nwet == 0 )  THEN
5327!
5328!--   ------------------------
5329!--         dry surface
5330!--   ------------------------
5331!--         T > -1 C
5332          IF ( t > -1.0_wp )  THEN
5333             IF ( rh < 81.3_wp )  THEN
5334                rw = 25000.0_wp * EXP( -0.0693_wp * rh )
5335             ELSE
5336                rw = 0.58e12 * EXP( -0.278_wp * rh ) + 10.0_wp
5337             ENDIF
5338          ELSE
5339             ! -5 C < T <= -1 C
5340             IF ( t > -5.0_wp )  THEN
5341                rw = 200.0_wp
5342             ELSE
5343                ! T <= -5 C
5344                rw = 500.0_wp
5345             ENDIF
5346          ENDIF
5347       ELSE
5348!
5349!--   ------------------------
5350!--         wet surface
5351!--   ------------------------
5352          rw = 10.0_wp !see Table 5, Erisman et al, 1994 Atm. Environment, 0 is impl. as 10
5353       ENDIF
5354!
5355!--    Very low NH3/SO2 ratio:
5356       IF ( iratns == iratns_very_low ) rw = rw + 50.0_wp
5357!
5358!--      Conductance:
5359       gw = 1.0_wp / rw
5360    ELSE
5361!
5362!--      No vegetation:
5363       gw = 0.0_wp
5364    ENDIF
5365
5366 END SUBROUTINE rw_so2
5367
5368
5369!--------------------------------------------------------------------------------------------------!
5370! Description:
5371! ------------
5372!> Subroutine to compute external leaf conductance for NH3, following Sutton & Fowler, 1993
5373!--------------------------------------------------------------------------------------------------!
5374 SUBROUTINE rw_nh3_sutton( tsurf, rh,sai_present, gw )
5375
5376!
5377!-- Input/output variables:
5378    LOGICAL, INTENT(IN) ::  sai_present
5379
5380    REAL(wp), INTENT(IN) ::  rh             !< relative humidity (%)
5381    REAL(wp), INTENT(IN) ::  tsurf          !< surface temperature (C)
5382
5383    REAL(wp), INTENT(OUT) ::  gw            !< external leaf conductance (m/s)
5384!
5385!-- Local variables:
5386    REAL(wp) ::  rw                         !< external leaf resistance (s/m)
5387    REAL(wp) ::  sai_grass_haarweg          !< surface area index at experimental site Haarweg
5388!
5389!-- Fix sai_grass at value valid for Haarweg data for which gamma_w parametrization is derived
5390    sai_grass_haarweg = 3.5_wp
5391!
5392!-- Calculation rw:
5393!--                    100 - rh
5394!--    rw = 2.0 * exp(----------)
5395!--                      12
5396
5397    IF ( sai_present )  THEN
5398!
5399!--    External resistance according to Sutton & Fowler, 1993
5400       rw = 2.0_wp * EXP( ( 100.0_wp - rh ) / 12.0_wp )
5401       rw = sai_grass_haarweg * rw
5402!
5403!--    Frozen soil (from Depac v1):
5404       IF ( tsurf < 0.0_wp ) rw = 200.0_wp
5405!
5406!--    Conductance:
5407       gw = 1.0_wp / rw
5408    ELSE
5409       ! no vegetation:
5410       gw = 0.0_wp
5411    ENDIF
5412
5413 END SUBROUTINE rw_nh3_sutton
5414
5415
5416!--------------------------------------------------------------------------------------------------!
5417! Description:
5418! ------------
5419!> Subroutine to compute external leaf conductance
5420!--------------------------------------------------------------------------------------------------!
5421 SUBROUTINE rw_constant( rw_val, sai_present, gw )
5422
5423!
5424!-- Input/output variables:
5425    LOGICAL, INTENT(IN) ::  sai_present
5426
5427    REAL(wp), INTENT(IN) ::  rw_val       !< constant value of Rw
5428
5429    REAL(wp), INTENT(OUT) ::  gw          !< wernal leaf conductance (m/s)
5430!
5431!-- Compute conductance:
5432    IF ( sai_present  .AND.  .NOT. missing(rw_val) )  THEN
5433       gw = 1.0_wp / rw_val
5434    ELSE
5435       gw = 0.0_wp
5436    ENDIF
5437
5438 END SUBROUTINE rw_constant
5439
5440
5441!--------------------------------------------------------------------------------------------------!
5442! Description:
5443! ------------
5444!> Subroutine to compute stomatal conductance
5445!--------------------------------------------------------------------------------------------------!
5446 SUBROUTINE rc_gstom( icmp, compnam, lu, lai_present, lai, solar_rad, sinphi, t, rh, diffusivity,  &
5447                      gstom, p )
5448
5449!
5450!-- input/output variables:
5451    CHARACTER(LEN=*), INTENT(IN) ::  compnam       !< component name
5452
5453    INTEGER(iwp), INTENT(IN) ::  icmp              !< component index
5454    INTEGER(iwp), INTENT(IN) ::  lu                !< land use type , lu = 1,...,nlu
5455
5456    LOGICAL, INTENT(IN) ::  lai_present
5457
5458    REAL(wp), INTENT(IN) ::  diffusivity           !< diffusion coefficient of the gas involved
5459    REAL(wp), INTENT(IN) ::  lai                   !< one-sided leaf area index
5460    REAL(wp), INTENT(IN) ::  rh                    !< relative humidity (%)
5461    REAL(wp), INTENT(IN) ::  sinphi                !< sin of solar elevation angle
5462    REAL(wp), INTENT(IN) ::  solar_rad             !< solar radiation, dirict+diffuse (W/m2)
5463    REAL(wp), INTENT(IN) ::  t                     !< temperature (C)
5464
5465    REAL(wp), OPTIONAL,INTENT(IN) :: p             !< pressure (Pa)
5466
5467    REAL(wp), INTENT(OUT) ::  gstom                !< stomatal conductance (m/s)
5468!
5469!-- Local variables
5470    REAL(wp), PARAMETER ::  dO3 = 0.13e-4          !< diffusion coefficient of ozon (m2/s)
5471
5472    REAL(wp) ::  vpd                               !< vapour pressure deficit (kPa)
5473
5474!
5475!-- Next line is to avoid compiler warning about unused variables
5476    IF ( icmp == 0 )  CONTINUE
5477
5478    SELECT CASE( TRIM( compnam ) )
5479
5480    CASE( 'NO', 'CO' )
5481!
5482!--    For no stomatal uptake is neglected:
5483       gstom = 0.0_wp
5484
5485    CASE( 'NO2', 'O3', 'SO2', 'NH3' )
5486!
5487!--    If vegetation present:
5488       IF ( lai_present )  THEN
5489
5490          IF ( solar_rad > 0.0_wp )  THEN
5491             CALL rc_get_vpd( t, rh, vpd )
5492             CALL rc_gstom_emb( lu, solar_rad, t, vpd, lai_present, lai, sinphi, gstom, p )
5493             gstom = gstom * diffusivity / dO3       !< Gstom of Emberson is derived for ozone
5494          ELSE
5495             gstom = 0.0_wp
5496          ENDIF
5497       ELSE
5498!
5499!--       No vegetation; zero conductance (infinite resistance):
5500          gstom = 0.0_wp
5501       ENDIF
5502
5503    CASE default
5504       message_string = 'Component '// TRIM( compnam ) // ' not supported'
5505       CALL message( 'rc_gstom', 'CM0459', 1, 2, 0, 6, 0 )
5506    END SELECT
5507
5508 END SUBROUTINE rc_gstom
5509
5510
5511!--------------------------------------------------------------------------------------------------!
5512! Description:
5513! ------------
5514!> Subroutine to compute stomatal conductance according to Emberson
5515!--------------------------------------------------------------------------------------------------!
5516 SUBROUTINE rc_gstom_emb( lu, solar_rad, T, vpd, lai_present, lai, sinp, Gsto, p )
5517!
5518!>  History
5519!>   Original code from Lotos-Euros, TNO, M. Schaap
5520!>   2009-08, M.C. van Zanten, Rivm
5521!>     Updated and extended.
5522!>   2009-09, Arjo Segers, TNO
5523!>     Limitted temperature influence to range to avoid floating point exceptions.
5524
5525!> Method
5526
5527!>   Code based on Emberson et al, 2000, Env. Poll., 403-413
5528!>   Notation conform Unified EMEP Model Description Part 1, ch 8
5529!
5530!>   In the calculation of f_light the modification of L. Zhang 2001, AE to the PARshade and PARsun
5531!>   parametrizations of Norman 1982 are applied
5532!>   f_phen and f_SWP are set to 1
5533!
5534!>   Land use types DEPAC versus Emberson (Table 5.1, EMEP model description)
5535!>   DEPAC                     Emberson
5536!>     1 = grass                 GR = grassland
5537!>     2 = arable land           TC = temperate crops ( lai according to RC = rootcrops)
5538!>     3 = permanent crops       TC = temperate crops ( lai according to RC = rootcrops)
5539!>     4 = coniferous forest     CF = tempareate/boREAL(wp) coniferous forest
5540!>     5 = deciduous forest      DF = temperate/boREAL(wp) deciduous forest
5541!>     6 = water                 W  = water
5542!>     7 = urban                 U  = urban
5543!>     8 = other                 GR = grassland
5544!>     9 = desert                DE = desert
5545!
5546!-- Emberson specific declarations
5547!
5548!-- Input/output variables:
5549    INTEGER(iwp), INTENT(IN) ::  lu             !< land use type, lu = 1,...,nlu
5550
5551    LOGICAL, INTENT(IN) ::  lai_present
5552
5553    REAL(wp), INTENT(IN) ::  lai                !< one-sided leaf area index
5554    REAL(wp), INTENT(IN) ::  sinp               !< sin of solar elevation angle
5555    REAL(wp), INTENT(IN) ::  solar_rad          !< solar radiation, dirict+diffuse (W/m2)
5556    REAL(wp), INTENT(IN) ::  t                  !< temperature (C)
5557    REAL(wp), INTENT(IN) ::  vpd                !< vapour pressure deficit (kPa)
5558
5559
5560    REAL(wp), OPTIONAL, INTENT(IN) ::  p        !< pressure (Pa)
5561
5562    REAL(wp), INTENT(OUT) ::  gsto              !< stomatal conductance (m/s)
5563!
5564!-- Local variables:
5565    REAL(wp), PARAMETER ::  p_sealevel = 1.01325e05    !< Pa
5566
5567    REAL(wp) ::  bt
5568    REAL(wp) ::  f_env
5569    REAL(wp) ::  f_light
5570    REAL(wp) ::  f_phen
5571    REAL(wp) ::  f_temp
5572    REAL(wp) ::  f_swp
5573    REAL(wp) ::  f_vpd
5574    REAL(wp) ::  laishade
5575    REAL(wp) ::  laisun
5576    REAL(wp) ::  pardiff
5577    REAL(wp) ::  pardir
5578    REAL(wp) ::  parshade
5579    REAL(wp) ::  parsun
5580    REAL(wp) ::  pres
5581    REAL(wp) ::  sinphi
5582
5583!
5584!-- Check whether vegetation is present:
5585    IF ( lai_present )  THEN
5586
5587       ! Calculation of correction factors for stomatal conductance
5588       IF ( sinp <= 0.0_wp )  THEN
5589          sinphi = 0.0001_wp
5590       ELSE
5591          sinphi = sinp
5592       END IF
5593!
5594!--    Ratio between actual and sea-level pressure is used to correct for height in the computation
5595!--    of par; should not exceed sea-level pressure therefore ...
5596       IF (  PRESENT( p ) )  THEN
5597          pres = MIN( p, p_sealevel )
5598       ELSE
5599          pres = p_sealevel
5600       ENDIF
5601!
5602!--    Direct and diffuse par, Photoactive (=visible) radiation:
5603       CALL par_dir_diff( solar_rad, sinphi, pres, p_sealevel, pardir, pardiff )
5604!
5605!--    Par for shaded leaves (canopy averaged):
5606       parshade = pardiff * EXP( -0.5 * lai**0.7 ) + 0.07 * pardir * ( 1.1 - 0.1 * lai ) *         &
5607                  EXP( -sinphi )     !< Norman,1982
5608       IF ( solar_rad > 200.0_wp  .AND.  lai > 2.5_wp )  THEN
5609          parshade = pardiff * EXP( -0.5 * lai**0.8 ) + 0.07 * pardir * ( 1.1 - 0.1 * lai ) *      &
5610                     EXP( -sinphi )  !< Zhang et al., 2001
5611       END IF
5612!
5613!--    Par for sunlit leaves (canopy averaged):
5614!--    alpha -> mean angle between leaves and the sun is fixed at 60 deg -> i.e. cos alpha = 0.5
5615       parsun = pardir * 0.5/sinphi + parshade             !< Norman, 1982
5616       IF ( solar_rad > 200.0_wp  .AND.  lai > 2.5_wp )  THEN
5617          parsun = pardir**0.8 * 0.5 / sinphi + parshade   !< Zhang et al., 2001
5618       END IF
5619!
5620!--    Leaf area index for sunlit and shaded leaves:
5621       IF ( sinphi > 0 )  THEN
5622          laisun = 2 * sinphi * ( 1 - EXP( -0.5 * lai / sinphi ) )
5623          laishade = lai - laisun
5624       ELSE
5625          laisun = 0
5626          laishade = lai
5627       END IF
5628
5629       f_light = ( laisun * ( 1 - EXP( -1.0_wp * alpha(lu) * parsun ) ) +                          &
5630                   laishade * ( 1 - EXP( -1.0_wp * alpha(lu) * parshade ) ) ) / lai
5631
5632       f_light = MAX(f_light,f_min(lu))
5633!
5634!--    Temperature influence; only non-zero within range [tmin,tmax]:
5635       IF ( ( tmin(lu) < t )  .AND.  ( t < tmax(lu) ) )  THEN
5636          bt = ( tmax(lu) - topt(lu) ) / ( topt(lu) - tmin(lu) )
5637          f_temp = ( ( t - tmin(lu) ) / ( topt(lu) - tmin(lu) ) ) *                                &
5638                   ( ( tmax(lu) - t ) / ( tmax(lu) - topt(lu) ) )**bt
5639       ELSE
5640          f_temp = 0.0_wp
5641       END IF
5642       f_temp = MAX( f_temp, f_min(lu) )
5643!
5644!--    Vapour pressure deficit influence
5645       f_vpd = MIN( 1.0_wp, ( ( 1.0_wp - f_min(lu) ) * ( vpd_min(lu) - vpd ) /                     &
5646                              ( vpd_min(lu) - vpd_max(lu) ) + f_min(lu) ) )
5647       f_vpd = MAX( f_vpd, f_min(lu) )
5648
5649       f_swp = 1.0_wp
5650!
5651!--    Influence of phenology on stom. conductance
5652!--    Ignored for now in DEPAC since influence of f_phen on lu classes in use is negligible.
5653!--    When other EMEP classes (e.g. med. broadleaf) are used f_phen might be too important to
5654!--    ignore.
5655       f_phen = 1.0_wp
5656!
5657!--    Evaluate total stomatal conductance
5658       f_env = f_temp * f_vpd * f_swp
5659       f_env = MAX( f_env,f_min(lu) )
5660       gsto = g_max(lu) * f_light * f_phen * f_env
5661!
5662!--    gstom expressed per m2 leafarea;
5663!--    This is converted with lai to m2 surface.
5664       gsto = lai * gsto    ! in m/s
5665
5666    ELSE
5667       gsto = 0.0_wp
5668    ENDIF
5669
5670 END SUBROUTINE rc_gstom_emb
5671
5672
5673!--------------------------------------------------------------------------------------------------!
5674 !> par_dir_diff
5675 !>     Weiss, A., Norman, J.M. (1985) Partitioning solar radiation into direct and diffuse, visible
5676 !>     and near-infrared components. Agric. Forest Meteorol. 34, 205-213.
5677 !>     From a SUBROUTINE obtained from Leiming Zhang,
5678 !>     Meteorological Service of Canada
5679 !>     Leiming uses solar irradiance. This should be equal to global radiation and
5680 !>     Willem Asman set it to global radiation (here defined as solar radiation, dirict+diffuse)
5681 !>
5682 !>     @todo Check/connect/replace with radiation_model_mod variables
5683 !-------------------------------------------------------------------------------------------------!
5684 SUBROUTINE par_dir_diff( solar_rad, sinphi, pres, pres_0, par_dir, par_diff )
5685
5686
5687    REAL(wp), INTENT(IN) ::  pres            !< actual pressure (to correct for height) (Pa)
5688    REAL(wp), INTENT(IN) ::  pres_0          !< pressure at sea level (Pa)
5689    REAL(wp), INTENT(IN) ::  sinphi          !< sine of the solar elevation
5690    REAL(wp), INTENT(IN) ::  solar_rad       !< solar radiation, dirict+diffuse (W m-2)
5691
5692    REAL(wp), INTENT(OUT) ::  par_diff       !< par diffuse: visible (photoactive) diffuse radiation
5693                                             !< (W m-2)
5694    REAL(wp), INTENT(OUT) ::  par_dir        !< par direct : visible (photoactive) direct beam
5695                                             !< radiation (W m-2)
5696
5697    REAL(wp) ::  fv                          !< par direct beam fraction (dimensionless)
5698    REAL(wp) ::  ratio                       !< ratio measured to potential solar radiation
5699                                             !< (dimensionless)
5700    REAL(wp) ::  rdm                         !< potential direct beam near-infrared radiation
5701                                             !< (W m-2); "potential" means clear-sky
5702    REAL(wp) ::  rdn                         !< potential diffuse near-infrared radiation (W m-2)
5703    REAL(wp) ::  rdu                         !< visible (par) direct beam radiation (W m-2)
5704    REAL(wp) ::  rdv                         !< potential visible (par) diffuse radiation (W m-2)
5705    REAL(wp) ::  rn                          !< near-infrared radiation (W m-2)
5706    REAL(wp) ::  rv                          !< visible radiation (W m-2)
5707    REAL(wp) ::  sv                          !< total visible radiation
5708    REAL(wp) ::  ww                          !< water absorption in the near infrared for 10 mm of
5709                                             !< precipitable water
5710
5711!
5712!-- Calculate visible (PAR) direct beam radiation
5713!-- 600 W m-2 represents average amount of par (400-700 nm wavelength) at the top of the atmosphere;
5714!-- this is roughly 0.45*solar constant (solar constant=1320 Wm-2)
5715    rdu = 600.0_wp* EXP( -0.185_wp * ( pres / pres_0 ) / sinphi ) * sinphi
5716!
5717!-- Calculate potential visible diffuse radiation
5718    rdv = 0.4_wp * ( 600.0_wp - rdu ) * sinphi
5719!
5720!-- Calculate the water absorption in the-near infrared
5721    ww = 1320 * 10**( -1.195_wp + 0.4459_wp * LOG10( 1.0_wp / sinphi ) - 0.0345_wp *               &
5722                      ( LOG10( 1.0_wp / sinphi ) )**2 )
5723!
5724!-- Calculate potential direct beam near-infrared radiation
5725    rdm = ( 720.0_wp * EXP( -0.06_wp * ( pres / pres_0) / sinphi ) - ww ) * sinphi  !< 720 = solar
5726                                                                                    !< constant - 600
5727!
5728!-- Calculate potential diffuse near-infrared radiation
5729    rdn = 0.6_wp * ( 720 - rdm - ww ) * sinphi
5730!
5731!-- Compute visible and near-infrared radiation
5732    rv = MAX( 0.1_wp, rdu + rdv )
5733    rn = MAX( 0.01_wp, rdm + rdn )
5734!
5735!-- Compute ratio between input global radiation (here defined as solar radiation, dirict+diffuse)
5736!-- and total radiation computed here.
5737    ratio = MIN( 0.89_wp, solar_rad / ( rv + rn ) )
5738!
5739!-- Calculate total visible radiation
5740    sv = ratio * rv
5741!
5742!-- Calculate fraction of par in the direct beam
5743    fv = MIN( 0.99_wp, ( 0.9_wp - ratio ) / 0.7_wp )              !< help variable
5744    fv = MAX( 0.01_wp, rdu / rv * ( 1.0_wp - fv**0.6667_wp ) )    !< fraction of par in the direct
5745                                                                  !< beam
5746!
5747!-- Compute direct and diffuse parts of par
5748    par_dir = fv * sv
5749    par_diff = sv - par_dir
5750
5751 END SUBROUTINE par_dir_diff
5752
5753
5754!--------------------------------------------------------------------------------------------------!
5755!> rc_get_vpd: get vapour pressure deficit (kPa)
5756!--------------------------------------------------------------------------------------------------!
5757 SUBROUTINE rc_get_vpd( temp, rh, vpd )
5758
5759!
5760!-- Input/output variables:
5761    REAL(wp), INTENT(IN) ::  rh    !< relative humidity (%)
5762    REAL(wp), INTENT(IN) ::  temp    !< temperature (C)
5763
5764    REAL(wp), INTENT(OUT) ::  vpd    !< vapour pressure deficit (kPa)
5765!
5766!-- Local variables:
5767    REAL(wp) ::  esat
5768!
5769!-- Fit parameters:
5770    REAL(wp), PARAMETER ::  a1 = 6.113718e-01
5771    REAL(wp), PARAMETER ::  a2 = 4.43839e-02
5772    REAL(wp), PARAMETER ::  a3 = 1.39817e-03
5773    REAL(wp), PARAMETER ::  a4 = 2.9295e-05
5774    REAL(wp), PARAMETER ::  a5 = 2.16e-07
5775    REAL(wp), PARAMETER ::  a6 = 3.0e-09
5776!
5777!-- esat is saturation vapour pressure (kPa) at temp(C) following Monteith (1973)
5778    esat = a1 + a2 * temp + a3 * temp**2 + a4 * temp**3 + a5 * temp**4 + a6 * temp**5
5779    vpd  = esat * ( 1 - rh / 100 )
5780
5781 END SUBROUTINE rc_get_vpd
5782
5783
5784!--------------------------------------------------------------------------------------------------!
5785!> rc_gsoil_eff: compute effective soil conductance
5786!--------------------------------------------------------------------------------------------------!
5787 SUBROUTINE rc_gsoil_eff( icmp, lu, sai, ust, nwet, t, gsoil_eff )
5788
5789!
5790!-- Input/output variables:
5791    INTEGER(iwp), INTENT(IN) ::  icmp          !< component index
5792    INTEGER(iwp), INTENT(IN) ::  nwet          !< index for wetness
5793                                               !< nwet = 0 -> dry; nwet = 1 -> wet; nwet = 9 -> snow
5794                                               !< N.B. this routine cannot be called with nwet = 9,
5795                                               !< nwet = 9 should be handled outside this routine.
5796    INTEGER(iwp), INTENT(IN) ::  lu            !< land use type, lu = 1,..., nlu
5797
5798    REAL(wp), INTENT(IN) ::  sai               !< surface area index
5799    REAL(wp), INTENT(IN) ::  t                 !< temperature (C)
5800    REAL(wp), INTENT(IN) ::  ust               !< friction velocity (m/s)
5801
5802    REAL(wp), INTENT(OUT) ::  gsoil_eff        !< effective soil conductance (m/s)
5803!
5804!-- local variables:
5805    REAL(wp) ::  rinc                          !< in canopy resistance  (s/m)
5806    REAL(wp) ::  rsoil_eff                     !< effective soil resistance (s/m)
5807!
5808!-- Soil resistance (numbers matched with lu_classes and component numbers)
5809    !     grs    ara    crp    cnf    dec    wat    urb   oth    des    ice    sav    trf    wai    med    sem
5810    REAL(wp), PARAMETER ::  rsoil(nlu_dep,ncmp) = RESHAPE( (/                                      &
5811         1000.,  200.,  200.,  200.,  200., 2000.,  400., 1000., 2000., 2000., 1000.,  200., 2000.,  200.,  400., &    !< O3
5812         1000., 1000., 1000., 1000., 1000.,   10., 1000., 1000., 1000.,  500., 1000., 1000.,   10., 1000., 1000., &    !< SO2
5813         1000., 1000., 1000., 1000., 1000., 2000., 1000., 1000., 1000., 2000., 1000., 1000., 2000., 1000., 1000., &    !< NO2
5814         -999., -999., -999., -999., -999., 2000., 1000., -999., 2000., 2000., -999., -999., 2000., -999., -999., &    !< NO
5815         100.,  100.,  100.,  100.,  100.,   10.,  100.,  100.,  100., 1000.,  100.,  100.,   10.,  100.,  100.,  &    !< NH3
5816         -999., -999., -999., -999., -999., 2000., 1000., -999., 2000., 2000., -999., -999., 2000., -999., -999., &    !< CO
5817         -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., &    !< NO3
5818         -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., &    !< HNO3
5819         -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., &    !< N2O5
5820         -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999., -999. /),&  !< H2O2
5821         (/nlu_dep,ncmp/) )
5822!
5823!-- For                                          o3    so2   no2     no    nh3     co     no3    hno3   n2o5   h2o2
5824    REAL(wp), PARAMETER ::  rsoil_frozen(ncmp) = (/ 2000., 500., 2000., -999., 1000., -999., -999., -999., -999., -999. /)
5825    REAL(wp), PARAMETER ::  rsoil_wet(ncmp)    = (/ 2000., 10. , 2000., -999., 10.  , -999., -999., -999., -999., -999. /)
5826!
5827!-- Compute in canopy (in crop) resistance:
5828    CALL rc_rinc( lu, sai, ust, rinc )
5829!
5830!-- Check for missing deposition path:
5831    IF ( missing(rinc) )  THEN
5832       rsoil_eff = -9999.0_wp
5833    ELSE
5834!
5835!--    Frozen soil (temperature below 0):
5836       IF ( t < 0.0_wp )  THEN
5837          IF ( missing( rsoil_frozen( icmp ) ) )  THEN
5838             rsoil_eff = -9999.0_wp
5839          ELSE
5840             rsoil_eff = rsoil_frozen( icmp ) + rinc
5841          ENDIF
5842       ELSE
5843!
5844!--       Non-frozen soil; dry:
5845          IF ( nwet == 0 )  THEN
5846             IF ( missing( rsoil( lu, icmp ) ) )  THEN
5847                rsoil_eff = -9999.0_wp
5848             ELSE
5849                rsoil_eff = rsoil( lu, icmp ) + rinc
5850             ENDIF
5851!
5852!--       Non-frozen soil; wet:
5853          ELSEIF ( nwet == 1 )  THEN
5854             IF ( missing( rsoil_wet( icmp ) ) )  THEN
5855                rsoil_eff = -9999.0_wp
5856             ELSE
5857                rsoil_eff = rsoil_wet( icmp ) + rinc
5858             ENDIF
5859          ELSE
5860             message_string = 'nwet can only be 0 or 1'
5861             CALL message( 'rc_gsoil_eff', 'CM0460', 1, 2, 0, 6, 0 )
5862          ENDIF
5863       ENDIF
5864    ENDIF
5865!
5866!-- Compute conductance:
5867    IF ( rsoil_eff > 0.0_wp )  THEN
5868       gsoil_eff = 1.0_wp / rsoil_eff
5869    ELSE
5870       gsoil_eff = 0.0_wp
5871    ENDIF
5872
5873 END SUBROUTINE rc_gsoil_eff
5874
5875
5876!--------------------------------------------------------------------------------------------------!
5877!> rc_rinc: compute in canopy (or in crop) resistance van Pul and Jacobs, 1993, BLM
5878!--------------------------------------------------------------------------------------------------!
5879 SUBROUTINE rc_rinc( lu, sai, ust, rinc )
5880
5881!
5882!-- Input/output variables:
5883    INTEGER(iwp), INTENT(IN) ::  lu          !< land use class, lu = 1, ..., nlu
5884
5885    REAL(wp), INTENT(IN) ::  sai             !< surface area index
5886    REAL(wp), INTENT(IN) ::  ust             !< friction velocity (m/s)
5887
5888    REAL(wp), INTENT(OUT) ::  rinc           !< in canopy resistance (s/m)
5889!
5890!-- b = empirical constant for computation of rinc (in canopy resistance) (= 14 m-1 or -999 if not
5891!--     applicable)
5892!-- h = vegetation height (m)                     gra  ara crop con dec wat   urb   oth   des   ice   sav   trf  wai  med semi
5893    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  b = (/ -999, 14, 14, 14, 14, -999, -999, -999, -999, -999, -999, 14, -999,  &
5894         14, 14 /)
5895    REAL(wp), DIMENSION(nlu_dep), PARAMETER ::  h = (/ -999, 1,  1,  20, 20, -999, -999, -999, -999, -999, -999, 20, -999,  &
5896         1 ,  1 /)
5897!
5898!-- Compute Rinc only for arable land, perm. crops, forest; otherwise Rinc = 0:
5899    IF ( b(lu) > 0.0_wp )  THEN
5900!
5901!--    Check for u* > 0 (otherwise denominator = 0):
5902       IF ( ust > 0.0_wp )  THEN
5903          rinc = b(lu) * h(lu) * sai/ust
5904       ELSE
5905          rinc = 1000.0_wp
5906       ENDIF
5907    ELSE
5908       IF ( lu == ilu_grass  .OR.  lu == ilu_other )  THEN
5909          rinc = -999.0_wp     !< no deposition path for grass, other, and semi-natural
5910       ELSE
5911          rinc = 0.0_wp        !< no in-canopy resistance
5912       ENDIF
5913    ENDIF
5914
5915 END SUBROUTINE rc_rinc
5916
5917
5918!--------------------------------------------------------------------------------------------------!
5919!> rc_rctot: compute total canopy (or surface) resistance Rc
5920!--------------------------------------------------------------------------------------------------!
5921 SUBROUTINE rc_rctot( gstom, gsoil_eff, gw, gc_tot, rc_tot )
5922
5923!
5924!-- Input/output variables:
5925    REAL(wp), INTENT(IN) ::  gsoil_eff     !< effective soil conductance (s/m)
5926    REAL(wp), INTENT(IN) ::  gstom         !< stomatal conductance (s/m)
5927    REAL(wp), INTENT(IN) ::  gw            !< external leaf conductance (s/m)
5928
5929    REAL(wp), INTENT(OUT) ::  gc_tot       !< total canopy conductance (m/s)
5930    REAL(wp), INTENT(OUT) ::  rc_tot       !< total canopy resistance Rc (s/m)
5931!
5932!-- Total conductance:
5933    gc_tot = gstom + gsoil_eff + gw
5934!
5935!-- Total resistance (note: gw can be negative, but no total emission allowed here):
5936    IF ( gc_tot <= 0.0_wp .OR. gw < 0.0_wp )  THEN
5937       rc_tot = -9999.0_wp
5938    ELSE
5939       rc_tot = 1.0_wp / gc_tot
5940    ENDIF
5941
5942 END SUBROUTINE rc_rctot
5943
5944
5945!--------------------------------------------------------------------------------------------------!
5946!> rc_comp_point_rc_eff: calculate the effective resistance Rc
5947!> based on one or more compensation points
5948!--------------------------------------------------------------------------------------------------!
5949!> NH3rc (see depac v3.6 is based on Avero workshop Marc Sutton. p. 173. Sutton 1998 AE 473-480)
5950!>
5951!> Documentation by Ferd Sauter, 2008; see also documentation block in header of depac subroutine.
5952!> FS 2009-01-29: variable names made consistent with DEPAC
5953!> FS 2009-03-04: use total compensation point
5954!>
5955!> C: with total compensation point   ! D: approximation of C
5956!>                                    !    with classical approach
5957!>  zr --------- Catm                 !  zr --------- Catm
5958!>         |                          !         |
5959!>         Ra                         !         Ra
5960!>         |                          !         |
5961!>         Rb                         !         Rb
5962!>         |                          !         |
5963!>  z0 --------- Cc                   !  z0 --------- Cc
5964!>         |                          !         |
5965!>        Rc                          !        Rc_eff
5966!>         |                          !         |
5967!>     --------- Ccomp_tot            !     --------- C=0
5968!>
5969!>
5970!> The effective Rc is defined such that instead of using
5971!>
5972!>   F = -vd*[Catm - Ccomp_tot]                                    (1)
5973!>
5974!> we can use the 'normal' flux formula
5975!>
5976!>   F = -vd'*Catm,                                                (2)
5977!>
5978!> with vd' = 1/(Ra + Rb + Rc')                                    (3)
5979!>
5980!> and Rc' the effective Rc (rc_eff).
5981!>                                                (Catm - Ccomp_tot)
5982!> vd'*Catm = vd*(Catm - Ccomp_tot) <=> vd' = vd* ------------------
5983!>                                                      Catm
5984!>
5985!>                                        (Catm - Ccomp_tot)
5986!> 1/(Ra + Rb + Rc') = (1/Ra + Rb + Rc) * ------------------
5987!>                                              Catm
5988!>
5989!>                                          Catm
5990!> (Ra + Rb + Rc') = (Ra + Rb + Rc) * ------------------
5991!>                                     (Catm - Ccomp_tot)
5992!>
5993!>                              Catm
5994!> Rc' = (Ra + Rb + Rc) * ------------------ - Ra - Rb
5995!>                        (Catm - Ccomp_tot)
5996!>
5997!>                        Catm                           Catm
5998!> Rc' = (Ra + Rb) [------------------ - 1 ] + Rc * ------------------
5999!>                  (Catm - Ccomp_tot)              (Catm - Ccomp_tot)
6000!>
6001!> Rc' = [(Ra + Rb)*Ccomp_tot + Rc*Catm ] / (Catm - Ccomp_tot)
6002!>
6003! -------------------------------------------------------------------------------------------
6004! SUBROUTINE rc_comp_point_rc_eff( ccomp_tot, conc_ijk_ugm3, ra, rb, rc_tot, rc_eff )
6005!
6006!
6007!!-- Input/output variables:
6008!    REAL(wp), INTENT(IN) ::  ccomp_tot     !< total compensation point (weighed average of separate compensation points) (ug/m3)
6009!    REAL(wp), INTENT(IN) ::  conc_ijk_ugm3 !< atmospheric concentration (ug/m3) above Catm
6010!    REAL(wp), INTENT(IN) ::  ra            !< aerodynamic resistance (s/m)
6011!    REAL(wp), INTENT(IN) ::  rb            !< boundary layer resistance (s/m)
6012!    REAL(wp), INTENT(IN) ::  rc_tot        !< total canopy resistance (s/m)
6013!
6014!    REAL(wp), INTENT(OUT) ::  rc_eff       !< effective total canopy resistance (s/m)
6015!
6016!    !
6017!!-- Compute effective resistance:
6018!    IF ( ccomp_tot == 0.0_wp )  THEN
6019!       !
6020!!--    Trace with no compensiation point ( or compensation point equal to zero)
6021!       rc_eff = rc_tot
6022!
6023!    ELSE IF ( ccomp_tot > 0.0_wp  .AND.  ( abs( conc_ijk_ugm3 - ccomp_tot ) < 1.e-8 ) )  THEN
6024!       !
6025!!--   Surface concentration (almost) equal to atmospheric concentration
6026!!--    no exchange between surface and atmosphere, infinite RC --> vd=0
6027!       rc_eff = 9999999999.0_wp
6028!
6029!    ELSE IF ( ccomp_tot > 0.0_wp )  THEN
6030!       !
6031!!--    Compensation point available, calculate effective resistance
6032!       rc_eff = ( ( ra + rb ) * ccomp_tot + rc_tot * conc_ijk_ugm3 ) / ( conc_ijk_ugm3 - ccomp_tot )
6033!
6034!    ELSE
6035!       rc_eff = -999.0_wp
6036!       message_string = 'This should not be possible, check ccomp_tot'
6037!       CALL message( 'rc_comp_point_rc_eff', 'CM0461', 1, 2, 0, 6, 0 )
6038!    ENDIF
6039!
6040!    RETURN
6041!
6042! END SUBROUTINE rc_comp_point_rc_eff
6043
6044
6045!--------------------------------------------------------------------------------------------------!
6046!> missing: check for data that correspond with a missing deposition path this data is represented
6047!>          by -999
6048!--------------------------------------------------------------------------------------------------!
6049 LOGICAL function missing( x )
6050
6051    REAL(wp), INTENT(IN) ::  x
6052
6053!
6054!-- Bandwidth for checking (in)equalities of floats
6055    REAL(wp), PARAMETER :: eps = 1.0e-5
6056
6057    missing = ( ABS( x + 999.0_wp ) <= eps )
6058
6059 END function missing
6060
6061
6062 ELEMENTAL FUNCTION sedimentation_velocity( rhopart, partsize, slipcor, visc ) RESULT( vs )
6063
6064!
6065!-- in/out
6066    REAL(wp), INTENT(IN) ::  rhopart                 !< particle density (kg/m3)
6067    REAL(wp), INTENT(IN) ::  partsize                !< particle size (m)
6068    REAL(wp), INTENT(IN) ::  slipcor                 !< slip correction factor (m)
6069    REAL(wp), INTENT(IN) ::  visc                    !< viscosity
6070
6071    REAL(wp) ::  vs
6072!
6073!-- acceleration of gravity:
6074    REAL(wp), PARAMETER         ::  grav = 9.80665_wp   !< m/s2
6075
6076!-- sedimentation velocity
6077    vs = rhopart * ( partsize**2 ) * grav * slipcor / ( 18.0_wp * visc )
6078
6079 END FUNCTION sedimentation_velocity
6080
6081
6082 !-------------------------------------------------------------------------------------------------!
6083 !> Boundary-layer deposition resistance following Zhang (2001)
6084 !-------------------------------------------------------------------------------------------------!
6085 SUBROUTINE drydepo_aero_zhang_vd( vd, rs, vs1, partsize, slipcor, nwet, tsurf, dens1, viscos1,    &
6086                                   luc, ftop_lu, ustar )
6087
6088!
6089!-- in/out
6090    INTEGER(iwp), INTENT(IN) ::  luc         !< DEPAC LU
6091    INTEGER(iwp), INTENT(IN) ::  nwet        !< 1=rain, 9=snowcover
6092
6093    REAL(wp), INTENT(IN) ::  dens1           !< air density (kg/m3) in lowest layer
6094    REAL(wp), INTENT(IN) ::  ftop_lu         !< atmospheric resistnace Ra
6095    REAL(wp), INTENT(IN) ::  partsize        !< particle diameter (m)
6096    REAL(wp), INTENT(IN) ::  slipcor         !< slip correction factor
6097    REAL(wp), INTENT(IN) ::  tsurf           !< surface temperature (K)
6098    REAL(wp), INTENT(IN) ::  ustar           !< friction velocity u*
6099    REAL(wp), INTENT(IN) ::  viscos1         !< air viscosity in lowest layer
6100    REAL(wp), INTENT(IN) ::  vs1             !< sedimentation velocity in lowest layer
6101
6102    REAL(wp), INTENT(OUT) ::  rs             !< sedimentaion resistance (s/m)
6103    REAL(wp), INTENT(OUT) ::  vd             !< deposition velocity (m/s)
6104!
6105!-- Constants
6106    REAL(wp), PARAMETER ::  grav     = 9.80665_wp             !< acceleration of gravity (m/s2)
6107    REAL(wp), PARAMETER ::  epsilon0 = 3.0_wp
6108    REAL(wp), PARAMETER ::  kb       = 1.38066E-23_wp
6109    REAL(wp), PARAMETER ::  pi       = 3.141592654_wp      !< pi
6110
6111    REAL(wp), PARAMETER :: alfa_lu(nlu_dep) = &
6112         (/ 1.2_wp,  1.2_wp,   1.2_wp,  1.0_wp,  1.0_wp,   100.0_wp, 1.5_wp,  1.2_wp, 50.0_wp, 100.0_wp, &
6113              1.2_wp, 1.0_wp, 100.0_wp, 1.2_wp, 50.0_wp /)
6114    REAL(wp), PARAMETER :: gamma_lu(nlu_dep) = &
6115         (/ 0.54_wp, 0.54_wp,  0.54_wp, 0.56_wp, 0.56_wp,  0.50_wp,  0.56_wp, 0.54_wp, 0.58_wp, 0.50_wp, &
6116              0.54_wp, 0.56_wp, 0.50_wp, 0.54_wp, 0.54_wp /)
6117    REAL(wp), PARAMETER ::A_lu(nlu_dep) = &
6118         (/ 3.0_wp,  3.0_wp,   2.0_wp,  2.0_wp,  7.0_wp, -99.0_wp, 10.0_wp, 3.0_wp, -99.0_wp, -99.0_wp,  &
6119              3.0_wp, 7.0_wp, -99.0_wp, 2.0_wp, -99.0_wp /)
6120!
6121!--   grass  arabl crops conif decid  water  urba  othr  desr  ice   sav  trf   wai  med   sem
6122!
6123!-- local
6124    REAL(wp) ::  diff_part
6125    REAL(wp) ::  ebrown
6126    REAL(wp) ::  eimpac
6127    REAL(wp) ::  einterc
6128    REAL(wp) ::  kinvisc
6129    REAL(wp) ::  reffic
6130    REAL(wp) ::  schmidt
6131    REAL(wp) ::  stokes
6132!
6133!-- Kinetic viscosity & diffusivity
6134    kinvisc = viscos1 / dens1    !< only needed at surface
6135
6136    diff_part = kb * tsurf * slipcor / ( 3.0_wp * pi * viscos1 * partsize )
6137!
6138!-- Schmidt number
6139    schmidt = kinvisc / diff_part
6140!
6141!-- Calculate collection efficiencie E
6142    Ebrown = Schmidt**( -gamma_lu(luc) )    !< Brownian diffusion
6143!
6144!-- Determine Stokes number, interception efficiency and sticking efficiency R (1 = no rebound)
6145    IF ( luc == ilu_ice  .OR.  nwet == 9  .OR.  luc == ilu_water_sea  .OR.                         &
6146         luc == ilu_water_inland )  THEN
6147       stokes = vs1 * ustar**2 / ( grav * kinvisc )
6148       einterc = 0.0_wp
6149       reffic = 1.0_wp
6150    ELSE IF ( luc == ilu_other  .OR.  luc == ilu_desert )  THEN     !<tundra of desert
6151       stokes = vs1 * ustar**2 / ( grav * kinvisc )
6152       einterc = 0.0_wp
6153       reffic = EXP( - stokes**0.5_wp )
6154    ELSE
6155       stokes = vs1 * ustar / ( grav * a_lu(luc) * 1.0E-3_wp )
6156       einterc = 0.5_wp * ( partsize / ( a_lu(luc) * 1.0E-3_wp ) )**2
6157       reffic = EXP( - stokes**0.5_wp )
6158    END IF
6159!
6160!-- When surface is wet all particles do not rebound:
6161    IF ( nwet == 1 )  reffic = 1.0_wp
6162!
6163!-- Determine impaction efficiency:
6164    eimpac = ( stokes / ( alfa_lu(luc) + stokes ) )**2
6165!
6166!-- Sedimentation resistance:
6167    rs = 1.0_wp / ( epsilon0 * MAX( 1.0E-5_wp, ustar ) * ( ebrown + eimpac + einterc ) * reffic )
6168
6169!-- Deposition velocity according to Seinfeld and Pandis (2006; eq 19.7):
6170!--
6171!--              1
6172!--      vd = ------------------ + vs
6173!--           Ra + Rs + Ra*Rs*vs
6174!--
6175!-- where: Rs = Rb (in Seinfeld and Pandis, 2006)
6176
6177    vd = 1.0_wp / ( ftop_lu + rs + ftop_lu * rs * vs1) + vs1
6178
6179
6180 END SUBROUTINE drydepo_aero_zhang_vd
6181
6182
6183 !-------------------------------------------------------------------------------------------------!
6184 !> Compute quasi-laminar boundary layer resistance as a function of landuse and tracer
6185 !> Original EMEP formulation by (Simpson et al, 2003) is used.
6186 !-------------------------------------------------------------------------------------------------!
6187 SUBROUTINE get_rb_cell( is_water, z0h, ustar, diffusivity, rb )
6188
6189!
6190!-- in/out
6191    LOGICAL , INTENT(IN) ::  is_water
6192
6193    REAL(wp), INTENT(IN) ::  diffusivity          !< coefficient of diffusivity
6194    REAL(wp), INTENT(IN) ::  ustar                !< friction velocity
6195    REAL(wp), INTENT(IN) ::  z0h                  !< roughness length for heat
6196
6197    REAL(wp), INTENT(OUT) ::  rb                  !< boundary layer resistance
6198!
6199!-- const
6200    REAL(wp), PARAMETER ::  kappa_stab = 0.35     !< von Karman constant
6201    REAL(wp), PARAMETER ::  thk = 0.19e-4         !< thermal diffusivity of dry air 20 C
6202!
6203!-- Next line is to avoid compiler warning about unused variable
6204    IF ( is_water  .OR.  ( z0h + kappa_stab ) > 0.0_wp )  CONTINUE
6205!
6206!-- Use Simpson et al. (2003)
6207!-- @TODO: Check rb over water calculation, until then leave commented lines
6208!--  IF ( is_water )  THEN
6209!--   org: rb = 1.0_wp / ( kappa_stab * MAX( 0.01_wp, ustar ) ) * LOG( z0h / diffusivity * kappa_stab * MAX( 0.01_wp, ustar ) )
6210!--        rb = 1.0_wp / ( kappa_stab * MAX( 0.1_wp, ustar ) ) *  LOG( z0h / diffusivity * kappa_stab * MAX( 0.1_wp, ustar ) )
6211!--  ELSE
6212    rb = 5.0_wp / MAX( 0.01_wp, ustar ) * ( thk / diffusivity )**0.67_wp
6213!--  END IF
6214
6215 END SUBROUTINE get_rb_cell
6216
6217
6218!--------------------------------------------------------------------------------------------------!
6219!>  Compute water vapor partial pressure (e_w) given specific humidity Q [(kg water)/(kg air)].
6220!>
6221!>  Use that gas law for volume V with temperature T holds for the total mixture as well as the
6222!>  water part:
6223!>
6224!>    R T / V = p_air / n_air = p_water / n_water
6225!>
6226!>  thus:
6227!>
6228!>    p_water = p_air n_water / n_air
6229!>
6230!>  Use:
6231!>    n_air =   m_air   /        xm_air
6232!>            [kg air]  /  [(kg air)/(mole air)]
6233!>  and:
6234!>    n_water =  m_air * Q  /     xm_water
6235!>              [kg water]  /  [(kg water)/(mole water)]
6236!>  thus:
6237!>    p_water = p_air Q / (xm_water/xm_air)
6238!--------------------------------------------------------------------------------------------------!
6239
6240 ELEMENTAL FUNCTION watervaporpartialpressure( q, p ) RESULT( p_w )
6241
6242!
6243!-- in/out
6244    REAL(wp), INTENT(IN) ::  p                      !< air pressure [Pa]
6245    REAL(wp), INTENT(IN) ::  q                      !< specific humidity [(kg water)/(kg air)]
6246
6247    REAL(wp) ::  p_w                                !< water vapor partial pressure [Pa]
6248!
6249!-- Const
6250    REAL(wp), PARAMETER  ::  eps = xm_h2o / xm_air  !< mole mass ratio ~ 0.622
6251!
6252!-- Partial pressure of water vapor:
6253    p_w = p * q / eps
6254
6255 END FUNCTION watervaporpartialpressure
6256
6257
6258!--------------------------------------------------------------------------------------------------!
6259!>  Saturation vapor pressure.
6260!>  From (Stull 1988, eq. 7.5.2d):
6261!>
6262!>      e_sat = p0 exp( 17.67 * (T-273.16) / (T-29.66) )     [Pa]
6263!>
6264!>  where:
6265!>      p0 = 611.2 [Pa]   : reference pressure
6266!>
6267!>  Arguments:
6268!>      T  [K]  : air temperature
6269!>  Result:
6270!>      e_sat_w  [Pa]  : saturation vapor pressure
6271!>
6272!>  References:
6273!>      Roland B. Stull, 1988
6274!>      An introduction to boundary layer meteorology.
6275!--------------------------------------------------------------------------------------------------!
6276 ELEMENTAL FUNCTION saturationvaporpressure( t ) RESULT( e_sat_w )
6277
6278!
6279!-- in/out
6280    REAL(wp), INTENT(IN) ::  t            !< temperature [K]
6281
6282    REAL(wp) ::  e_sat_w                  !< saturation vapor pressure  [Pa]
6283!
6284!-- Const
6285    REAL(wp), PARAMETER ::  p0 = 611.2   !< base pressure [Pa]
6286!
6287!-- Saturation vapor pressure:
6288    e_sat_w = p0 * EXP( 17.67_wp * ( t - 273.16_wp ) / ( t - 29.66_wp ) )    !< [Pa]
6289
6290 END FUNCTION saturationvaporpressure
6291
6292
6293!--------------------------------------------------------------------------------------------------!
6294!>  Relative humidity RH [%] is by definition:
6295!>
6296!>           e_w             water vapor partial pressure
6297!>    Rh = -------- * 100
6298!>         e_sat_w           saturation vapor pressure
6299!--------------------------------------------------------------------------------------------------!
6300
6301 ELEMENTAL FUNCTION relativehumidity_from_specifichumidity( q, t, p ) RESULT( rh )
6302
6303!
6304!-- in/out
6305    REAL(wp), INTENT(IN) ::  p    !< air pressure [Pa]
6306    REAL(wp), INTENT(IN) ::  q    !< specific humidity [(kg water)/(kg air)]
6307    REAL(wp), INTENT(IN) ::  t    !< temperature [K]
6308
6309    REAL(wp) ::  rh               !< relative humidity [%]
6310!
6311!-- Relative humidity:
6312    rh = watervaporpartialpressure( q, p ) / saturationvaporpressure( t ) * 100.0_wp
6313
6314 END FUNCTION relativehumidity_from_specifichumidity
6315
6316
6317 END MODULE chemistry_model_mod
Note: See TracBrowser for help on using the repository browser.