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

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

first preliminary update for turbulent inflow

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