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

Last change on this file since 1952 was 1852, checked in by hoffmann, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 37.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!
22!
23! Former revisions:
24! -----------------
25! $Id: read_var_list.f90 1852 2016-04-08 14:07:36Z 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 grid_variables,                                                        &
179        ONLY:  dx, dy
180
181    USE indices,                                                               &
182        ONLY:  nz, nx, nx_on_file, ny, ny_on_file
183
184    USE microphysics_mod,                                                      &
185        ONLY:  c_sedimentation, collision_turbulence,                          &
186               cloud_water_sedimentation, limiter_sedimentation,               &
187               nc_const, ventilation_effect
188
189    USE model_1d,                                                              &
190        ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
191
192    USE netcdf_interface,                                                      &
193        ONLY:  netcdf_precision, output_for_t0
194
195    USE particle_attributes,                                                   &
196        ONLY:  curvature_solution_effects, time_sort_particles
197
198    USE pegrid
199
200    USE radiation_model_mod,                                                   &
201        ONLY:  time_radiation
202
203    USE spectra_mod,                                                           &
204        ONLY:  average_count_sp
205
206    USE statistics,                                                            &
207        ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
208               v_max, v_max_ijk, w_max, w_max_ijk
209
210
211    IMPLICIT NONE
212
213    CHARACTER (LEN=10) ::  binary_version, version_on_file
214    CHARACTER (LEN=30) ::  variable_chr
215
216
217    CALL check_open( 13 )
218
219!
220!-- Make version number check first
221    READ ( 13 )  version_on_file
222    binary_version = '4.1'
223    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
224       WRITE( message_string, * ) 'version mismatch concerning control ', &
225                                  'variables',                            &
226                                  '&version on file    = "',              &
227                                  TRIM( version_on_file ), '"',           &
228                                  '&version on program = "',              &
229                                  TRIM( binary_version ), '"'
230       CALL message( 'read_var_list', 'PA0296', 1, 2, 0, 6, 0 )
231    ENDIF
232
233!
234!-- Read number of PEs and horizontal index bounds of all PEs used in previous
235!-- run
236    READ ( 13 )  variable_chr
237    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
238       WRITE( message_string, * ) 'numprocs not found in data from prior ', &
239                                  'run on PE ', myid
240       CALL message( 'read_var_list', 'PA0297', 1, 2, 0, 6, 0 )
241    ENDIF
242    READ ( 13 )  numprocs_previous_run
243
244    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
245       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
246    ENDIF
247
248    READ ( 13 )  variable_chr
249    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
250       WRITE( message_string, * ) 'hor_index_bounds not found in data from ', &
251                                  'prior run on PE ', myid
252       CALL message( 'read_var_list', 'PA0298', 1, 2, 0, 6, 0 )
253    ENDIF
254    READ ( 13 )  hor_index_bounds_previous_run
255
256!
257!-- Read vertical number of gridpoints and number of different areas used
258!-- for computing statistics. Allocate arrays depending on these values,
259!-- which are needed for the following read instructions.
260    READ ( 13 )  variable_chr
261    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
262       WRITE( message_string, * ) 'nz not found in data from prior run on PE ',&
263                                  myid
264       CALL message( 'read_var_list', 'PA0299', 1, 2, 0, 6, 0 )
265    ENDIF
266    READ ( 13 )  nz
267
268    READ ( 13 )  variable_chr
269    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
270       WRITE( message_string, * ) 'max_pr_user not found in data from ', &
271                    'prior run on PE ', myid
272       CALL message( 'read_var_list', 'PA0300', 1, 2, 0, 6, 0 )
273    ENDIF
274    READ ( 13 )  max_pr_user    ! This value is checked against the number of
275                                ! user profiles given for the current run
276                                ! in routine user_parin (it has to match)
277
278    READ ( 13 )  variable_chr
279    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
280       WRITE( message_string, * ) 'statistic_regions not found in data from ', &
281                    'prior run on PE ', myid
282       CALL message( 'read_var_list', 'PA0301', 1, 2, 0, 6, 0 )
283    ENDIF
284    READ ( 13 )  statistic_regions
285    IF ( .NOT. ALLOCATED( ug ) )  THEN
286       ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                       &
287                 v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),              &
288                 ref_state(0:nz+1), sa_init(0:nz+1),                           &
289                 hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions),        &
290                 hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) )
291    ENDIF
292
293!
294!-- Now read all control parameters:
295!-- Caution: When the following read instructions have been changed, the
296!-- -------  version number stored in the variable binary_version has to be
297!--          increased. The same changes must also be done in write_var_list.
298    READ ( 13 )  variable_chr
299    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
300
301       SELECT CASE ( TRIM( variable_chr ) )
302
303          CASE ( 'advected_distance_x' )
304             READ ( 13 )  advected_distance_x
305          CASE ( 'advected_distance_y' )
306             READ ( 13 )  advected_distance_y
307          CASE ( 'alpha_surface' )
308             READ ( 13 )  alpha_surface
309          CASE ( 'average_count_pr' )
310             READ ( 13 )  average_count_pr
311          CASE ( 'average_count_sp' )
312             READ ( 13 )  average_count_sp
313          CASE ( 'average_count_3d' )
314             READ ( 13 )  average_count_3d
315          CASE ( 'bc_e_b' )
316             READ ( 13 )  bc_e_b
317          CASE ( 'bc_lr' )
318             READ ( 13 )  bc_lr
319          CASE ( 'bc_ns' )
320             READ ( 13 )  bc_ns
321          CASE ( 'bc_p_b' )
322             READ ( 13 )  bc_p_b
323          CASE ( 'bc_p_t' )
324             READ ( 13 )  bc_p_t
325          CASE ( 'bc_pt_b' )
326             READ ( 13 )  bc_pt_b
327          CASE ( 'bc_pt_t' )
328             READ ( 13 )  bc_pt_t
329          CASE ( 'bc_pt_t_val' )
330             READ ( 13 )  bc_pt_t_val
331          CASE ( 'bc_q_b' )
332             READ ( 13 )  bc_q_b
333          CASE ( 'bc_q_t' )
334             READ ( 13 )  bc_q_t
335          CASE ( 'bc_q_t_val' )
336             READ ( 13 )  bc_q_t_val
337          CASE ( 'bc_s_b' )
338             READ ( 13 )  bc_s_b
339          CASE ( 'bc_s_t' )
340             READ ( 13 )  bc_s_t
341          CASE ( 'bc_sa_t' )
342             READ ( 13 )  bc_sa_t
343          CASE ( 'bc_uv_b' )
344             READ ( 13 )  bc_uv_b
345          CASE ( 'bc_uv_t' )
346             READ ( 13 )  bc_uv_t
347          CASE ( 'bottom_salinityflux' )
348             READ ( 13 )  bottom_salinityflux
349          CASE ( 'building_height' )
350             READ ( 13 )  building_height
351          CASE ( 'building_length_x' )
352             READ ( 13 )  building_length_x
353          CASE ( 'building_length_y' )
354             READ ( 13 )  building_length_y
355          CASE ( 'building_wall_left' )
356             READ ( 13 )  building_wall_left
357          CASE ( 'building_wall_south' )
358             READ ( 13 )  building_wall_south
359          CASE ( 'call_psolver_at_all_substeps' )
360             READ ( 13 )  call_psolver_at_all_substeps
361          CASE ( 'canyon_height' )
362             READ ( 13 )  canyon_height
363          CASE ( 'canyon_width_x' )
364             READ ( 13 )  canyon_width_x
365          CASE ( 'canyon_width_y' )
366             READ ( 13 )  canyon_width_y
367          CASE ( 'canyon_wall_left' )
368             READ ( 13 )  canyon_wall_left
369          CASE ( 'canyon_wall_south' )
370             READ ( 13 )  canyon_wall_south
371          CASE ( 'c_sedimentation' )
372             READ ( 13 )  c_sedimentation
373          CASE ( 'cfl_factor' )
374             READ ( 13 )  cfl_factor
375          CASE ( 'cloud_droplets' )
376             READ ( 13 )  cloud_droplets
377          CASE ( 'cloud_physics' )
378             READ ( 13 )  cloud_physics
379          CASE ( 'cloud_scheme' )
380             READ ( 13 )  cloud_scheme
381          CASE ( 'collective_wait' )
382             READ ( 13 )  collective_wait
383          CASE ( 'conserve_volume_flow' )
384             READ ( 13 )  conserve_volume_flow
385          CASE ( 'conserve_volume_flow_mode' )
386             READ ( 13 )  conserve_volume_flow_mode
387          CASE ( 'constant_flux_layer' )
388             READ ( 13 )  constant_flux_layer
389          CASE ( 'coupling_start_time' )
390             READ ( 13 )  coupling_start_time
391          CASE ( 'current_timestep_number' )
392             READ ( 13 )  current_timestep_number
393          CASE ( 'curvature_solution_effects' )
394             READ ( 13 )  curvature_solution_effects
395          CASE ( 'cycle_mg' )
396             READ ( 13 )  cycle_mg
397          CASE ( 'damp_level_1d' )
398             READ ( 13 )  damp_level_1d
399          CASE ( 'dissipation_1d' )
400             READ ( 13 )  dissipation_1d
401          CASE ( 'do2d_xy_time_count' )
402             READ ( 13 )  do2d_xy_time_count
403          CASE ( 'do2d_xz_time_count' )
404             READ ( 13 )  do2d_xz_time_count
405          CASE ( 'do2d_yz_time_count' )
406             READ ( 13 )  do2d_yz_time_count
407          CASE ( 'do3d_time_count' )
408             READ ( 13 )  do3d_time_count
409          CASE ( 'dp_external' )
410             READ ( 13 )  dp_external
411          CASE ( 'dp_level_b' )
412             READ ( 13 )  dp_level_b
413          CASE ( 'dp_smooth' )
414             READ ( 13 )  dp_smooth
415          CASE ( 'dpdxy' )
416             READ ( 13 )  dpdxy
417          CASE ( 'cloud_water_sedimentation' )
418             READ ( 13 )  cloud_water_sedimentation
419          CASE ( 'dt_pr_1d' )
420             READ ( 13 )  dt_pr_1d
421          CASE ( 'dt_run_control_1d' )
422             READ ( 13 )  dt_run_control_1d
423          CASE ( 'dt_3d' )
424             READ ( 13 )  dt_3d
425          CASE ( 'dvrp_filecount' )
426             READ ( 13 )  dvrp_filecount
427          CASE ( 'dx' )
428             READ ( 13 )  dx
429          CASE ( 'dy' )
430             READ ( 13 )  dy
431          CASE ( 'dz' )
432             READ ( 13 )  dz
433          CASE ( 'dz_max' )
434             READ ( 13 )  dz_max
435          CASE ( 'dz_stretch_factor' )
436             READ ( 13 )  dz_stretch_factor
437          CASE ( 'dz_stretch_level' )
438             READ ( 13 )  dz_stretch_level
439          CASE ( 'e_min' )
440             READ ( 13 )  e_min
441          CASE ( 'end_time_1d' )
442             READ ( 13 )  end_time_1d
443          CASE ( 'fft_method' )
444             READ ( 13 )  fft_method
445          CASE ( 'first_call_lpm' )
446             READ ( 13 )  first_call_lpm
447          CASE ( 'galilei_transformation' )
448             READ ( 13 )  galilei_transformation
449          CASE ( 'hom' )
450             READ ( 13 )  hom
451          CASE ( 'hom_sum' )
452             READ ( 13 )  hom_sum
453          CASE ( 'humidity' )
454             READ ( 13 )  humidity
455          CASE ( 'inflow_damping_factor' )
456             IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
457                ALLOCATE( inflow_damping_factor(0:nz+1) )
458             ENDIF
459             READ ( 13 )  inflow_damping_factor
460          CASE ( 'inflow_damping_height' )
461             READ ( 13 )  inflow_damping_height
462          CASE ( 'inflow_damping_width' )
463             READ ( 13 )  inflow_damping_width
464          CASE ( 'inflow_disturbance_begin' )
465             READ ( 13 )  inflow_disturbance_begin
466          CASE ( 'inflow_disturbance_end' )
467             READ ( 13 )  inflow_disturbance_end
468          CASE ( 'km_constant' )
469             READ ( 13 )  km_constant
470          CASE ( 'large_scale_forcing' )
471             READ ( 13 )  large_scale_forcing
472           CASE ( 'large_scale_subsidence' )
473             READ ( 13 )  large_scale_subsidence
474          CASE ( 'limiter_sedimentation' )
475             READ ( 13 )  limiter_sedimentation
476          CASE ( 'loop_optimization' )
477             READ ( 13 )  loop_optimization
478          CASE ( 'masking_method' )
479             READ ( 13 )  masking_method
480          CASE ( 'mean_inflow_profiles' )
481             IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
482                ALLOCATE( mean_inflow_profiles(0:nz+1,6) )
483             ENDIF
484             READ ( 13 )  mean_inflow_profiles
485          CASE ( 'mg_cycles' )
486             READ ( 13 )  mg_cycles
487          CASE ( 'mg_switch_to_pe0_level' )
488             READ ( 13 )  mg_switch_to_pe0_level
489          CASE ( 'mixing_length_1d' )
490             READ ( 13 )  mixing_length_1d
491          CASE ( 'momentum_advec' )
492             READ ( 13 )  momentum_advec
493          CASE ( 'most_method' )
494             READ ( 13 )  most_method
495          CASE ( 'nc_const' )
496             READ ( 13 )  nc_const
497          CASE ( 'netcdf_precision' )
498             READ ( 13 )  netcdf_precision
499          CASE ( 'neutral' )
500             READ ( 13 )  neutral
501          CASE ( 'ngsrb' )
502             READ ( 13 )  ngsrb
503          CASE ( 'nsor' )
504             READ ( 13 )  nsor
505          CASE ( 'nsor_ini' )
506             READ ( 13 )  nsor_ini
507          CASE ( 'nudging' )
508             READ ( 13 )  nudging
509          CASE ( 'nx' )
510             READ ( 13 )  nx
511             nx_on_file = nx
512          CASE ( 'ny' )
513             READ ( 13 )  ny
514             ny_on_file = ny
515          CASE ( 'ocean' )
516             READ ( 13 )  ocean
517          CASE ( 'old_dt' )
518             READ ( 13 )  old_dt
519          CASE ( 'omega' )
520             READ ( 13 )  omega
521          CASE ( 'omega_sor' )
522             READ ( 13 )  omega_sor
523          CASE ( 'output_for_t0' )
524             READ (13)    output_for_t0
525          CASE ( 'passive_scalar' )
526             READ ( 13 )  passive_scalar
527          CASE ( 'phi' )
528             READ ( 13 )  phi
529          CASE ( 'prandtl_number' )
530             READ ( 13 )  prandtl_number
531          CASE ( 'precipitation' )
532             READ ( 13 ) precipitation
533          CASE ( 'psolver' )
534             READ ( 13 )  psolver
535          CASE ( 'pt_damping_factor' )
536             READ ( 13 )  pt_damping_factor
537          CASE ( 'pt_damping_width' )
538             READ ( 13 )  pt_damping_width
539          CASE ( 'pt_init' )
540             READ ( 13 )  pt_init
541          CASE ( 'pt_reference' )
542             READ ( 13 )  pt_reference
543          CASE ( 'pt_surface' )
544             READ ( 13 )  pt_surface
545          CASE ( 'pt_surface_initial_change' )
546             READ ( 13 )  pt_surface_initial_change
547          CASE ( 'pt_vertical_gradient' )
548             READ ( 13 )  pt_vertical_gradient
549          CASE ( 'pt_vertical_gradient_level' )
550             READ ( 13 )  pt_vertical_gradient_level
551          CASE ( 'pt_vertical_gradient_level_ind' )
552             READ ( 13 )  pt_vertical_gradient_level_ind
553          CASE ( 'q_init' )
554             READ ( 13 )  q_init
555          CASE ( 'q_surface' )
556             READ ( 13 )  q_surface
557          CASE ( 'q_surface_initial_change' )
558             READ ( 13 )  q_surface_initial_change
559          CASE ( 'q_vertical_gradient' )
560             READ ( 13 )  q_vertical_gradient
561          CASE ( 'q_vertical_gradient_level' )
562             READ ( 13 )  q_vertical_gradient_level
563          CASE ( 'q_vertical_gradient_level_ind' )
564             READ ( 13 )  q_vertical_gradient_level_ind
565          CASE ( 'cloud_top_radiation' )
566             READ ( 13 )  cloud_top_radiation
567          CASE ( 'random_generator' )
568             READ ( 13 )  random_generator
569          CASE ( 'random_heatflux' )
570             READ ( 13 )  random_heatflux
571          CASE ( 'rayleigh_damping_factor' )
572             READ ( 13 )  rayleigh_damping_factor
573          CASE ( 'rayleigh_damping_height' )
574             READ ( 13 )  rayleigh_damping_height
575          CASE ( 'recycling_width' )
576             READ ( 13 )  recycling_width
577          CASE ( 'recycling_yshift' )
578             READ ( 13 ) recycling_yshift
579          CASE ( 'reference_state' )
580             READ ( 13 )  reference_state
581          CASE ( 'ref_state' )
582             READ ( 13 )  ref_state
583          CASE ( 'residual_limit' )
584             READ ( 13 )  residual_limit
585          CASE ( 'roughness_length' )
586             READ ( 13 )  roughness_length
587          CASE ( 'runnr' )
588             READ ( 13 )  runnr
589          CASE ( 'run_coupled' )
590             READ ( 13 )  run_coupled
591          CASE ( 'sa_init' )
592             READ ( 13 )  sa_init
593          CASE ( 'sa_surface' )
594             READ ( 13 )  sa_surface
595          CASE ( 'sa_vertical_gradient' )
596             READ ( 13 )  sa_vertical_gradient
597          CASE ( 'sa_vertical_gradient_level' )
598             READ ( 13 )  sa_vertical_gradient_level
599          CASE ( 'scalar_advec' )
600             READ ( 13 )  scalar_advec
601          CASE ( 'simulated_time' )
602             READ ( 13 )  simulated_time
603          CASE ( 'surface_heatflux' )
604             READ ( 13 )  surface_heatflux
605          CASE ( 'surface_pressure' )
606             READ ( 13 )  surface_pressure
607          CASE ( 'surface_scalarflux' )
608             READ ( 13 )  surface_scalarflux             
609          CASE ( 'surface_waterflux' )
610             READ ( 13 )  surface_waterflux     
611          CASE ( 's_surface' )
612             READ ( 13 )  s_surface
613          CASE ( 's_surface_initial_change' )
614             READ ( 13 )  s_surface_initial_change
615          CASE ( 's_vertical_gradient' )
616             READ ( 13 )  s_vertical_gradient
617          CASE ( 's_vertical_gradient_level' )
618             READ ( 13 )  s_vertical_gradient_level
619          CASE ( 'time_coupling' )
620             READ ( 13 )  time_coupling
621          CASE ( 'time_disturb' )
622             READ ( 13 )  time_disturb
623          CASE ( 'time_dopr' )
624             READ ( 13 )  time_dopr
625          CASE ( 'time_domask' )
626             READ ( 13 )  time_domask
627          CASE ( 'time_dopr_av' )
628             READ ( 13 )  time_dopr_av
629          CASE ( 'time_dopr_listing' )
630             READ ( 13 )  time_dopr_listing
631          CASE ( 'time_dopts' )
632             READ ( 13 )  time_dopts
633          CASE ( 'time_dosp' )
634             READ ( 13 )  time_dosp
635          CASE ( 'time_dots' )
636             READ ( 13 )  time_dots
637          CASE ( 'time_do2d_xy' )
638             READ ( 13 )  time_do2d_xy
639          CASE ( 'time_do2d_xz' )
640             READ ( 13 )  time_do2d_xz
641          CASE ( 'time_do2d_yz' )
642             READ ( 13 )  time_do2d_yz
643          CASE ( 'time_do3d' )
644             READ ( 13 )  time_do3d
645          CASE ( 'time_do_av' )
646             READ ( 13 )  time_do_av
647          CASE ( 'time_do_sla' )
648             READ ( 13 )  time_do_sla
649          CASE ( 'time_dvrp' )
650             READ ( 13 )  time_dvrp
651          CASE ( 'time_radiation' )
652             READ ( 13 )  time_radiation
653          CASE ( 'time_restart' )
654             READ ( 13 )  time_restart
655          CASE ( 'time_run_control' )
656             READ ( 13 )  time_run_control
657          CASE ( 'time_since_reference_point' )
658             READ ( 13 )  time_since_reference_point
659          CASE ( 'time_sort_particles' )
660             READ ( 13 )  time_sort_particles
661          CASE ( 'timestep_scheme' )
662             READ ( 13 )  timestep_scheme
663          CASE ( 'topography' )
664             READ ( 13 )  topography
665          CASE ( 'topography_grid_convention' )
666             READ ( 13 )  topography_grid_convention
667          CASE ( 'top_heatflux' )
668             READ ( 13 )  top_heatflux
669          CASE ( 'top_momentumflux_u' )
670             READ ( 13 )  top_momentumflux_u
671          CASE ( 'top_momentumflux_v' )
672             READ ( 13 )  top_momentumflux_v
673          CASE ( 'top_salinityflux' )
674             READ ( 13 )  top_salinityflux
675          CASE ( 'tsc' )
676             READ ( 13 )  tsc
677          CASE ( 'collision_turbulence' )
678             READ ( 13 )  collision_turbulence
679          CASE ( 'turbulent_inflow' )
680             READ ( 13 )  turbulent_inflow
681          CASE ( 'u_bulk' )
682             READ ( 13 )  u_bulk
683          CASE ( 'u_init' )
684             READ ( 13 )  u_init
685          CASE ( 'u_max' )
686             READ ( 13 )  u_max
687          CASE ( 'u_max_ijk' )
688             READ ( 13 )  u_max_ijk
689          CASE ( 'ug' )
690             READ ( 13 )  ug
691          CASE ( 'ug_surface' )
692             READ ( 13 )  ug_surface
693          CASE ( 'ug_vertical_gradient' )
694             READ ( 13 )  ug_vertical_gradient
695          CASE ( 'ug_vertical_gradient_level' )
696             READ ( 13 )  ug_vertical_gradient_level
697          CASE ( 'ug_vertical_gradient_level_ind' )
698             READ ( 13 )  ug_vertical_gradient_level_ind
699          CASE ( 'use_surface_fluxes' )
700             READ ( 13 )  use_surface_fluxes
701          CASE ( 'use_top_fluxes' )
702             READ ( 13 )  use_top_fluxes
703          CASE ( 'use_ug_for_galilei_tr' )
704             READ ( 13 )  use_ug_for_galilei_tr
705          CASE ( 'use_upstream_for_tke' )
706             READ ( 13 )  use_upstream_for_tke
707          CASE ( 'v_bulk' )
708             READ ( 13 )  v_bulk
709          CASE ( 'v_init' )
710             READ ( 13 )  v_init
711          CASE ( 'v_max' )
712             READ ( 13 )  v_max
713          CASE ( 'v_max_ijk' )
714             READ ( 13 )  v_max_ijk
715          CASE ( 'ventilation_effect' )
716             READ ( 13 )  ventilation_effect
717          CASE ( 'vg' )
718             READ ( 13 )  vg
719          CASE ( 'vg_surface' )
720             READ ( 13 )  vg_surface
721          CASE ( 'vg_vertical_gradient' )
722             READ ( 13 )  vg_vertical_gradient
723          CASE ( 'vg_vertical_gradient_level' )
724             READ ( 13 )  vg_vertical_gradient_level
725          CASE ( 'vg_vertical_gradient_level_ind' )
726             READ ( 13 )  vg_vertical_gradient_level_ind
727          CASE ( 'volume_flow_area' )
728             READ ( 13 )  volume_flow_area
729          CASE ( 'volume_flow_initial' )
730             READ ( 13 )  volume_flow_initial
731          CASE ( 'wall_adjustment' )
732             READ ( 13 )  wall_adjustment
733          CASE ( 'subs_vertical_gradient' )
734             READ ( 13 )  subs_vertical_gradient
735          CASE ( 'subs_vertical_gradient_level' )
736             READ ( 13 )  subs_vertical_gradient_level
737          CASE ( 'subs_vertical_gradient_level_i' )
738             READ ( 13 )  subs_vertical_gradient_level_i
739          CASE ( 'w_max' )
740             READ ( 13 )  w_max
741          CASE ( 'w_max_ijk' )
742             READ ( 13 )  w_max_ijk
743          CASE ( 'zeta_max' )
744             READ ( 13 )  zeta_max
745          CASE ( 'zeta_min' )
746             READ ( 13 )  zeta_min
747          CASE ( 'z0h_factor' )
748             READ ( 13 )  z0h_factor
749
750          CASE DEFAULT
751             WRITE( message_string, * ) 'unknown variable named "',         &
752                                        TRIM( variable_chr ), '" found in', &
753                                        ' data from prior run on PE ', myid 
754             CALL message( 'read_var_list', 'PA0302', 1, 2, 0, 6, 0 )
755        END SELECT
756!
757!--    Read next string
758       READ ( 13 )  variable_chr
759
760    ENDDO
761
762
763 END SUBROUTINE read_var_list
764
765
766
767!------------------------------------------------------------------------------!
768! Description:
769! ------------
770!> Skipping the global control variables from restart-file (binary format)
771!> except some information needed when reading restart data from a previous
772!> run which used a smaller total domain or/and a different domain decomposition.
773!------------------------------------------------------------------------------!
774 
775 SUBROUTINE read_parts_of_var_list
776
777
778    USE arrays_3d,                                                             &
779        ONLY:  inflow_damping_factor, mean_inflow_profiles, pt_init,           &
780               q_init, ref_state, sa_init, u_init, ug, v_init, vg
781
782    USE control_parameters
783
784    USE indices,                                                               &
785        ONLY:  nz, nx, nx_on_file, ny, ny_on_file
786
787    USE kinds
788
789    USE pegrid
790
791    USE statistics,                                                            &
792        ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
793               v_max, v_max_ijk, w_max, w_max_ijk
794
795    IMPLICIT NONE
796
797    CHARACTER (LEN=10) ::  version_on_file
798    CHARACTER (LEN=20) ::  momentum_advec_check
799    CHARACTER (LEN=20) ::  scalar_advec_check
800    CHARACTER (LEN=30) ::  variable_chr
801    CHARACTER (LEN=1)  ::  cdum
802
803    INTEGER(iwp) ::  max_pr_user_on_file
804    INTEGER(iwp) ::  nz_on_file
805    INTEGER(iwp) ::  statistic_regions_on_file
806    INTEGER(iwp) ::  tmp_mpru
807    INTEGER(iwp) ::  tmp_sr
808
809    REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
810    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
811
812
813    CALL check_open( 13 )
814
815    READ ( 13 )  version_on_file
816
817!
818!-- Read number of PEs and horizontal index bounds of all PEs used in previous
819!-- run
820    READ ( 13 )  variable_chr
821    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
822       WRITE( message_string, * ) 'numprocs not found in data from prior ', &
823                                  'run on PE ', myid
824       CALL message( 'read_parts_of_var_list', 'PA0297', 1, 2, 0, 6, 0 )
825    ENDIF
826    READ ( 13 )  numprocs_previous_run
827
828    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
829       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
830    ENDIF
831
832    READ ( 13 )  variable_chr
833    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
834       WRITE( message_string, * ) 'hor_index_bounds not found in data from ', &
835                                  'prior run on PE ', myid
836       CALL message( 'read_parts_of_var_list', 'PA0298', 1, 2, 0, 6, 0 )
837    ENDIF
838    READ ( 13 )  hor_index_bounds_previous_run
839
840!
841!-- Read vertical number of gridpoints and number of different areas used
842!-- for computing statistics. Allocate arrays depending on these values,
843!-- which are needed for the following read instructions.
844    READ ( 13 )  variable_chr
845    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
846       message_string = 'nz not found in restart data file'
847       CALL message( 'read_parts_of_var_list', 'PA0303', 1, 2, 0, 6, 0 )
848    ENDIF
849    READ ( 13 )  nz_on_file
850    IF ( nz_on_file /= nz )  THEN
851       WRITE( message_string, * ) 'mismatch concerning number of ',      &
852                                  'gridpoints along z',                  &
853                                  '&nz on file    = "', nz_on_file, '"', &
854                                  '&nz from run   = "', nz, '"'
855       CALL message( 'read_parts_of_var_list', 'PA0304', 1, 2, 0, 6, 0 )
856    ENDIF
857
858    READ ( 13 )  variable_chr
859    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
860       message_string = 'max_pr_user not found in restart data file'
861       CALL message( 'read_parts_of_var_list', 'PA0305', 1, 2, 0, 6, 0 )
862    ENDIF
863    READ ( 13 )  max_pr_user_on_file
864    IF ( max_pr_user_on_file /= max_pr_user )  THEN
865       WRITE( message_string, * ) 'number of user profiles on res',           &
866                                  'tart data file differs from the current ', &
867                                  'run&max_pr_user on file    = "',           &
868                                  max_pr_user_on_file, '"',                   &
869                                  '&max_pr_user from run   = "',              &
870                                  max_pr_user, '"'
871       CALL message( 'read_parts_of_var_list', 'PA0306', 0, 0, 0, 6, 0 )
872       tmp_mpru = MIN( max_pr_user_on_file, max_pr_user )
873    ELSE
874       tmp_mpru = max_pr_user
875    ENDIF
876
877    READ ( 13 )  variable_chr
878    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
879       message_string = 'statistic_regions not found in restart data file'
880       CALL message( 'read_parts_of_var_list', 'PA0307', 1, 2, 0, 6, 0 )
881    ENDIF
882    READ ( 13 )  statistic_regions_on_file
883    IF ( statistic_regions_on_file /= statistic_regions )  THEN
884       WRITE( message_string, * ) 'statistic regions on restart data file ',& 
885                                  'differ from the current run',            &
886                                  '&statistic regions on file    = "',      &
887                                  statistic_regions_on_file, '"',           &
888                                  '&statistic regions from run   = "',      &
889                                   statistic_regions, '"',                  &
890                                  '&statistic data may be lost!'
891       CALL message( 'read_parts_of_var_list', 'PA0308', 0, 1, 0, 6, 0 )
892       tmp_sr = MIN( statistic_regions_on_file, statistic_regions )
893    ELSE
894       tmp_sr = statistic_regions
895    ENDIF
896
897
898!
899!-- Now read and check some control parameters and skip the rest
900    READ ( 13 )  variable_chr
901
902    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
903
904       SELECT CASE ( TRIM( variable_chr ) )
905
906          CASE ( 'average_count_pr' )
907             READ ( 13 )  average_count_pr
908             IF ( average_count_pr /= 0 )  THEN
909                WRITE( message_string, * ) 'inflow profiles not temporally ',  &
910                               'averaged. &Averaging will be done now using ', &
911                               average_count_pr, ' samples.'
912                CALL message( 'read_parts_of_var_list', 'PA0309', &
913                                                                 0, 1, 0, 6, 0 )
914             ENDIF
915
916          CASE ( 'hom' )
917             ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file, &
918                       0:statistic_regions_on_file) )
919             READ ( 13 )  hom_on_file
920             hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) = &
921                          hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr)
922             DEALLOCATE( hom_on_file )
923
924          CASE ( 'hom_sum' )
925             ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file, &
926                       0:statistic_regions_on_file) )
927             READ ( 13 )  hom_sum_on_file
928             hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) = &
929                          hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr)
930             DEALLOCATE( hom_sum_on_file )
931
932          CASE ( 'momentum_advec' )
933             momentum_advec_check = momentum_advec
934             READ ( 13 )  momentum_advec
935             IF ( TRIM( momentum_advec_check ) /= TRIM( momentum_advec ) )  THEN
936                WRITE( message_string, * ) 'momentum_advec of the restart run ',&
937                               'differs from momentum_advec of the initial run.'
938                CALL message( 'read_parts_of_var_list', 'PA0100', &
939                                                                 1, 2, 0, 6, 0 )
940             END IF                           
941             
942          CASE ( 'nx' )
943             READ ( 13 )  nx_on_file
944
945          CASE ( 'ny' )
946             READ ( 13 )  ny_on_file
947
948          CASE ( 'ref_state' )
949             READ ( 13 )  ref_state
950
951          CASE ( 'scalar_advec' )
952             scalar_advec_check = scalar_advec
953             READ ( 13 )  scalar_advec
954             IF ( TRIM( scalar_advec_check ) /= TRIM( scalar_advec ) )  THEN
955                WRITE( message_string, * ) 'scalar_advec of the restart run ', &
956                               'differs from scalar_advec of the initial run.'
957                CALL message( 'read_parts_of_var_list', 'PA0101', &
958                                                                 1, 2, 0, 6, 0 )
959             END IF             
960             
961          CASE DEFAULT
962
963             READ ( 13 )  cdum
964
965       END SELECT
966
967       READ ( 13 )  variable_chr
968
969    ENDDO
970
971!
972!-- Calculate the temporal average of vertical profiles, if neccessary
973    IF ( average_count_pr /= 0 )  THEN
974       hom_sum = hom_sum / REAL( average_count_pr, KIND=wp )
975    ENDIF
976
977
978 END SUBROUTINE read_parts_of_var_list
979
980
981
982!------------------------------------------------------------------------------!
983! Description:
984! ------------
985!> Skipping the global control variables from restart-file (binary format)
986!------------------------------------------------------------------------------!
987 
988 SUBROUTINE skip_var_list
989
990
991    IMPLICIT NONE
992
993    CHARACTER (LEN=10) ::  version_on_file
994    CHARACTER (LEN=30) ::  variable_chr
995
996    CHARACTER (LEN=1) ::  cdum
997
998
999    READ ( 13 )  version_on_file
1000
1001    READ ( 13 )  variable_chr
1002
1003    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
1004
1005       READ ( 13 )  cdum
1006       READ ( 13 )  variable_chr
1007
1008    ENDDO
1009
1010
1011 END SUBROUTINE skip_var_list
Note: See TracBrowser for help on using the repository browser.