source: palm/trunk/SOURCE/read_3d_binary.f90 @ 69

Last change on this file since 69 was 51, checked in by raasch, 17 years ago

preliminary version, several changes to be explained later

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