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

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

preliminary changes for radiation conditions

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