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

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

cloud physics variables renamed

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