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

Last change on this file since 4017 was 4017, checked in by schwenkel, 5 years ago

Modularization of all lagrangian particle model code components

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