source: palm/tags/release-3.1b/SOURCE/read_3d_binary.f90 @ 389

Last change on this file since 389 was 4, checked in by raasch, 17 years ago

Id keyword set as property for all *.f90 files

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