source: palm/tags/release-3.2b/SOURCE/read_var_list.f90 @ 1552

Last change on this file since 1552 was 90, checked in by raasch, 17 years ago

New:
---
Calculation and output of user-defined profiles. New &userpar parameters data_output_pr_user and max_pr_user.

check_parameters, flow_statistics, modules, parin, read_var_list, user_interface, write_var_list

Changed:


Division through dt_3d replaced by multiplication of the inverse. For performance optimisation, this is done in the loop calculating the divergence instead of using a seperate loop. (pres.f90) var_hom and var_sum renamed pr_palm.

data_output_profiles, flow_statistics, init_3d_model, modules, parin, pres, read_var_list, run_control, time_integration

Errors:


Bugfix: work_fft*_vec removed from some PRIVATE-declarations (poisfft).

Bugfix: field_chr renamed field_char (user_interface).

Bugfix: output of use_upstream_for_tke (header).

header, poisfft, user_interface

  • Property svn:keywords set to Id
File size: 15.9 KB
Line 
1 SUBROUTINE read_var_list
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: read_var_list.f90 90 2007-05-30 09:18:47Z maronga $
11!
12! 87 2007-05-22 15:46:47Z raasch
13! +max_pr_user (version 3.1), var_hom renamed pr_palm
14!
15! 75 2007-03-22 09:54:05Z raasch
16! +loop_optimization, pt_reference, moisture renamed humidity
17!
18! 20 2007-02-26 00:12:32Z raasch
19! +top_heatflux, use_top_fluxes
20!
21! RCS Log replace by Id keyword, revision history cleaned up
22!
23! Revision 1.34  2006/08/22 14:14:27  raasch
24! +dz_max
25!
26! Revision 1.1  1998/03/18 20:18:48  raasch
27! Initial revision
28!
29!
30! Description:
31! ------------
32! Reading values of control variables from restart-file (binary format)
33!------------------------------------------------------------------------------!
34
35    USE arrays_3d
36    USE averaging
37    USE control_parameters
38    USE grid_variables
39    USE indices
40    USE model_1d
41    USE pegrid
42    USE profil_parameter
43    USE statistics
44
45    IMPLICIT NONE
46
47    CHARACTER (LEN=10) ::  binary_version, version_on_file
48    CHARACTER (LEN=30) ::  variable_chr
49
50    INTEGER            ::  max_pr_user_on_file
51   
52    CALL check_open( 13 )
53
54!
55!-- Make version number check first
56    READ ( 13 )  version_on_file
57    binary_version = '3.1'
58    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
59       IF ( myid == 0 )  THEN
60          PRINT*, '+++ read_var_list: version mismatch concerning control', &
61                  ' variables'
62          PRINT*, '                   version on file    = "', &
63                  TRIM( version_on_file ), '"'
64          PRINT*, '                   version on program = "', &
65                  TRIM( binary_version ), '"'
66       ENDIF
67       CALL local_stop
68    ENDIF
69
70!
71!-- Read vertical number of gridpoints and number of different areas used
72!-- for computing statistics. Allocate arrays depending on these values,
73!-- which are needed for the following read instructions.
74    READ ( 13 )  variable_chr
75    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
76       PRINT*, '+++ read_var_list: nz not found in data from prior run on PE ',&
77               myid
78       CALL local_stop
79    ENDIF
80    READ ( 13 )  nz
81
82    READ ( 13 )  variable_chr
83    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
84       PRINT*, '+++ read_var_list: max_pr_user not found in data from ', &
85                    'prior run on PE ', myid
86       CALL local_stop
87    ENDIF
88    READ ( 13 )  max_pr_user_on_file
89    IF ( max_pr_user_on_file /= max_pr_user )  THEN
90       IF ( myid == 0 )  THEN
91          PRINT*, '+++ read_var_list: version mismatch concerning maximum', &
92                  ' number of user profiles'
93          PRINT*, '                   max_pr_user on file    = "', &
94                  max_pr_user_on_file, '"'
95          PRINT*, '                   max_pr_user from run   = "', &
96                  max_pr_user, '"'
97       ENDIF
98       CALL local_stop
99    ENDIF
100
101    READ ( 13 )  variable_chr
102    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
103       PRINT*, '+++ read_var_list: statistic_regions not found in data from ', &
104                    'prior run on PE ', myid
105       CALL local_stop
106    ENDIF
107    READ ( 13 )  statistic_regions
108    ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1), v_init(0:nz+1), & 
109              pt_init(0:nz+1), q_init(0:nz+1), &
110              hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions) )
111
112!
113!-- Now read all control parameters:
114!-- Caution: When the following read instructions have been changed, the
115!-- -------  version number stored in the variable binary_version has to be
116!--          increased. The same changes must also be done in write_var_list.
117    READ ( 13 )  variable_chr
118    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
119
120       SELECT CASE ( TRIM( variable_chr ) )
121
122          CASE ( 'adjust_mixing_length' )
123             READ ( 13 )  adjust_mixing_length
124          CASE ( 'advected_distance_x' )
125             READ ( 13 )  advected_distance_x
126          CASE ( 'advected_distance_y' )
127             READ ( 13 )  advected_distance_y
128          CASE ( 'alpha_surface' )
129             READ ( 13 )  alpha_surface
130          CASE ( 'average_count_pr' )
131             READ ( 13 )  average_count_pr
132          CASE ( 'average_count_sp' )
133             READ ( 13 )  average_count_sp
134          CASE ( 'average_count_3d' )
135             READ ( 13 )  average_count_3d
136          CASE ( 'bc_e_b' )
137             READ ( 13 )  bc_e_b
138          CASE ( 'bc_lr' )
139             READ ( 13 )  bc_lr
140          CASE ( 'bc_ns' )
141             READ ( 13 )  bc_ns
142          CASE ( 'bc_p_b' )
143             READ ( 13 )  bc_p_b
144          CASE ( 'bc_p_t' )
145             READ ( 13 )  bc_p_t
146          CASE ( 'bc_pt_b' )
147             READ ( 13 )  bc_pt_b
148          CASE ( 'bc_pt_t' )
149             READ ( 13 )  bc_pt_t
150          CASE ( 'bc_pt_t_val' )
151             READ ( 13 )  bc_pt_t_val
152          CASE ( 'bc_q_b' )
153             READ ( 13 )  bc_q_b
154          CASE ( 'bc_q_t' )
155             READ ( 13 )  bc_q_t
156          CASE ( 'bc_q_t_val' )
157             READ ( 13 )  bc_q_t_val
158          CASE ( 'bc_s_b' )
159             READ ( 13 )  bc_s_b
160          CASE ( 'bc_s_t' )
161             READ ( 13 )  bc_s_t
162          CASE ( 'bc_uv_b' )
163             READ ( 13 )  bc_uv_b
164          CASE ( 'bc_uv_t' )
165             READ ( 13 )  bc_uv_t
166          CASE ( 'building_height' )
167             READ ( 13 )  building_height
168          CASE ( 'building_length_x' )
169             READ ( 13 )  building_length_x
170          CASE ( 'building_length_y' )
171             READ ( 13 )  building_length_y
172          CASE ( 'building_wall_left' )
173             READ ( 13 )  building_wall_left
174          CASE ( 'building_wall_south' )
175             READ ( 13 )  building_wall_south
176          CASE ( 'cloud_droplets' )
177             READ ( 13 )  cloud_droplets
178          CASE ( 'cloud_physics' )
179             READ ( 13 )  cloud_physics
180          CASE ( 'conserve_volume_flow' )
181             READ ( 13 )  conserve_volume_flow
182          CASE ( 'current_timestep_number' )
183             READ ( 13 )  current_timestep_number
184          CASE ( 'cut_spline_overshoot' )
185             READ ( 13 )  cut_spline_overshoot
186          CASE ( 'damp_level_1d' )
187             READ ( 13 )  damp_level_1d
188          CASE ( 'dissipation_1d' )
189             READ ( 13 )  dissipation_1d
190          CASE ( 'dt_fixed' )
191             READ ( 13 )  dt_fixed
192          CASE ( 'dt_pr_1d' )
193             READ ( 13 )  dt_pr_1d
194          CASE ( 'dt_run_control_1d' )
195             READ ( 13 )  dt_run_control_1d
196          CASE ( 'dt_3d' )
197             READ ( 13 )  dt_3d
198          CASE ( 'dvrp_filecount' )
199             READ ( 13 )  dvrp_filecount
200          CASE ( 'dx' )
201             READ ( 13 )  dx
202          CASE ( 'dy' )
203             READ ( 13 )  dy
204          CASE ( 'dz' )
205             READ ( 13 )  dz
206          CASE ( 'dz_max' )
207             READ ( 13 )  dz_max
208          CASE ( 'dz_stretch_factor' )
209             READ ( 13 )  dz_stretch_factor
210          CASE ( 'dz_stretch_level' )
211             READ ( 13 )  dz_stretch_level
212          CASE ( 'e_min' )
213             READ ( 13 )  e_min
214          CASE ( 'end_time_1d' )
215             READ ( 13 )  end_time_1d
216          CASE ( 'fft_method' )
217             READ ( 13 )  fft_method
218          CASE ( 'first_call_advec_particles' )
219             READ ( 13 )  first_call_advec_particles
220          CASE ( 'galilei_transformation' )
221             READ ( 13 )  galilei_transformation
222          CASE ( 'grid_matching' )
223             READ ( 13 )  grid_matching
224          CASE ( 'hom' )
225             READ ( 13 )  hom
226          CASE ( 'inflow_disturbance_begin' )
227             READ ( 13 )  inflow_disturbance_begin
228          CASE ( 'inflow_disturbance_end' )
229             READ ( 13 )  inflow_disturbance_end
230          CASE ( 'km_constant' )
231             READ ( 13 )  km_constant
232          CASE ( 'km_damp_max' )
233             READ ( 13 )  km_damp_max
234          CASE ( 'last_dt_change' )
235             READ ( 13 )  last_dt_change
236          CASE ( 'long_filter_factor' )
237             READ ( 13 )  long_filter_factor
238          CASE ( 'loop_optimization' )
239             READ ( 13 )  loop_optimization
240          CASE ( 'mixing_length_1d' )
241             READ ( 13 )  mixing_length_1d
242          CASE ( 'humidity' )
243             READ ( 13 )  humidity
244          CASE ( 'momentum_advec' )
245             READ ( 13 )  momentum_advec
246          CASE ( 'netcdf_precision' )
247             READ ( 13 )  netcdf_precision
248          CASE ( 'npex' )
249             READ ( 13 )  npex
250          CASE ( 'npey' )
251             READ ( 13 )  npey
252          CASE ( 'nsor_ini' )
253             READ ( 13 )  nsor_ini
254          CASE ( 'nx' )
255             READ ( 13 )  nx
256          CASE ( 'ny' )
257             READ ( 13 )  ny
258          CASE ( 'old_dt' )
259             READ ( 13 )  old_dt
260          CASE ( 'omega' )
261             READ ( 13 )  omega
262          CASE ( 'outflow_damping_width' )
263             READ ( 13 )  outflow_damping_width
264          CASE ( 'overshoot_limit_e' )
265             READ ( 13 )  overshoot_limit_e
266          CASE ( 'overshoot_limit_pt' )
267             READ ( 13 )  overshoot_limit_pt
268          CASE ( 'overshoot_limit_u' )
269             READ ( 13 )  overshoot_limit_u
270          CASE ( 'overshoot_limit_v' )
271             READ ( 13 )  overshoot_limit_v
272          CASE ( 'overshoot_limit_w' )
273             READ ( 13 )  overshoot_limit_w
274          CASE ( 'passive_scalar' )
275             READ ( 13 )  passive_scalar
276          CASE ( 'phi' )
277             READ ( 13 )  phi
278          CASE ( 'prandtl_layer' )
279             READ ( 13 )  prandtl_layer
280          CASE ( 'precipitation' )
281             READ ( 13 ) precipitation
282          CASE ( 'pt_init' )
283             READ ( 13 )  pt_init
284          CASE ( 'pt_reference' )
285             READ ( 13 )  pt_reference
286          CASE ( 'pt_surface' )
287             READ ( 13 )  pt_surface
288          CASE ( 'pt_surface_initial_change' )
289             READ ( 13 )  pt_surface_initial_change
290          CASE ( 'pt_vertical_gradient' )
291             READ ( 13 )  pt_vertical_gradient
292          CASE ( 'pt_vertical_gradient_level' )
293             READ ( 13 )  pt_vertical_gradient_level
294          CASE ( 'pt_vertical_gradient_level_ind' )
295             READ ( 13 )  pt_vertical_gradient_level_ind
296          CASE ( 'q_init' )
297             READ ( 13 )  q_init
298          CASE ( 'q_surface' )
299             READ ( 13 )  q_surface
300          CASE ( 'q_surface_initial_change' )
301             READ ( 13 )  q_surface_initial_change
302          CASE ( 'q_vertical_gradient' )
303             READ ( 13 )  q_vertical_gradient
304          CASE ( 'q_vertical_gradient_level' )
305             READ ( 13 )  q_vertical_gradient_level
306          CASE ( 'q_vertical_gradient_level_ind' )
307             READ ( 13 )  q_vertical_gradient_level_ind
308          CASE ( 'radiation' )
309             READ ( 13 )  radiation
310          CASE ( 'random_generator' )
311             READ ( 13 )  random_generator
312          CASE ( 'random_heatflux' )
313             READ ( 13 )  random_heatflux
314          CASE ( 'rif_max' )
315             READ ( 13 )  rif_max
316          CASE ( 'rif_min' )
317             READ ( 13 )  rif_min
318          CASE ( 'roughness_length' )
319             READ ( 13 )  roughness_length
320          CASE ( 'runnr' )
321             READ ( 13 )  runnr
322          CASE ( 'scalar_advec' )
323             READ ( 13 )  scalar_advec
324          CASE ( 'simulated_time' )
325             READ ( 13 )  simulated_time
326          CASE ( 'surface_heatflux' )
327             READ ( 13 )  surface_heatflux
328          CASE ( 'surface_pressure' )
329             READ ( 13 )  surface_pressure
330          CASE ( 'surface_scalarflux' )
331             READ ( 13 )  surface_scalarflux             
332          CASE ( 'surface_waterflux' )
333             READ ( 13 )  surface_waterflux             
334          CASE ( 's_surface' )
335             READ ( 13 )  s_surface
336          CASE ( 's_surface_initial_change' )
337             READ ( 13 )  s_surface_initial_change
338          CASE ( 's_vertical_gradient' )
339             READ ( 13 )  s_vertical_gradient
340          CASE ( 's_vertical_gradient_level' )
341             READ ( 13 )  s_vertical_gradient_level
342          CASE ( 'time_disturb' )
343             READ ( 13 )  time_disturb
344          CASE ( 'time_dopr' )
345             READ ( 13 )  time_dopr
346          CASE ( 'time_dopr_av' )
347             READ ( 13 )  time_dopr_av
348          CASE ( 'time_dopr_listing' )
349             READ ( 13 )  time_dopr_listing
350          CASE ( 'time_dopts' )
351             READ ( 13 )  time_dopts
352          CASE ( 'time_dosp' )
353             READ ( 13 )  time_dosp
354          CASE ( 'time_dots' )
355             READ ( 13 )  time_dots
356          CASE ( 'time_do2d_xy' )
357             READ ( 13 )  time_do2d_xy
358          CASE ( 'time_do2d_xz' )
359             READ ( 13 )  time_do2d_xz
360          CASE ( 'time_do2d_yz' )
361             READ ( 13 )  time_do2d_yz
362          CASE ( 'time_do3d' )
363             READ ( 13 )  time_do3d
364          CASE ( 'time_do_av' )
365             READ ( 13 )  time_do_av
366          CASE ( 'time_do_sla' )
367             READ ( 13 )  time_do_sla
368          CASE ( 'time_dvrp' )
369             READ ( 13 )  time_dvrp
370          CASE ( 'time_restart' )
371             READ ( 13 )  time_restart
372          CASE ( 'time_run_control' )
373             READ ( 13 )  time_run_control
374          CASE ( 'timestep_scheme' )
375             READ ( 13 )  timestep_scheme
376          CASE ( 'topography' )
377             READ ( 13 )  topography
378          CASE ( 'top_heatflux' )
379             READ ( 13 )  top_heatflux
380          CASE ( 'tsc' )
381             READ ( 13 )  tsc
382          CASE ( 'u_init' )
383             READ ( 13 )  u_init
384          CASE ( 'u_max' )
385             READ ( 13 )  u_max
386          CASE ( 'u_max_ijk' )
387             READ ( 13 )  u_max_ijk
388          CASE ( 'ug' )
389             READ ( 13 )  ug
390          CASE ( 'ug_surface' )
391             READ ( 13 )  ug_surface
392          CASE ( 'ug_vertical_gradient' )
393             READ ( 13 )  ug_vertical_gradient
394          CASE ( 'ug_vertical_gradient_level' )
395             READ ( 13 )  ug_vertical_gradient_level
396          CASE ( 'ug_vertical_gradient_level_ind' )
397             READ ( 13 )  ug_vertical_gradient_level_ind
398          CASE ( 'ups_limit_e' )
399             READ ( 13 )  ups_limit_e
400          CASE ( 'ups_limit_pt' )
401             READ ( 13 )  ups_limit_pt
402          CASE ( 'ups_limit_u' )
403             READ ( 13 )  ups_limit_u
404          CASE ( 'ups_limit_v' )
405             READ ( 13 )  ups_limit_v
406          CASE ( 'ups_limit_w' )
407             READ ( 13 )  ups_limit_w
408          CASE ( 'use_surface_fluxes' )
409             READ ( 13 )  use_surface_fluxes
410          CASE ( 'use_top_fluxes' )
411             READ ( 13 )  use_top_fluxes
412          CASE ( 'use_ug_for_galilei_tr' )
413             READ ( 13 )  use_ug_for_galilei_tr
414          CASE ( 'use_upstream_for_tke' )
415             READ ( 13 )  use_upstream_for_tke
416          CASE ( 'v_init' )
417             READ ( 13 )  v_init
418          CASE ( 'v_max' )
419             READ ( 13 )  v_max
420          CASE ( 'v_max_ijk' )
421             READ ( 13 )  v_max_ijk
422          CASE ( 'vg' )
423             READ ( 13 )  vg
424          CASE ( 'vg_surface' )
425             READ ( 13 )  vg_surface
426          CASE ( 'vg_vertical_gradient' )
427             READ ( 13 )  vg_vertical_gradient
428          CASE ( 'vg_vertical_gradient_level' )
429             READ ( 13 )  vg_vertical_gradient_level
430          CASE ( 'vg_vertical_gradient_level_ind' )
431             READ ( 13 )  vg_vertical_gradient_level_ind
432          CASE ( 'wall_adjustment' )
433             READ ( 13 )  wall_adjustment
434          CASE ( 'w_max' )
435             READ ( 13 )  w_max
436          CASE ( 'w_max_ijk' )
437             READ ( 13 )  w_max_ijk
438          CASE ( 'time-series-quantities' )
439             READ ( 13 )  cross_ts_uymax, cross_ts_uymax_computed, &
440                          cross_ts_uymin, cross_ts_uymin_computed
441
442          CASE DEFAULT
443             PRINT*, '+++ read_var_list: unknown variable named "', &
444                     TRIM( variable_chr ), '" found in'
445             PRINT*, '                   data from prior run on PE ', myid
446             CALL local_stop
447        END SELECT
448!
449!--    Read next string
450       READ ( 13 )  variable_chr
451
452    ENDDO
453
454
455 END SUBROUTINE read_var_list
Note: See TracBrowser for help on using the repository browser.