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

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

flight module added

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