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

Last change on this file since 1809 was 1809, checked in by raasch, 8 years ago

last commit documented

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