source: palm/tags/release-3.4/SOURCE/read_3d_binary.f90 @ 4011

Last change on this file since 4011 was 110, checked in by raasch, 16 years ago

New:
---
Allows runs for a coupled atmosphere-ocean LES,
coupling frequency is controlled by new d3par-parameter dt_coupling,
the coupling mode (atmosphere_to_ocean or ocean_to_atmosphere) for the
respective processes is read from environment variable coupling_mode,
which is set by the mpiexec-command,
communication between the two models is done using the intercommunicator
comm_inter,
local files opened by the ocean model get the additional suffic "_O".
Assume saturation at k=nzb_s_inner(j,i) for atmosphere coupled to ocean.

A momentum flux can be set as top boundary condition using the new
inipar parameter top_momentumflux_u|v.

Non-cyclic boundary conditions can be used along all horizontal directions.

Quantities w*p* and w"e can be output as vertical profiles.

Initial profiles are reset to constant profiles in case that initializing_actions /= 'set_constant_profiles'. (init_rankine)

Optionally calculate km and kh from initial TKE e_init.

Changed:


Remaining variables iran changed to iran_part (advec_particles, init_particles).

In case that the presure solver is not called for every Runge-Kutta substep
(call_psolver_at_all_substeps = .F.), it is called after the first substep
instead of the last. In that case, random perturbations are also added to the
velocity field after the first substep.

Initialization of km,kh = 0.00001 for ocean = .T. (for ocean = .F. it remains 0.01).

Allow data_output_pr= q, wq, w"q", w*q* for humidity = .T. (instead of cloud_physics = .T.).

Errors:


Bugs from code parts for non-cyclic boundary conditions are removed: loops for
u and v are starting from index nxlu, nysv, respectively. The radiation boundary
condition is used for every Runge-Kutta substep. Velocity phase speeds for
the radiation boundary conditions are calculated for the first Runge-Kutta
substep only and reused for the further substeps. New arrays c_u, c_v, and c_w
are defined for this purpose. Several index errors are removed from the
radiation boundary condition code parts. Upper bounds for calculating
u_0 and v_0 (in production_e) are nxr+1 and nyn+1 because otherwise these
values are not available in case of non-cyclic boundary conditions.

+dots_num_palm in module user, +module netcdf_control in user_init (both in user_interface)

Bugfix: wrong sign removed from the buoyancy production term in the case use_reference = .T. (production_e)

Bugfix: Error message concerning output of particle concentration (pc) modified (check_parameters).

Bugfix: Rayleigh damping for ocean fixed.

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