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

Last change on this file since 493 was 493, checked in by raasch, 14 years ago

New:
---
Output in NetCDF4-format. New d3par-parameter netcdf_data_format.

(check_open, check_parameters, close_file, data_output_2d, data_output_3d, header, modules, netcdf, parin)

Modules to be loaded for compilation (mbuild) or job execution (mrun)
can be given in the configuration file using variable modules. Example:

%modules ifort/11.0.069:netcdf lcsgih parallel

This method replaces the (undocumented) mpilib-variable.

WARNING: All fixed settings of modules in the scripts mbuild, mrun, and subjob
have been removed! Please set the modules variable appropriately in your
configuration file. (mbuild, mrun, subjob)

Changed:


Parameters netcdf_64bit and netcdf_64bit_3d have been removed. Use
netcdf_data_format = 2 for choosing the classic 64bit-offset format (this is
the default). The offset-format can not be set independently for the
3d-output-data any more.

Parameters netcdf_format_mask, netcdf_format_mask_av, and variables
nc_format_mask, format_parallel_io removed. They are replaced by the new
parameter netcdf_data_format. (check_open, close_file,
data_output_mask, header, init_masks, modules, parin)

Errors:


bugfix in trunk/UTIL/Makefile: forgot to compile for interpret_config

Bugfix: timeseries data have to be collected by PE0 (user_statistics)

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