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

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

preliminary changes for precipitation output

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