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

Last change on this file since 1699 was 1699, checked in by maronga, 8 years ago

bugfix: binary version increased

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