source: palm/trunk/SOURCE/read_var_list.f90 @ 2693

Last change on this file since 2693 was 2576, checked in by Giersch, 6 years ago

Bugfixes for restart runs

  • Property svn:keywords set to Id
File size: 41.1 KB
Line 
1!> @file read_var_list.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: read_var_list.f90 2576 2017-10-24 13:49:46Z raasch $
27! *** end *** marks the end of the standard parameter list of restart files
28! like it was before revision 2563. To skip also the variables of the modules 
29! wind_turbine_model_mod, flight_mod and synthetic_turbulence_generator_mod
30! three new functions has to be defined which are called in skip_var_list.
31! Adapted binary version number
32!
33! 2575 2017-10-24 09:57:58Z maronga
34! Renamed phi -> latitude, added longitude
35!
36! 2563 2017-10-19 15:36:10Z Giersch
37! CALL stg_read_restart_data moved to synthetic_turbulence_generator_mod and
38! CALL flight_read_restart_data moved to virtual_flights_mod. Furthermore
39! *** end default *** marks the end of the standard parameter list of restart
40! files and *** end *** marks the end of all parameter including module
41! parameter. Therefore the call of flight_skip_var_list becomes unnecessary.
42!
43! 2372 2017-08-25 12:37:32Z sward
44! y_shift added to vars, version no. increased
45!
46! 2365 2017-08-21 14:59:59Z kanani
47! Vertical grid nesting implemented (SadiqHuq)
48!
49! 2339 2017-08-07 13:55:26Z gronemeier
50! corrected timestamp in header
51!
52! 2338 2017-08-07 12:15:38Z gronemeier
53! Modularize 1D model
54!
55! 2320 2017-07-21 12:47:43Z suehring
56! Formatting adjustment
57!
58! 2265 2017-06-08 16:58:28Z schwenkel
59! Unused variables removed.
60!
61! 2259 2017-06-08 09:09:11Z gronemeier
62! Implemented synthetic turbulence generator
63!
64! 2233 2017-05-30 18:08:54Z suehring
65!
66! 2232 2017-05-30 17:47:52Z suehring
67! Replace wall_qflux, wall_sflux by wall_humidityflux and wall_scalarflux; add
68! wall_salinityflux
69! +tunnel_height, tunnel_length, tunnel_width_x, tunnel_width_y,
70!  tunnel_wall_depth
71!
72! 2042 2016-11-02 13:47:31Z suehring
73! Bugfix, read restart data for wall_heatflux, wall_qflux and wall_sflux
74!
75! 2000 2016-08-20 18:09:15Z knoop
76! Forced header and separation lines into 80 columns
77!
78! 1992 2016-08-12 15:14:59Z suehring
79! top_scalarflux added
80!
81! 1960 2016-07-12 16:34:24Z suehring
82! Separate humidity and passive scalar
83! Remove unused variables from ONLY list
84!
85! 1957 2016-07-07 10:43:48Z suehring
86! flight module added
87!
88! 1849 2016-04-08 11:33:18Z hoffmann
89! Adapted for modularization of microphysics
90!
91! 1833 2016-04-07 14:23:03Z raasch
92! spectra_mod added
93!
94! 1831 2016-04-07 13:15:51Z hoffmann
95! turbulence renamed collision_turbulence, drizzle renamed
96! cloud_water_sedimentation
97!
98! 1808 2016-04-05 19:44:00Z raasch
99! test output removed
100!
101! 1783 2016-03-06 18:36:17Z raasch
102! netcdf module name changed + related changes
103!
104! 1699 2015-10-29 08:02:35Z maronga
105! Bugfix: update of binary version from 3.9b to 4.0 was missing
106!
107! 1691 2015-10-26 16:17:44Z maronga
108! Added output of most_method, constant_flux_layer, zeta_min, zeta_max. Removed
109! output of prandtl_layer and rif_min, rif_max.
110!
111! 1682 2015-10-07 23:56:08Z knoop
112! Code annotations made doxygen readable
113!
114! 1615 2015-07-08 18:49:19Z suehring
115! Enable turbulent inflow for passive_scalar and humidity
116!
117! 1585 2015-04-30 07:05:52Z maronga
118! Adapted for RRTMG
119!
120! 1560 2015-03-06 10:48:54Z keck
121! +recycling_yshift
122!
123! 1522 2015-01-14 10:53:12Z keck
124! added query for checking if the advection scheme in the restart run is the
125! same as the advection scheme in the corresponding initial run
126!
127! 1502 2014-12-03 18:22:31Z kanani
128! Canopy module and parameters removed (parameters are always read from
129! canopy_par NAMELIST for initial and restart runs)
130!
131! 1496 2014-12-02 17:25:50Z maronga
132! Renamed "radiation" -> "cloud_top_radiation"
133!
134! 1484 2014-10-21 10:53:05Z kanani
135! Changes in the course of the canopy-model modularization:
136!   parameters alpha_lad, beta_lad, lai_beta added,
137!   module plant_canopy_model_mod added,
138!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
139!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff
140!
141! 1322 2014-03-20 16:38:49Z raasch
142! REAL functions provided with KIND-attribute
143!
144! 1320 2014-03-20 08:40:49Z raasch
145! ONLY-attribute added to USE-statements,
146! kind-parameters added to all INTEGER and REAL declaration statements,
147! kinds are defined in new module kinds,
148! old module precision_kind is removed,
149! revision history before 2012 removed,
150! comment fields (!:) to be used for variable explanations added to
151! all variable declaration statements
152!
153! 1308 2014-03-13 14:58:42Z fricke
154! +do2d_xy_time_count, do2d_xz_time_count, do2d_yz_time_count,
155! +do3d_time_count
156!
157! 1253 2013-11-07 10:48:12Z fricke
158! Bugfix: add ref_state to read_parts_of_var_list, otherwise ref_state
159! is zero for initializing_actions = 'cyclic_fill'
160!
161! 1241 2013-10-30 11:36:58Z heinze
162! +nudging
163! +large_scale_forcing
164!
165! 1195 2013-07-01 12:27:57Z heinze
166! Bugfix: allocate ref_state
167!
168! 1179 2013-06-14 05:57:58Z raasch
169! +ref_state
170!
171! 1115 2013-03-26 18:16:16Z hoffmann
172! unused variables removed
173!
174! 1092 2013-02-02 11:24:22Z raasch
175! unused variables removed
176!
177! 1065 2012-11-22 17:42:36Z hoffmann
178! +nc, c_sedimentation, limiter_sedimentation, turbulence
179! -mu_constant, mu_constant_value
180!
181! 1053 2012-11-13 17:11:03Z hoffmann
182! necessary expansions according to the two new prognostic equations (nr, qr)
183! of the two-moment cloud physics scheme:
184! +bc_*_b, +bc_*_t, +bc_*_t_val, *_init, *_surface, *_surface_initial_change,
185! +*_vertical_gradient, +*_vertical_gradient_level, *_vertical_gradient_level_ind,
186! +surface_waterflux_*
187!
188! in addition, steering parameters parameters of the two-moment cloud physics
189! scheme:
190! +cloud_scheme, +drizzle, +mu_constant, +mu_constant_value, +ventilation_effect
191!
192! 1036 2012-10-22 13:43:42Z raasch
193! code put under GPL (PALM 3.9)
194!
195! 1015 2012-09-27 09:23:24Z raasch
196! -adjust_mixing_length
197!
198! 1003 2012-09-14 14:35:53Z raasch
199! -grid_matching
200!
201! 1001 2012-09-13 14:08:46Z raasch
202! -cut_spline_overshoot, dt_fixed, last_dt_change, long_filter_factor,
203! overshoot_limit_*, ups_limit_*
204!
205! 978 2012-08-09 08:28:32Z fricke
206! -km_damp_max, outflow_damping_width
207! +pt_damping_factor, pt_damping_width
208! +z0h_factor
209!
210! 940 2012-07-09 14:31:00Z raasch
211! +neutral
212!
213! 927 2012-06-06 19:15:04Z raasch
214! +masking_method
215!
216! 849 2012-03-15 10:35:09Z raasch
217! first_call_advec_particles renamed first_call_lpm
218!
219! 824 2012-02-17 09:09:57Z raasch
220! +curvature_solution_effects
221!
222! Revision 1.1  1998/03/18 20:18:48  raasch
223! Initial revision
224!
225!
226! Description:
227! ------------
228!> Reading values of global control variables from restart-file (binary format)
229!------------------------------------------------------------------------------!
230 SUBROUTINE read_var_list
231
232
233    USE arrays_3d,                                                             &
234        ONLY:  inflow_damping_factor, mean_inflow_profiles, pt_init,           &
235               q_init, ref_state, s_init, sa_init, u_init, ug, v_init, vg
236
237    USE control_parameters
238
239    USE grid_variables,                                                        &
240        ONLY:  dx, dy
241
242    USE indices,                                                               &
243        ONLY:  nz, nx, nx_on_file, ny, ny_on_file
244
245    USE microphysics_mod,                                                      &
246        ONLY:  c_sedimentation, collision_turbulence,                          &
247               cloud_water_sedimentation, limiter_sedimentation,               &
248               nc_const, ventilation_effect
249
250    USE model_1d_mod,                                                          &
251        ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
252
253    USE netcdf_interface,                                                      &
254        ONLY:  netcdf_precision, output_for_t0
255
256    USE particle_attributes,                                                   &
257        ONLY:  curvature_solution_effects
258
259    USE pegrid
260
261    USE radiation_model_mod,                                                   &
262        ONLY:  time_radiation
263
264    USE spectra_mod,                                                           &
265        ONLY:  average_count_sp
266
267    USE statistics,                                                            &
268        ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
269               v_max, v_max_ijk, w_max, w_max_ijk
270
271    USE vertical_nesting_mod,                                                  &
272        ONLY:  vnest_init
273
274    IMPLICIT NONE
275
276    CHARACTER (LEN=10) ::  binary_version, version_on_file
277    CHARACTER (LEN=30) ::  variable_chr
278
279
280    CALL check_open( 13 )
281
282!
283!-- Make version number check first
284    READ ( 13 )  version_on_file
285    binary_version = '4.4'
286    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
287       WRITE( message_string, * ) 'version mismatch concerning control ', &
288                                  'variables',                            &
289                                  '&version on file    = "',              &
290                                  TRIM( version_on_file ), '"',           &
291                                  '&version on program = "',              &
292                                  TRIM( binary_version ), '"'
293       CALL message( 'read_var_list', 'PA0296', 1, 2, 0, 6, 0 )
294    ENDIF
295
296!
297!-- Read number of PEs and horizontal index bounds of all PEs used in previous
298!-- run
299    READ ( 13 )  variable_chr
300    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
301       WRITE( message_string, * ) 'numprocs not found in data from prior ', &
302                                  'run on PE ', myid
303       CALL message( 'read_var_list', 'PA0297', 1, 2, 0, 6, 0 )
304    ENDIF
305    READ ( 13 )  numprocs_previous_run
306
307    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
308       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
309    ENDIF
310
311    READ ( 13 )  variable_chr
312    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
313       WRITE( message_string, * ) 'hor_index_bounds not found in data from ', &
314                                  'prior run on PE ', myid
315       CALL message( 'read_var_list', 'PA0298', 1, 2, 0, 6, 0 )
316    ENDIF
317    READ ( 13 )  hor_index_bounds_previous_run
318
319!
320!-- Read vertical number of gridpoints and number of different areas used
321!-- for computing statistics. Allocate arrays depending on these values,
322!-- which are needed for the following read instructions.
323    READ ( 13 )  variable_chr
324    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
325       WRITE( message_string, * ) 'nz not found in data from prior run on PE ',&
326                                  myid
327       CALL message( 'read_var_list', 'PA0299', 1, 2, 0, 6, 0 )
328    ENDIF
329    READ ( 13 )  nz
330
331    READ ( 13 )  variable_chr
332    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
333       WRITE( message_string, * ) 'max_pr_user not found in data from ', &
334                    'prior run on PE ', myid
335       CALL message( 'read_var_list', 'PA0300', 1, 2, 0, 6, 0 )
336    ENDIF
337    READ ( 13 )  max_pr_user    ! This value is checked against the number of
338                                ! user profiles given for the current run
339                                ! in routine user_parin (it has to match)
340
341    READ ( 13 )  variable_chr
342    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
343       WRITE( message_string, * ) 'statistic_regions not found in data from ', &
344                    'prior run on PE ', myid
345       CALL message( 'read_var_list', 'PA0301', 1, 2, 0, 6, 0 )
346    ENDIF
347    READ ( 13 )  statistic_regions
348    IF ( .NOT. ALLOCATED( ug ) )  THEN
349       ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                       &
350                 v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),              &
351                 ref_state(0:nz+1), s_init(0:nz+1), sa_init(0:nz+1),           &
352                 hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions),        &
353                 hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) )
354    ENDIF
355
356!
357!-- Now read all control parameters:
358!-- Caution: When the following read instructions have been changed, the
359!-- -------  version number stored in the variable binary_version has to be
360!--          increased. The same changes must also be done in write_var_list.
361    READ ( 13 )  variable_chr
362    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
363
364       SELECT CASE ( TRIM( variable_chr ) )
365
366          CASE ( 'advected_distance_x' )
367             READ ( 13 )  advected_distance_x
368          CASE ( 'advected_distance_y' )
369             READ ( 13 )  advected_distance_y
370          CASE ( 'alpha_surface' )
371             READ ( 13 )  alpha_surface
372          CASE ( 'average_count_pr' )
373             READ ( 13 )  average_count_pr
374          CASE ( 'average_count_sp' )
375             READ ( 13 )  average_count_sp
376          CASE ( 'average_count_3d' )
377             READ ( 13 )  average_count_3d
378          CASE ( 'bc_e_b' )
379             READ ( 13 )  bc_e_b
380          CASE ( 'bc_lr' )
381             READ ( 13 )  bc_lr
382          CASE ( 'bc_ns' )
383             READ ( 13 )  bc_ns
384          CASE ( 'bc_p_b' )
385             READ ( 13 )  bc_p_b
386          CASE ( 'bc_p_t' )
387             READ ( 13 )  bc_p_t
388          CASE ( 'bc_pt_b' )
389             READ ( 13 )  bc_pt_b
390          CASE ( 'bc_pt_t' )
391             READ ( 13 )  bc_pt_t
392          CASE ( 'bc_pt_t_val' )
393             READ ( 13 )  bc_pt_t_val
394          CASE ( 'bc_q_b' )
395             READ ( 13 )  bc_q_b
396          CASE ( 'bc_q_t' )
397             READ ( 13 )  bc_q_t
398          CASE ( 'bc_q_t_val' )
399             READ ( 13 )  bc_q_t_val
400          CASE ( 'bc_s_b' )
401             READ ( 13 )  bc_s_b
402          CASE ( 'bc_s_t' )
403             READ ( 13 )  bc_s_t
404          CASE ( 'bc_sa_t' )
405             READ ( 13 )  bc_sa_t
406          CASE ( 'bc_uv_b' )
407             READ ( 13 )  bc_uv_b
408          CASE ( 'bc_uv_t' )
409             READ ( 13 )  bc_uv_t
410          CASE ( 'bottom_salinityflux' )
411             READ ( 13 )  bottom_salinityflux
412          CASE ( 'building_height' )
413             READ ( 13 )  building_height
414          CASE ( 'building_length_x' )
415             READ ( 13 )  building_length_x
416          CASE ( 'building_length_y' )
417             READ ( 13 )  building_length_y
418          CASE ( 'building_wall_left' )
419             READ ( 13 )  building_wall_left
420          CASE ( 'building_wall_south' )
421             READ ( 13 )  building_wall_south
422          CASE ( 'call_psolver_at_all_substeps' )
423             READ ( 13 )  call_psolver_at_all_substeps
424          CASE ( 'canyon_height' )
425             READ ( 13 )  canyon_height
426          CASE ( 'canyon_width_x' )
427             READ ( 13 )  canyon_width_x
428          CASE ( 'canyon_width_y' )
429             READ ( 13 )  canyon_width_y
430          CASE ( 'canyon_wall_left' )
431             READ ( 13 )  canyon_wall_left
432          CASE ( 'canyon_wall_south' )
433             READ ( 13 )  canyon_wall_south
434          CASE ( 'c_sedimentation' )
435             READ ( 13 )  c_sedimentation
436          CASE ( 'cfl_factor' )
437             READ ( 13 )  cfl_factor
438          CASE ( 'cloud_droplets' )
439             READ ( 13 )  cloud_droplets
440          CASE ( 'cloud_physics' )
441             READ ( 13 )  cloud_physics
442          CASE ( 'cloud_scheme' )
443             READ ( 13 )  cloud_scheme
444          CASE ( 'collective_wait' )
445             READ ( 13 )  collective_wait
446          CASE ( 'conserve_volume_flow' )
447             READ ( 13 )  conserve_volume_flow
448          CASE ( 'conserve_volume_flow_mode' )
449             READ ( 13 )  conserve_volume_flow_mode
450          CASE ( 'constant_flux_layer' )
451             READ ( 13 )  constant_flux_layer
452          CASE ( 'coupling_start_time' )
453             READ ( 13 )  coupling_start_time
454          CASE ( 'current_timestep_number' )
455             READ ( 13 )  current_timestep_number
456          CASE ( 'curvature_solution_effects' )
457             READ ( 13 )  curvature_solution_effects
458          CASE ( 'cycle_mg' )
459             READ ( 13 )  cycle_mg
460          CASE ( 'damp_level_1d' )
461             READ ( 13 )  damp_level_1d
462          CASE ( 'dissipation_1d' )
463             READ ( 13 )  dissipation_1d
464          CASE ( 'do2d_xy_time_count' )
465             READ ( 13 )  do2d_xy_time_count
466          CASE ( 'do2d_xz_time_count' )
467             READ ( 13 )  do2d_xz_time_count
468          CASE ( 'do2d_yz_time_count' )
469             READ ( 13 )  do2d_yz_time_count
470          CASE ( 'do3d_time_count' )
471             READ ( 13 )  do3d_time_count
472          CASE ( 'dp_external' )
473             READ ( 13 )  dp_external
474          CASE ( 'dp_level_b' )
475             READ ( 13 )  dp_level_b
476          CASE ( 'dp_smooth' )
477             READ ( 13 )  dp_smooth
478          CASE ( 'dpdxy' )
479             READ ( 13 )  dpdxy
480          CASE ( 'cloud_water_sedimentation' )
481             READ ( 13 )  cloud_water_sedimentation
482          CASE ( 'dt_pr_1d' )
483             READ ( 13 )  dt_pr_1d
484          CASE ( 'dt_run_control_1d' )
485             READ ( 13 )  dt_run_control_1d
486          CASE ( 'dt_3d' )
487             READ ( 13 )  dt_3d
488          CASE ( 'dvrp_filecount' )
489             READ ( 13 )  dvrp_filecount
490          CASE ( 'dx' )
491             READ ( 13 )  dx
492          CASE ( 'dy' )
493             READ ( 13 )  dy
494          CASE ( 'dz' )
495             READ ( 13 )  dz
496          CASE ( 'dz_max' )
497             READ ( 13 )  dz_max
498          CASE ( 'dz_stretch_factor' )
499             READ ( 13 )  dz_stretch_factor
500          CASE ( 'dz_stretch_level' )
501             READ ( 13 )  dz_stretch_level
502          CASE ( 'e_min' )
503             READ ( 13 )  e_min
504          CASE ( 'end_time_1d' )
505             READ ( 13 )  end_time_1d
506          CASE ( 'fft_method' )
507             READ ( 13 )  fft_method
508          CASE ( 'first_call_lpm' )
509             READ ( 13 )  first_call_lpm
510          CASE ( 'galilei_transformation' )
511             READ ( 13 )  galilei_transformation
512          CASE ( 'hom' )
513             READ ( 13 )  hom
514          CASE ( 'hom_sum' )
515             READ ( 13 )  hom_sum
516          CASE ( 'humidity' )
517             READ ( 13 )  humidity
518          CASE ( 'inflow_damping_factor' )
519             IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
520                ALLOCATE( inflow_damping_factor(0:nz+1) )
521             ENDIF
522             READ ( 13 )  inflow_damping_factor
523          CASE ( 'inflow_damping_height' )
524             READ ( 13 )  inflow_damping_height
525          CASE ( 'inflow_damping_width' )
526             READ ( 13 )  inflow_damping_width
527          CASE ( 'inflow_disturbance_begin' )
528             READ ( 13 )  inflow_disturbance_begin
529          CASE ( 'inflow_disturbance_end' )
530             READ ( 13 )  inflow_disturbance_end
531          CASE ( 'km_constant' )
532             READ ( 13 )  km_constant
533          CASE ( 'large_scale_forcing' )
534             READ ( 13 )  large_scale_forcing
535          CASE ( 'large_scale_subsidence' )
536             READ ( 13 )  large_scale_subsidence
537          CASE ( 'limiter_sedimentation' )
538             READ ( 13 )  limiter_sedimentation
539          CASE ( 'loop_optimization' )
540             READ ( 13 )  loop_optimization
541          CASE ( 'masking_method' )
542             READ ( 13 )  masking_method
543          CASE ( 'mean_inflow_profiles' )
544             IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
545                ALLOCATE( mean_inflow_profiles(0:nz+1,7) )
546             ENDIF
547             READ ( 13 )  mean_inflow_profiles
548          CASE ( 'mg_cycles' )
549             READ ( 13 )  mg_cycles
550          CASE ( 'mg_switch_to_pe0_level' )
551             READ ( 13 )  mg_switch_to_pe0_level
552          CASE ( 'mixing_length_1d' )
553             READ ( 13 )  mixing_length_1d
554          CASE ( 'momentum_advec' )
555             READ ( 13 )  momentum_advec
556          CASE ( 'most_method' )
557             READ ( 13 )  most_method
558          CASE ( 'nc_const' )
559             READ ( 13 )  nc_const
560          CASE ( 'netcdf_precision' )
561             READ ( 13 )  netcdf_precision
562          CASE ( 'neutral' )
563             READ ( 13 )  neutral
564          CASE ( 'ngsrb' )
565             READ ( 13 )  ngsrb
566          CASE ( 'nsor' )
567             READ ( 13 )  nsor
568          CASE ( 'nsor_ini' )
569             READ ( 13 )  nsor_ini
570          CASE ( 'nudging' )
571             READ ( 13 )  nudging
572          CASE ( 'num_leg' )
573             READ ( 13 )  num_leg
574          CASE ( 'nx' )
575             READ ( 13 )  nx
576             nx_on_file = nx
577          CASE ( 'ny' )
578             READ ( 13 )  ny
579             ny_on_file = ny
580          CASE ( 'ocean' )
581             READ ( 13 )  ocean
582          CASE ( 'old_dt' )
583             READ ( 13 )  old_dt
584          CASE ( 'omega' )
585             READ ( 13 )  omega
586          CASE ( 'omega_sor' )
587             READ ( 13 )  omega_sor
588          CASE ( 'output_for_t0' )
589             READ (13)    output_for_t0
590          CASE ( 'passive_scalar' )
591             READ ( 13 )  passive_scalar
592          CASE ( 'latitude' )
593             READ ( 13 )  latitude
594          CASE ( 'longitude' )
595             READ ( 13 )  longitude
596          CASE ( 'prandtl_number' )
597             READ ( 13 )  prandtl_number
598          CASE ( 'precipitation' )
599             READ ( 13 ) precipitation
600          CASE ( 'psolver' )
601             READ ( 13 )  psolver
602          CASE ( 'pt_damping_factor' )
603             READ ( 13 )  pt_damping_factor
604          CASE ( 'pt_damping_width' )
605             READ ( 13 )  pt_damping_width
606          CASE ( 'pt_init' )
607             READ ( 13 )  pt_init
608          CASE ( 'pt_reference' )
609             READ ( 13 )  pt_reference
610          CASE ( 'pt_surface' )
611             READ ( 13 )  pt_surface
612          CASE ( 'pt_surface_initial_change' )
613             READ ( 13 )  pt_surface_initial_change
614          CASE ( 'pt_vertical_gradient' )
615             READ ( 13 )  pt_vertical_gradient
616          CASE ( 'pt_vertical_gradient_level' )
617             READ ( 13 )  pt_vertical_gradient_level
618          CASE ( 'pt_vertical_gradient_level_ind' )
619             READ ( 13 )  pt_vertical_gradient_level_ind
620          CASE ( 'q_init' )
621             READ ( 13 )  q_init
622          CASE ( 'q_surface' )
623             READ ( 13 )  q_surface
624          CASE ( 'q_surface_initial_change' )
625             READ ( 13 )  q_surface_initial_change
626          CASE ( 'q_vertical_gradient' )
627             READ ( 13 )  q_vertical_gradient
628          CASE ( 'q_vertical_gradient_level' )
629             READ ( 13 )  q_vertical_gradient_level
630          CASE ( 'q_vertical_gradient_level_ind' )
631             READ ( 13 )  q_vertical_gradient_level_ind
632          CASE ( 'cloud_top_radiation' )
633             READ ( 13 )  cloud_top_radiation
634          CASE ( 'random_generator' )
635             READ ( 13 )  random_generator
636          CASE ( 'random_heatflux' )
637             READ ( 13 )  random_heatflux
638          CASE ( 'rayleigh_damping_factor' )
639             READ ( 13 )  rayleigh_damping_factor
640          CASE ( 'rayleigh_damping_height' )
641             READ ( 13 )  rayleigh_damping_height
642          CASE ( 'recycling_width' )
643             READ ( 13 )  recycling_width
644          CASE ( 'recycling_yshift' )
645             READ ( 13 ) recycling_yshift
646          CASE ( 'reference_state' )
647             READ ( 13 )  reference_state
648          CASE ( 'ref_state' )
649             READ ( 13 )  ref_state
650          CASE ( 'residual_limit' )
651             READ ( 13 )  residual_limit
652          CASE ( 'roughness_length' )
653             READ ( 13 )  roughness_length
654          CASE ( 'runnr' )
655             READ ( 13 )  runnr
656          CASE ( 'run_coupled' )
657             READ ( 13 )  run_coupled
658          CASE ( 's_init' )
659             READ ( 13 )  s_init
660          CASE ( 's_surface' )
661             READ ( 13 )  s_surface
662          CASE ( 's_surface_initial_change' )
663             READ ( 13 )  s_surface_initial_change
664          CASE ( 's_vertical_gradient' )
665             READ ( 13 )  s_vertical_gradient
666          CASE ( 's_vertical_gradient_level' )
667             READ ( 13 )  s_vertical_gradient_level
668          CASE ( 's_vertical_gradient_level_ind' )
669             READ ( 13 )  s_vertical_gradient_level_ind
670          CASE ( 'sa_init' )
671             READ ( 13 )  sa_init
672          CASE ( 'sa_surface' )
673             READ ( 13 )  sa_surface
674          CASE ( 'sa_vertical_gradient' )
675             READ ( 13 )  sa_vertical_gradient
676          CASE ( 'sa_vertical_gradient_level' )
677             READ ( 13 )  sa_vertical_gradient_level
678          CASE ( 'scalar_advec' )
679             READ ( 13 )  scalar_advec
680          CASE ( 'simulated_time' )
681             READ ( 13 )  simulated_time
682          CASE ( 'surface_heatflux' )
683             READ ( 13 )  surface_heatflux
684          CASE ( 'surface_pressure' )
685             READ ( 13 )  surface_pressure
686          CASE ( 'surface_scalarflux' )
687             READ ( 13 )  surface_scalarflux
688          CASE ( 'surface_waterflux' )
689             READ ( 13 )  surface_waterflux
690          CASE ( 'time_coupling' )
691             READ ( 13 )  time_coupling
692          CASE ( 'time_disturb' )
693             READ ( 13 )  time_disturb
694          CASE ( 'time_dopr' )
695             READ ( 13 )  time_dopr
696          CASE ( 'time_domask' )
697             READ ( 13 )  time_domask
698          CASE ( 'time_dopr_av' )
699             READ ( 13 )  time_dopr_av
700          CASE ( 'time_dopr_listing' )
701             READ ( 13 )  time_dopr_listing
702          CASE ( 'time_dopts' )
703             READ ( 13 )  time_dopts
704          CASE ( 'time_dosp' )
705             READ ( 13 )  time_dosp
706          CASE ( 'time_dots' )
707             READ ( 13 )  time_dots
708          CASE ( 'time_do2d_xy' )
709             READ ( 13 )  time_do2d_xy
710          CASE ( 'time_do2d_xz' )
711             READ ( 13 )  time_do2d_xz
712          CASE ( 'time_do2d_yz' )
713             READ ( 13 )  time_do2d_yz
714          CASE ( 'time_do3d' )
715             READ ( 13 )  time_do3d
716          CASE ( 'time_do_av' )
717             READ ( 13 )  time_do_av
718          CASE ( 'time_do_sla' )
719             READ ( 13 )  time_do_sla
720          CASE ( 'time_dvrp' )
721             READ ( 13 )  time_dvrp
722          CASE ( 'time_radiation' )
723             READ ( 13 )  time_radiation
724          CASE ( 'time_restart' )
725             READ ( 13 )  time_restart
726          CASE ( 'time_run_control' )
727             READ ( 13 )  time_run_control
728          CASE ( 'time_since_reference_point' )
729             READ ( 13 )  time_since_reference_point
730          CASE ( 'timestep_scheme' )
731             READ ( 13 )  timestep_scheme
732          CASE ( 'topography' )
733             READ ( 13 )  topography
734          CASE ( 'topography_grid_convention' )
735             READ ( 13 )  topography_grid_convention
736          CASE ( 'top_heatflux' )
737             READ ( 13 )  top_heatflux
738          CASE ( 'top_momentumflux_u' )
739             READ ( 13 )  top_momentumflux_u
740          CASE ( 'top_momentumflux_v' )
741             READ ( 13 )  top_momentumflux_v
742          CASE ( 'top_salinityflux' )
743             READ ( 13 )  top_salinityflux
744          CASE ( 'top_scalarflux' )
745             READ ( 13 )  top_scalarflux
746          CASE ( 'tsc' )
747             READ ( 13 )  tsc
748          CASE ( 'collision_turbulence' )
749             READ ( 13 )  collision_turbulence
750          CASE ( 'tunnel_height' )
751             READ ( 13 )  tunnel_height
752          CASE ( 'tunnel_length' )
753             READ ( 13 )  tunnel_length
754          CASE ( 'tunnel_width_x' )
755             READ ( 13 )  tunnel_width_x
756          CASE ( 'tunnel_width_y' )
757             READ ( 13 )  tunnel_width_y
758          CASE ( 'tunnel_wall_depth' )
759             READ ( 13 )  tunnel_wall_depth
760          CASE ( 'turbulent_inflow' )
761             READ ( 13 )  turbulent_inflow
762          CASE ( 'u_bulk' )
763             READ ( 13 )  u_bulk
764          CASE ( 'u_init' )
765             READ ( 13 )  u_init
766          CASE ( 'u_max' )
767             READ ( 13 )  u_max
768          CASE ( 'u_max_ijk' )
769             READ ( 13 )  u_max_ijk
770          CASE ( 'ug' )
771             READ ( 13 )  ug
772          CASE ( 'ug_surface' )
773             READ ( 13 )  ug_surface
774          CASE ( 'ug_vertical_gradient' )
775             READ ( 13 )  ug_vertical_gradient
776          CASE ( 'ug_vertical_gradient_level' )
777             READ ( 13 )  ug_vertical_gradient_level
778          CASE ( 'ug_vertical_gradient_level_ind' )
779             READ ( 13 )  ug_vertical_gradient_level_ind
780          CASE ( 'use_surface_fluxes' )
781             READ ( 13 )  use_surface_fluxes
782          CASE ( 'use_top_fluxes' )
783             READ ( 13 )  use_top_fluxes
784          CASE ( 'use_ug_for_galilei_tr' )
785             READ ( 13 )  use_ug_for_galilei_tr
786          CASE ( 'use_upstream_for_tke' )
787             READ ( 13 )  use_upstream_for_tke
788          CASE ( 'v_bulk' )
789             READ ( 13 )  v_bulk
790          CASE ( 'v_init' )
791             READ ( 13 )  v_init
792          CASE ( 'v_max' )
793             READ ( 13 )  v_max
794          CASE ( 'v_max_ijk' )
795             READ ( 13 )  v_max_ijk
796          CASE ( 'ventilation_effect' )
797             READ ( 13 )  ventilation_effect
798          CASE ( 'vg' )
799             READ ( 13 )  vg
800          CASE ( 'vg_surface' )
801             READ ( 13 )  vg_surface
802          CASE ( 'vg_vertical_gradient' )
803             READ ( 13 )  vg_vertical_gradient
804          CASE ( 'vg_vertical_gradient_level' )
805             READ ( 13 )  vg_vertical_gradient_level
806          CASE ( 'vg_vertical_gradient_level_ind' )
807             READ ( 13 )  vg_vertical_gradient_level_ind
808          CASE ( 'virtual_flight' )
809             READ ( 13 )  virtual_flight
810          CASE ( 'vnest_init' )
811             READ ( 13 )  vnest_init
812          CASE ( 'volume_flow_area' )
813             READ ( 13 )  volume_flow_area
814          CASE ( 'volume_flow_initial' )
815             READ ( 13 )  volume_flow_initial
816          CASE ( 'wall_adjustment' )
817             READ ( 13 )  wall_adjustment
818          CASE ( 'subs_vertical_gradient' )
819             READ ( 13 )  subs_vertical_gradient
820          CASE ( 'subs_vertical_gradient_level' )
821             READ ( 13 )  subs_vertical_gradient_level
822          CASE ( 'subs_vertical_gradient_level_i' )
823             READ ( 13 )  subs_vertical_gradient_level_i
824          CASE ( 'wall_heatflux' )
825             READ ( 13 )  wall_heatflux
826          CASE ( 'wall_humidityflux' )
827             READ ( 13 )  wall_humidityflux
828          CASE ( 'wall_scalarflux' )
829             READ ( 13 )  wall_scalarflux
830          CASE ( 'wall_salinityflux' )
831             READ ( 13 )  wall_salinityflux
832          CASE ( 'w_max' )
833             READ ( 13 )  w_max
834          CASE ( 'w_max_ijk' )
835             READ ( 13 )  w_max_ijk
836          CASE ( 'y_shift' )
837             READ ( 13 )  y_shift
838          CASE ( 'zeta_max' )
839             READ ( 13 )  zeta_max
840          CASE ( 'zeta_min' )
841             READ ( 13 )  zeta_min
842          CASE ( 'z0h_factor' )
843             READ ( 13 )  z0h_factor
844
845          CASE DEFAULT
846             WRITE( message_string, * ) 'unknown variable named "',         &
847                                        TRIM( variable_chr ), '" found in', &
848                                        ' data from prior run on PE ', myid
849             CALL message( 'read_var_list', 'PA0302', 1, 2, 0, 6, 0 )
850        END SELECT
851!
852!--    Read next string
853       READ ( 13 )  variable_chr
854
855    ENDDO
856
857
858 END SUBROUTINE read_var_list
859
860
861
862!------------------------------------------------------------------------------!
863! Description:
864! ------------
865!> Skipping the global control variables from restart-file (binary format)
866!> except some information needed when reading restart data from a previous
867!> run which used a smaller total domain or/and a different domain decomposition.
868!------------------------------------------------------------------------------!
869
870 SUBROUTINE read_parts_of_var_list
871
872
873    USE arrays_3d,                                                             &
874        ONLY:  inflow_damping_factor, mean_inflow_profiles, ref_state, ug, vg
875
876    USE control_parameters
877
878    USE indices,                                                               &
879        ONLY:  nz, nx, nx_on_file, ny, ny_on_file
880
881    USE kinds
882
883    USE pegrid
884
885    USE statistics,                                                            &
886        ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
887               v_max, v_max_ijk, w_max, w_max_ijk
888
889    IMPLICIT NONE
890
891    CHARACTER (LEN=10) ::  version_on_file
892    CHARACTER (LEN=20) ::  momentum_advec_check
893    CHARACTER (LEN=20) ::  scalar_advec_check
894    CHARACTER (LEN=30) ::  variable_chr
895    CHARACTER (LEN=1)  ::  cdum
896
897    INTEGER(iwp) ::  max_pr_user_on_file
898    INTEGER(iwp) ::  nz_on_file
899    INTEGER(iwp) ::  statistic_regions_on_file
900    INTEGER(iwp) ::  tmp_mpru
901    INTEGER(iwp) ::  tmp_sr
902
903    REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
904    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
905
906
907    CALL check_open( 13 )
908
909    READ ( 13 )  version_on_file
910
911
912!
913!-- Read number of PEs and horizontal index bounds of all PEs used in previous
914!-- run
915    READ ( 13 )  variable_chr
916    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
917       WRITE( message_string, * ) 'numprocs not found in data from prior ', &
918                                  'run on PE ', myid
919       CALL message( 'read_parts_of_var_list', 'PA0297', 1, 2, 0, 6, 0 )
920    ENDIF
921    READ ( 13 )  numprocs_previous_run
922
923    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
924       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
925    ENDIF
926
927    READ ( 13 )  variable_chr
928    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
929       WRITE( message_string, * ) 'hor_index_bounds not found in data from ', &
930                                  'prior run on PE ', myid
931       CALL message( 'read_parts_of_var_list', 'PA0298', 1, 2, 0, 6, 0 )
932    ENDIF
933    READ ( 13 )  hor_index_bounds_previous_run
934
935!
936!-- Read vertical number of gridpoints and number of different areas used
937!-- for computing statistics. Allocate arrays depending on these values,
938!-- which are needed for the following read instructions.
939    READ ( 13 )  variable_chr
940    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
941       message_string = 'nz not found in restart data file'
942       CALL message( 'read_parts_of_var_list', 'PA0303', 1, 2, 0, 6, 0 )
943    ENDIF
944    READ ( 13 )  nz_on_file
945    IF ( nz_on_file /= nz )  THEN
946       WRITE( message_string, * ) 'mismatch concerning number of ',      &
947                                  'gridpoints along z',                  &
948                                  '&nz on file    = "', nz_on_file, '"', &
949                                  '&nz from run   = "', nz, '"'
950       CALL message( 'read_parts_of_var_list', 'PA0304', 1, 2, 0, 6, 0 )
951    ENDIF
952
953    READ ( 13 )  variable_chr
954    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
955       message_string = 'max_pr_user not found in restart data file'
956       CALL message( 'read_parts_of_var_list', 'PA0305', 1, 2, 0, 6, 0 )
957    ENDIF
958    READ ( 13 )  max_pr_user_on_file
959    IF ( max_pr_user_on_file /= max_pr_user )  THEN
960       WRITE( message_string, * ) 'number of user profiles on res',           &
961                                  'tart data file differs from the current ', &
962                                  'run&max_pr_user on file    = "',           &
963                                  max_pr_user_on_file, '"',                   &
964                                  '&max_pr_user from run   = "',              &
965                                  max_pr_user, '"'
966       CALL message( 'read_parts_of_var_list', 'PA0306', 0, 0, 0, 6, 0 )
967       tmp_mpru = MIN( max_pr_user_on_file, max_pr_user )
968    ELSE
969       tmp_mpru = max_pr_user
970    ENDIF
971
972    READ ( 13 )  variable_chr
973    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
974       message_string = 'statistic_regions not found in restart data file'
975       CALL message( 'read_parts_of_var_list', 'PA0307', 1, 2, 0, 6, 0 )
976    ENDIF
977    READ ( 13 )  statistic_regions_on_file
978    IF ( statistic_regions_on_file /= statistic_regions )  THEN
979       WRITE( message_string, * ) 'statistic regions on restart data file ',&
980                                  'differ from the current run',            &
981                                  '&statistic regions on file    = "',      &
982                                  statistic_regions_on_file, '"',           &
983                                  '&statistic regions from run   = "',      &
984                                   statistic_regions, '"',                  &
985                                  '&statistic data may be lost!'
986       CALL message( 'read_parts_of_var_list', 'PA0308', 0, 1, 0, 6, 0 )
987       tmp_sr = MIN( statistic_regions_on_file, statistic_regions )
988    ELSE
989       tmp_sr = statistic_regions
990    ENDIF
991
992!
993!-- Now read and check some control parameters and skip the rest
994    READ ( 13 )  variable_chr
995
996    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
997
998       SELECT CASE ( TRIM( variable_chr ) )
999
1000          CASE ( 'average_count_pr' )
1001             READ ( 13 )  average_count_pr
1002             IF ( average_count_pr /= 0 )  THEN
1003                WRITE( message_string, * ) 'inflow profiles not temporally ',  &
1004                               'averaged. &Averaging will be done now using ', &
1005                               average_count_pr, ' samples.'
1006                CALL message( 'read_parts_of_var_list', 'PA0309', &
1007                                                                 0, 1, 0, 6, 0 )
1008             ENDIF
1009
1010          CASE ( 'hom' )
1011             ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file, &
1012                       0:statistic_regions_on_file) )
1013             READ ( 13 )  hom_on_file
1014             hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) = &
1015                          hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr)
1016             DEALLOCATE( hom_on_file )
1017
1018          CASE ( 'hom_sum' )
1019             ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file, &
1020                       0:statistic_regions_on_file) )
1021             READ ( 13 )  hom_sum_on_file
1022             hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) = &
1023                          hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr)
1024             DEALLOCATE( hom_sum_on_file )
1025
1026          CASE ( 'momentum_advec' )
1027             momentum_advec_check = momentum_advec
1028             READ ( 13 )  momentum_advec
1029             IF ( TRIM( momentum_advec_check ) /= TRIM( momentum_advec ) )  THEN
1030                WRITE( message_string, * ) 'momentum_advec of the restart run ',&
1031                               'differs from momentum_advec of the initial run.'
1032                CALL message( 'read_parts_of_var_list', 'PA0100', &
1033                                                                 1, 2, 0, 6, 0 )
1034             END IF
1035
1036          CASE ( 'nx' )
1037             READ ( 13 )  nx_on_file
1038
1039          CASE ( 'ny' )
1040             READ ( 13 )  ny_on_file
1041
1042          CASE ( 'ref_state' )
1043             READ ( 13 )  ref_state
1044
1045          CASE ( 'scalar_advec' )
1046             scalar_advec_check = scalar_advec
1047             READ ( 13 )  scalar_advec
1048             IF ( TRIM( scalar_advec_check ) /= TRIM( scalar_advec ) )  THEN
1049                WRITE( message_string, * ) 'scalar_advec of the restart run ', &
1050                               'differs from scalar_advec of the initial run.'
1051                CALL message( 'read_parts_of_var_list', 'PA0101', &
1052                                                                 1, 2, 0, 6, 0 )
1053             END IF
1054
1055          CASE DEFAULT
1056
1057             READ ( 13 )  cdum
1058
1059       END SELECT
1060
1061       READ ( 13 )  variable_chr
1062
1063    ENDDO
1064
1065!
1066!-- Calculate the temporal average of vertical profiles, if neccessary
1067    IF ( average_count_pr /= 0 )  THEN
1068       hom_sum = hom_sum / REAL( average_count_pr, KIND=wp )
1069    ENDIF
1070
1071
1072 END SUBROUTINE read_parts_of_var_list
1073
1074
1075
1076!------------------------------------------------------------------------------!
1077! Description:
1078! ------------
1079!> Skipping the global control variables from restart-file (binary format)
1080!------------------------------------------------------------------------------!
1081
1082 SUBROUTINE skip_var_list
1083
1084    USE control_parameters,                                                    &
1085        ONLY: wind_turbine, virtual_flight, synthetic_turbulence_generator
1086
1087    USE wind_turbine_model_mod,                                                &
1088        ONLY: wtm_skip_var_list
1089
1090    USE flight_mod,                                                            &
1091        ONLY: flight_skip_var_list
1092
1093    USE synthetic_turbulence_generator_mod,                                    &
1094        ONLY: stg_skip_var_list
1095
1096
1097    IMPLICIT NONE
1098
1099    CHARACTER (LEN=10) ::  version_on_file
1100    CHARACTER (LEN=30) ::  variable_chr
1101
1102    CHARACTER (LEN=1) ::  cdum
1103
1104
1105    READ ( 13 )  version_on_file
1106
1107    READ ( 13 )  variable_chr
1108
1109    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
1110
1111       READ ( 13 )  cdum
1112       READ ( 13 )  variable_chr
1113
1114    ENDDO
1115
1116!
1117!-- In case of virtual flights, skip also variables related to
1118!-- this module.
1119    IF ( wind_turbine )  CALL wtm_skip_var_list
1120
1121!
1122!-- In case of virtual flights, skip also variables related to
1123!-- this module.
1124    IF ( virtual_flight )  CALL flight_skip_var_list
1125
1126!
1127!-- In case of virtual flights, skip also variables related to
1128!-- this module.
1129    IF ( synthetic_turbulence_generator )  CALL stg_skip_var_list
1130
1131
1132 END SUBROUTINE skip_var_list
Note: See TracBrowser for help on using the repository browser.