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

Last change on this file since 2232 was 2232, checked in by suehring, 7 years ago

Adjustments according new topography and surface-modelling concept implemented

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