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

Last change on this file since 3806 was 3806, checked in by raasch, 5 years ago

bugfix: intent of dummy arguments changed to inout, additional check for lateral boundary conditions added

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