source: palm/trunk/SOURCE/data_output_3d.f90 @ 759

Last change on this file since 759 was 759, checked in by raasch, 13 years ago

New:
---

The number of parallel I/O operations can be limited with new mrun-option -w.
(advec_particles, data_output_2d, data_output_3d, header, init_grid, init_pegrid, init_3d_model, modules, palm, parin, write_3d_binary)

Changed:


mrun option -T is obligatory

Errors:


Bugfix: No zero assignments to volume_flow_initial and volume_flow_area in
case of normal restart runs. (init_3d_model)

initialization of u_0, v_0. This is just to avoid access of uninitialized
memory in exchange_horiz_2d, which causes respective error messages
when the Intel thread checker (inspector) is used. (production_e)

Bugfix for ts limitation (prandtl_fluxes)

  • Property svn:keywords set to Id
File size: 16.2 KB
Line 
1 SUBROUTINE data_output_3d( av )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! Splitting of parallel I/O
7!
8! Former revisions:
9! -----------------
10! $Id: data_output_3d.f90 759 2011-09-15 13:58:31Z raasch $
11!
12! 727 2011-04-20 20:05:25Z suehring
13! Exchange ghost layers also for p_av.
14!
15! 725 2011-04-11 09:37:01Z suehring
16! Exchange ghost layers for p regardless of used pressure solver (except SOR).
17!
18! 691 2011-03-04 08:45:30Z maronga
19! Replaced simulated_time by time_since_reference_point
20!
21! 673 2011-01-18 16:19:48Z suehring
22! When using Multigrid or SOR solver an additional CALL exchange_horiz is
23! is needed for pressure output.
24!
25! 667 2010-12-23 12:06:00Z suehring/gryschka
26! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
27! allocation of arrays.  Calls of exchange_horiz are modified.
28! Skip-value skip_do_avs changed to a dynamic adaption of ghost points.
29!
30! 646 2010-12-15 13:03:52Z raasch
31! bugfix: missing define statements for netcdf added
32!
33! 493 2010-03-01 08:30:24Z raasch
34! NetCDF4 support (parallel output)
35!
36! 355 2009-07-17 01:03:01Z letzel
37! simulated_time in NetCDF output replaced by time_since_reference_point.
38! Output of NetCDF messages with aid of message handling routine.
39! Output of messages replaced by message handling routine.
40! Bugfix: to_be_resorted => s_av for time-averaged scalars
41!
42! 96 2007-06-04 08:07:41Z raasch
43! Output of density and salinity
44!
45! 75 2007-03-22 09:54:05Z raasch
46! 2nd+3rd argument removed from exchange horiz
47!
48! RCS Log replace by Id keyword, revision history cleaned up
49!
50! Revision 1.3  2006/06/02 15:18:59  raasch
51! +argument "found", -argument grid in call of routine user_data_output_3d
52!
53! Revision 1.2  2006/02/23 10:23:07  raasch
54! Former subroutine plot_3d renamed data_output_3d, pl.. renamed do..,
55! .._anz renamed .._n,
56! output extended to (almost) all quantities, output of user-defined quantities
57!
58! Revision 1.1  1997/09/03 06:29:36  raasch
59! Initial revision
60!
61!
62! Description:
63! ------------
64! Output of the 3D-arrays in NetCDF and/or AVS format.
65!------------------------------------------------------------------------------!
66
67    USE array_kind
68    USE arrays_3d
69    USE averaging
70    USE cloud_parameters
71    USE control_parameters
72    USE cpulog
73    USE indices
74    USE interfaces
75    USE netcdf_control
76    USE particle_attributes
77    USE pegrid
78
79    IMPLICIT NONE
80
81    CHARACTER (LEN=9) ::  simulated_time_mod
82
83    INTEGER           ::  av, i, if, j, k, n, pos, prec, psi
84
85    LOGICAL           ::  found, resorted
86
87    REAL              ::  mean_r, s_r3, s_r4
88
89    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE  ::  local_pf
90
91    REAL, DIMENSION(:,:,:), POINTER ::  to_be_resorted
92
93!
94!-- Return, if nothing to output
95    IF ( do3d_no(av) == 0 )  RETURN
96
97    CALL cpu_log (log_point(14),'data_output_3d','start')
98
99!
100!-- Open output file.
101!-- Also creates coordinate and fld-file for AVS.
102!-- For classic or 64bit NetCDF output or output of other (old) data formats,
103!-- for a run on more than one PE, each PE opens its own file and
104!-- writes the data of its subdomain in binary format (regardless of the format
105!-- the user has requested). After the run, these files are combined to one
106!-- file by combine_plot_fields in the format requested by the user (netcdf
107!-- and/or avs).
108!-- For NetCDF4/HDF5 output, data is written in parallel into one file.
109    IF ( netcdf_output )  THEN
110       IF ( netcdf_data_format < 3 )  THEN
111          CALL check_open( 30 )
112          IF ( myid == 0 )  CALL check_open( 106+av*10 )
113       ELSE
114          CALL check_open( 106+av*10 )
115       ENDIF
116    ELSE
117       IF ( avs_output  .OR.  ( numprocs > 1 ) )  CALL check_open( 30 )
118    ENDIF
119
120!
121!-- Allocate a temporary array with the desired output dimensions.
122    ALLOCATE( local_pf(nxlg:nxrg,nysg:nyng,nzb:nz_do3d) )
123
124!
125!-- Update the NetCDF time axis
126#if defined( __netcdf )
127    IF ( myid == 0  .OR.  netcdf_data_format > 2 )  THEN
128       do3d_time_count(av) = do3d_time_count(av) + 1
129       IF ( netcdf_output )  THEN
130          nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_time_3d(av), &
131                                  (/ time_since_reference_point /),  &
132                                  start = (/ do3d_time_count(av) /), &
133                                  count = (/ 1 /) )
134          CALL handle_netcdf_error( 'data_output_3d', 376 )
135       ENDIF
136    ENDIF
137#endif
138
139!
140!-- Loop over all variables to be written.
141    if = 1
142
143    DO  WHILE ( do3d(av,if)(1:1) /= ' ' )
144!
145!--    Set the precision for data compression.
146       IF ( do3d_compress )  THEN
147          DO  i = 1, 100
148             IF ( plot_3d_precision(i)%variable == do3d(av,if) )  THEN
149                prec = plot_3d_precision(i)%precision
150                EXIT
151             ENDIF
152          ENDDO
153       ENDIF
154
155!
156!--    Store the array chosen on the temporary array.
157       resorted = .FALSE.
158       SELECT CASE ( TRIM( do3d(av,if) ) )
159
160          CASE ( 'e' )
161             IF ( av == 0 )  THEN
162                to_be_resorted => e
163             ELSE
164                to_be_resorted => e_av
165             ENDIF
166
167          CASE ( 'p' )
168             IF ( av == 0 )  THEN
169                IF ( psolver /= 'sor' )  CALL exchange_horiz( p, nbgp )
170                to_be_resorted => p
171             ELSE
172                IF ( psolver /= 'sor' )  CALL exchange_horiz( p_av, nbgp )
173                to_be_resorted => p_av
174             ENDIF
175
176          CASE ( 'pc' )  ! particle concentration (requires ghostpoint exchange)
177             IF ( av == 0 )  THEN
178                tend = prt_count
179                CALL exchange_horiz( tend, nbgp )
180                DO  i = nxlg, nxrg
181                   DO  j = nysg, nyng
182                      DO  k = nzb, nz_do3d
183                         local_pf(i,j,k) = tend(k,j,i)
184                      ENDDO
185                   ENDDO
186                ENDDO
187                resorted = .TRUE.
188             ELSE
189                CALL exchange_horiz( pc_av, nbgp )
190                to_be_resorted => pc_av
191             ENDIF
192
193          CASE ( 'pr' )  ! mean particle radius
194             IF ( av == 0 )  THEN
195                DO  i = nxl, nxr
196                   DO  j = nys, nyn
197                      DO  k = nzb, nzt+1
198                         psi = prt_start_index(k,j,i)
199                         s_r3 = 0.0
200                         s_r4 = 0.0
201                         DO  n = psi, psi+prt_count(k,j,i)-1
202                            s_r3 = s_r3 + particles(n)%radius**3
203                            s_r4 = s_r4 + particles(n)%radius**4
204                         ENDDO
205                         IF ( s_r3 /= 0.0 )  THEN
206                            mean_r = s_r4 / s_r3
207                         ELSE
208                            mean_r = 0.0
209                         ENDIF
210                         tend(k,j,i) = mean_r
211                      ENDDO
212                   ENDDO
213                ENDDO
214                CALL exchange_horiz( tend, nbgp )
215                DO  i = nxlg, nxrg
216                   DO  j = nysg, nyng
217                      DO  k = nzb, nzt+1
218                         local_pf(i,j,k) = tend(k,j,i)
219                      ENDDO
220                   ENDDO
221                ENDDO
222                resorted = .TRUE.
223             ELSE
224                CALL exchange_horiz( pr_av, nbgp )
225                to_be_resorted => pr_av
226             ENDIF
227
228          CASE ( 'pt' )
229             IF ( av == 0 )  THEN
230                IF ( .NOT. cloud_physics ) THEN
231                   to_be_resorted => pt
232                ELSE
233                   DO  i = nxlg, nxrg
234                      DO  j = nysg, nyng
235                         DO  k = nzb, nz_do3d
236                            local_pf(i,j,k) = pt(k,j,i) + l_d_cp *    &
237                                                          pt_d_t(k) * &
238                                                          ql(k,j,i)
239                         ENDDO
240                      ENDDO
241                   ENDDO
242                   resorted = .TRUE.
243                ENDIF
244             ELSE
245                to_be_resorted => pt_av
246             ENDIF
247
248          CASE ( 'q' )
249             IF ( av == 0 )  THEN
250                to_be_resorted => q
251             ELSE
252                to_be_resorted => q_av
253             ENDIF
254
255          CASE ( 'ql' )
256             IF ( av == 0 )  THEN
257                to_be_resorted => ql
258             ELSE
259                to_be_resorted => ql_av
260             ENDIF
261
262          CASE ( 'ql_c' )
263             IF ( av == 0 )  THEN
264                to_be_resorted => ql_c
265             ELSE
266                to_be_resorted => ql_c_av
267             ENDIF
268
269          CASE ( 'ql_v' )
270             IF ( av == 0 )  THEN
271                to_be_resorted => ql_v
272             ELSE
273                to_be_resorted => ql_v_av
274             ENDIF
275
276          CASE ( 'ql_vp' )
277             IF ( av == 0 )  THEN
278                to_be_resorted => ql_vp
279             ELSE
280                to_be_resorted => ql_vp_av
281             ENDIF
282
283          CASE ( 'qv' )
284             IF ( av == 0 )  THEN
285                DO  i = nxlg, nxrg
286                   DO  j = nysg, nyng
287                      DO  k = nzb, nz_do3d
288                         local_pf(i,j,k) = q(k,j,i) - ql(k,j,i)
289                      ENDDO
290                   ENDDO
291                ENDDO
292                resorted = .TRUE.
293             ELSE
294                to_be_resorted => qv_av
295             ENDIF
296
297          CASE ( 'rho' )
298             IF ( av == 0 )  THEN
299                to_be_resorted => rho
300             ELSE
301                to_be_resorted => rho_av
302             ENDIF
303
304          CASE ( 's' )
305             IF ( av == 0 )  THEN
306                to_be_resorted => q
307             ELSE
308                to_be_resorted => s_av
309             ENDIF
310
311          CASE ( 'sa' )
312             IF ( av == 0 )  THEN
313                to_be_resorted => sa
314             ELSE
315                to_be_resorted => sa_av
316             ENDIF
317
318          CASE ( 'u' )
319             IF ( av == 0 )  THEN
320                to_be_resorted => u
321             ELSE
322                to_be_resorted => u_av
323             ENDIF
324
325          CASE ( 'v' )
326             IF ( av == 0 )  THEN
327                to_be_resorted => v
328             ELSE
329                to_be_resorted => v_av
330             ENDIF
331
332          CASE ( 'vpt' )
333             IF ( av == 0 )  THEN
334                to_be_resorted => vpt
335             ELSE
336                to_be_resorted => vpt_av
337             ENDIF
338
339          CASE ( 'w' )
340             IF ( av == 0 )  THEN
341                to_be_resorted => w
342             ELSE
343                to_be_resorted => w_av
344             ENDIF
345
346          CASE DEFAULT
347!
348!--          User defined quantity
349             CALL user_data_output_3d( av, do3d(av,if), found, local_pf, &
350                                       nz_do3d )
351             resorted = .TRUE.
352
353             IF ( .NOT. found )  THEN
354                message_string =  'no output available for: ' //   &
355                                  TRIM( do3d(av,if) )
356                CALL message( 'data_output_3d', 'PA0182', 0, 0, 0, 6, 0 )
357             ENDIF
358
359       END SELECT
360
361!
362!--    Resort the array to be output, if not done above
363       IF ( .NOT. resorted )  THEN
364          DO  i = nxlg, nxrg
365             DO  j = nysg, nyng
366                DO  k = nzb, nz_do3d
367                   local_pf(i,j,k) = to_be_resorted(k,j,i)
368                ENDDO
369             ENDDO
370          ENDDO
371       ENDIF
372
373!
374!--    Output of the volume data information for the AVS-FLD-file.
375       do3d_avs_n = do3d_avs_n + 1
376       IF ( myid == 0  .AND.  avs_output )  THEN
377!
378!--       AVS-labels must not contain any colons. Hence they must be removed
379!--       from the time character string.
380          simulated_time_mod = simulated_time_chr
381          DO  WHILE ( SCAN( simulated_time_mod, ':' ) /= 0 )
382             pos = SCAN( simulated_time_mod, ':' )
383             simulated_time_mod(pos:pos) = '/'
384          ENDDO
385
386          IF ( av == 0 )  THEN
387             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
388                                 skip_do_avs, TRIM( do3d(av,if) ), &
389                                 TRIM( simulated_time_mod )
390          ELSE
391             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
392                                 skip_do_avs, TRIM( do3d(av,if) ) // &
393                                 ' averaged', TRIM( simulated_time_mod )
394          ENDIF
395!
396!--       Determine the Skip-value for the next array. Record end and start
397!--       require 4 byte each.
398          skip_do_avs = skip_do_avs + ( ( ( nx+2*nbgp ) * ( ny+2*nbgp ) * &
399                                          ( nz_do3d+1 ) ) * 4 + 8 )
400       ENDIF
401
402!
403!--    Output of the 3D-array. (compressed/uncompressed)
404       IF ( do3d_compress )  THEN
405!
406!--       Compression, output of compression information on FLD-file and output
407!--       of compressed data.
408          CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, nyn, nys, &
409                                 nzb, nz_do3d, prec, nbgp )
410       ELSE
411!
412!--       Uncompressed output.
413#if defined( __parallel )
414          IF ( netcdf_output )  THEN
415             IF ( netcdf_data_format < 3 )  THEN
416!
417!--             Classic or 64bit format. Data is output in parallel in FORTRAN
418!--             binary format here, and later collected into one file by
419!--             combine_plot_fields
420                IF ( myid == 0 )  THEN
421                   WRITE ( 30 )  time_since_reference_point,                   &
422                                 do3d_time_count(av), av
423                ENDIF
424                DO  i = 0, io_blocks-1
425                   IF ( i == io_group )  THEN
426                      WRITE ( 30 )  nxlg, nxrg, nysg, nyng, nzb, nz_do3d
427                      WRITE ( 30 )  local_pf
428                   ENDIF
429#if defined( __parallel )
430                   CALL MPI_BARRIER( comm2d, ierr )
431#endif
432                ENDDO
433
434             ELSE
435#if defined( __netcdf )
436!
437!--             Output in NetCDF4/HDF5 format.
438!--             Do not output redundant ghost point data except for the
439!--             boundaries of the total domain.
440                IF ( nxr == nx  .AND.  nyn /= ny )  THEN
441                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
442                                  local_pf(nxl:nxrg,nys:nyn,nzb:nz_do3d),    &
443                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
444                      count = (/ nxr-nxl+1+nbgp, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
445                ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
446                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
447                                  local_pf(nxl:nxr,nys:nyng,nzb:nz_do3d),    &
448                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
449                      count = (/ nxr-nxl+1, nyn-nys+1+nbgp, nz_do3d-nzb+1, 1 /) )
450                ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
451                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
452                                  local_pf(nxl:nxrg,nys:nyng,nzb:nz_do3d),  &
453                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
454                      count = (/ nxr-nxl+1+nbgp, nyn-nys+1+nbgp, nz_do3d-nzb+1, 1 /) )
455                ELSE
456                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
457                                  local_pf(nxl:nxr,nys:nyn,nzb:nz_do3d),      &
458                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
459                      count = (/ nxr-nxl+1, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
460                ENDIF
461                CALL handle_netcdf_error( 'data_output_3d', 386 )
462#endif
463             ENDIF
464          ENDIF
465#else
466          IF ( avs_output )  THEN
467             WRITE ( 30 )  local_pf(nxl:nxr+1,nys:nyn+1,:)
468          ENDIF
469#if defined( __netcdf )
470          IF ( netcdf_output )  THEN
471
472             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),    &
473                               local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),  &
474                               start = (/ 1, 1, 1, do3d_time_count(av) /), &
475                               count = (/ nx+2, ny+2, nz_do3d-nzb+1, 1 /) )
476             CALL handle_netcdf_error( 'data_output_3d', 446 )
477
478          ENDIF
479#endif
480#endif
481       ENDIF
482
483       if = if + 1
484
485    ENDDO
486
487!
488!-- Deallocate temporary array.
489    DEALLOCATE( local_pf )
490
491
492    CALL cpu_log (log_point(14),'data_output_3d','stop','nobarrier')
493
494!
495!-- Formats.
4963300 FORMAT ('variable ',I4,'  file=',A,'  filetype=unformatted  skip=',I12/ &
497             'label = ',A,A)
498
499 END SUBROUTINE data_output_3d
Note: See TracBrowser for help on using the repository browser.