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

Last change on this file since 145 was 145, checked in by raasch, 16 years ago

second preliminary update for turbulent inflow

  • Property svn:keywords set to Id
File size: 13.2 KB
Line 
1 SUBROUTINE read_3d_binary
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Restart file has to be re-opened on all PEs except PE0
7! +call of user_read_restart_data,
8! -dopr_time_count,
9! hom_sum, volume_flow_area, volume_flow_initial moved to read_var_list,
10! reading of old profil parameters (cross_..., dopr_crossindex, profile_***)
11! removed
12!
13! Former revisions:
14! -----------------
15! $Id: read_3d_binary.f90 145 2008-01-09 08:17:38Z raasch $
16!
17! 102 2007-07-27 09:09:17Z raasch
18! +uswst, uswst_m, vswst, vswst_m
19!
20! 96 2007-06-04 08:07:41Z raasch
21! +rho_av, sa, sa_av, saswsb, saswst
22!
23! 73 2007-03-20 08:33:14Z raasch
24! +precipitation_amount, precipitation_rate_av, rif_wall, u_m_l, u_m_r, etc.,
25! z0_av
26!
27! 19 2007-02-23 04:53:48Z raasch
28! +qswst, qswst_m, tswst, tswst_m
29!
30! RCS Log replace by Id keyword, revision history cleaned up
31!
32! Revision 1.4  2006/08/04 15:02:32  raasch
33! +iran, iran_part
34!
35! Revision 1.1  2004/04/30 12:47:27  raasch
36! Initial revision
37!
38!
39! Description:
40! ------------
41! Binary input of variables and arrays from restart file
42!------------------------------------------------------------------------------!
43
44    USE arrays_3d
45    USE averaging
46    USE cloud_parameters
47    USE control_parameters
48    USE cpulog
49    USE indices
50    USE interfaces
51    USE particle_attributes
52    USE pegrid
53    USE profil_parameter
54    USE random_function_mod
55    USE statistics
56
57    IMPLICIT NONE
58
59    CHARACTER (LEN=10) ::  binary_version, version_on_file
60    CHARACTER (LEN=20) ::  field_chr
61
62    INTEGER ::  idum1, myid_on_file, numprocs_on_file, nxl_on_file, &
63                nxr_on_file, nyn_on_file, nys_on_file, nzb_on_file, nzt_on_file
64
65!
66!-- Read data from previous model run. unit 13 already opened in parin
67    CALL cpu_log( log_point_s(14), 'read_3d_binary', 'start' )
68
69!
70!-- Restart file has to be re-opened on all PEs except PE0
71    CALL check_open( 13 )
72
73!
74!-- First compare the version numbers
75    READ ( 13 )  version_on_file
76    binary_version = '3.1'
77    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
78       IF ( myid == 0 )  THEN
79          PRINT*, '+++ init_3d_model: version mismatch concerning data ', &
80                  'from prior run'
81          PRINT*, '        version on file    = "', TRIM( version_on_file ),&
82                  '"'
83          PRINT*, '        version in program = "', TRIM( binary_version ), &
84                  '"'
85       ENDIF
86       CALL local_stop
87    ENDIF
88
89!
90!-- Read and compare number of processors, processor-id and array ranges
91    READ ( 13 )  numprocs_on_file, myid_on_file, nxl_on_file, nxr_on_file, &
92                 nys_on_file, nyn_on_file, nzb_on_file, nzt_on_file
93
94    IF ( numprocs_on_file /= numprocs )  THEN
95       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
96       PRINT*, '                   from prior run on PE ', myid
97       PRINT*, '                   numprocs on file = ', numprocs_on_file
98       PRINT*, '                   numprocs         = ', numprocs
99       CALL local_stop
100    ENDIF
101
102    IF ( myid_on_file /= myid )  THEN
103       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
104       PRINT*, '                   from prior run'
105       PRINT*, '                   myid_on_file = ', myid_on_file
106       PRINT*, '                   myid         = ', myid
107#if defined( __parallel )
108       CALL MPI_ABORT( comm2d, 9999, ierr )
109#else
110       CALL local_stop
111#endif
112    ENDIF
113
114    IF ( nxl_on_file /= nxl )  THEN
115       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
116       PRINT*, '                   from prior run on PE ', myid
117       PRINT*, '                   nxl on file = ', nxl_on_file
118       PRINT*, '                   nxl         = ', nxl
119#if defined( __parallel )
120       CALL MPI_ABORT( comm2d, 9999, ierr )
121#else
122       CALL local_stop
123#endif
124    ENDIF
125
126    IF ( nxr_on_file /= nxr )  THEN
127       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
128       PRINT*, '                   from prior run on PE ', myid
129       PRINT*, '                   nxr on file = ', nxr_on_file
130       PRINT*, '                   nxr         = ', nxr
131#if defined( __parallel )
132       CALL MPI_ABORT( comm2d, 9999, ierr )
133#else
134       CALL local_stop
135#endif
136    ENDIF
137
138    IF ( nys_on_file /= nys )  THEN
139       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
140       PRINT*, '                   from prior run on PE ', myid
141       PRINT*, '                   nys on file = ', nys_on_file
142       PRINT*, '                   nys         = ', nys
143#if defined( __parallel )
144       CALL MPI_ABORT( comm2d, 9999, ierr )
145#else
146       CALL local_stop
147#endif
148    ENDIF
149
150    IF ( nyn_on_file /= nyn )  THEN
151       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
152       PRINT*, '                   from prior run on PE ', myid
153       PRINT*, '                   nyn on file = ', nyn_on_file
154       PRINT*, '                   nyn         = ', nyn
155#if defined( __parallel )
156       CALL MPI_ABORT( comm2d, 9999, ierr )
157#else
158       CALL local_stop
159#endif
160    ENDIF
161
162    IF ( nzb_on_file /= nzb )  THEN
163       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
164       PRINT*, '                   from prior run on PE ', myid
165       PRINT*, '                   nzb on file = ', nzb_on_file
166       PRINT*, '                   nzb         = ', nzb
167       CALL local_stop
168    ENDIF
169
170    IF ( nzt_on_file /= nzt )  THEN
171       PRINT*, '+++ init_3d_model: mismatch between actual data and data '
172       PRINT*, '                   from prior run on PE ', myid
173       PRINT*, '                   nzt on file = ', nzt_on_file
174       PRINT*, '                   nzt         = ', nzt
175       CALL local_stop
176    ENDIF
177
178!
179!-- Initialize spectra (for the case of just starting spectra computation
180!-- in continuation runs)
181    IF ( dt_dosp /= 9999999.9 )  THEN
182       spectrum_x = 0.0
183       spectrum_y = 0.0
184    ENDIF
185
186!
187!-- Read arrays
188!-- ATTENTION: If the following read commands have been altered, the
189!-- ---------- version number of the variable binary_version must be altered,
190!--            too. Furthermore, the output list of arrays in write_3d_binary
191!--            must also be altered accordingly.
192    READ ( 13 )  field_chr
193    DO  WHILE ( TRIM( field_chr ) /= '*** end ***' )
194
195       SELECT CASE ( TRIM( field_chr ) )
196
197          CASE ( 'e' )
198             READ ( 13 )  e
199          CASE ( 'e_av' )
200             ALLOCATE( e_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
201             READ ( 13 )  e_av
202          CASE ( 'e_m' )
203             READ ( 13 )  e_m
204          CASE ( 'iran' )
205             READ ( 13 )  iran, iran_part
206          CASE ( 'kh' )
207             READ ( 13 )  kh
208          CASE ( 'kh_m' )
209             READ ( 13 )  kh_m
210          CASE ( 'km' )
211             READ ( 13 )  km
212          CASE ( 'km_m' )
213             READ ( 13 )  km_m
214          CASE ( 'lwp_av' )
215             ALLOCATE( lwp_av(nys-1:nyn+1,nxl-1:nxr+1) )
216             READ ( 13 )  lwp_av
217          CASE ( 'p' )
218             READ ( 13 )  p
219          CASE ( 'p_av' )
220             ALLOCATE( p_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
221             READ ( 13 )  p_av
222          CASE ( 'pc_av' )
223             ALLOCATE( pc_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
224             READ ( 13 )  pc_av
225          CASE ( 'pr_av' )
226             ALLOCATE( pr_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
227             READ ( 13 )  pr_av
228          CASE ( 'precipitation_amount' )
229             READ ( 13 )  precipitation_amount
230          CASE ( 'precipitation_rate_a' )
231             ALLOCATE( precipitation_rate_av(nys-1:nyn+1,nxl-1:nxr+1) )
232             READ ( 13 )  precipitation_rate_av
233          CASE ( 'pt' )
234             READ ( 13 )  pt
235          CASE ( 'pt_av' )
236             ALLOCATE( pt_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
237             READ ( 13 )  pt_av
238          CASE ( 'pt_m' )
239             READ ( 13 )  pt_m
240          CASE ( 'q' )
241             READ ( 13 )  q
242          CASE ( 'q_av' )
243             ALLOCATE( q_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
244             READ ( 13 )  q_av
245          CASE ( 'q_m' )
246             READ ( 13 )  q_m
247          CASE ( 'ql' )
248             READ ( 13 )  ql
249          CASE ( 'ql_av' )
250             ALLOCATE( ql_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
251             READ ( 13 )  ql_av
252          CASE ( 'ql_c_av' )
253             ALLOCATE( ql_c_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
254             READ ( 13 )  ql_c_av
255          CASE ( 'ql_v_av' )
256             ALLOCATE( ql_v_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
257             READ ( 13 )  ql_v_av
258          CASE ( 'ql_vp_av' )
259             ALLOCATE( ql_vp_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
260             READ ( 13 )  ql_vp_av
261          CASE ( 'qs' )
262             READ ( 13 )  qs
263          CASE ( 'qsws' )
264             READ ( 13 )  qsws
265          CASE ( 'qsws_m' )
266             READ ( 13 )  qsws_m
267          CASE ( 'qswst' )
268             READ ( 13 )  qswst
269          CASE ( 'qswst_m' )
270             READ ( 13 )  qswst_m
271          CASE ( 'qv_av' )
272             ALLOCATE( qv_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
273             READ ( 13 )  qv_av
274          CASE ( 'random_iv' )
275             READ ( 13 )  random_iv
276             READ ( 13 )  random_iy
277          CASE ( 'rho_av' )
278             ALLOCATE( rho_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
279             READ ( 13 )  rho_av
280          CASE ( 'rif' )
281             READ ( 13 )  rif
282          CASE ( 'rif_m' )
283             READ ( 13 )  rif_m
284          CASE ( 'rif_wall' )
285             READ ( 13 )  rif_wall
286          CASE ( 's_av' )
287             ALLOCATE( s_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
288             READ ( 13 )  s_av
289          CASE ( 'sa' )
290             READ ( 13 )  sa
291          CASE ( 'sa_av' )
292             ALLOCATE( sa_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
293             READ ( 13 )  sa_av
294          CASE ( 'saswsb' )
295             READ ( 13 )  saswsb
296          CASE ( 'saswst' )
297             READ ( 13 )  saswst
298          CASE ( 'shf' )
299             READ ( 13 )  shf
300          CASE ( 'shf_m' )
301             READ ( 13 )  shf_m
302          CASE ( 'spectrum_x' )
303             READ ( 13 )  spectrum_x
304          CASE ( 'spectrum_y' )
305             READ ( 13 )  spectrum_y
306          CASE ( 'ts' )
307             READ ( 13 )  ts
308          CASE ( 'ts_av' )
309             ALLOCATE( ts_av(nys-1:nyn+1,nxl-1:nxr+1) )
310             READ ( 13 )  ts_av
311          CASE ( 'tswst' )
312             READ ( 13 )  tswst
313          CASE ( 'tswst_m' )
314             READ ( 13 )  tswst_m
315          CASE ( 'u' )
316             READ ( 13 )  u
317          CASE ( 'u_av' )
318             ALLOCATE( u_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
319             READ ( 13 )  u_av
320          CASE ( 'u_m' )
321             READ ( 13 )  u_m
322          CASE ( 'u_m_l' )
323             READ ( 13 )  u_m_l
324          CASE ( 'u_m_n' )
325             READ ( 13 )  u_m_n
326          CASE ( 'u_m_r' )
327             READ ( 13 )  u_m_r
328          CASE ( 'u_m_s' )
329             READ ( 13 )  u_m_s
330          CASE ( 'us' )
331             READ ( 13 )  us
332          CASE ( 'usws' )
333             READ ( 13 )  usws
334          CASE ( 'uswst' )
335             READ ( 13 )  uswst
336          CASE ( 'usws_m' )
337             READ ( 13 )  usws_m
338          CASE ( 'uswst_m' )
339             READ ( 13 )  uswst_m
340          CASE ( 'us_av' )
341             ALLOCATE( us_av(nys-1:nyn+1,nxl-1:nxr+1) )
342             READ ( 13 )  us_av
343          CASE ( 'v' )
344             READ ( 13 )  v
345          CASE ( 'v_av' )
346             ALLOCATE( v_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
347             READ ( 13 )  v_av
348          CASE ( 'v_m' )
349             READ (13 )   v_m
350          CASE ( 'v_m_l' )
351             READ ( 13 )  v_m_l
352          CASE ( 'v_m_n' )
353             READ ( 13 )  v_m_n
354          CASE ( 'v_m_r' )
355             READ ( 13 )  v_m_r
356          CASE ( 'v_m_s' )
357             READ ( 13 )  v_m_s
358          CASE ( 'vpt' )
359             READ ( 13 )  vpt
360          CASE ( 'vpt_av' )
361             ALLOCATE( vpt_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
362             READ ( 13 )  vpt_av
363          CASE ( 'vpt_m' )
364             READ ( 13 )  vpt_m
365          CASE ( 'vsws' )
366             READ ( 13 )  vsws
367          CASE ( 'vswst' )
368             READ ( 13 )  vswst
369          CASE ( 'vsws_m' )
370             READ ( 13 )  vsws_m
371          CASE ( 'vswst_m' )
372             READ ( 13 )  vswst_m
373          CASE ( 'w' )
374             READ ( 13 )  w
375          CASE ( 'w_av' )
376             ALLOCATE( w_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
377             READ ( 13 )  w_av
378          CASE ( 'w_m' )
379             READ ( 13 )  w_m
380          CASE ( 'w_m_l' )
381             READ ( 13 )  w_m_l
382          CASE ( 'w_m_n' )
383             READ ( 13 )  w_m_n
384          CASE ( 'w_m_r' )
385             READ ( 13 )  w_m_r
386          CASE ( 'w_m_s' )
387             READ ( 13 )  w_m_s
388          CASE ( 'z0' )
389             READ ( 13 )  z0
390          CASE ( 'z0_av' )
391             ALLOCATE( z0_av(nys-1:nyn+1,nxl-1:nxr+1) )
392             READ ( 13 )  z0_av
393
394          CASE DEFAULT
395             PRINT*, '+++ init_3d_model: unknown field named "', &
396                     TRIM( field_chr ), '" found in'
397             PRINT*, '                   data from prior run on PE ', myid
398             CALL local_stop
399
400       END SELECT
401!
402!--    Read next character string
403       READ ( 13 )  field_chr
404
405    ENDDO
406
407!
408!-- Read user-defined restart data
409    CALL user_read_restart_data
410
411!
412!-- End of time measuring for reading binary data
413    CALL cpu_log( log_point_s(14), 'read_3d_binary', 'stop' )
414
415 END SUBROUTINE read_3d_binary
Note: See TracBrowser for help on using the repository browser.