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

Last change on this file since 3448 was 3448, checked in by kanani, 5 years ago

Implementation of human thermal indices (from branch biomet_p2 at r3444)

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