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

Last change on this file since 4843 was 4842, checked in by raasch, 3 years ago

reading of namelist file and actions in case of namelist errors revised so that statement labels and goto statements are not required any more, deprecated namelists removed

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