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

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

further preliminary uncomplete changes for ocean version

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