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

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

Prescribing scalar flux at model top; several bugfixes concering data output of scalars and output of flight data

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