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

Last change on this file since 2014 was 2001, checked in by knoop, 8 years ago

last commit documented

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