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

Last change on this file since 4828 was 4828, checked in by Giersch, 3 years ago

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

  • Property svn:keywords set to Id
File size: 72.2 KB
Line 
1!> @file parin.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2021 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: parin.f90 4828 2021-01-05 11:21:41Z Giersch $
26! file re-formatted to follow the PALM coding standard
27!
28! 4783 2020-11-13 13:58:45Z raasch
29! bugfix for reading restart data with MPI-I/O (does not work with blockwise I/O)
30!
31! 4680 2020-09-16 10:20:34Z gronemeier
32! Add option to fix date or time of the simulation
33!
34! 4565 2020-06-15 08:30:38Z oliver.maas
35! added pt_surface_heating_rate
36!
37! 4564 2020-06-12 14:03:36Z raasch
38! Vertical nesting method of Huq et al. (2019) removed
39!
40! 4536 2020-05-17 17:24:13Z raasch
41! bugfix for restart data format query
42!
43! 4505 2020-04-20 15:37:15Z schwenkel
44! Add flag for saturation check
45!
46! 4495 2020-04-13 20:11:20Z raasch
47! restart data handling with MPI-IO added
48!
49! 4360 2020-01-07 11:25:50Z suehring
50! removed recycling_yshift
51!
52! 4227 2019-09-10 18:04:34Z gronemeier
53! implement new palm_date_time_mod
54!
55! 4146 2019-08-07 07:47:36Z gronemeier
56! added rotation_angle to initialization_parameters
57!
58! 4191 2019-08-27 15:45:07Z gronemeier
59! bugfix: add recycling_method_for_thermodynamic_quantities to inipar namelist
60!
61! 4183 2019-08-23 07:33:16Z oliver.maas
62! replaced recycle_absolute_quantities by recycling_method_for_thermodynamic_quantities
63!
64! 4182 2019-08-22 15:20:23Z scharf
65! Corrected "Former revisions" section
66!
67! 4176 2019-08-20 14:10:41Z oliver.maas
68! added recycle_absolute_quantities to initialization_parameters namelist
69!
70! 4173 2019-08-20 12:04:06Z gronemeier
71! add vdi_internal_controls
72!
73! 4131 2019-08-02 11:06:18Z monakurppa
74! Allocate hom and hom_sum to allow profile output for salsa variables.
75!
76! 4079 2019-07-09 18:04:41Z suehring
77! +monotonic_limiter_z
78!
79! 4022 2019-06-12 11:52:39Z suehring
80! Change default top boundary condition for pressure to Neumann in offline nesting case
81!
82! 4017 2019-06-06 12:16:46Z schwenkel
83! Introduce alternative switch for debug output during timestepping
84!
85! 3885 2019-04-11 11:29:34Z kanani
86! Changes related to global restructuring of location messages and introduction of additional debug
87! messages
88!
89! 3806 2019-03-21 12:45:50Z raasch
90! additional check for lateral boundary conditions added
91!
92! 3747 2019-02-16 15:15:23Z gronemeier
93! removed setting of parameter region
94!
95! 3746 2019-02-16 12:41:27Z gronemeier
96! Removed most_method
97!
98! 3649 2019-01-02 16:52:21Z suehring
99! Delete debug-print statements
100!
101! Revision 1.1  1997/07/24 11:22:50  raasch
102! Initial revision
103!
104!
105! Description:
106! ------------
107!> This subroutine reads variables controling the run from the NAMELIST files
108!>
109!> @todo: Revise max_pr_cs (profiles for chemistry)
110!--------------------------------------------------------------------------------------------------!
111 SUBROUTINE parin
112
113
114    USE arrays_3d,                                                                                 &
115        ONLY:  pt_init, q_init, ref_state, s_init, sa_init, ug, u_init, v_init, vg
116
117    USE chem_modules
118
119    USE control_parameters
120
121    USE cpulog,                                                                                    &
122        ONLY:  cpu_log_barrierwait
123
124    USE grid_variables,                                                                            &
125        ONLY:  dx, dy
126
127    USE indices,                                                                                   &
128        ONLY:  nx, ny, nz
129
130    USE kinds
131
132    USE model_1d_mod,                                                                              &
133        ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
134
135    USE module_interface,                                                                          &
136        ONLY:  module_interface_parin
137
138    USE netcdf_interface,                                                                          &
139        ONLY:  netcdf_data_format, netcdf_deflate, netcdf_precision
140
141    USE pegrid
142
143    USE pmc_interface,                                                                             &
144        ONLY:  nested_run, nesting_mode
145
146    USE profil_parameter,                                                                          &
147        ONLY:  cross_profiles, profile_columns, profile_rows
148
149    USE progress_bar,                                                                              &
150        ONLY :  progress_bar_disabled
151
152    USE read_restart_data_mod,                                                                     &
153        ONLY:  rrd_global
154
155    USE statistics,                                                                                &
156        ONLY:  hom, hom_sum, pr_palm, statistic_regions
157
158    USE turbulence_closure_mod,                                                                    &
159        ONLY:  rans_const_c, rans_const_sigma
160
161
162    IMPLICIT NONE
163
164    CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
165
166    INTEGER(iwp) ::  global_id      !< process id with respect to MPI_COMM_WORLD
167    INTEGER(iwp) ::  global_procs   !< # of procs with respect to MPI_COMM_WORLD
168    INTEGER(iwp) ::  i              !<
169    INTEGER(iwp) ::  ioerr          !< error flag for open/read/write
170
171    NAMELIST /inipar/  alpha_surface,                                                              &
172                       approximation,                                                              &
173                       bc_e_b,                                                                     &
174                       bc_lr,                                                                      &
175                       bc_ns,                                                                      &
176                       bc_p_b,                                                                     &
177                       bc_p_t,                                                                     &
178                       bc_pt_b,                                                                    &
179                       bc_pt_t,                                                                    &
180                       bc_q_b,                                                                     &
181                       bc_q_t,                                                                     &
182                       bc_s_b,                                                                     &
183                       bc_s_t,                                                                     &
184                       bc_uv_b,                                                                    &
185                       bc_uv_t,                                                                    &
186                       building_height,                                                            &
187                       building_length_x,                                                          &
188                       building_length_y,                                                          &
189                       building_wall_left,                                                         &
190                       building_wall_south,                                                        &
191                       calc_soil_moisture_during_spinup,                                           &
192                       call_psolver_at_all_substeps,                                               &
193                       canyon_height,                                                              &
194                       canyon_wall_left,                                                           &
195                       canyon_wall_south,                                                          &
196                       canyon_width_x,                                                             &
197                       canyon_width_y,                                                             &
198                       cfl_factor,                                                                 &
199                       check_realistic_q,                                                          &
200                       cloud_droplets,                                                             &
201                       collective_wait,                                                            &
202                       complex_terrain,                                                            &
203                       conserve_volume_flow,                                                       &
204                       conserve_volume_flow_mode,                                                  &
205                       constant_flux_layer,                                                        &
206                       coupling_start_time,                                                        &
207                       cycle_mg,                                                                   &
208                       damp_level_1d,                                                              &
209                       data_output_during_spinup,                                                  &
210                       dissipation_1d,                                                             &
211                       dp_external,                                                                &
212                       dp_level_b,                                                                 &
213                       dp_smooth,                                                                  &
214                       dpdxy,                                                                      &
215                       dt,                                                                         &
216                       dt_pr_1d,                                                                   &
217                       dt_run_control_1d,                                                          &
218                       dt_spinup,                                                                  &
219                       dx,                                                                         &
220                       dy,                                                                         &
221                       dz,                                                                         &
222                       dz_max,                                                                     &
223                       dz_stretch_factor,                                                          &
224                       dz_stretch_level,                                                           &
225                       dz_stretch_level_end,                                                       &
226                       dz_stretch_level_start,                                                     &
227                       e_init,                                                                     &
228                       e_min,                                                                      &
229                       end_time_1d,                                                                &
230                       ensemble_member_nr,                                                         &
231                       fft_method,                                                                 &
232                       flux_input_mode,                                                            &
233                       flux_output_mode,                                                           &
234                       galilei_transformation,                                                     &
235                       humidity,                                                                   &
236                       inflow_damping_height,                                                      &
237                       inflow_damping_width,                                                       &
238                       inflow_disturbance_begin,                                                   &
239                       inflow_disturbance_end,                                                     &
240                       initializing_actions,                                                       &
241                       km_constant,                                                                &
242                       large_scale_forcing,                                                        &
243                       large_scale_subsidence,                                                     &
244                       latitude,                                                                   &
245                       longitude,                                                                  &
246                       loop_optimization,                                                          &
247                       lsf_exception,                                                              &
248                       masking_method,                                                             &
249                       mg_cycles,                                                                  &
250                       mg_switch_to_pe0_level,                                                     &
251                       mixing_length_1d,                                                           &
252                       momentum_advec,                                                             &
253                       monotonic_limiter_z,                                                        &
254                       netcdf_precision,                                                           &
255                       neutral,                                                                    &
256                       ngsrb,                                                                      &
257                       nsor,                                                                       &
258                       nsor_ini,                                                                   &
259                       nudging,                                                                    &
260                       nx,                                                                         &
261                       ny,                                                                         &
262                       nz,                                                                         &
263                       ocean_mode,                                                                 &
264                       omega,                                                                      &
265                       omega_sor,                                                                  &
266                       origin_date_time,                                                           &
267                       outflow_source_plane,                                                       &
268                       passive_scalar,                                                             &
269                       prandtl_number,                                                             &
270                       psolver,                                                                    &
271                       pt_damping_factor,                                                          &
272                       pt_damping_width,                                                           &
273                       pt_reference,                                                               &
274                       pt_surface,                                                                 &
275                       pt_surface_heating_rate,                                                    &
276                       pt_surface_initial_change,                                                  &
277                       pt_vertical_gradient,                                                       &
278                       pt_vertical_gradient_level,                                                 &
279                       q_surface,                                                                  &
280                       q_surface_initial_change,                                                   &
281                       q_vertical_gradient,                                                        &
282                       q_vertical_gradient_level,                                                  &
283                       random_generator,                                                           &
284                       random_heatflux,                                                            &
285                       rans_const_c,                                                               &
286                       rans_const_sigma,                                                           &
287                       rayleigh_damping_factor,                                                    &
288                       rayleigh_damping_height,                                                    &
289                       recycling_method_for_thermodynamic_quantities,                              &
290                       recycling_width,                                                            &
291                       reference_state,                                                            &
292                       residual_limit,                                                             &
293                       rotation_angle,                                                             &
294                       roughness_length,                                                           &
295                       scalar_advec,                                                               &
296                       scalar_rayleigh_damping,                                                    &
297                       spinup_time,                                                                &
298                       spinup_pt_amplitude,                                                        &
299                       spinup_pt_mean,                                                             &
300                       statistic_regions,                                                          &
301                       subs_vertical_gradient,                                                     &
302                       subs_vertical_gradient_level,                                               &
303                       surface_heatflux,                                                           &
304                       surface_pressure,                                                           &
305                       surface_scalarflux,                                                         &
306                       surface_waterflux,                                                          &
307                       s_surface,                                                                  &
308                       s_surface_initial_change,                                                   &
309                       s_vertical_gradient,                                                        &
310                       s_vertical_gradient_level,                                                  &
311                       timestep_scheme,                                                            &
312                       topography,                                                                 &
313                       topography_grid_convention,                                                 &
314                       top_heatflux,                                                               &
315                       top_momentumflux_u,                                                         &
316                       top_momentumflux_v,                                                         &
317                       top_scalarflux,                                                             &
318                       transpose_compute_overlap,                                                  &
319                       tunnel_height,                                                              &
320                       tunnel_length,                                                              &
321                       tunnel_wall_depth,                                                          &
322                       tunnel_width_x,                                                             &
323                       tunnel_width_y,                                                             &
324                       turbulence_closure,                                                         &
325                       turbulent_inflow,                                                           &
326                       turbulent_outflow,                                                          &
327                       u_bulk,                                                                     &
328                       u_profile,                                                                  &
329                       ug_surface,                                                                 &
330                       ug_vertical_gradient,                                                       &
331                       ug_vertical_gradient_level,                                                 &
332                       use_cmax,                                                                   &
333                       use_fixed_date,                                                             &
334                       use_fixed_time,                                                             &
335                       use_free_convection_scaling,                                                &
336                       use_ug_for_galilei_tr,                                                      &
337                       use_subsidence_tendencies,                                                  &
338                       use_surface_fluxes,                                                         &
339                       use_top_fluxes,                                                             &
340                       use_upstream_for_tke,                                                       &
341                       uv_heights,                                                                 &
342                       v_bulk,                                                                     &
343                       v_profile,                                                                  &
344                       vdi_checks,                                                                 &
345                       vg_surface,                                                                 &
346                       vg_vertical_gradient,                                                       &
347                       vg_vertical_gradient_level,                                                 &
348                       wall_adjustment,                                                            &
349                       wall_heatflux,                                                              &
350                       wall_humidityflux,                                                          &
351                       wall_scalarflux,                                                            &
352                       y_shift,                                                                    &
353                       zeta_max,                                                                   &
354                       zeta_min,                                                                   &
355                       z0h_factor
356
357    NAMELIST /initialization_parameters/  alpha_surface,                                           &
358                                          approximation,                                           &
359                                          bc_e_b,                                                  &
360                                          bc_lr,                                                   &
361                                          bc_ns,                                                   &
362                                          bc_p_b,                                                  &
363                                          bc_p_t,                                                  &
364                                          bc_pt_b,                                                 &
365                                          bc_pt_t,                                                 &
366                                          bc_q_b,                                                  &
367                                          bc_q_t,                                                  &
368                                          bc_s_b,                                                  &
369                                          bc_s_t,                                                  &
370                                          bc_uv_b,                                                 &
371                                          bc_uv_t,                                                 &
372                                          building_height,                                         &
373                                          building_length_x,                                       &
374                                          building_length_y,                                       &
375                                          building_wall_left,                                      &
376                                          building_wall_south,                                     &
377                                          calc_soil_moisture_during_spinup,                        &
378                                          call_psolver_at_all_substeps,                            &
379                                          canyon_height,                                           &
380                                          canyon_wall_left,                                        &
381                                          canyon_wall_south,                                       &
382                                          canyon_width_x,                                          &
383                                          canyon_width_y,                                          &
384                                          cfl_factor,                                              &
385                                          check_realistic_q,                                       &
386                                          cloud_droplets,                                          &
387                                          collective_wait,                                         &
388                                          complex_terrain,                                         &
389                                          conserve_volume_flow,                                    &
390                                          conserve_volume_flow_mode,                               &
391                                          constant_flux_layer,                                     &
392                                          coupling_start_time,                                     &
393                                          cycle_mg,                                                &
394                                          damp_level_1d,                                           &
395                                          data_output_during_spinup,                               &
396                                          dissipation_1d,                                          &
397                                          dp_external,                                             &
398                                          dp_level_b,                                              &
399                                          dp_smooth, dpdxy,                                        &
400                                          dt,                                                      &
401                                          dt_pr_1d,                                                &
402                                          dt_run_control_1d,                                       &
403                                          dt_spinup,                                               &
404                                          dx,                                                      &
405                                          dy,                                                      &
406                                          dz,                                                      &
407                                          dz_max,                                                  &
408                                          dz_stretch_factor,                                       &
409                                          dz_stretch_level,                                        &
410                                          dz_stretch_level_start,                                  &
411                                          dz_stretch_level_end,                                    &
412                                          e_init,                                                  &
413                                          e_min,                                                   &
414                                          end_time_1d,                                             &
415                                          ensemble_member_nr,                                      &
416                                          fft_method,                                              &
417                                          flux_input_mode,                                         &
418                                          flux_output_mode,                                        &
419                                          galilei_transformation,                                  &
420                                          humidity,                                                &
421                                          inflow_damping_height,                                   &
422                                          inflow_damping_width,                                    &
423                                          inflow_disturbance_begin,                                &
424                                          inflow_disturbance_end,                                  &
425                                          initializing_actions,                                    &
426                                          km_constant,                                             &
427                                          large_scale_forcing,                                     &
428                                          large_scale_subsidence,                                  &
429                                          latitude,                                                &
430                                          longitude,                                               &
431                                          loop_optimization,                                       &
432                                          lsf_exception,                                           &
433                                          masking_method,                                          &
434                                          mg_cycles,                                               &
435                                          mg_switch_to_pe0_level,                                  &
436                                          mixing_length_1d,                                        &
437                                          momentum_advec,                                          &
438                                          monotonic_limiter_z,                                     &
439                                          netcdf_precision,                                        &
440                                          neutral,                                                 &
441                                          ngsrb,                                                   &
442                                          nsor,                                                    &
443                                          nsor_ini,                                                &
444                                          nudging,                                                 &
445                                          nx,                                                      &
446                                          ny,                                                      &
447                                          nz,                                                      &
448                                          ocean_mode,                                              &
449                                          omega,                                                   &
450                                          omega_sor,                                               &
451                                          origin_date_time,                                        &
452                                          outflow_source_plane,                                    &
453                                          passive_scalar,                                          &
454                                          prandtl_number,                                          &
455                                          psolver,                                                 &
456                                          pt_damping_factor,                                       &
457                                          pt_damping_width,                                        &
458                                          pt_reference, pt_surface,                                &
459                                          pt_surface_heating_rate,                                 &
460                                          pt_surface_initial_change,                               &
461                                          pt_vertical_gradient,                                    &
462                                          pt_vertical_gradient_level,                              &
463                                          q_surface,                                               &
464                                          q_surface_initial_change,                                &
465                                          q_vertical_gradient,                                     &
466                                          q_vertical_gradient_level,                               &
467                                          random_generator,                                        &
468                                          random_heatflux,                                         &
469                                          rans_const_c,                                            &
470                                          rans_const_sigma,                                        &
471                                          rayleigh_damping_factor,                                 &
472                                          rayleigh_damping_height,                                 &
473                                          recycling_method_for_thermodynamic_quantities,           &
474                                          recycling_width,                                         &
475                                          reference_state,                                         &
476                                          residual_limit,                                          &
477                                          restart_data_format,                                     &
478                                          restart_data_format_input,                               &
479                                          restart_data_format_output,                              &
480                                          rotation_angle,                                          &
481                                          roughness_length,                                        &
482                                          s_surface,                                               &
483                                          s_surface_initial_change,                                &
484                                          s_vertical_gradient,                                     &
485                                          s_vertical_gradient_level,                               &
486                                          scalar_advec,                                            &
487                                          scalar_rayleigh_damping,                                 &
488                                          spinup_time,                                             &
489                                          spinup_pt_amplitude,                                     &
490                                          spinup_pt_mean,                                          &
491                                          statistic_regions,                                       &
492                                          subs_vertical_gradient,                                  &
493                                          subs_vertical_gradient_level,                            &
494                                          surface_heatflux,                                        &
495                                          surface_pressure,                                        &
496                                          surface_scalarflux,                                      &
497                                          surface_waterflux,                                       &
498                                          timestep_scheme,                                         &
499                                          topography,                                              &
500                                          topography_grid_convention,                              &
501                                          top_heatflux,                                            &
502                                          top_momentumflux_u,                                      &
503                                          top_momentumflux_v,                                      &
504                                          top_scalarflux,                                          &
505                                          transpose_compute_overlap,                               &
506                                          tunnel_height,                                           &
507                                          tunnel_length,                                           &
508                                          tunnel_wall_depth,                                       &
509                                          tunnel_width_x,                                          &
510                                          tunnel_width_y,                                          &
511                                          turbulence_closure,                                      &
512                                          turbulent_inflow,                                        &
513                                          turbulent_outflow,                                       &
514                                          u_bulk,                                                  &
515                                          u_profile,                                               &
516                                          ug_surface,                                              &
517                                          ug_vertical_gradient,                                    &
518                                          ug_vertical_gradient_level,                              &
519                                          use_fixed_date,                                          &
520                                          use_fixed_time,                                          &
521                                          use_free_convection_scaling,                             &
522                                          use_ug_for_galilei_tr,                                   &
523                                          use_subsidence_tendencies,                               &
524                                          use_surface_fluxes, use_cmax,                            &
525                                          use_top_fluxes,                                          &
526                                          use_upstream_for_tke,                                    &
527                                          uv_heights,                                              &
528                                          v_bulk,                                                  &
529                                          v_profile,                                               &
530                                          vdi_checks,                                              &
531                                          vg_surface,                                              &
532                                          vg_vertical_gradient,                                    &
533                                          vg_vertical_gradient_level,                              &
534                                          wall_adjustment,                                         &
535                                          wall_heatflux,                                           &
536                                          wall_humidityflux,                                       &
537                                          wall_scalarflux,                                         &
538                                          y_shift,                                                 &
539                                          zeta_max,                                                &
540                                          zeta_min,                                                &
541                                          z0h_factor
542
543    NAMELIST /d3par/  averaging_interval,                                                          &
544                      averaging_interval_pr,                                                       &
545                      cpu_log_barrierwait,                                                         &
546                      create_disturbances,                                                         &
547                      cross_profiles,                                                              &
548                      data_output,                                                                 &
549                      data_output_2d_on_each_pe,                                                   &
550                      data_output_masks,                                                           &
551                      data_output_pr,                                                              &
552                      debug_output,                                                                &
553                      debug_output_timestep,                                                       &
554                      disturbance_amplitude,                                                       &
555                      disturbance_energy_limit,                                                    &
556                      disturbance_level_b,                                                         &
557                      disturbance_level_t,                                                         &
558                      do2d_at_begin,                                                               &
559                      do3d_at_begin,                                                               &
560                      dt,                                                                          &
561                      dt_averaging_input,                                                          &
562                      dt_averaging_input_pr,                                                       &
563                      dt_coupling,                                                                 &
564                      dt_data_output,                                                              &
565                      dt_data_output_av,                                                           &
566                      dt_disturb,                                                                  &
567                      dt_domask,                                                                   &
568                      dt_dopr,                                                                     &
569                      dt_dopr_listing,                                                             &
570                      dt_dots,                                                                     &
571                      dt_do2d_xy,                                                                  &
572                      dt_do2d_xz,                                                                  &
573                      dt_do2d_yz,                                                                  &
574                      dt_do3d,                                                                     &
575                      dt_max,                                                                      &
576                      dt_restart,                                                                  &
577                      dt_run_control,                                                              &
578                      end_time,                                                                    &
579                      force_print_header,                                                          &
580                      mask_k_over_surface,                                                         &
581                      mask_scale_x,                                                                &
582                      mask_scale_y,                                                                &
583                      mask_scale_z,                                                                &
584                      mask_x,                                                                      &
585                      mask_y,                                                                      &
586                      mask_z,                                                                      &
587                      mask_x_loop,                                                                 &
588                      mask_y_loop,                                                                 &
589                      mask_z_loop,                                                                 &
590                      netcdf_data_format,                                                          &
591                      netcdf_deflate,                                                              &
592                      normalizing_region,                                                          &
593                      npex,                                                                        &
594                      npey,                                                                        &
595                      nz_do3d,                                                                     &
596                      profile_columns,                                                             &
597                      profile_rows,                                                                &
598                      restart_time,                                                                &
599                      section_xy,                                                                  &
600                      section_xz,                                                                  &
601                      section_yz,                                                                  &
602                      skip_time_data_output,                                                       &
603                      skip_time_data_output_av,                                                    &
604                      skip_time_dopr,                                                              &
605                      skip_time_do2d_xy,                                                           &
606                      skip_time_do2d_xz,                                                           &
607                      skip_time_do2d_yz,                                                           &
608                      skip_time_do3d,                                                              &
609                      skip_time_domask,                                                            &
610                      synchronous_exchange,                                                        &
611                      termination_time_needed
612
613    NAMELIST /runtime_parameters/  averaging_interval,                                             &
614                                   averaging_interval_pr,                                          &
615                                   cpu_log_barrierwait,                                            &
616                                   create_disturbances,                                            &
617                                   cross_profiles,                                                 &
618                                   data_output,                                                    &
619                                   data_output_2d_on_each_pe,                                      &
620                                   data_output_masks,                                              &
621                                   data_output_pr,                                                 &
622                                   debug_output,                                                   &
623                                   debug_output_timestep,                                          &
624                                   disturbance_amplitude,                                          &
625                                   disturbance_energy_limit,                                       &
626                                   disturbance_level_b,                                            &
627                                   disturbance_level_t,                                            &
628                                   do2d_at_begin,                                                  &
629                                   do3d_at_begin,                                                  &
630                                   dt,                                                             &
631                                   dt_averaging_input,                                             &
632                                   dt_averaging_input_pr,                                          &
633                                   dt_coupling,                                                    &
634                                   dt_data_output,                                                 &
635                                   dt_data_output_av,                                              &
636                                   dt_disturb,                                                     &
637                                   dt_domask,                                                      &
638                                   dt_dopr,                                                        &
639                                   dt_dopr_listing,                                                &
640                                   dt_dots,                                                        &
641                                   dt_do2d_xy,                                                     &
642                                   dt_do2d_xz,                                                     &
643                                   dt_do2d_yz,                                                     &
644                                   dt_do3d,                                                        &
645                                   dt_max,                                                         &
646                                   dt_restart,                                                     &
647                                   dt_run_control,                                                 &
648                                   end_time,                                                       &
649                                   force_print_header,                                             &
650                                   mask_k_over_surface,                                            &
651                                   mask_scale_x,                                                   &
652                                   mask_scale_y,                                                   &
653                                   mask_scale_z,                                                   &
654                                   mask_x,                                                         &
655                                   mask_y,                                                         &
656                                   mask_z,                                                         &
657                                   mask_x_loop,                                                    &
658                                   mask_y_loop,                                                    &
659                                   mask_z_loop,                                                    &
660                                   netcdf_data_format,                                             &
661                                   netcdf_deflate,                                                 &
662                                   normalizing_region,                                             &
663                                   npex,                                                           &
664                                   npey,                                                           &
665                                   nz_do3d,                                                        &
666                                   profile_columns,                                                &
667                                   profile_rows,                                                   &
668                                   restart_time,                                                   &
669                                   section_xy,                                                     &
670                                   section_xz,                                                     &
671                                   section_yz,                                                     &
672                                   restart_data_format,                                            &
673                                   restart_data_format_input,                                      &
674                                   restart_data_format_output,                                     &
675                                   skip_time_data_output,                                          &
676                                   skip_time_data_output_av,                                       &
677                                   skip_time_dopr,                                                 &
678                                   skip_time_do2d_xy,                                              &
679                                   skip_time_do2d_xz,                                              &
680                                   skip_time_do2d_yz,                                              &
681                                   skip_time_do3d,                                                 &
682                                   skip_time_domask,                                               &
683                                   synchronous_exchange,                                           &
684                                   termination_time_needed
685
686    NAMELIST /envpar/  host,                                                                       &
687                       maximum_cpu_time_allowed,                                                   &
688                       maximum_parallel_io_streams,                                                &
689                       progress_bar_disabled,                                                      &
690                       read_svf,                                                                   &
691                       revision,                                                                   &
692                       run_identifier,                                                             &
693                       tasks_per_node,                                                             &
694                       write_binary,                                                               &
695                       write_svf
696
697!
698!-- First read values of environment variables (this NAMELIST file is generated by palmrun)
699    CALL location_message( 'reading environment parameters from ENVPAR', 'start' )
700
701    OPEN( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', IOSTAT=ioerr )
702
703    IF ( ioerr /= 0 )  THEN
704       message_string = 'local file ENVPAR not found' //                                           &
705                        '&some variables for steering may not be properly set'
706       CALL message( 'parin', 'PA0276', 0, 1, 0, 6, 0 )
707    ELSE
708       READ( 90, envpar, IOSTAT=ioerr )
709       IF ( ioerr < 0 )  THEN
710          message_string = 'no envpar-NAMELIST found in local file '  //                           &
711                           'ENVPAR& or some variables for steering may '  //   &
712                           'not be properly set'
713          CALL message( 'parin', 'PA0278', 0, 1, 0, 6, 0 )
714       ELSEIF ( ioerr > 0 )  THEN
715          message_string = 'errors in local file ENVPAR' //                                        &
716                           '&some variables for steering may not be properly set'
717          CALL message( 'parin', 'PA0277', 0, 1, 0, 6, 0 )
718       ENDIF
719       CLOSE( 90 )
720    ENDIF
721
722    CALL location_message( 'reading environment parameters from ENVPAR', 'finished' )
723
724    CALL location_message( 'reading NAMELIST parameters from PARIN', 'start' )
725
726!
727!-- Open the NAMELIST-file which is send with this job
728    CALL check_open( 11 )
729
730!
731!-- Read the control parameters for initialization.
732!-- The namelist "inipar" must be provided in the NAMELIST-file.
733    READ ( 11, initialization_parameters, ERR=10, END=11 )
734    GOTO 14
735
736 10 BACKSPACE( 11 )
737    READ( 11 , '(A)') line
738    CALL parin_fail_message( 'initialization_parameters', line )
739
740 11 REWIND ( 11 )
741    READ( 11, inipar, ERR=12, END=13 )
742
743    message_string = 'namelist inipar is deprecated and will be ' //                               &
744                     'removed in near future. & Please use namelist ' //                           &
745                     'initialization_parameters instead'
746    CALL message( 'parin', 'PA0017', 0, 1, 0, 6, 0 )
747
748    GOTO 14
749
750 12 BACKSPACE( 11 )
751    READ( 11 , '(A)') line
752    CALL parin_fail_message( 'inipar', line )
753
754 13 message_string = 'no initialization_parameters-namelist found'
755    CALL message( 'parin', 'PA0272', 1, 2, 0, 6, 0 )
756
757!
758!-- Try to read runtime parameters given by the user for this run (namelist "runtime_parameters").
759!-- The namelist "runtime_parmeters" can be omitted. In that case default values are used for the
760!-- parameters.
761 14 line = ' '
762
763    REWIND( 11 )
764    line = ' '
765    DO WHILE ( INDEX( line, '&runtime_parameters' ) == 0 )
766       READ( 11, '(A)', END=16 )  line
767    ENDDO
768    BACKSPACE( 11 )
769
770!
771!-- Read namelist
772    READ( 11, runtime_parameters, ERR = 15 )
773    GOTO 18
774
775 15 BACKSPACE( 11 )
776    READ( 11 , '(A)') line
777    CALL parin_fail_message( 'runtime_parameters', line )
778
779 16 REWIND( 11 )
780    line = ' '
781    DO WHILE ( INDEX( line, '&d3par' ) == 0 )
782       READ( 11, '(A)', END=18 )  line
783    ENDDO
784    BACKSPACE ( 11 )
785
786!
787!-- Read namelist
788    READ( 11, d3par, ERR = 17, END = 18 )
789
790    message_string = 'namelist d3par is deprecated and will be ' //                                &
791                     'removed in near future. &Please use namelist ' //                            &
792                     'runtime_parameters instead'
793    CALL message( 'parin', 'PA0487', 0, 1, 0, 6, 0 )
794
795    GOTO 18
796
797 17 BACKSPACE( 11 )
798    READ( 11 , '(A)') line
799    CALL parin_fail_message( 'd3par', line )
800
801 18 CONTINUE
802
803!
804!-- Check for module namelists and read them
805    CALL module_interface_parin
806
807!
808!-- Calculate the number of groups into which parallel I/O is split.
809!-- The default for files which are opened by all PEs (or where each PE opens its own independent
810!-- file) is, that all PEs are doing input/output in parallel at the same time. This might cause
811!-- performance or even more severe problems depending on the configuration of the underlying file
812!-- system.
813!-- Calculation of the number of blocks and the I/O group must be based on all PEs involved in this
814!-- run. Since myid and numprocs are related to the comm2d communicator, which gives only a subset
815!-- of all PEs in case of nested runs, that information must be inquired again from the global
816!-- communicator.
817!-- First, set the default:
818#if defined( __parallel )
819    CALL MPI_COMM_RANK( MPI_COMM_WORLD, global_id, ierr )
820    CALL MPI_COMM_SIZE( MPI_COMM_WORLD, global_procs, ierr )
821#else
822    global_id    = 0
823    global_procs = 1
824#endif
825    IF ( maximum_parallel_io_streams == -1  .OR.  maximum_parallel_io_streams > global_procs )  THEN
826       maximum_parallel_io_streams = global_procs
827    ENDIF
828!
829!-- Now calculate the number of io_blocks and the io_group to which the respective PE belongs. I/O
830!-- of the groups is done in serial, but in parallel for all PEs belonging to the same group.
831    io_blocks = global_procs / maximum_parallel_io_streams
832    io_group  = MOD( global_id+1, io_blocks )
833
834!
835!-- If required, read control parameters from restart file (produced by a prior run). All PEs are
836!-- reading from file created by PE0 (see check_open)
837    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
838
839!
840!--    If not set by the user in the runtime parameters, the data format for restart input needs to
841!--    be set now! This is normally done later in check parameters.
842       IF ( TRIM( restart_data_format ) /= 'fortran_binary'  .AND.                                 &
843            TRIM( restart_data_format ) /= 'mpi'             .AND.                                 &
844            TRIM( restart_data_format ) /= 'mpi_shared_memory' )  THEN
845          message_string = 'illegal restart data format "' // TRIM( restart_data_format ) // '"'
846          CALL message( 'parin', 'PA0724', 1, 2, 0, 6, 0 )
847       ENDIF
848       IF ( TRIM( restart_data_format_input ) == 'undefined' )  THEN
849          restart_data_format_input = restart_data_format
850       ENDIF
851
852!
853!--    Blockwise I/O does not work together with MPI-I/O
854       IF ( restart_data_format_input(1:3) == 'mpi'  .AND.  io_blocks /= 1 )  THEN
855          CALL rrd_global
856       ELSE
857!
858!--       Data is read in parallel by groups of PEs
859          DO  i = 0, io_blocks-1
860             IF ( i == io_group )  THEN
861                CALL rrd_global
862             ENDIF
863#if defined( __parallel )
864             CALL MPI_BARRIER( comm2d, ierr )
865#endif
866          ENDDO
867       ENDIF
868
869
870!
871!--    Increment the run count
872       runnr = runnr + 1
873!
874!--    In case of a restart run, the number of user-defined profiles on the restart file (already
875!--    stored in max_pr_user) has to match the one given for the current run. max_pr_user_tmp is
876!--    calculated in user_parin and max_pr_user is read in via rrd_global.
877       IF ( max_pr_user /= max_pr_user_tmp )  THEN
878          WRITE( message_string, * ) 'the number of user-defined ',                                &
879                                     'profiles given in data_output_pr (', max_pr_user_tmp,        &
880                                     ') does not match the one ',                                  &
881                                     'found in the restart file (', max_pr_user, ')'
882          CALL message( 'user_parin', 'UI0009', 1, 2, 0, 6, 0 )
883       ENDIF
884    ELSE
885       max_pr_user = max_pr_user_tmp
886    ENDIF
887!
888!-- Activate spinup
889    IF ( land_surface  .OR.  urban_surface )  THEN
890       IF ( spinup_time > 0.0_wp )  THEN
891          coupling_start_time = spinup_time
892          time_since_reference_point = simulated_time - coupling_start_time
893          IF ( spinup_pt_mean == 9999999.9_wp )  THEN
894             spinup_pt_mean = pt_surface
895          ENDIF
896          end_time = end_time + spinup_time
897          IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
898             spinup = .TRUE.
899          ELSEIF ( TRIM( initializing_actions ) == 'read_restart_data'  .AND.                      &
900                   time_since_reference_point > 0.0_wp )  THEN
901             data_output_during_spinup = .FALSE.  !< required for correct ntdim calculation
902                                                  !< in check_parameters for restart run
903          ENDIF
904       ENDIF
905    ENDIF
906
907!
908!-- In case of nested runs, explicitly set nesting boundary conditions.
909!-- This will overwrite the user settings and basic defaults.
910!-- bc_lr and bc_ns always need to be cyclic for vertical nesting.
911    IF ( nested_run )  THEN
912       IF ( nesting_mode == 'vertical' )  THEN
913          IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
914             WRITE ( message_string, *) 'bc_lr and bc_ns were set to ,',                           &
915                                        'cyclic for vertical nesting'
916             CALL message( 'parin', 'PA0428', 0, 0, 0, 6, 0 )
917             bc_lr   = 'cyclic'
918             bc_ns   = 'cyclic'
919          ENDIF
920          IF ( child_domain )  THEN
921             bc_uv_t  = 'nested'
922             bc_pt_t  = 'nested'
923             bc_q_t   = 'nested'
924             bc_s_t   = 'nested'
925             bc_cs_t  = 'nested'
926             bc_p_t   = 'neumann'
927          ENDIF
928!
929!--    For other nesting modes only set boundary conditions for nested domains.
930       ELSE
931          IF ( child_domain )  THEN
932             bc_lr    = 'nested'
933             bc_ns    = 'nested'
934             bc_uv_t  = 'nested'
935             bc_pt_t  = 'nested'
936             bc_q_t   = 'nested'
937             bc_s_t   = 'nested'
938             bc_cs_t  = 'nested'
939             bc_p_t   = 'neumann'
940          ENDIF
941       ENDIF
942    ENDIF
943!
944!-- Set boundary conditions also in case the model is offline-nested in larger-scale models.
945    IF ( nesting_offline )  THEN
946       bc_lr    = 'nesting_offline'
947       bc_ns    = 'nesting_offline'
948       bc_uv_t  = 'nesting_offline'
949       bc_pt_t  = 'nesting_offline'
950       bc_q_t   = 'nesting_offline'
951     !  bc_s_t   = 'nesting_offline'  ! scalar boundary condition is not clear yet
952     !  bc_cs_t  = 'nesting_offline'  ! same for chemical species
953       bc_p_t   = 'neumann'
954    ENDIF
955
956!
957!-- In case of nested runs, make sure that initializing_actions = 'set_constant_profiles' even
958!-- though the constant-profiles initializations for the prognostic variables will be overwritten by
959!-- pmci_child_initialize and pmci_parent_initialize. This is, however, important e.g. to make sure
960!-- that diagnostic variables are set properly. An exception is made in case of restart runs and if
961!-- user decides to do everything by its own.
962    IF ( child_domain  .AND.  .NOT. ( TRIM( initializing_actions ) == 'read_restart_data'     .OR. &
963                                      TRIM( initializing_actions ) == 'set_constant_profiles' .OR. &
964                                      TRIM( initializing_actions ) == 'by_user' )                  &
965                                    )  THEN
966       message_string = 'initializing_actions = ' // TRIM( initializing_actions ) //               &
967                        ' has been ' // 'changed to set_constant_profiles in child ' // 'domain.'
968       CALL message( 'parin', 'PA0492', 0, 0, 0, 6, 0 )
969
970       initializing_actions = 'set_constant_profiles'
971    ENDIF
972!
973!-- Check validity of lateral boundary conditions. This has to be done here because they are already
974!-- used in init_pegrid and init_grid and therefore cannot be check in check_parameters
975    IF ( bc_lr /= 'cyclic'               .AND.  bc_lr /= 'dirichlet/radiation'  .AND.              &
976         bc_lr /= 'radiation/dirichlet'  .AND.  bc_lr /= 'nested'               .AND.              &
977         bc_lr /= 'nesting_offline' )  THEN
978       message_string = 'unknown boundary condition: bc_lr = "' // TRIM( bc_lr ) // '"'
979       CALL message( 'parin', 'PA0049', 1, 2, 0, 6, 0 )
980    ENDIF
981    IF ( bc_ns /= 'cyclic'               .AND.  bc_ns /= 'dirichlet/radiation'  .AND.              &
982         bc_ns /= 'radiation/dirichlet'  .AND.  bc_ns /= 'nested'               .AND.              &
983         bc_ns /= 'nesting_offline' )  THEN
984       message_string = 'unknown boundary condition: bc_ns = "' // TRIM( bc_ns ) // '"'
985       CALL message( 'parin', 'PA0050', 1, 2, 0, 6, 0 )
986    ENDIF
987!
988!-- Set internal variables used for speed optimization in if clauses
989    IF ( bc_lr /= 'cyclic' )               bc_lr_cyc    = .FALSE.
990    IF ( bc_lr == 'dirichlet/radiation' )  bc_lr_dirrad = .TRUE.
991    IF ( bc_lr == 'radiation/dirichlet' )  bc_lr_raddir = .TRUE.
992    IF ( bc_ns /= 'cyclic' )               bc_ns_cyc    = .FALSE.
993    IF ( bc_ns == 'dirichlet/radiation' )  bc_ns_dirrad = .TRUE.
994    IF ( bc_ns == 'radiation/dirichlet' )  bc_ns_raddir = .TRUE.
995!
996!-- Radiation-Dirichlet conditions are allowed along one of the horizontal directions only.
997!-- In general, such conditions along x and y may work, but require a) some code changes (e.g.
998!-- concerning allocation of c_u, c_v ... arrays), and b) a careful model setup by the user, in
999!-- order to guarantee that there is a clearly defined outflow at two sides.
1000!-- Otherwise, the radiation condition may produce wrong results.
1001    IF ( ( bc_lr_dirrad .OR. bc_lr_raddir )  .AND.  ( bc_ns_dirrad .OR. bc_ns_raddir ) )  THEN
1002       message_string = 'bc_lr = "' // TRIM( bc_lr ) // '" and bc_ns = "' // TRIM( bc_ns ) //      &
1003                        '" are not allowed to be set at the same time'
1004       CALL message( 'parin', 'PA0589', 1, 2, 0, 6, 0 )
1005    ENDIF
1006!
1007!-- Check in case of initial run, if the grid point numbers are well defined and allocate some
1008!-- arrays which are already needed in init_pegrid or check_parameters. During restart jobs, these
1009!-- arrays will be allocated in rrd_global. All other arrays are allocated in init_3d_model.
1010    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
1011
1012       IF ( nx <= 0 )  THEN
1013          WRITE( message_string, * ) 'no value or wrong value given', ' for nx: nx=', nx
1014          CALL message( 'parin', 'PA0273', 1, 2, 0, 6, 0 )
1015       ENDIF
1016       IF ( ny <= 0 )  THEN
1017          WRITE( message_string, * ) 'no value or wrong value given', ' for ny: ny=', ny
1018          CALL message( 'parin', 'PA0274', 1, 2, 0, 6, 0 )
1019       ENDIF
1020       IF ( nz <= 0 )  THEN
1021          WRITE( message_string, * ) 'no value or wrong value given', ' for nz: nz=', nz
1022          CALL message( 'parin', 'PA0275', 1, 2, 0, 6, 0 )
1023       ENDIF
1024
1025!
1026!--    As a side condition, routine flow_statistics require at least 14 vertical grid levels (they
1027!--    are used to store time-series data)
1028!>     @todo   Remove this restriction
1029       IF ( nz < 14 )  THEN
1030          WRITE( message_string, * ) 'nz >= 14 is required'
1031          CALL message( 'parin', 'PA0362', 1, 2, 0, 6, 0 )
1032       ENDIF
1033
1034!
1035!--    ATTENTION: in case of changes to the following statement please also check the allocate
1036!--               statement in routine rrd_global
1037       ALLOCATE( pt_init(0:nz+1), q_init(0:nz+1), s_init(0:nz+1),                                  &
1038                 ref_state(0:nz+1), sa_init(0:nz+1), ug(0:nz+1),                                   &
1039                 u_init(0:nz+1), v_init(0:nz+1), vg(0:nz+1),                                       &
1040                 hom(0:nz+1,2,pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0:statistic_regions),     &
1041                 hom_sum(0:nz+1,pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0:statistic_regions) )
1042
1043       hom = 0.0_wp
1044
1045    ENDIF
1046
1047!
1048!-- NAMELIST-file is not needed anymore
1049    CALL close_file( 11 )
1050
1051    CALL location_message( 'reading NAMELIST parameters from PARIN', 'finished' )
1052
1053 END SUBROUTINE parin
Note: See TracBrowser for help on using the repository browser.