source: palm/tags/release-3.2b/SOURCE/read_3d_binary.f90 @ 1614

Last change on this file since 1614 was 77, checked in by raasch, 17 years ago

New:
---

particle reflection from vertical walls implemented, particle SGS model adjusted to walls

Wall functions for vertical walls now include diabatic conditions. New subroutines wall_fluxes, wall_fluxes_e. New 4D-array rif_wall.

new d3par-parameter netcdf_64bit_3d to switch on 64bit offset only for 3D files

new d3par-parameter dt_max to define the maximum value for the allowed timestep

new inipar-parameter loop_optimization to control the loop optimization method

new inipar-parameter pt_refrence. If given, this value is used as the reference that in buoyancy terms (otherwise, the instantaneous horizontally averaged temperature is used).

new user interface user_advec_particles

new initializing action "by_user" calls user_init_3d_model and allows the initial setting of all 3d arrays

topography height informations are stored on arrays zu_s_inner and zw_w_inner and output to the 2d/3d NetCDF files

samples added to the user interface which show how to add user-define time series quantities.

calculation/output of precipitation amount, precipitation rate and z0 (by setting "pra*", "prr*", "z0*" with data_output). The time interval on which the precipitation amount is defined is set by new d3par-parameter precipitation_amount_interval

unit 9 opened for debug output (file DEBUG_<pe#>)

Makefile, advec_particles, average_3d_data, buoyancy, calc_precipitation, check_open, check_parameters, data_output_2d, diffusion_e, diffusion_u, diffusion_v, diffusion_w, diffusivities, header, impact_of_latent_heat, init_particles, init_3d_model, modules, netcdf, parin, production_e, read_var_list, read_3d_binary, sum_up_3d_data, user_interface, write_var_list, write_3d_binary

New: wall_fluxes

Changed:


General revision of non-cyclic horizontal boundary conditions: radiation boundary conditions are now used instead of Neumann conditions at the outflow (calculation needs velocity values for t-dt, which are stored on new arrays u_m_l, u_m_r, etc.), calculation of mean outflow is not needed any more, volume flow control is added for the outflow boundary (currently only for the north boundary!!), additional gridpoints along x and y (uxrp, vynp) are not needed any more, routine "boundary_conds" now operates on timelevel t+dt and is not split in two parts (main, uvw_outflow) any more, Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary conditions for all 2d-arrays that are handled by exchange_horiz_2d

The FFT-method for solving the Poisson-equation is now working with Neumann boundary conditions both at the bottom and the top. This requires adjustments of the tridiagonal coefficients and subtracting the horizontally averaged mean from the vertical velocity field.

+age_m in particle_type

Particles-package is now part of the default code ("-p particles" is not needed any more).

Move call of user_actions( 'after_integration' ) below increment of times
and counters. user_actions is now called for each statistic region and has as an argument the number of the respective region (sr)

d3par-parameter data_output_ts removed. Timeseries output for "profil" removed. Timeseries are now switched on by dt_dots. Timeseries data is collected in flow_statistics.

Initial velocities at nzb+1 are regarded for volume flow control in case they have been set zero before (to avoid small timesteps); see new internal parameters u/v_nzb_p1_for_vfc.

q is not allowed to become negative (prognostic_equations).

poisfft_init is only called if fft-solver is switched on (init_pegrid).

d3par-parameter moisture renamed to humidity.

Subversion global revision number is read from mrun and added to the run description header and to the run control (_rc) file.

vtk directives removed from main program.

The uitility routine interpret_config reads PALM environment variables from NAMELIST instead using the system call GETENV.

advec_u_pw, advec_u_up, advec_v_pw, advec_v_up, asselin_filter, check_parameters, coriolis, data_output_dvrp, data_output_ptseries, data_output_ts, data_output_2d, data_output_3d, diffusion_u, diffusion_v, exchange_horiz, exchange_horiz_2d, flow_statistics, header, init_grid, init_particles, init_pegrid, init_rankine, init_pt_anomaly, init_1d_model, init_3d_model, modules, palm, package_parin, parin, poisfft, poismg, prandtl_fluxes, pres, production_e, prognostic_equations, read_var_list, read_3d_binary, sor, swap_timelevel, time_integration, write_var_list, write_3d_binary

Errors:


Bugfix: preset of tendencies te_em, te_um, te_vm in init_1d_model

Bugfix in sample for reading user defined data from restart file (user_init)

Bugfix in setting diffusivities for cases with the outflow damping layer extending over more than one subdomain (init_3d_model)

Check for possible negative humidities in the initial humidity profile.

in Makefile, default suffixes removed from the suffix list to avoid calling of m2c in
# case of .mod files

Makefile
check_parameters, init_1d_model, init_3d_model, user_interface

  • Property svn:keywords set to Id
File size: 18.0 KB
Line 
1 SUBROUTINE read_3d_binary
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: read_3d_binary.f90 77 2007-03-29 04:26:56Z maronga $
11!
12! 73 2007-03-20 08:33:14Z raasch
13! +precipitation_amount, precipitation_rate_av, rif_wall, u_m_l, u_m_r, etc.,
14! z0_av
15!
16! 19 2007-02-23 04:53:48Z raasch
17! +qswst, qswst_m, tswst, tswst_m
18!
19! RCS Log replace by Id keyword, revision history cleaned up
20!
21! Revision 1.4  2006/08/04 15:02:32  raasch
22! +iran, iran_part
23!
24! Revision 1.1  2004/04/30 12:47:27  raasch
25! Initial revision
26!
27!
28! Description:
29! ------------
30! Binary input of variables and arrays from restart file
31!------------------------------------------------------------------------------!
32
33    USE arrays_3d
34    USE averaging
35    USE cloud_parameters
36    USE control_parameters
37    USE cpulog
38    USE indices
39    USE interfaces
40    USE particle_attributes
41    USE pegrid
42    USE profil_parameter
43    USE random_function_mod
44    USE statistics
45
46    IMPLICIT NONE
47
48    CHARACTER (LEN=10) ::  binary_version, version_on_file
49    CHARACTER (LEN=20) ::  field_chr
50    CHARACTER (LEN=10),  DIMENSION(:), ALLOCATABLE ::  chdum10
51    CHARACTER (LEN=40),  DIMENSION(:), ALLOCATABLE ::  chdum40
52    CHARACTER (LEN=100), DIMENSION(:), ALLOCATABLE ::  chdum100
53
54    INTEGER ::  idum1, myid_on_file, numprocs_on_file, nxl_on_file, &
55                nxr_on_file, nyn_on_file, nys_on_file, nzb_on_file, nzt_on_file
56
57    INTEGER, DIMENSION(:), ALLOCATABLE ::  idum
58
59    REAL, DIMENSION(:), ALLOCATABLE ::  rdum
60
61!
62!-- Read data from previous model run. unit 13 already opened in parin
63    CALL cpu_log( log_point_s(14), 'read_3d_binary', 'start' )
64
65!
66!-- First compare the version numbers
67    READ ( 13 )  version_on_file
68    binary_version = '3.0'
69    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
70       IF ( myid == 0 )  THEN
71          PRINT*, '+++ init_3d_model: version mismatch concerning data ', &
72                  'from prior run'
73          PRINT*, '        version on file    = "', TRIM( version_on_file ),&
74                  '"'
75          PRINT*, '        version in program = "', TRIM( binary_version ), &
76                  '"'
77       ENDIF
78       CALL local_stop
79    ENDIF
80
81!
82!-- Read and compare number of processors, processor-id and array ranges
83    READ ( 13 )  numprocs_on_file, myid_on_file, nxl_on_file, nxr_on_file, &
84                 nys_on_file, nyn_on_file, nzb_on_file, nzt_on_file
85
86    IF ( numprocs_on_file /= numprocs )  THEN
87       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
88       PRINT*, '                   from prior run on PE ', myid
89       PRINT*, '                   numprocs on file = ', numprocs_on_file
90       PRINT*, '                   numprocs         = ', numprocs
91       CALL local_stop
92    ENDIF
93
94    IF ( myid_on_file /= myid )  THEN
95       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
96       PRINT*, '                   from prior run'
97       PRINT*, '                   myid_on_file = ', myid_on_file
98       PRINT*, '                   myid         = ', myid
99#if defined( __parallel )
100       CALL MPI_ABORT( comm2d, 9999, ierr )
101#else
102       CALL local_stop
103#endif
104    ENDIF
105
106    IF ( nxl_on_file /= nxl )  THEN
107       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
108       PRINT*, '                   from prior run on PE ', myid
109       PRINT*, '                   nxl on file = ', nxl_on_file
110       PRINT*, '                   nxl         = ', nxl
111#if defined( __parallel )
112       CALL MPI_ABORT( comm2d, 9999, ierr )
113#else
114       CALL local_stop
115#endif
116    ENDIF
117
118    IF ( nxr_on_file /= nxr )  THEN
119       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
120       PRINT*, '                   from prior run on PE ', myid
121       PRINT*, '                   nxr on file = ', nxr_on_file
122       PRINT*, '                   nxr         = ', nxr
123#if defined( __parallel )
124       CALL MPI_ABORT( comm2d, 9999, ierr )
125#else
126       CALL local_stop
127#endif
128    ENDIF
129
130    IF ( nys_on_file /= nys )  THEN
131       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
132       PRINT*, '                   from prior run on PE ', myid
133       PRINT*, '                   nys on file = ', nys_on_file
134       PRINT*, '                   nys         = ', nys
135#if defined( __parallel )
136       CALL MPI_ABORT( comm2d, 9999, ierr )
137#else
138       CALL local_stop
139#endif
140    ENDIF
141
142    IF ( nyn_on_file /= nyn )  THEN
143       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
144       PRINT*, '                   from prior run on PE ', myid
145       PRINT*, '                   nyn on file = ', nyn_on_file
146       PRINT*, '                   nyn         = ', nyn
147#if defined( __parallel )
148       CALL MPI_ABORT( comm2d, 9999, ierr )
149#else
150       CALL local_stop
151#endif
152    ENDIF
153
154    IF ( nzb_on_file /= nzb )  THEN
155       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
156       PRINT*, '                   from prior run on PE ', myid
157       PRINT*, '                   nzb on file = ', nzb_on_file
158       PRINT*, '                   nzb         = ', nzb
159       CALL local_stop
160    ENDIF
161
162    IF ( nzt_on_file /= nzt )  THEN
163       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
164       PRINT*, '                   from prior run on PE ', myid
165       PRINT*, '                   nzt on file = ', nzt_on_file
166       PRINT*, '                   nzt         = ', nzt
167       CALL local_stop
168    ENDIF
169
170!
171!-- Local arrays that may be required for possible temporary information
172!-- storage in the following
173    ALLOCATE( chdum10(crmax), chdum40(crmax), chdum100(crmax), &
174              idum(100*crmax), rdum(100*crmax) )
175
176!
177!-- Initialize spectra (for the case of just starting spectra computation
178!-- in continuation runs)
179    IF ( dt_dosp /= 9999999.9 )  THEN
180       spectrum_x = 0.0
181       spectrum_y = 0.0
182    ENDIF
183
184!
185!-- Read arrays
186!-- ATTENTION: If the following read commands have been altered, the
187!-- ---------- version number of the variable binary_version must be altered,
188!--            too. Furthermore, the output list of arrays in write_3d_binary
189!--            must also be altered accordingly.
190    READ ( 13 )  field_chr
191    DO  WHILE ( TRIM( field_chr ) /= '*** end ***' )
192
193       SELECT CASE ( TRIM( field_chr ) )
194
195          CASE ( 'e' )
196             READ ( 13 )  e
197          CASE ( 'e_av' )
198             ALLOCATE( e_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
199             READ ( 13 )  e_av
200          CASE ( 'e_m' )
201             READ ( 13 )  e_m
202          CASE ( 'iran' )
203             READ ( 13 )  iran, iran_part
204          CASE ( 'kh' )
205             READ ( 13 )  kh
206          CASE ( 'kh_m' )
207             READ ( 13 )  kh_m
208          CASE ( 'km' )
209             READ ( 13 )  km
210          CASE ( 'km_m' )
211             READ ( 13 )  km_m
212          CASE ( 'lwp_av' )
213             ALLOCATE( lwp_av(nys-1:nyn+1,nxl-1:nxr+1) )
214             READ ( 13 )  lwp_av
215          CASE ( 'p' )
216             READ ( 13 )  p
217          CASE ( 'p_av' )
218             ALLOCATE( p_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
219             READ ( 13 )  p_av
220          CASE ( 'pc_av' )
221             ALLOCATE( pc_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
222             READ ( 13 )  pc_av
223          CASE ( 'pr_av' )
224             ALLOCATE( pr_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
225             READ ( 13 )  pr_av
226          CASE ( 'precipitation_amount' )
227             READ ( 13 )  precipitation_amount
228          CASE ( 'precipitation_rate_a' )
229             ALLOCATE( precipitation_rate_av(nys-1:nyn+1,nxl-1:nxr+1) )
230             READ ( 13 )  precipitation_rate_av
231          CASE ( 'pt' )
232             READ ( 13 )  pt
233          CASE ( 'pt_av' )
234             ALLOCATE( pt_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
235             READ ( 13 )  pt_av
236          CASE ( 'pt_m' )
237             READ ( 13 )  pt_m
238          CASE ( 'q' )
239             READ ( 13 )  q
240          CASE ( 'q_av' )
241             ALLOCATE( q_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
242             READ ( 13 )  q_av
243          CASE ( 'q_m' )
244             READ ( 13 )  q_m
245          CASE ( 'ql' )
246             READ ( 13 )  ql
247          CASE ( 'ql_av' )
248             ALLOCATE( ql_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
249             READ ( 13 )  ql_av
250          CASE ( 'ql_c_av' )
251             ALLOCATE( ql_c_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
252             READ ( 13 )  ql_c_av
253          CASE ( 'ql_v_av' )
254             ALLOCATE( ql_v_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
255             READ ( 13 )  ql_v_av
256          CASE ( 'ql_vp_av' )
257             ALLOCATE( ql_vp_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
258             READ ( 13 )  ql_vp_av
259          CASE ( 'qs' )
260             READ ( 13 )  qs
261          CASE ( 'qsws' )
262             READ ( 13 )  qsws
263          CASE ( 'qsws_m' )
264             READ ( 13 )  qsws_m
265          CASE ( 'qswst' )
266             READ ( 13 )  qswst
267          CASE ( 'qswst_m' )
268             READ ( 13 )  qswst_m
269          CASE ( 'qv_av' )
270             ALLOCATE( qv_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
271             READ ( 13 )  qv_av
272          CASE ( 'random_iv' )
273             READ ( 13 )  random_iv
274             READ ( 13 )  random_iy
275          CASE ( 'rif' )
276             READ ( 13 )  rif
277          CASE ( 'rif_m' )
278             READ ( 13 )  rif_m
279          CASE ( 'rif_wall' )
280             READ ( 13 )  rif_wall
281          CASE ( 's_av' )
282             ALLOCATE( s_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
283             READ ( 13 )  s_av
284          CASE ( 'shf' )
285             READ ( 13 )  shf
286          CASE ( 'shf_m' )
287             READ ( 13 )  shf_m
288          CASE ( 'tswst' )
289             READ ( 13 )  tswst
290          CASE ( 'tswst_m' )
291             READ ( 13 )  tswst_m
292          CASE ( 'spectrum_x' )
293             READ ( 13 )  spectrum_x
294          CASE ( 'spectrum_y' )
295             READ ( 13 )  spectrum_y
296          CASE ( 'ts' )
297             READ ( 13 )  ts
298          CASE ( 'ts_av' )
299             ALLOCATE( ts_av(nys-1:nyn+1,nxl-1:nxr+1) )
300             READ ( 13 )  ts_av
301          CASE ( 'u' )
302             READ ( 13 )  u
303          CASE ( 'u_av' )
304             ALLOCATE( u_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
305             READ ( 13 )  u_av
306          CASE ( 'u_m' )
307             READ ( 13 )  u_m
308          CASE ( 'u_m_l' )
309             READ ( 13 )  u_m_l
310          CASE ( 'u_m_n' )
311             READ ( 13 )  u_m_n
312          CASE ( 'u_m_r' )
313             READ ( 13 )  u_m_r
314          CASE ( 'u_m_s' )
315             READ ( 13 )  u_m_s
316          CASE ( 'us' )
317             READ ( 13 )  us
318          CASE ( 'usws' )
319             READ ( 13 )  usws
320          CASE ( 'usws_m' )
321             READ ( 13 )  usws_m
322          CASE ( 'us_av' )
323             ALLOCATE( us_av(nys-1:nyn+1,nxl-1:nxr+1) )
324             READ ( 13 )  us_av
325          CASE ( 'v' )
326             READ ( 13 )  v
327          CASE ( 'volume_flow_area' )
328             READ ( 13 )  volume_flow_area
329          CASE ( 'volume_flow_initial' )
330             READ ( 13 )  volume_flow_initial
331          CASE ( 'v_av' )
332             ALLOCATE( v_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
333             READ ( 13 )  v_av
334          CASE ( 'v_m' )
335             READ (13 )   v_m
336          CASE ( 'v_m_l' )
337             READ ( 13 )  v_m_l
338          CASE ( 'v_m_n' )
339             READ ( 13 )  v_m_n
340          CASE ( 'v_m_r' )
341             READ ( 13 )  v_m_r
342          CASE ( 'v_m_s' )
343             READ ( 13 )  v_m_s
344          CASE ( 'vpt' )
345             READ ( 13 )  vpt
346          CASE ( 'vpt_av' )
347             ALLOCATE( vpt_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
348             READ ( 13 )  vpt_av
349          CASE ( 'vpt_m' )
350             READ ( 13 )  vpt_m
351          CASE ( 'vsws' )
352             READ ( 13 )  vsws
353          CASE ( 'vsws_m' )
354             READ ( 13 )  vsws_m
355          CASE ( 'w' )
356             READ ( 13 )  w
357          CASE ( 'w_av' )
358             ALLOCATE( w_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
359             READ ( 13 )  w_av
360          CASE ( 'w_m' )
361             READ ( 13 )  w_m
362          CASE ( 'w_m_l' )
363             READ ( 13 )  w_m_l
364          CASE ( 'w_m_n' )
365             READ ( 13 )  w_m_n
366          CASE ( 'w_m_r' )
367             READ ( 13 )  w_m_r
368          CASE ( 'w_m_s' )
369             READ ( 13 )  w_m_s
370          CASE ( 'z0' )
371             READ ( 13 )  z0
372          CASE ( 'z0_av' )
373             ALLOCATE( z0_av(nys-1:nyn+1,nxl-1:nxr+1) )
374             READ ( 13 )  z0_av
375
376          CASE ( 'cross_linecolors' )
377             IF ( use_prior_plot1d_parameters )  THEN
378                READ ( 13 )  cross_linecolors
379             ELSE
380                READ ( 13 )  idum
381             ENDIF
382          CASE ( 'cross_linestyles' )
383             IF ( use_prior_plot1d_parameters )  THEN
384                READ ( 13 )  cross_linestyles
385             ELSE
386                READ ( 13 )  idum
387             ENDIF
388          CASE ( 'cross_normalized_x' )
389             IF ( use_prior_plot1d_parameters )  THEN
390                READ ( 13 )  cross_normalized_x
391             ELSE
392                READ ( 13 )  chdum10
393             ENDIF
394          CASE ( 'cross_normalized_y' )
395             IF ( use_prior_plot1d_parameters )  THEN
396                READ ( 13 )  cross_normalized_y
397             ELSE
398                READ ( 13 )  chdum10
399             ENDIF
400          CASE ( 'cross_normx_factor' )
401             IF ( use_prior_plot1d_parameters )  THEN
402                READ ( 13 )  cross_normx_factor
403             ELSE
404                READ ( 13 )  rdum
405             ENDIF
406          CASE ( 'cross_normy_factor' )
407             IF ( use_prior_plot1d_parameters )  THEN
408                READ ( 13 )  cross_normy_factor
409             ELSE
410                READ ( 13 )  rdum
411             ENDIF
412          CASE ( 'cross_profiles' )
413             IF ( use_prior_plot1d_parameters )  THEN
414                READ ( 13 )  cross_profiles
415             ELSE
416                READ ( 13 )  chdum100
417             ENDIF
418          CASE ( 'cross_profile_n_coun' )
419             IF ( use_prior_plot1d_parameters )  THEN
420                READ ( 13 )  cross_profile_number_count
421             ELSE
422                READ ( 13 )  idum(1:crmax)
423             ENDIF
424          CASE ( 'cross_profile_number' )
425             IF ( use_prior_plot1d_parameters )  THEN
426                READ ( 13 )  cross_profile_numbers
427             ELSE
428                READ ( 13 )  idum
429             ENDIF
430          CASE ( 'cross_uxmax' )
431             IF ( use_prior_plot1d_parameters )  THEN
432                READ ( 13 )  cross_uxmax
433             ELSE
434                READ ( 13 )  rdum(1:crmax)
435             ENDIF
436          CASE ( 'cross_uxmax_computed' )
437             IF ( use_prior_plot1d_parameters )  THEN
438                READ ( 13 )  cross_uxmax_computed
439             ELSE
440                READ ( 13 )  rdum(1:crmax)
441             ENDIF
442          CASE ( 'cross_uxmax_normaliz' )
443             IF ( use_prior_plot1d_parameters )  THEN
444                READ ( 13 )  cross_uxmax_normalized
445             ELSE
446                READ ( 13 )  rdum(1:crmax)
447             ENDIF
448          CASE ( 'cross_uxmax_norm_com' )
449             IF ( use_prior_plot1d_parameters )  THEN
450                READ ( 13 )  cross_uxmax_normalized_computed
451             ELSE
452                READ ( 13 )  rdum(1:crmax)
453             ENDIF
454          CASE ( 'cross_uxmin' )
455             IF ( use_prior_plot1d_parameters )  THEN
456                READ ( 13 )  cross_uxmin
457             ELSE
458                READ ( 13 )  rdum(1:crmax)
459             ENDIF
460          CASE ( 'cross_uxmin_computed' )
461             IF ( use_prior_plot1d_parameters )  THEN
462                READ ( 13 )  cross_uxmin_computed
463             ELSE
464                READ ( 13 )  rdum(1:crmax)
465             ENDIF
466          CASE ( 'cross_uxmin_normaliz' )
467             IF ( use_prior_plot1d_parameters )  THEN
468                READ ( 13 )  cross_uxmin_normalized
469             ELSE
470                READ ( 13 )  rdum(1:crmax)
471             ENDIF
472          CASE ( 'cross_uxmin_norm_com' )
473             IF ( use_prior_plot1d_parameters )  THEN
474                READ ( 13 )  cross_uxmin_normalized_computed
475             ELSE
476                READ ( 13 )  rdum(1:crmax)
477             ENDIF
478          CASE ( 'cross_uymax' )
479             IF ( use_prior_plot1d_parameters )  THEN
480                READ ( 13 )  cross_uymax
481             ELSE
482                READ ( 13 )  rdum(1:crmax)
483             ENDIF
484          CASE ( 'cross_uymin' )
485             IF ( use_prior_plot1d_parameters )  THEN
486                READ ( 13 )  cross_uymin
487             ELSE
488                READ ( 13 )  rdum(1:crmax)
489             ENDIF
490          CASE ( 'cross_xtext' )
491             IF ( use_prior_plot1d_parameters )  THEN
492                READ ( 13 )  cross_xtext
493             ELSE
494                READ ( 13 )  chdum40
495             ENDIF
496          CASE ( 'dopr_crossindex' )
497             IF ( use_prior_plot1d_parameters )  THEN
498                READ ( 13 )  dopr_crossindex
499             ELSE
500                READ ( 13 )  idum(1:100)
501             ENDIF
502          CASE ( 'dopr_time_count' )
503             IF ( use_prior_plot1d_parameters )  THEN
504                READ ( 13 )  dopr_time_count
505             ELSE
506                READ ( 13 )  idum1
507             ENDIF
508          CASE ( 'hom_sum' )
509             READ ( 13 )  hom_sum
510          CASE ( 'profile_columns' )
511             IF ( use_prior_plot1d_parameters )  THEN
512                READ ( 13 )  profile_columns
513             ELSE
514                READ ( 13 )  idum1
515             ENDIF
516          CASE ( 'profile_number' )
517             IF ( use_prior_plot1d_parameters )  THEN
518                READ ( 13 )  profile_number
519             ELSE
520                READ ( 13 )  idum1
521             ENDIF
522          CASE ( 'profile_rows' )
523             IF ( use_prior_plot1d_parameters )  THEN
524                READ ( 13 )  profile_rows
525             ELSE
526                READ ( 13 )  idum1
527             ENDIF
528
529          CASE DEFAULT
530             PRINT*, '+++ init_3d_model: unknown field named "', &
531                     TRIM( field_chr ), '" found in'
532             PRINT*, '                   data from prior run on PE ', myid
533             CALL local_stop
534
535       END SELECT
536!
537!--    Read next character string
538       READ ( 13 )  field_chr
539
540    ENDDO
541
542    DEALLOCATE( chdum10, chdum40, chdum100, idum, rdum )
543
544!
545!-- End of time measuring for reading binary data
546    CALL cpu_log( log_point_s(14), 'read_3d_binary', 'stop' )
547
548 END SUBROUTINE read_3d_binary
Note: See TracBrowser for help on using the repository browser.