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

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

last commit documented

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