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

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

preliminary version for coupled runs

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