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

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

Implementation of a monotonic flux limiter for vertical advection term in Wicker-Skamarock scheme. The flux limiter is currently only applied for passive scalars (passive scalar, chemical species, aerosols) within the region up to the highest topography, in order to avoid the built-up of large concentrations within poorly resolved cavities in urban environments. To enable the limiter monotonic_limiter_z = .T. must be set. Note, the limiter is currently only implemented for the cache-optimized version of advec_ws. Further changes in offline nesting: Set boundary condition for w at nzt+1 at all lateral boundaries (even though these won't enter the numerical solution), in order to avoid high vertical velocities in the run-control file which might built-up due to the mass-conservation; bugfix in offline nesting for chemical species

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