source: palm/trunk/SOURCE/parin.f90 @ 4178

Last change on this file since 4178 was 4176, checked in by oliver.maas, 5 years ago

added recycle_absolute_quantities to initialization_parameters namelist in parin.f90, bugfix: replace PA184 by PA0184 in check_parameters.f90

  • Property svn:keywords set to Id
File size: 47.9 KB
RevLine 
[1682]1!> @file parin.f90
[2000]2!------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]4!
[2000]5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
[1036]9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
[3649]17! Copyright 1997-2019 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[257]20! Current revisions:
[1484]21! -----------------
[2233]22!
[3747]23!
[2233]24! Former revisions:
25! -----------------
26! $Id: parin.f90 4176 2019-08-20 14:10:41Z suehring $
[4176]27! added recycle_absolute_quantities to initialization_parameters namelist
28!
29! 4173 2019-08-20 12:04:06Z gronemeier
[4173]30! add vdi_internal_controls
31!
32! 4131 2019-08-02 11:06:18Z monakurppa
[4131]33! Allocate hom and hom_sum to allow profile output for salsa variables.
34!
35! 4079 2019-07-09 18:04:41Z suehring
[4079]36! +monotonic_limiter_z
37!
38! 4022 2019-06-12 11:52:39Z suehring
[4022]39! Change default top boundary condition for pressure to Neumann in offline
40! nesting case
41!
42! 4017 2019-06-06 12:16:46Z schwenkel
[3987]43! Introduce alternative switch for debug output during timestepping
44!
45! 3885 2019-04-11 11:29:34Z kanani
[3885]46! Changes related to global restructuring of location messages and introduction
47! of additional debug messages
48!
49! 3806 2019-03-21 12:45:50Z raasch
[3806]50! additional check for lateral boundary conditions added
51!
52! 3747 2019-02-16 15:15:23Z gronemeier
[3747]53! removed setting of parameter region
54!
55! 3746 2019-02-16 12:41:27Z gronemeier
[3668]56! Removed most_method
57!
58! 3649 2019-01-02 16:52:21Z suehring
[3649]59! Delete debug-print statements
60!
61! 3646 2018-12-28 17:58:49Z kanani
[3646]62! Bugfix: for restarts, reset data_output_during_spinup to FALSE to enable
63! correct calculation of ntdim in check_parameters
64!
65! 3637 2018-12-20 01:51:36Z knoop
[3637]66! Implementation of the PALM module interface
67!
68! 3569 2018-11-27 17:03:40Z kanani
[3569]69! dom_dwd_user, Schrempf:
70! Remove uv exposure model code, this is now part of biometeorology_mod.
71!
72! 3545 2018-11-21 11:19:41Z gronemeier
[3545]73! remove rans_mode from initialization_parameters
74!
75! 3525 2018-11-14 16:06:14Z kanani
[3525]76! Changes related to clean-up of biometeorology (dom_dwd_user)
77!
78! 3473 2018-10-30 20:50:15Z suehring
[3473]79! Add virtual measurement module
80!
81! 3472 2018-10-30 20:43:50Z suehring
[3469]82! Add indoor model (kanani, srissman, tlang),
83! minor formatting
84!
85! 3467 2018-10-30 19:05:21Z suehring
[3467]86! Implementation of a new aerosol module salsa.
87!
88! 3448 2018-10-29 18:14:31Z kanani
[3448]89! Add biometeorology
90!
91! 3435 2018-10-26 18:25:44Z gronemeier
[3435]92! Add mask_k_over_surface
93!
94! 3421 2018-10-24 18:39:32Z gronemeier
[3421]95! Added module for data output at surfaces
96!
97! 3355 2018-10-16 14:03:34Z knoop
[3347]98! - offline nesting separated from large-scale forcing module
99! - top boundary condition for pressure in offline nesting changed
100!
101! 3343 2018-10-15 10:38:52Z suehring
[3298]102! Introduced reading of date_init to inipar.(Russo)
103! Add extra profiles for chemistry (basit)
104!
105! 3294 2018-10-01 02:37:10Z raasch
[3294]106! changes concerning modularization of ocean option
107!
108! 3274 2018-09-24 15:42:55Z knoop
[3274]109! Modularization of all bulk cloud physics code components
110!
111! 3248 2018-09-14 09:42:06Z sward
[3248]112! Minor formating changes
113!
114! 3246 2018-09-13 15:14:50Z sward
[3246]115! Added error handling for input namelist via parin_fail_message
116!
117! 3240 2018-09-12 12:04:40Z Giersch
[3240]118! A check that controls the number of user-defined profiles on the restart file
119! with the one given for the current run has been added.
120!
121! 3204 2018-08-23 10:49:05Z raasch
[3204]122! additional check for nz
123!
124! 3184 2018-07-27 17:13:09Z suehring
[3184]125! Bugfix, comment setting of chemistry and passive scalar top boundary condition
126! in case of offline nesting
127!
128! 3183 2018-07-27 14:25:55Z suehring
[3183]129! Rename variables and boundary conditions in mesoscale-offline nesting mode
130!
131! 3182 2018-07-27 13:36:03Z suehring
[3159]132! Added multi agent system
133!
134! 3157 2018-07-19 21:08:49Z maronga
[3157]135! added use_free_convection_scaling
136!
137! 3083 2018-06-19 14:03:12Z gronemeier
[3083]138! Added rans_const_c and rans_const_sigma as input parameters (TG)
139!
140! 3065 2018-06-12 07:03:02Z Giersch
[3065]141! New initialization parameters added
142!
143! 3049 2018-05-29 13:52:36Z Giersch
[3049]144! Error messages revised
145!
146! 3045 2018-05-28 07:55:41Z Giersch
[3045]147! z_max_do2d removed, error messages revised
148!
149! 2995 2018-04-19 12:13:16Z Giersch
[2995]150! time_since_reference_point must be calculated/initialized before the first 
151! call of functions related to the radiation model which occur in
152! time_integration_spinup or time_integration
153!
154! 2980 2018-04-17 15:19:27Z suehring
[2980]155! Revise message call
156!
157! 2975 2018-04-16 15:22:20Z suehring
[2975]158! - Informative message when initializing_actions has been changed
159!   to set_constant_profile in child domain
160! - Change location in message call
161!
162! 2967 2018-04-13 11:22:08Z raasch
[2967]163! bugfix: missing parallel cpp-directives added
164!
165! 2941 2018-04-03 11:54:58Z kanani
[2941]166! Fix for spinup in case of restart run
167!
168! 2938 2018-03-27 15:52:42Z suehring
[2938]169! Change initialization in case child domain should be initialized with Inifor.
170!
171! 2936 2018-03-27 14:49:27Z suehring
[2932]172! inipar renamed to initialization_parameters.
173! d3par renamed to runtime_parameters.
174!
175! 2921 2018-03-22 15:05:23Z Giersch
[2921]176! Activation of spinup has been moved from lsm/usm_parin to parin itself
177!
178! 2906 2018-03-19 08:56:40Z Giersch
[2906]179! ENVIRONMENT variables read/write_svf has been added
180!
181! 2894 2018-03-15 09:17:58Z Giersch
[2894]182! read_var_list has been renamed to rrd_global, all module related _parin
183! routines are called before reading the global restart data to overwrite them
184! in case of restart runs
185!
186! 2881 2018-03-13 16:24:40Z suehring
[2881]187! Added flag for switching on/off calculation of soil moisture
188!
189! 2849 2018-03-05 10:49:33Z Giersch
[2849]190! Position of d3par namelist in parameter file is unimportant now
191!
192! 2826 2018-02-21 12:39:28Z Giersch
[2826]193! Bugfix in setting the default boundary conditions for nest domains
[2849]194!
[2826]195! 2817 2018-02-19 16:32:21Z knoop
[2817]196! Preliminary gust module interface implemented
[2849]197!
[2817]198! 2773 2018-01-30 14:12:54Z suehring
[2773]199! Nesting for chemical species implemented
200!
201! 2766 2018-01-22 17:17:47Z kanani
[2766]202! Removed preprocessor directive __chem
203!
204! 2718 2018-01-02 08:49:38Z maronga
[2716]205! Corrected "Former revisions" section
206!
207! 2696 2017-12-14 17:12:51Z kanani
208! Change in file header (GPL part)
[2696]209! Implementation of uv exposure model (FK)
210! Added rans_mode and turbulence_closure to inipar (TG)
211! Implementation of chemistry module
212! Sorting of USE list (FK)
213! Forcing implemented, and initialization with inifor (MS)
214!
215! 2600 2017-11-01 14:11:20Z raasch
[2600]216! some comments added and variables renamed concerning r2599
217!
218! 2599 2017-11-01 13:18:45Z hellstea
[2599]219! The i/o grouping is updated to work correctly also in nested runs.
220!
221! 2575 2017-10-24 09:57:58Z maronga
[2575]222! Renamed phi -> latitude, added longitude
223!
224! 2563 2017-10-19 15:36:10Z Giersch
[2563]225! Changed position where restart files are closed.
226!
227! 2550 2017-10-16 17:12:01Z boeske
[2550]228! Added complex_terrain
229!
230! 2544 2017-10-13 18:09:32Z maronga
[2544]231! Moved day_of_year_init and time_utc_init to inipar.
232!
233! 2397 2017-09-04 16:22:48Z suehring
[2397]234! Enable initialization of 3d model by user in the child domain.
235!
236! 2375 2017-08-29 14:10:28Z schwenkel
[2375]237! Added aerosol initialization for bulk microphysics
238!
239! 2372 2017-08-25 12:37:32Z sward
[2372]240! y_shift added to namelist
241!
242! 2365 2017-08-21 14:59:59Z kanani
[2365]243! Vertical grid nesting: add vnest_start_time to d3par (SadiqHuq)
244!
245! 2339 2017-08-07 13:55:26Z gronemeier
[2339]246! corrected timestamp in header
247!
248! 2338 2017-08-07 12:15:38Z gronemeier
[2338]249! Modularize 1D model
250!
[2339]251! 2310 2017-07-11 09:37:02Z gronemeier
[2310]252! Bugfix: re-arranged call for error messages for ENVPAR file
253!
254! 2304 2017-07-04 14:35:55Z suehring
[2304]255! Bugfix, enable restarts for child domain.
256!
257! 2298 2017-06-29 09:28:18Z raasch
[2298]258! -return_addres, return_username in ENVPAR, -cross_ts_uymax, cross_ts_uymin in
259! d3par
260!
261! 2296 2017-06-28 07:53:56Z maronga
[2296]262! Added parameters for model spinup
263!
264! 2292 2017-06-20 09:51:42Z schwenkel
[2292]265! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
266! includes two more prognostic equations for cloud drop concentration (nc) 
267! and cloud water content (qc).
268!
269! 2267 2017-06-09 09:33:25Z gronemeier
[2267]270! Bugfix: removed skipping of reading namelists in case of omitted d3par
271!
272! 2259 2017-06-08 09:09:11Z gronemeier
[2259]273! Implemented synthetic turbulence generator
274!
275! 2233 2017-05-30 18:08:54Z suehring
[2233]276!
277! 2232 2017-05-30 17:47:52Z suehring
[2232]278! typo corrected
279! +wall_salinityflux
280! +tunnel_height, tunnel_lenght, tunnel_width_x, tunnel_width_y,
281!  tunnel_wall_depth
[1956]282!
[2119]283! 2118 2017-01-17 16:38:49Z raasch
284! -background_communication from inipar
285!
[2051]286! 2050 2016-11-08 15:00:55Z gronemeier
287! Implement turbulent outflow condition
288!
[2038]289! 2037 2016-10-26 11:15:40Z knoop
290! Anelastic approximation implemented
291!
[2036]292! 2035 2016-10-24 15:06:17Z suehring
293! Remove check for npex and npey in nesting case
294!
[2012]295! 2011 2016-09-19 17:29:57Z kanani
296! Added flag lsf_exception to allow explicit enabling of large scale forcing
297! together with buildings on flat terrain.
298!
[2008]299! 2007 2016-08-24 15:47:17Z kanani
300! Added call to urban surface model for reading of &urban_surface_par
301!
[2005]302! 2004 2016-08-24 10:25:59Z suehring
303! Humidity and passive scalar treated separately in nesting mode
304!
[2001]305! 2000 2016-08-20 18:09:15Z knoop
306! Forced header and separation lines into 80 columns
307!
[1993]308! 1992 2016-08-12 15:14:59Z suehring
309! +top_scalarflux
310!
[1961]311! 1960 2016-07-12 16:34:24Z suehring
312! Allocation of s_init
313!
[1958]314! 1957 2016-07-07 10:43:48Z suehring
315! flight module added
316!
[1956]317! 1955 2016-07-01 12:38:59Z hellstea
[1955]318! The parameter intializating_actions is set to 'set_constant_profiles for
319! all nest domains in order to make sure that diagnostic variables are properly
320! initialized for nest domains. Prognostic variables are later initialized by
321! interpolation from the parent domain.
[1957]322!
[1933]323! 1917 2016-05-27 14:28:12Z witha
324! Initial version of purely vertical nesting introduced.
325!
[1917]326! 1914 2016-05-26 14:44:07Z witha
327! Added call to wind turbine model for reading of &wind_turbine_par
328!
[1851]329! 1849 2016-04-08 11:33:18Z hoffmann
330! Adapted for modularization of microphysics
[1852]331!
[1834]332! 1833 2016-04-07 14:23:03Z raasch
333! call of spectra_parin
334!
[1832]335! 1831 2016-04-07 13:15:51Z hoffmann
336! turbulence renamed collision_turbulence, drizzle renamed
337! cloud_water_sedimentation
338! curvature_solution_effects removed
339!
[1827]340! 1826 2016-04-07 12:01:39Z maronga
341! Added call to radiation model for reading of &radiation_par.
342! Added call to plant canopy model for reading of &canopy_par.
343!
[1818]344! 1817 2016-04-06 15:44:20Z maronga
[1826]345! Added call to land surface model for reading of &lsm_par
[1818]346!
[1805]347! 1804 2016-04-05 16:30:18Z maronga
348! Removed code for parameter file check (__check)
349!
[1784]350! 1783 2016-03-06 18:36:17Z raasch
351! +netcdf_deflate in d3par, netcdf module and variable names changed
352!
[1765]353! 1764 2016-02-28 12:45:19Z raasch
[1764]354! cpp-statements for nesting removed, explicit settings of boundary conditions
355! in nest domains,
356! bugfix: npex/npey message moved from inipar to d3par
357! bugfix: check of lateral boundary conditions from check_parameters to here,
358! because they will be already used in init_pegrid and init_grid
[1321]359!
[1763]360! 1762 2016-02-25 12:31:13Z hellstea
361! Introduction of nested domain feature
362!
[1692]363! 1691 2015-10-26 16:17:44Z maronga
364! Added parameter most_method. Renamed prandtl_layer to constant_flux_layer.
365!
[1683]366! 1682 2015-10-07 23:56:08Z knoop
367! Code annotations made doxygen readable
368!
[1561]369! 1560 2015-03-06 10:48:54Z keck
370! +recycling_yshift
371!
[3448]372! 1496 2014-12-02 17:25:50Z maronga
373! Renamed: "radiation -> "cloud_top_radiation"
374!
[1485]375! 1484 2014-10-21 10:53:05Z kanani
376! Changes due to new module structure of the plant canopy model:
377!   canopy-model related parameters moved to new package canopy_par in
378!   subroutine package_parin
379!
[1430]380! 1429 2014-07-15 12:53:45Z knoop
381! +ensemble_member_nr to prepare the random_generator for ensemble runs
382!
[1403]383! 1402 2014-05-09 14:25:13Z raasch
[3313]384! location messages modified, progress_bar_disabled included in envpar-NAMELIST
[1403]385!
[1385]386! 1384 2014-05-02 14:31:06Z raasch
387! location messages added
388!
[1366]389! 1365 2014-04-22 15:03:56Z boeske
390! Usage of large scale forcing enabled:
391! +use_subsidence_tendencies
392!
[1362]393! 1361 2014-04-16 15:17:48Z hoffmann
394! +call_microphysics_at_all_substeps
395!
[1360]396! 1359 2014-04-11 17:15:14Z hoffmann
397! REAL constants provided with KIND-attribute
398!
[1354]399! 1353 2014-04-08 15:21:23Z heinze
400! REAL constants provided with KIND-attribute
401!
[1329]402! 1327 2014-03-21 11:00:16Z raasch
403! -data_output_format, do3d_compress, do3d_comp_prec
404!
[1321]405! 1320 2014-03-20 08:40:49Z raasch
[1320]406! ONLY-attribute added to USE-statements,
407! kind-parameters added to all INTEGER and REAL declaration statements,
408! kinds are defined in new module kinds,
409! old module precision_kind is removed,
410! revision history before 2012 removed,
411! comment fields (!:) to be used for variable explanations added to
412! all variable declaration statements
[1054]413!
[1319]414! 1318 2014-03-17 13:35:16Z raasch
415! +cpu_log_barrierwait in d3par
416!
[1302]417! 1301 2014-03-06 13:29:46Z heinze
418! +large_scale_subsidence
419!
[1242]420! 1241 2013-10-30 11:36:58Z heinze
421! +nudging
422! +large_scale_forcing
423!
[1217]424! 1216 2013-08-26 09:31:42Z raasch
425! +transpose_compute_overlap in inipar
426!
[1196]427! 1195 2013-07-01 12:27:57Z heinze
428! Bugfix: allocate ref_state
429!
[1182]430! 1179 2013-06-14 05:57:58Z raasch
431! +reference_state in inipar
432!
[1160]433! 1159 2013-05-21 11:58:22Z fricke
434! +use_cmax
435!
[1132]436! 1128 2013-04-12 06:19:32Z raasch
437! +background_communication in inipar
438!
[1116]439! 1115 2013-03-26 18:16:16Z hoffmann
440! unused variables removed
441!
[1093]442! 1092 2013-02-02 11:24:22Z raasch
443! unused variables removed
444!
[1066]445! 1065 2012-11-22 17:42:36Z hoffmann
446! +nc, c_sedimentation, limiter_sedimentation, turbulence
447! -mu_constant, mu_constant_value
448!
[1054]449! 1053 2012-11-13 17:11:03Z hoffmann
[1053]450! necessary expansions according to the two new prognostic equations (nr, qr)
451! of the two-moment cloud physics scheme and steering parameters:
452! +*_init, *_surface, *_surface_initial_change, *_vertical_gradient,
453! +*_vertical_gradient_level, surface_waterflux_*,
454! +cloud_scheme, drizzle, mu_constant, mu_constant_value, ventilation_effect
[601]455!
[1037]456! 1036 2012-10-22 13:43:42Z raasch
457! code put under GPL (PALM 3.9)
458!
[1017]459! 1015 2012-09-27 09:23:24Z raasch
460! -adjust_mixing_length
461!
[1004]462! 1003 2012-09-14 14:35:53Z raasch
463! -grid_matching
464!
[1002]465! 1001 2012-09-13 14:08:46Z raasch
466! -cut_spline_overshoot, long_filter_factor, overshoot_limit_*, ups_limit_*
467!
[997]468! 996 2012-09-07 10:41:47Z raasch
469! -use_prior_plot1d_parameters
470!
[979]471! 978 2012-08-09 08:28:32Z fricke
472! -km_damp_max, outflow_damping_width
473! +pt_damping_factor, pt_damping_width
474! +z0h_factor
475!
[965]476! 964 2012-07-26 09:14:24Z raasch
477! -cross_normalized_x, cross_normalized_y, cross_xtext, z_max_do1d,
478! z_max_do1d_normalized
479!
[941]480! 940 2012-07-09 14:31:00Z raasch
481! +neutral in inipar
482!
[928]483! 927 2012-06-06 19:15:04Z raasch
484! +masking_method in inipar
485!
[826]486! 824 2012-02-17 09:09:57Z raasch
487! +curvature_solution_effects in inipar
488!
[810]489! 809 2012-01-30 13:32:58Z maronga
490! Bugfix: replaced .AND. and .NOT. with && and ! in the preprocessor directives
491!
[808]492! 807 2012-01-25 11:53:51Z maronga
493! New cpp directive "__check" implemented which is used by check_namelist_files
494!
[1]495! Revision 1.1  1997/07/24 11:22:50  raasch
496! Initial revision
497!
498!
499! Description:
500! ------------
[1682]501!> This subroutine reads variables controling the run from the NAMELIST files
[3298]502!>
503!> @todo: Revise max_pr_cs (profiles for chemistry)
[1]504!------------------------------------------------------------------------------!
[1682]505 SUBROUTINE parin
506 
[1]507
[1320]508    USE arrays_3d,                                                             &
[3274]509        ONLY:  pt_init, q_init, ref_state, s_init, sa_init,                    &
[2696]510               ug, u_init, v_init, vg
[1320]511
[2696]512    USE chem_modules
[1320]513
[1762]514    USE control_parameters
[1320]515
516    USE cpulog,                                                                &
517        ONLY:  cpu_log_barrierwait
518
[2696]519    USE date_and_time_mod,                                                     &
[3298]520        ONLY:  date_init, day_of_year_init, time_utc_init
[2696]521
[1320]522    USE grid_variables,                                                        &
523        ONLY:  dx, dy
524
525    USE indices,                                                               &
526        ONLY:  nx, ny, nz
527
[1764]528    USE kinds
529
[2338]530    USE model_1d_mod,                                                          &
[1320]531        ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
532
[3637]533    USE module_interface,                                                      &
534        ONLY:  module_interface_parin
[3159]535
[1783]536    USE netcdf_interface,                                                      &
537        ONLY:  netcdf_data_format, netcdf_deflate, netcdf_precision
538
[2696]539    USE pegrid
[3448]540
[1764]541    USE pmc_interface,                                                         &
[1933]542        ONLY:  nested_run, nesting_mode
[1764]543
[1320]544    USE profil_parameter,                                                      &
[2298]545        ONLY:  cross_profiles, profile_columns, profile_rows
[1320]546
[1402]547    USE progress_bar,                                                          &
[3313]548        ONLY :  progress_bar_disabled
[1402]549
[2894]550    USE read_restart_data_mod,                                                 &
[3637]551        ONLY:  rrd_global
[2894]552
[1320]553    USE statistics,                                                            &
[3746]554        ONLY:  hom, hom_sum, pr_palm, statistic_regions
[1320]555
[3083]556    USE turbulence_closure_mod,                                                &
557        ONLY:  rans_const_c, rans_const_sigma
558
[2365]559    USE vertical_nesting_mod,                                                  &
560        ONLY:  vnest_start_time
[1914]561
[2696]562
[1]563    IMPLICIT NONE
564
[2849]565    CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
566
[2600]567    INTEGER(iwp) ::  global_id      !< process id with respect to MPI_COMM_WORLD
568    INTEGER(iwp) ::  global_procs   !< # of procs with respect to MPI_COMM_WORLD
569    INTEGER(iwp) ::  i              !<
570    INTEGER(iwp) ::  ioerr          !< error flag for open/read/write
[1]571
[3274]572    NAMELIST /inipar/  alpha_surface, approximation, bc_e_b,     &
[2375]573                       bc_lr, bc_ns, bc_p_b, bc_p_t, bc_pt_b, bc_pt_t, bc_q_b, &
[3294]574             bc_q_t,bc_s_b, bc_s_t, bc_uv_b, bc_uv_t,                 &
575             building_height, building_length_x,          &
[1429]576             building_length_y, building_wall_left, building_wall_south,       &
[2881]577             calc_soil_moisture_during_spinup,                                 &
[3274]578             call_psolver_at_all_substeps,  &
[1484]579             canyon_height,                                                    &
[1429]580             canyon_width_x, canyon_width_y, canyon_wall_left,                 &
[3274]581             canyon_wall_south, cfl_factor, cloud_droplets,   &
582             collective_wait, complex_terrain,           &
[2550]583             conserve_volume_flow,                                             &
[1691]584             conserve_volume_flow_mode, constant_flux_layer,                   &
[3274]585             coupling_start_time,             &
[1831]586             cycle_mg, damp_level_1d,                                          &
[2296]587             data_output_during_spinup,                                        &
[3298]588             date_init,                                                        &
[2544]589             day_of_year_init,                                                 &
[1429]590             dissipation_1d,                                                   &
[3274]591             dp_external, dp_level_b, dp_smooth, dpdxy,    &
[2296]592             dt, dt_pr_1d, dt_run_control_1d, dt_spinup, dx, dy, dz, dz_max,   &
[3065]593             dz_stretch_factor, dz_stretch_level, dz_stretch_level_start,      &
594             dz_stretch_level_end, end_time_1d, ensemble_member_nr, e_init,    &
[3182]595             e_min, fft_method, flux_input_mode, flux_output_mode,             &
[2037]596             galilei_transformation, humidity,                                 &
[1429]597             inflow_damping_height, inflow_damping_width,                      &
598             inflow_disturbance_begin, inflow_disturbance_end,                 &
[1484]599             initializing_actions, km_constant,                                &
[2575]600             large_scale_forcing, large_scale_subsidence, latitude,            &
[3274]601             longitude,                                 &
[2011]602             loop_optimization, lsf_exception, masking_method, mg_cycles,      &
[1429]603             mg_switch_to_pe0_level, mixing_length_1d, momentum_advec,         &
[4079]604             monotonic_limiter_z,                                              &
[3182]605             netcdf_precision, neutral, ngsrb,                                 &
[3294]606             nsor, nsor_ini, nudging, nx, ny, nz, ocean_mode, omega,           &
607             omega_sor, outflow_source_plane, passive_scalar,                  &
[3274]608             prandtl_number, psolver, pt_damping_factor,        &
[1429]609             pt_damping_width, pt_reference, pt_surface,                       &
610             pt_surface_initial_change, pt_vertical_gradient,                  &
611             pt_vertical_gradient_level, q_surface, q_surface_initial_change,  &
612             q_vertical_gradient, q_vertical_gradient_level,                   &
[3083]613             random_generator, random_heatflux, rans_const_c, rans_const_sigma,&
[1560]614             rayleigh_damping_factor, rayleigh_damping_height,                 &
615             recycling_width, recycling_yshift,                                &
[1429]616             reference_state, residual_limit,                                  &
[3294]617             roughness_length,                                                 &
618             scalar_advec,   &
[3274]619             scalar_rayleigh_damping,                              &
[2296]620             spinup_time, spinup_pt_amplitude, spinup_pt_mean,                 &
[1429]621             statistic_regions, subs_vertical_gradient,                        &
[785]622             subs_vertical_gradient_level, surface_heatflux, surface_pressure, &
[1429]623             surface_scalarflux, surface_waterflux,                            &
624             s_surface, s_surface_initial_change, s_vertical_gradient,         &
[2544]625             s_vertical_gradient_level, time_utc_init, timestep_scheme,        &
[1429]626             topography, topography_grid_convention, top_heatflux,             &
[3294]627             top_momentumflux_u, top_momentumflux_v,                           &
[2232]628             top_scalarflux, transpose_compute_overlap,                        &
629             tunnel_height, tunnel_length, tunnel_width_x, tunnel_width_y,     &
[2696]630             tunnel_wall_depth, turbulence_closure,                            &
[2232]631             turbulent_inflow, turbulent_outflow,                              &
[1429]632             use_subsidence_tendencies, ug_surface, ug_vertical_gradient,      &
[3157]633             use_free_convection_scaling,                                      &
[1429]634             ug_vertical_gradient_level, use_surface_fluxes, use_cmax,         &
635             use_top_fluxes, use_ug_for_galilei_tr, use_upstream_for_tke,      &
[4173]636             uv_heights, u_bulk, u_profile, vdi_checks, vg_surface,            &
637             vg_vertical_gradient,  &
[3274]638             vg_vertical_gradient_level, v_bulk, v_profile,&
[1429]639             wall_adjustment, wall_heatflux, wall_humidityflux,                &
[3294]640             wall_scalarflux, y_shift, zeta_max, zeta_min,  &
[2372]641             z0h_factor
[2932]642
[3294]643    NAMELIST /initialization_parameters/  alpha_surface,                       &
[2932]644             approximation, bc_e_b,                                            &
645             bc_lr, bc_ns, bc_p_b, bc_p_t, bc_pt_b, bc_pt_t, bc_q_b,           &
[3294]646             bc_q_t,bc_s_b, bc_s_t, bc_uv_b, bc_uv_t,                          &
647             building_height, building_length_x,                               &
[2932]648             building_length_y, building_wall_left, building_wall_south,       &
649             calc_soil_moisture_during_spinup,                                 &
[3294]650             call_psolver_at_all_substeps,                                     &
[2932]651             canyon_height,                                                    &
652             canyon_width_x, canyon_width_y, canyon_wall_left,                 &
[3294]653             canyon_wall_south, cfl_factor, cloud_droplets,                    &
654             collective_wait, complex_terrain,                                 &
[2932]655             conserve_volume_flow,                                             &
656             conserve_volume_flow_mode, constant_flux_layer,                   &
[3294]657             coupling_start_time,                                              &
[2932]658             cycle_mg, damp_level_1d,                                          &
659             data_output_during_spinup,                                        &
[3298]660             date_init,                                                        &
[2932]661             day_of_year_init,                                                 &
662             dissipation_1d,                                                   &
[3294]663             dp_external, dp_level_b, dp_smooth, dpdxy,                        &
[2932]664             dt, dt_pr_1d, dt_run_control_1d, dt_spinup, dx, dy, dz, dz_max,   &
[3065]665             dz_stretch_factor, dz_stretch_level, dz_stretch_level_start,      &
666             dz_stretch_level_end, end_time_1d, ensemble_member_nr, e_init,    &
[3182]667             e_min, fft_method, flux_input_mode, flux_output_mode,             &
[2932]668             galilei_transformation, humidity,                                 &
669             inflow_damping_height, inflow_damping_width,                      &
670             inflow_disturbance_begin, inflow_disturbance_end,                 &
671             initializing_actions, km_constant,                                &
672             large_scale_forcing, large_scale_subsidence, latitude,            &
[3294]673             longitude,                                                        &
[2932]674             loop_optimization, lsf_exception, masking_method, mg_cycles,      &
675             mg_switch_to_pe0_level, mixing_length_1d, momentum_advec,         &
[4079]676             monotonic_limiter_z,                                              &
[3182]677             netcdf_precision, neutral, ngsrb,                                 &
[3294]678             nsor, nsor_ini, nudging, nx, ny, nz, ocean_mode, omega,           &
679             omega_sor, outflow_source_plane, passive_scalar,                  &
680             prandtl_number, psolver, pt_damping_factor,                       &
[2932]681             pt_damping_width, pt_reference, pt_surface,                       &
682             pt_surface_initial_change, pt_vertical_gradient,                  &
683             pt_vertical_gradient_level, q_surface, q_surface_initial_change,  &
684             q_vertical_gradient, q_vertical_gradient_level,                   &
[3083]685             random_generator, random_heatflux, rans_const_c, rans_const_sigma,&
[2932]686             rayleigh_damping_factor, rayleigh_damping_height,                 &
[4176]687             recycling_width, recycling_yshift, recycle_absolute_quantities,   &
[2932]688             reference_state, residual_limit,                                  &
[3294]689             roughness_length, scalar_advec,                                   &
690             scalar_rayleigh_damping,                                          &
[2932]691             spinup_time, spinup_pt_amplitude, spinup_pt_mean,                 &
692             statistic_regions, subs_vertical_gradient,                        &
693             subs_vertical_gradient_level, surface_heatflux, surface_pressure, &
694             surface_scalarflux, surface_waterflux,                            &
695             s_surface, s_surface_initial_change, s_vertical_gradient,         &
696             s_vertical_gradient_level, time_utc_init, timestep_scheme,        &
697             topography, topography_grid_convention, top_heatflux,             &
[3294]698             top_momentumflux_u, top_momentumflux_v,                           &
[2932]699             top_scalarflux, transpose_compute_overlap,                        &
700             tunnel_height, tunnel_length, tunnel_width_x, tunnel_width_y,     &
701             tunnel_wall_depth, turbulence_closure,                            &
702             turbulent_inflow, turbulent_outflow,                              &
703             use_subsidence_tendencies, ug_surface, ug_vertical_gradient,      &
704             ug_vertical_gradient_level, use_surface_fluxes, use_cmax,         &
705             use_top_fluxes, use_ug_for_galilei_tr, use_upstream_for_tke,      &
[3157]706             use_free_convection_scaling,                                      &
[4173]707             uv_heights, u_bulk, u_profile, vdi_checks,                        &
708             vg_surface, vg_vertical_gradient,  &
[3294]709             vg_vertical_gradient_level, v_bulk, v_profile,                    &
[2932]710             wall_adjustment, wall_heatflux, wall_humidityflux,                &
[3294]711             wall_scalarflux, y_shift, zeta_max, zeta_min, z0h_factor
[2932]712             
[1429]713    NAMELIST /d3par/  averaging_interval, averaging_interval_pr,               &
714             cpu_log_barrierwait, create_disturbances,                         &
[2298]715             cross_profiles, data_output, data_output_masks,                   &
[3885]716             data_output_pr, data_output_2d_on_each_pe,                        &
717             debug_output,                                                     &
[3987]718             debug_output_timestep,                                            &
[3885]719             disturbance_amplitude,                                            &
[1429]720             disturbance_energy_limit, disturbance_level_b,                    &
[1327]721             disturbance_level_t, do2d_at_begin, do3d_at_begin,                &
[1429]722             dt, dt_averaging_input, dt_averaging_input_pr,                    &
723             dt_coupling, dt_data_output, dt_data_output_av, dt_disturb,       &
724             dt_domask, dt_dopr, dt_dopr_listing, dt_dots, dt_do2d_xy,         &
725             dt_do2d_xz, dt_do2d_yz, dt_do3d, dt_max, dt_restart,              &
[3435]726             dt_run_control,end_time, force_print_header, mask_k_over_surface, &
[3448]727             mask_scale_x,                                                     &
[1429]728             mask_scale_y, mask_scale_z, mask_x, mask_y, mask_z, mask_x_loop,  &
[1783]729             mask_y_loop, mask_z_loop, netcdf_data_format, netcdf_deflate,     &
730             normalizing_region, npex, npey, nz_do3d,                          &
[3274]731             profile_columns, profile_rows,     &
[1783]732             restart_time, section_xy, section_xz, section_yz,                 &
733             skip_time_data_output, skip_time_data_output_av, skip_time_dopr,  &
734             skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,          &
735             skip_time_do3d, skip_time_domask, synchronous_exchange,           &
[3045]736             termination_time_needed, vnest_start_time
[1]737
[2932]738    NAMELIST /runtime_parameters/  averaging_interval, averaging_interval_pr,  &
739             cpu_log_barrierwait, create_disturbances,                         &
740             cross_profiles, data_output, data_output_masks,                   &
[3885]741             data_output_pr, data_output_2d_on_each_pe,                        &
742             debug_output,                                                     &
[3987]743             debug_output_timestep,                                            &
[3885]744             disturbance_amplitude,                                            &
[2932]745             disturbance_energy_limit, disturbance_level_b,                    &
746             disturbance_level_t, do2d_at_begin, do3d_at_begin,                &
747             dt, dt_averaging_input, dt_averaging_input_pr,                    &
748             dt_coupling, dt_data_output, dt_data_output_av, dt_disturb,       &
749             dt_domask, dt_dopr, dt_dopr_listing, dt_dots, dt_do2d_xy,         &
750             dt_do2d_xz, dt_do2d_yz, dt_do3d, dt_max, dt_restart,              &
[3435]751             dt_run_control,end_time, force_print_header, mask_k_over_surface, &
[3448]752             mask_scale_x,                                                     &
[2932]753             mask_scale_y, mask_scale_z, mask_x, mask_y, mask_z, mask_x_loop,  &
754             mask_y_loop, mask_z_loop, netcdf_data_format, netcdf_deflate,     &
755             normalizing_region, npex, npey, nz_do3d,                          &
[3274]756             profile_columns, profile_rows,     &
[2932]757             restart_time, section_xy, section_xz, section_yz,                 &
758             skip_time_data_output, skip_time_data_output_av, skip_time_dopr,  &
759             skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,          &
760             skip_time_do3d, skip_time_domask, synchronous_exchange,           &
[3045]761             termination_time_needed, vnest_start_time
[1]762
[4017]763    NAMELIST /envpar/  progress_bar_disabled, host,                            &
[1429]764                       maximum_cpu_time_allowed, maximum_parallel_io_streams,  &
[2906]765                       read_svf, revision, run_identifier, tasks_per_node,     &
766                       write_binary, write_svf
[1]767
768!
[759]769!-- First read values of environment variables (this NAMELIST file is
[3045]770!-- generated by palmrun)
[3885]771    CALL location_message( 'reading environment parameters from ENVPAR', 'start' )
[2310]772
773    OPEN ( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', IOSTAT=ioerr )
774
775    IF ( ioerr /= 0 )  THEN
776       message_string = 'local file ENVPAR not found' //                       &
[3046]777                        '&some variables for steering may not be properly set'
[2310]778       CALL message( 'parin', 'PA0276', 0, 1, 0, 6, 0 )
779    ELSE
780       READ ( 90, envpar, IOSTAT=ioerr )
781       IF ( ioerr < 0 )  THEN
782          message_string = 'no envpar-NAMELIST found in local file '  //       &
[3046]783                           'ENVPAR& or some variables for steering may '  //   &
[2310]784                           'not be properly set'
785          CALL message( 'parin', 'PA0278', 0, 1, 0, 6, 0 )
786       ELSEIF ( ioerr > 0 )  THEN
787          message_string = 'errors in local file ENVPAR' //                    &
[3046]788                           '&some variables for steering may not be properly set'
[2310]789          CALL message( 'parin', 'PA0277', 0, 1, 0, 6, 0 )
790       ENDIF
791       CLOSE ( 90 )
792    ENDIF
793
[3885]794    CALL location_message( 'reading environment parameters from ENVPAR', 'finished' )
[1]795!
[759]796!-- Calculate the number of groups into which parallel I/O is split.
797!-- The default for files which are opened by all PEs (or where each
798!-- PE opens his own independent file) is, that all PEs are doing input/output
799!-- in parallel at the same time. This might cause performance or even more
800!-- severe problems depending on the configuration of the underlying file
801!-- system.
[2600]802!-- Calculation of the number of blocks and the I/O group must be based on all
803!-- PEs involved in this run. Since myid and numprocs are related to the
804!-- comm2d communicator, which gives only a subset of all PEs in case of
805!-- nested runs, that information must be inquired again from the global
806!-- communicator.
[759]807!-- First, set the default:
[2967]808#if defined( __parallel )
[2600]809    CALL MPI_COMM_RANK( MPI_COMM_WORLD, global_id, ierr )
810    CALL MPI_COMM_SIZE( MPI_COMM_WORLD, global_procs, ierr )
[2967]811#else
812    global_id    = 0
813    global_procs = 1
814#endif
[1429]815    IF ( maximum_parallel_io_streams == -1  .OR.                               &
[2600]816         maximum_parallel_io_streams > global_procs )  THEN
817       maximum_parallel_io_streams = global_procs
[759]818    ENDIF
819!
820!-- Now calculate the number of io_blocks and the io_group to which the
821!-- respective PE belongs. I/O of the groups is done in serial, but in parallel
822!-- for all PEs belonging to the same group.
[2600]823    io_blocks = global_procs / maximum_parallel_io_streams
824    io_group  = MOD( global_id+1, io_blocks )
[2599]825   
[3885]826    CALL location_message( 'reading NAMELIST parameters from PARIN', 'start' )
[759]827!
828!-- Data is read in parallel by groups of PEs
829    DO  i = 0, io_blocks-1
830       IF ( i == io_group )  THEN
[559]831
[1]832!
[759]833!--       Open the NAMELIST-file which is send with this job
834          CALL check_open( 11 )
[559]835
[1]836!
[759]837!--       Read the control parameters for initialization.
[996]838!--       The namelist "inipar" must be provided in the NAMELIST-file.
[2932]839          READ ( 11, initialization_parameters, ERR=10, END=11 )
[3246]840          GOTO 14
841         
842 10       BACKSPACE( 11 )
[3248]843          READ( 11 , '(A)') line
844          CALL parin_fail_message( 'initialization_parameters', line )
[807]845
[2932]846 11       REWIND ( 11 )
[3246]847          READ ( 11, inipar, ERR=12, END=13 )
[2932]848 
[3046]849          message_string = 'namelist inipar is deprecated and will be ' //    &
850                          'removed in near future. & Please use namelist ' // &
851                          'initialization_parameters instead'
[3045]852          CALL message( 'parin', 'PA0017', 0, 1, 0, 6, 0 )
[2932]853 
[3246]854          GOTO 14
[2932]855 
[3246]856 12       BACKSPACE( 11 )
[3248]857          READ( 11 , '(A)') line
858          CALL parin_fail_message( 'inipar', line )
[3246]859
860 13       message_string = 'no initialization_parameters-namelist found'
[759]861          CALL message( 'parin', 'PA0272', 1, 2, 0, 6, 0 )
862
[146]863!
[2894]864!--       Try to read runtime parameters given by the user for this run
[2932]865!--       (namelist "runtime_parameters"). The namelist "runtime_parmeters"   
866!--       can be omitted. In that case default values are used for the         
867!--       parameters.
[3246]868 14       line = ' '
[2894]869
870          REWIND ( 11 )
871          line = ' '
[3248]872          DO WHILE ( INDEX( line, '&runtime_parameters' ) == 0 )
[3246]873             READ ( 11, '(A)', END=16 )  line
[2894]874          ENDDO
875          BACKSPACE ( 11 )
876
877!
878!--       Read namelist
[3246]879          READ ( 11, runtime_parameters, ERR = 15 )
880          GOTO 18
[2932]881
[3246]882 15       BACKSPACE( 11 )
[3248]883          READ( 11 , '(A)') line
884          CALL parin_fail_message( 'runtime_parameters', line )
[3246]885
886 16       REWIND ( 11 )
[2932]887          line = ' '
[3248]888          DO WHILE ( INDEX( line, '&d3par' ) == 0 )
[3246]889             READ ( 11, '(A)', END=18 )  line
[2932]890          ENDDO
891          BACKSPACE ( 11 )
[3246]892
893!
[2932]894!--       Read namelist
[3246]895          READ ( 11, d3par, ERR = 17, END = 18 )
896
[2932]897          message_string = 'namelist d3par is deprecated and will be ' //      &
[3046]898                          'removed in near future. &Please use namelist ' //   &
[2932]899                          'runtime_parameters instead'
900          CALL message( 'parin', 'PA0487', 0, 1, 0, 6, 0 )
[2894]901
[3246]902          GOTO 18
903
904 17       BACKSPACE( 11 )
[3248]905          READ( 11 , '(A)') line
906          CALL parin_fail_message( 'd3par', line )
[3246]907
908 18       CONTINUE
909
[2894]910!
[3294]911!--       Check for module namelists and read them
[3637]912          CALL module_interface_parin
[2894]913
914!
[759]915!--       If required, read control parameters from restart file (produced by
916!--       a prior run). All PEs are reading from file created by PE0 (see
917!--       check_open)
[2894]918          IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
[87]919
[2894]920             CALL rrd_global
[1]921!
[759]922!--          Increment the run count
923             runnr = runnr + 1
[3240]924!
925!--          In case of a restart run, the number of user-defined profiles on
926!--          the restart file (already stored in max_pr_user) has to match the
927!--          one given for the current run. max_pr_user_tmp is calculated in
928!--          user_parin and max_pr_user is read in via rrd_global.
929             IF ( max_pr_user /= max_pr_user_tmp )  THEN
930                WRITE( message_string, * ) 'the number of user-defined ',      &
931                      'profiles given in data_output_pr (', max_pr_user_tmp,   &
932                      ') does not match the one ',                             &
933                      'found in the restart file (', max_pr_user, ')'
934                CALL message( 'user_parin', 'UI0009', 1, 2, 0, 6, 0 )
935             ENDIF
936          ELSE
937             max_pr_user = max_pr_user_tmp
[759]938          ENDIF
[87]939!
[2921]940!--       Activate spinup
941          IF ( land_surface .OR. urban_surface )  THEN
942             IF ( spinup_time > 0.0_wp )  THEN
943                coupling_start_time = spinup_time
[2995]944                time_since_reference_point = simulated_time - coupling_start_time
[2921]945                IF ( spinup_pt_mean == 9999999.9_wp )  THEN
946                   spinup_pt_mean = pt_surface
947                ENDIF
948                end_time = end_time + spinup_time
[3646]949                IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
[2941]950                   spinup = .TRUE.
[3646]951                ELSEIF (        TRIM( initializing_actions ) == 'read_restart_data'      &
952                         .AND.  time_since_reference_point > 0.0_wp )  THEN
953                   data_output_during_spinup = .FALSE.  !< required for correct ntdim calculation
954                                                        !< in check_parameters for restart run
955                ENDIF
[2921]956             ENDIF
957          ENDIF
958
959!
[1933]960!--       In case of nested runs, explicitly set nesting boundary conditions.
[2826]961!--       This will overwrite the user settings and basic defaults.
962!--       bc_lr and bc_ns always need to be cyclic for vertical nesting.
963          IF ( nested_run )  THEN
964             IF ( nesting_mode == 'vertical' )  THEN
965                IF (bc_lr /= 'cyclic' .OR. bc_ns /= 'cyclic' )  THEN
966                   WRITE ( message_string, *) 'bc_lr and bc_ns were set to ,', &
967                        'cyclic for vertical nesting'
968                   CALL message( 'parin', 'PA0428', 0, 0, 0, 6, 0 )
969                   bc_lr   = 'cyclic'
970                   bc_ns   = 'cyclic'
971                ENDIF
[3182]972                IF ( child_domain )  THEN
[2826]973                   bc_uv_t  = 'nested'
974                   bc_pt_t  = 'nested'
975                   bc_q_t   = 'nested'
976                   bc_s_t   = 'nested'
977                   bc_cs_t  = 'nested'
978                   bc_p_t   = 'neumann' 
979                ENDIF
[1933]980!
[2826]981!--          For other nesting modes only set boundary conditions for
982!--          nested domains.
983             ELSE
[3182]984                IF ( child_domain )  THEN
[2826]985                   bc_lr    = 'nested'
986                   bc_ns    = 'nested'
987                   bc_uv_t  = 'nested'
988                   bc_pt_t  = 'nested'
989                   bc_q_t   = 'nested'
990                   bc_s_t   = 'nested'
991                   bc_cs_t  = 'nested'
992                   bc_p_t   = 'neumann'
993                ENDIF
[1933]994             ENDIF
[1764]995          ENDIF
[3182]996!
997!--       Set boundary conditions also in case the model is offline-nested in
998!--       larger-scale models.
999          IF ( nesting_offline )  THEN
1000             bc_lr    = 'nesting_offline'
1001             bc_ns    = 'nesting_offline'
1002             bc_uv_t  = 'nesting_offline'
1003             bc_pt_t  = 'nesting_offline'
1004             bc_q_t   = 'nesting_offline'
[4022]1005           !  bc_s_t   = 'nesting_offline'  ! scalar boundary condition is not clear yet
[3184]1006           !  bc_cs_t  = 'nesting_offline'  ! same for chemical species
[4022]1007             bc_p_t   = 'neumann'
[2696]1008          ENDIF
1009
[1955]1010!         
1011!--       In case of nested runs, make sure that initializing_actions =
1012!--       'set_constant_profiles' even though the constant-profiles
1013!--       initializations for the prognostic variables will be overwritten
1014!--       by pmci_child_initialize and pmci_parent_initialize. This is,
1015!--       however, important e.g. to make sure that diagnostic variables
[2397]1016!--       are set properly. An exception is made in case of restart runs and
1017!--       if user decides to do everything by its own.
[3182]1018          IF ( child_domain  .AND.  .NOT. (                                    &
[2980]1019               TRIM( initializing_actions ) == 'read_restart_data'      .OR.   &
1020               TRIM( initializing_actions ) == 'set_constant_profiles'  .OR.   &
[2938]1021               TRIM( initializing_actions ) == 'by_user' ) )  THEN
[2975]1022             message_string = 'initializing_actions = ' //                     &
1023                              TRIM( initializing_actions ) // ' has been ' //  &
1024                              'changed to set_constant_profiles in child ' //  &
1025                              'domain.' 
1026             CALL message( 'parin', 'PA0492', 0, 0, 0, 6, 0 )
1027
[1955]1028             initializing_actions = 'set_constant_profiles'
[3182]1029          ENDIF           
[1764]1030!
1031!--       Check validity of lateral boundary conditions. This has to be done
1032!--       here because they are already used in init_pegrid and init_grid and
1033!--       therefore cannot be check in check_parameters
1034          IF ( bc_lr /= 'cyclic'  .AND.  bc_lr /= 'dirichlet/radiation'  .AND. &
[2696]1035               bc_lr /= 'radiation/dirichlet'  .AND.  bc_lr /= 'nested'  .AND. &
[3182]1036               bc_lr /= 'nesting_offline' )  THEN
[1764]1037             message_string = 'unknown boundary condition: bc_lr = "' // &
1038                              TRIM( bc_lr ) // '"'
[2975]1039             CALL message( 'parin', 'PA0049', 1, 2, 0, 6, 0 )
[1764]1040          ENDIF
1041          IF ( bc_ns /= 'cyclic'  .AND.  bc_ns /= 'dirichlet/radiation'  .AND. &
[2696]1042               bc_ns /= 'radiation/dirichlet'  .AND.  bc_ns /= 'nested'  .AND. &
[3182]1043               bc_ns /= 'nesting_offline' )  THEN
[1764]1044             message_string = 'unknown boundary condition: bc_ns = "' // &
1045                              TRIM( bc_ns ) // '"'
[2975]1046             CALL message( 'parin', 'PA0050', 1, 2, 0, 6, 0 )
[1764]1047          ENDIF
1048!
1049!--       Set internal variables used for speed optimization in if clauses
1050          IF ( bc_lr /= 'cyclic' )               bc_lr_cyc    = .FALSE.
1051          IF ( bc_lr == 'dirichlet/radiation' )  bc_lr_dirrad = .TRUE.
1052          IF ( bc_lr == 'radiation/dirichlet' )  bc_lr_raddir = .TRUE.
1053          IF ( bc_ns /= 'cyclic' )               bc_ns_cyc    = .FALSE.
1054          IF ( bc_ns == 'dirichlet/radiation' )  bc_ns_dirrad = .TRUE.
1055          IF ( bc_ns == 'radiation/dirichlet' )  bc_ns_raddir = .TRUE.
1056!
[3806]1057!--       Radiation-Dirichlet conditions are allowed along one of the horizontal directions only.
1058!--       In general, such conditions along x and y may work, but require a) some code changes
1059!--       (e.g. concerning allocation of c_u, c_v ... arrays), and b) a careful model setup by the
1060!--       user, in order to guarantee that there is a clearly defined outflow at two sides.
1061!--       Otherwise, the radiation condition may produce wrong results.
1062          IF ( ( bc_lr_dirrad .OR. bc_lr_raddir )  .AND.  ( bc_ns_dirrad .OR. bc_ns_raddir ) )  THEN
1063             message_string = 'bc_lr = "' // TRIM( bc_lr ) // '" and bc_ns = "' //                 &
1064                              TRIM( bc_ns ) // '" are not allowed to be set at the same time'
1065             CALL message( 'parin', 'PA0589', 1, 2, 0, 6, 0 )
1066          ENDIF
1067!
[759]1068!--       Check in case of initial run, if the grid point numbers are well
1069!--       defined and allocate some arrays which are already needed in
1070!--       init_pegrid or check_parameters. During restart jobs, these arrays
[2894]1071!--       will be allocated in rrd_global. All other arrays are allocated
[759]1072!--       in init_3d_model.
1073          IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
[667]1074
[759]1075             IF ( nx <= 0 )  THEN
[1429]1076                WRITE( message_string, * ) 'no value or wrong value given',    &
[759]1077                                           ' for nx: nx=', nx
1078                CALL message( 'parin', 'PA0273', 1, 2, 0, 6, 0 )
1079             ENDIF
1080             IF ( ny <= 0 )  THEN
[1429]1081                WRITE( message_string, * ) 'no value or wrong value given',    &
[759]1082                                           ' for ny: ny=', ny
1083                CALL message( 'parin', 'PA0274', 1, 2, 0, 6, 0 )
1084             ENDIF
1085             IF ( nz <= 0 )  THEN
[1429]1086                WRITE( message_string, * ) 'no value or wrong value given',    &
[759]1087                                           ' for nz: nz=', nz
1088                CALL message( 'parin', 'PA0275', 1, 2, 0, 6, 0 )
1089             ENDIF
[3204]1090
[759]1091!
[3204]1092!--          As a side condition, routine flow_statistics require at least 14
1093!--          vertical grid levels (they are used to store time-series data)
1094!>           @todo   Remove this restriction
1095             IF ( nz < 14 )  THEN
1096                WRITE( message_string, * ) 'nz >= 14 is required'
1097                CALL message( 'parin', 'PA0362', 1, 2, 0, 6, 0 )
1098             ENDIF
1099
1100!
[759]1101!--          ATTENTION: in case of changes to the following statement please
[2894]1102!--                  also check the allocate statement in routine rrd_global
[1960]1103             ALLOCATE( pt_init(0:nz+1), q_init(0:nz+1), s_init(0:nz+1),        &
[1429]1104                       ref_state(0:nz+1), sa_init(0:nz+1), ug(0:nz+1),         &
1105                       u_init(0:nz+1), v_init(0:nz+1), vg(0:nz+1),             &
[4131]1106                    hom(0:nz+1,2,pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0:statistic_regions),  &
1107                    hom_sum(0:nz+1,pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0:statistic_regions) )
[1]1108
[1353]1109             hom = 0.0_wp
[1]1110
[759]1111          ENDIF
1112
[1]1113!
[759]1114!--       NAMELIST-file is not needed anymore
1115          CALL close_file( 11 )
[1]1116
[759]1117       ENDIF
[1804]1118#if defined( __parallel )
[759]1119       CALL MPI_BARRIER( MPI_COMM_WORLD, ierr )
1120#endif
1121    ENDDO
1122
[3885]1123    CALL location_message( 'reading NAMELIST parameters from PARIN', 'finished' )
[1384]1124
[1]1125 END SUBROUTINE parin
Note: See TracBrowser for help on using the repository browser.