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

Last change on this file since 1993 was 1993, checked in by suehring, 8 years ago

last commit documented

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