source: palm/trunk/SOURCE/parin.f90

Last change on this file was 4872, checked in by raasch, 3 years ago

internal switches removed from namelists

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