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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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