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

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

Separate balance equations for humidity and passive_scalar

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